Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://www.haskell.org/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.  Parsec Monad Type Confusion (Aleksandar Dimitrov)
   2. Re:  Parsec Monad Type Confusion (Stephen Tetley)
   3. Re:  Parsec Monad Type Confusion (Stephen Tetley)
   4. Re:  Parsec Monad Type Confusion (Magnus Therning)
   5. Re:  Parsec Monad Type Confusion (Stephen Tetley)
   6.  Some Code from XMonad (matthew coolbeth)
   7. Re:  Some Code from XMonad (Felipe Lessa)
   8. Re:  Some Code from XMonad (Daniel Fischer)


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

Message: 1
Date: Sat, 10 Jul 2010 01:31:11 +0200
From: Aleksandar Dimitrov <aleks.dimit...@googlemail.com>
Subject: [Haskell-beginners] Parsec Monad Type Confusion
To: beginners@haskell.org
Message-ID: <1278718271.2032.12.ca...@bylha>
Content-Type: text/plain; charset="UTF-8"

Hello list,

I have a rather trivial question, but one that I can't seem to get my
head around. In the following example function (using
Text.ParserCombinators.Parsec) I'm getting an error without the type
declaration, but it compiles just fine with it:

> parseNumber' :: Parser LispVal
> parseNumber'  = do x <- many1 digit
>                    return $ Number . read $ x

The error message when compiling without the type declaration is the
following:

    No instance for (Text.Parsec.Prim.Stream s m Char)
      arising from a use of `digit' at Scheme.hs:33:30-34
    Possible fix:
      add an instance declaration for (Text.Parsec.Prim.Stream s m Char)
    In the first argument of `many1', namely `digit'
    In a stmt of a 'do' expression: x <- many1 digit
    In the expression:
        do { x <- many1 digit;
               return $ Number . read $ x }

The function is an example in "Write yourself a Scheme in 48 hours." I'd
consider myself fairly accustomed to programming with monads; and still,
I can't seem to find out *why* exactly GHC ( 6.12.1 ) cannot compile
this without the type signature. What does it try to build here? Why
does the inferencing fail?

My best guess is that it somehow doesn't get that 'x' is supposed to be
a String value ([Char], not Char.) What really confuses me, though, is
that adding the instance declaration makes the whole thing work! The
type declaration for LispVal looks like this:

> data LispVal = Number Integer

So it should be pretty clear to GHC that, due to `Number . read`
demanding a [Char], I actually want x to be a [Char]. I'm assuming here
that I'm just in the wrong Monad, starting with `do`. Somehow, GHC
assumes it's not Parser LispVal, but something more complex, possibly
Text.Parsec.Prim.Stream s m LispVal or so?

Thank you everybody for you help :-) This list is a truly amazing place
with a lot of helpful people!
Aleks



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

Message: 2
Date: Sat, 10 Jul 2010 08:52:18 +0100
From: Stephen Tetley <stephen.tet...@gmail.com>
Subject: Re: [Haskell-beginners] Parsec Monad Type Confusion
To: Aleksandar Dimitrov <aleks.dimit...@googlemail.com>
Cc: beginners@haskell.org
Message-ID:
        <aanlktimiwc6w6uhjbuon6xsomdcugot5cj27xnbya...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

Hi Aleksandar

This line looks wrong

>                    return $ Number . read $ x

Try this

>                    return $ Number $ read x

If that doesn't work then I'm not sure. The tutorial was written for
Parsec 2 but it looks like you are using Parsec 3. In practice there
aren't many differences to users at least once you import the right
see of modules (the modules to import are slightly different). Maybe
you could post your whole module if there are still problems.

Best wishes

Stephen


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

Message: 3
Date: Sat, 10 Jul 2010 09:02:21 +0100
From: Stephen Tetley <stephen.tet...@gmail.com>
Subject: Re: [Haskell-beginners] Parsec Monad Type Confusion
To: Aleksandar Dimitrov <aleks.dimit...@googlemail.com>
Cc: beginners@haskell.org
Message-ID:
        <aanlktil86zddhqdi9f9fd8sj5wq7j_fmgql9yatoo...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

Further...

If you are using Strings (rather than ByteStrings) you want to import
this module with Parsec 3:

import Text.Parsec.String

This should bring in the right instances for Stream. You may have to
import other modules as well for particular parsers.


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

Message: 4
Date: Sat, 10 Jul 2010 10:54:02 +0100
From: Magnus Therning <mag...@therning.org>
Subject: Re: [Haskell-beginners] Parsec Monad Type Confusion
To: beginners@haskell.org
Message-ID: <4c38433a.1010...@therning.org>
Content-Type: text/plain; charset="utf-8"

On 10/07/10 08:52, Stephen Tetley wrote:
> Hi Aleksandar
> 
> This line looks wrong
> 
>>                    return $ Number . read $ x
> 
> Try this
> 
>>                    return $ Number $ read x

AFAICS that change should make no difference at all.  In fact the line
could also be written as

    return . Number . read $ x

/M

-------------- next part --------------
A non-text attachment was scrubbed...
Name: signature.asc
Type: application/pgp-signature
Size: 262 bytes
Desc: OpenPGP digital signature
Url : 
http://www.haskell.org/pipermail/beginners/attachments/20100710/4693f7c5/signature-0001.bin

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

