Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        beginners-requ...@haskell.org

You can reach the person managing the list at
        beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1. Re:  Ambiguous type variable (Markus Läll)
   2. Re:  Ambiguous type variable (Francesco Ariis)
   3. Re:  Ambiguous type variable (Michael Snoyman)
   4. Re:  Ambiguous type variable (Jonathon Delgado)
   5. Re:  Applicative: how <*> really works (Ivan Llopard)


----------------------------------------------------------------------

Message: 1
Date: Thu, 17 Aug 2017 15:25:43 +0200
From: Markus Läll <markus.l...@gmail.com>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] Ambiguous type variable
Message-ID:
        <caldaiubmf_g9nev4l5vvv+p1hkya-i9zhw8gvoim3zkxn-a...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

Hi Jonathon!

You only catch some specific type of exception, everything else is simply
past onwards. See end of p. 2/beginning of p. 3 here:
http://community.haskell.org/~simonmar/papers/ext-exceptions.pdf

On Thu, Aug 17, 2017 at 2:24 PM, Jonathon Delgado <volderm...@hotmail.com>
wrote:

> I'm sure it makes sense! I'm not really following though.
>
> I understood typeclasses to be analogous to OO interfaces. So if a
> variable implements the Exception interface, and Exception implements the
> Show interface, then it should automatically support show.
>
> I take it this was wrong? How does the compiler use typeclasses if they're
> not interfaces?
>
>
> Francesco Ariis  wrote:
>
> > I'm trying to use
> >   catch (...) (\e -> putStrLn $ show e)
> > However, I get an error
> >   Ambiguous type variable ‘a0’ arising from a use of ‘show’ prevents the
> constraint ‘(Show a0)’ from being solved.
> > This goes away if I change the code to
> >   catch (...) (\e -> putStrLn $ show (e::IOException))
> >
> > A couple of things I don't understand here:
> > - The signature for catch begins "Exception e", and exception it "class
> (Typeable e, Show e) => Exception e". So why isn't show automatically
> available?
> > - Why does the new code work at all? e is Exception, not IOException.
> What would happen if it caught a different Exception?
>
> IOException is a concrete type while Exception is a typeclass. In the end,
> the compiler needs the former, the latter not being enough.
>
> The code works as any other class-based function would
>
>     someFunction :: Monoid a -> [a] -> a
>     -- ^-- in the end `Monoid a` will become something concrete, like
>     -- a String, a Sum, etc.
>
> Does that make sense?
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>



-- 
Markus Läll
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://mail.haskell.org/pipermail/beginners/attachments/20170817/cf71e1f8/attachment-0001.html>

------------------------------

Message: 2
Date: Thu, 17 Aug 2017 15:29:27 +0200
From: Francesco Ariis <fa...@ariis.it>
To: beginners@haskell.org
Subject: Re: [Haskell-beginners] Ambiguous type variable
Message-ID: <20170817132927.pvwg64etmjuxz...@x60s.casa>
Content-Type: text/plain; charset=utf-8

On Thu, Aug 17, 2017 at 12:24:07PM +0000, Jonathon Delgado wrote:
> I'm sure it makes sense! I'm not really following though.
> 
> I understood typeclasses to be analogous to OO interfaces. So if a variable
> implements the Exception interface, and Exception implements the Show
> interface, then it should automatically support show.
> 
> I take it this was wrong? How does the compiler use typeclasses if they're
> not interfaces?

That's correct! Indeed ghc is not complaining about a lack of
instances, as it would with, say

    λ> putStrLn 5
    -- • No instance for (Num String) arising from etc etc.

but about the *ambiguity* of type variable `e`.  How does `catch` know
_which_ exception to deal with if you don't specify the concrete type?
Consider:

    prova = catch (print $ div (error "hey bby") 0)
                  (\e -> print "ouch" >>
                         print (e :: ErrorCall))

    -- I want to deal with arithmetic errors here and not in `prova`
    palla = catch prova
                  (\e -> print "baaah" >>
                         print (e :: ArithException))

If I switch ArithException and ErrorCall the behaviour of invoking `palla`
changes.

Having a catch-all `catch` is possible by using (e :: SomeException);
if you don't care about `e` and just want to do an action regardless, you
are probably better off with `onException`.

Ask more if needed!


------------------------------

Message: 3
Date: Thu, 17 Aug 2017 16:36:49 +0300
From: Michael Snoyman <mich...@snoyman.com>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] Ambiguous type variable
Message-ID:
        <cakt9ecnotwg1prg1vcgqak9wbza8_png5ub4qyfk7uxerz0...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

On Thu, Aug 17, 2017 at 4:29 PM, Francesco Ariis <fa...@ariis.it> wrote:

> On Thu, Aug 17, 2017 at 12:24:07PM +0000, Jonathon Delgado wrote:
> > I'm sure it makes sense! I'm not really following though.
> >
> > I understood typeclasses to be analogous to OO interfaces. So if a
> variable
> > implements the Exception interface, and Exception implements the Show
> > interface, then it should automatically support show.
> >
> > I take it this was wrong? How does the compiler use typeclasses if
> they're
> > not interfaces?
>
> That's correct! Indeed ghc is not complaining about a lack of
> instances, as it would with, say
>
>     λ> putStrLn 5
>     -- • No instance for (Num String) arising from etc etc.
>
> but about the *ambiguity* of type variable `e`.  How does `catch` know
> _which_ exception to deal with if you don't specify the concrete type?
> Consider:
>
>     prova = catch (print $ div (error "hey bby") 0)
>                   (\e -> print "ouch" >>
>                          print (e :: ErrorCall))
>
>     -- I want to deal with arithmetic errors here and not in `prova`
>     palla = catch prova
>                   (\e -> print "baaah" >>
>                          print (e :: ArithException))
>
> If I switch ArithException and ErrorCall the behaviour of invoking `palla`
> changes.
>
> Having a catch-all `catch` is possible by using (e :: SomeException);
> if you don't care about `e` and just want to do an action regardless, you
> are probably better off with `onException`.
>
>
This is dangerous: `catch` with `e :: SomeException` will catch all
asynchronous exceptions, breaking things like timeout, race, and the async
library in general. That's why my message about mentioned the
safe-exceptions package.

Michael


> Ask more if needed!
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://mail.haskell.org/pipermail/beginners/attachments/20170817/d820d2cd/attachment-0001.html>

------------------------------

Message: 4
Date: Thu, 17 Aug 2017 14:18:41 +0000
From: Jonathon Delgado <volderm...@hotmail.com>
To: "beginners@haskell.org" <beginners@haskell.org>
Subject: Re: [Haskell-beginners] Ambiguous type variable
Message-ID:
        
<vi1p18901mb0144a56af9de1366ac262468cd...@vi1p18901mb0144.eurp189.prod.outlook.com>
        
Content-Type: text/plain; charset="windows-1253"

Thank you very much, that does clarify things!

Francesco Ariis  wrote:

That's correct! Indeed ghc is not complaining about a lack of 
instances, as it would with, say 

    λ> putStrLn 5 
    -- • No instance for (Num String) arising from etc etc. 

but about the *ambiguity* of type variable `e`.  How does `catch` know 
_which_ exception to deal with if you don't specify the concrete type? 
Consider: 

    prova = catch (print $ div (error "hey bby") 0) 
                  (\e -> print "ouch" >> 
                         print (e :: ErrorCall)) 

    -- I want to deal with arithmetic errors here and not in `prova` 
    palla = catch prova 
                  (\e -> print "baaah" >> 
                         print (e :: ArithException)) 

If I switch ArithException and ErrorCall the behaviour of invoking `palla` 
changes. 

Having a catch-all `catch` is possible by using (e :: SomeException); 
if you don't care about `e` and just want to do an action regardless, you 
are probably better off with `onException`. 

Ask more if needed! 

------------------------------

Message: 5
Date: Thu, 17 Aug 2017 21:20:10 +0200
From: Ivan Llopard <ivanllop...@gmail.com>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] Applicative: how <*> really works
Message-ID:
        <cafyf_fwayh6qhxu60kuln1obuin+y9ogc0500nwpvqmftxs...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

Exactly, It is left-associative and it will apply "pure g", which does
nothing in terms of parsing but put g into the parsing result, and then
apply item.

Another way to think about it, is to forget about the list and think only
in terms of types.
With a value of type Parser (a -> (b, c)) and Parser a you can use <*> to
get a value of type Parser (b, c).
Then, if you execute such a parser you will have a list of nested tuples as
you requested, i.e. [(b, c), String].

Try your first example with g = (\x -> (x,0)) and pure g <*> item. Play
with different expressions and the applicative operator.

Best,
Ivan

2017-08-05 0:29 GMT+02:00 Yassine <yassine...@gmail.com>:

> Thanks for you nice answer but I still have some difficulties.
>
> When you do:
> g = (\x y -> (x,y))
> first_item = pure g <*> item
>
> Because <*> is left associative, we do first the application of g on
> item before apply item, is it correct ?
>
> Furthermore, item return a list containing a tuple with the first
> character and the remaining of the string. So how can I get a list
> with a tuple containing another tuple with the parsed characters
> (inner tuple) and the remaining of the string (in the outer tuple).
>
> 2017-08-04 23:30 GMT+02:00 Ivan Llopard <ivanllop...@gmail.com>:
> > Hi Yassine,
> >
> > I prefer to explain you with an abstract view of these definitions.
> > Unrolling this stuff in your mind (or paper) can be complex and, IMO, it
> > might be useless as it does not give you any specific hints to build even
> > more complex ones.
> >
> > You can view Parser a as an object with a certain structure (or form, or
> > definition if you prefer). However, you do not want to know how complex
> its
> > structure or definition is. You are certain about one thing, it holds
> some
> > value of type a.
> > Let's say that such value is "hidden" by Parser. The same idea applies to
> > Maybe a.
> >
> > Then, you want to work with that value no matter the structure of
> Parser. As
> > you already know, fmap allows you to do that. You can go from Parser a to
> > Parser b with a function from a to b.
> > The applicative allows you to go further. If you have a hidden function
> > (e.g. Parser (a->b)) and a hidden parameter (Parser a). Then you want to
> > apply that hidden function to the hidden parameter in order to obtain a
> > Parser b.
> > That is what the expression parserF <*> ParserA would do if parserF
> hides a
> > function and parserA its parameter.
> >
> > Now, you need to know more about the meaning of Parser a. It is an object
> > that reads the input and produce a result (or token) accordingly.
> > The returned value of the parser is a list of (result, remaining_input).
> > The interesting part is the result value, which is of type a. You want to
> > play around with it. Again, fmap is an easy way. Going from Parser a to
> > Parser b via fmap does not change the parsing action of Parser a, you
> will
> > have a Parser b but the behavior remains the same. You just played with
> the
> > result of the first parser.
> >
> > The functor instance tells that more precisely (fixed):
> >
> > instance Functor Parser where
> > fmap g (P p) = P (\inp -> case p inp of
> > []              -> []
> >  [(v, out)]      -> [(g v, out)])
> >
> > Now look at the definition of the applicative
> >
> > instance Applicative Parser where
> > pure v = P (\inp -> [(v, inp)])
> > pg <*> px = P (\inp -> case parse pg inp of
> > []              -> []
> > [(g, out)]      -> parse (fmap g px) out)
> >
> > First of all, the function "parser" applies the parser, i.e., it parses
> the
> > input and returns the list [(g, out)]. Here, we have two applications of
> > "parser".
> > The first one applies parser pg, "case parse pg inp". Obviously, pg
> hides a
> > function "g".
> > Now you preserve the same behavior of px but you fmap on it function "g".
> > That is, the parser "fmap g px" will do the same as px but its result is
> > changed by g.
> > And finally, you apply such parser.
> >
> > Let us take the first two terms of your example
> >
> > first_item = pure (\x y -> (x,y)) <*> item
> >
> > then g = \x y -> (x,y)
> > which is a higher order function. In the expression, g is applied
> partially
> > over the result of item. You know that item returns the first char of the
> > input, 'a'.
> > first_item is then a parser that hides a function of the form h = \y ->
> > ('a', y).
> >
> > Because it hides a function, you can use the applicative again
> >
> > first_term <*> item
> >
> > and h will be applied to the result of item again. Because we already
> > applied item once, the remaining input is "bc". Then, item will give you
> 'b'
> > as a result.
> > Now h 'b' = ('a, 'b'), which is the result of your final parser plus the
> > remaining input "c". Applying the final parser, you obtain
> >
> > [('a', 'b'), "c")]
> >
> > I hope this will help you !
> >
> > Best,
> > Ivan
> >
> > 2017-08-03 21:19 GMT+02:00 Yassine <yassine...@gmail.com>:
> >>
> >> Hi,
> >>
> >> I have a question about functor applicate.
> >>
> >> I know that:
> >> pure (+1) <*> Just 2
> >>
> >>
> >> produce: Just 3
> >> because pure (+1) produce Just (+1) and then Just (+1) <*> Just 2
> >> produce Just (2+1)
> >>
> >>
> >> but in more complex case like:
> >> newtype Parser a = P (String -> [(a,String)])
> >>
> >> parse :: Parser a -> String -> [(a,String)]
> >> parse (P p) inp = p inp
> >>
> >>
> >> item :: Parser Char
> >> item = P (\inp -> case inp of
> >>  []     -> []
> >> (x:xs) -> [(x,xs)])
> >>
> >> instance Functor Parser where
> >> fmap g p = P (\inp -> case p inp of
> >> []              -> []
> >>  [(v, out)]      -> [(g v, out)])
> >>
> >> instance Applicative Parser where
> >> pure v = P (\inp -> [(v, inp)])
> >> pg <*> px = P (\inp -> case parse pg inp of
> >> []              -> []
> >> [(g, out)]      -> parse (fmap g px) out)
> >>
> >>
> >> When I do:
> >> parse (pure (\x y -> (x,y)) <*> item <*> item) "abc"
> >>
> >> The answer is:
> >> [(('a','b'),"c")]
> >>
> >> But I don't understand what exactly happens.
> >> First:
> >> pure (\x y -> (x,y)) => P (\inp -> [(\x y -> (x,y), inp)])
> >>
> >> Then:
> >> P (\inp -> [(\x y -> (x,y), inp)]) <*> item => ???
> >>
> >> Can someone explain what's happens step by step please.
> >>
> >> Thank you.
> >> _______________________________________________
> >> Beginners mailing list
> >> Beginners@haskell.org
> >> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
> >
> >
> >
> > _______________________________________________
> > Beginners mailing list
> > Beginners@haskell.org
> > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
> >
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://mail.haskell.org/pipermail/beginners/attachments/20170817/5e0e9d57/attachment.html>

------------------------------

Subject: Digest Footer

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners


------------------------------

End of Beginners Digest, Vol 110, Issue 17
******************************************

Reply via email to