Message: 5
Date: Sat, 10 Jul 2010 12:22:49 +0100
From: Stephen Tetley <stephen.tet...@gmail.com>
Subject: Re: [Haskell-beginners] Parsec Monad Type Confusion
Cc: beginners@haskell.org
Message-ID:
        <aanlktika12kfvzhxlwttvhfm3ikcb6bltpb5mizrp...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

On 10 July 2010 10:54, Magnus Therning <mag...@therning.org> wrote:
>
> AFAICS that change should make no difference at all.  In fact the line
> could also be written as
>
>    return . Number . read $ x
>


Yeah - it was a rather poor answer especially as on a proper reading
the original poster's question was even asking about that...

Here's a better answer:

Starting from the line:

x <- many1 digit

Without a type decl, at this point x :: [a]. /a/ is constrained, as
the parsers answer type as the whole computation is with the ParsecT
monad transformer. But other than that /a/ is polymorphic.

The next line with the read obliges x to be a String (for read to type check):

return $ Number . read $ x

But this is not enough to give a full type to the whole computation,
with the lifting to Number of the "x" the type of the whole function
is going to be :: ParsecT s m Number.

The stream type /s/ and the monad type /m/ are not resolved. Adding a
type signature with the Parser type in Parsec 3 resolves the types of
the stream and monad via 2 type synonyms:

type Parser  = Parsec  String  ()

type Parsec s u = ParsecT  s u Identity

where u is a further type parameter for user state.

The base monad is resolved to Identity, the stream is resolved to String.


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

Message: 6
Date: Sat, 10 Jul 2010 07:41:15 -0400
From: matthew coolbeth <mac01...@engr.uconn.edu>
Subject: [Haskell-beginners] Some Code from XMonad
To: Haskell-beginners <beginners@haskell.org>
Message-ID:
        <aanlktilhtb5m6xpbw7jpmwpyi0dgposnzitvcectl...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

Hi.

This is not standard haskell98, right?

It appears as though a container module can very succinctly expose ALL items
exposed by "submodules" that it has imported within itself.

Does anyone know where I can find a document specifying the language
behaviour for code that does this?

------------------------------------------------------------------------------------------------------------
module XMonad (

    module XMonad.Main,
    module XMonad.Core,
    module XMonad.Config,
    module XMonad.Layout,
    module XMonad.ManageHook,
    module XMonad.Operations,
    module Graphics.X11,
    module Graphics.X11.Xlib.Extras,
    (.|.),
    MonadState(..), gets, modify,
    MonadReader(..), asks,
    MonadIO(..)

 ) where

-- core modules
import XMonad.Main
import XMonad.Core
import XMonad.Config
import XMonad.Layout
import XMonad.ManageHook
import XMonad.Operations
-- import XMonad.StackSet -- conflicts with 'workspaces' defined in
XMonad.hs

-- modules needed to get basic configuration working
import Data.Bits
import Graphics.X11 hiding (refreshKeyboardMapping)
import Graphics.X11.Xlib.Extras

import Control.Monad.State
import Control.Monad.Reader


-- 
mac
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20100710/86818e5f/attachment-0001.html

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

Message: 7
Date: Sat, 10 Jul 2010 08:44:55 -0300
From: Felipe Lessa <felipe.le...@gmail.com>
Subject: Re: [Haskell-beginners] Some Code from XMonad
To: matthew coolbeth <mac01...@engr.uconn.edu>
Cc: Haskell-beginners <beginners@haskell.org>
Message-ID:
        <aanlktimqqditjwbhaqdps43tfytrknd_dtrej5l47...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

On Sat, Jul 10, 2010 at 8:41 AM, matthew coolbeth
<mac01...@engr.uconn.edu> wrote:
> Hi.
> This is not standard haskell98, right?
> It appears as though a container module can very succinctly expose ALL items
> exposed by "submodules" that it has imported within itself.
> Does anyone know where I can find a document specifying the language
> behaviour for code that does this?

Yes, it is Haskell 98 =D.

http://www.haskell.org/onlinereport/modules.html#sect5.2

Cheers!

-- 
Felipe.


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

Message: 8
Date: Sat, 10 Jul 2010 13:50:55 +0200
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] Some Code from XMonad
To: beginners@haskell.org
Message-ID: <201007101350.56019.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="utf-8"

On Saturday 10 July 2010 13:44:55, Felipe Lessa wrote:
> On Sat, Jul 10, 2010 at 8:41 AM, matthew coolbeth
>
> <mac01...@engr.uconn.edu> wrote:
> > Hi.
> > This is not standard haskell98, right?
> > It appears as though a container module can very succinctly expose ALL
> > items exposed by "submodules" that it has imported within itself.
> > Does anyone know where I can find a document specifying the language
> > behaviour for code that does this?
>
> Yes, it is Haskell 98 =D.

Except that hierarchical modules weren't in H98.
(Everybody got hierarchical modules very soon, however, and they're in 
H2010.)

>
> http://www.haskell.org/onlinereport/modules.html#sect5.2
>
> Cheers!



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

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 25, Issue 28
*****************************************

Reply via email to