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.  type classes and multiple implementations (Michael Hendricks)
   2. Re:  type classes and multiple implementations (Sean Bartell)
   3.  Clearing Parsec error messages (Giuliano Vilela)
   4. Re:  Clearing Parsec error messages (Daniel Fischer)
   5.  Clearing Parsec error messages (Giuliano Vilela)
   6. Re:  Clearing Parsec error messages (Daniel Fischer)


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

Message: 1
Date: Fri, 5 Jun 2009 10:39:50 -0600
From: Michael Hendricks <mich...@ndrix.org>
Subject: [Haskell-beginners] type classes and multiple implementations
To: beginners@haskell.org
Message-ID: <20090605163950.ga71...@ginosko.ndrix.org>
Content-Type: text/plain; charset=us-ascii

I'm writing a tool for which there will be multiple storage formats.
The user can choose his favorite storage mechanism through a
configuration file.  Possible storage mechanisms might include
in-memory storage or on-disk storage.  To represent this abstraction,
I created a Storage type class and two simple instances:

    class Storage a where
        open :: String -> IO a

    data Disk = Disk
    instance Storage Disk where
        open file = do
            putStrLn $ "opening disk: " ++ file
            return Disk

    data Memory = Memory
    instance Storage Memory where
        open _ = do
            putStrLn "opening memory"
            return Memory


I can load this code into ghci (version 6.10.1, if that
matters) and it behaves as I expected it to:

    *Main> open "foo" :: IO Disk
    opening disk: foo
    *Main> open "foo" :: IO Memory
    opening memory

Eventually a configuration facility will provide a string indicating
which storage mechanism the user prefers.  This will return a string
like "memory" or "disk".  Based on that string, I want to return a
value whose type belongs to the Storage type class.  I thought this
would do the job:

    by_type :: Storage a => String -> String -> IO a
    by_type "disk"   x = open x :: IO Disk
    by_type "memory" x = open x :: IO Memory
    by_type _        t = error $ "no such storage type " ++ t

but I get the following compile errors:

    Couldn't match expected type `Disk' against inferred type `Memory'
      Expected type: IO a
      Inferred type: IO Memory
    In the expression: open x :: IO Memory
    In the definition of `by_type':
        by_type "memory" x = open x :: IO Memory

It seems as though the type variable `a' is binding to Disk which
prevents it from later binding to Memory.  That makes sense but I
don't see a way forward from here.  How can I accomplish multiple
implementations of the same interface?  Are type classes the right
way?

Thank you for any help.

-- 
Michael


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

Message: 2
Date: Fri, 5 Jun 2009 13:09:11 -0400
From: Sean Bartell <wingedtachik...@gmail.com>
Subject: Re: [Haskell-beginners] type classes and multiple
        implementations
To: Michael Hendricks <mich...@ndrix.org>
Cc: beginners@haskell.org
Message-ID:
        <dd3762960906051009l24a6714apb7c2e85d39220...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

    by_type :: Storage a => String -> String -> IO a
This function must, for any Storage type, take any two strings and produce
an IO value of that type. (by_type "disk" "xyz" :: Memory must be valid.) It
doesn't really have the option of choosing which instance of Storage to use.

In pure Haskell, you would probably have to do something like
  type Storage = Disk Handle | Memory String
  by_type :: String -> String -> Storage
That way, by_type can return any Storage it wants.

I'm sure there are also ways to do what you want with extensions.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20090605/be33076a/attachment-0001.html

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

Message: 3
Date: Fri, 5 Jun 2009 21:05:13 -0300
From: Giuliano Vilela <giulian...@gmail.com>
Subject: [Haskell-beginners] Clearing Parsec error messages
To: beginners@haskell.org
Message-ID:
        <4086423f0906051705r19c10da4k2626ff067c260...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

Hi all,

In a Parsec project I used the *fail* parser, wanting to show a message to
the user and halt the parsing process. That's okay, but the error message
showed included some other "unexpected" and "expecting" messages that did
not seem related to the fail.

My guess is that Parsec keeps these messages in an internal state, to use
them whenever needed. My question is, how can I clear those error messages
and only show the string I pass to fail?

-- 
[]'s

Giuliano Vilela.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20090605/d56bc967/attachment-0001.html

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

Message: 4
Date: Sat, 6 Jun 2009 13:36:33 +0200
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] Clearing Parsec error messages
To: beginners@haskell.org
Message-ID: <200906061336.33260.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="iso-8859-15"

Am Samstag 06 Juni 2009 02:05:13 schrieb Giuliano Vilela:
> Hi all,
>
> In a Parsec project I used the *fail* parser, wanting to show a message to
> the user and halt the parsing process. That's okay, but the error message
> showed included some other "unexpected" and "expecting" messages that did
> not seem related to the fail.

I suppose your parser is not

do return 'a'
   fail "No dice"

but rather something like

do commonPreamble
   foo <|> bar <|> baz <|> fail message

and fail is only called if none of the possibilities succeed?

Then each of the failing parsers foo, bar and baz may add messages what input 
would have 
allowed them to proceed:
---------------------------------
module FailTest where

import Text.ParserCombinators.Parsec

pa = char 'a'

pb = char 'b'

pc = char 'c'

parser1 = pa <|> pb <|> pc <|> fail "Sorry, no parse"

test1 = parse parser1 "test1" "d'oh"

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

*FailTest> test1
Left "test1" (line 1, column 1):
unexpected "d"
expecting "a", "b" or "c"
Sorry, no parse

That's probably the kind of output you get. But I'd say the messages are very 
much related 
to the fail, most likely it's better to keep them.

But if you absolutely want to get rid of them, you need a custom fail that 
consumes some 
input to remove the earlier expect messages. To avoid breaking the actual input 
or falling 
afoul of end of input, first inject a dummy token into the input, then consume 
that, and 
only thereafter fail:
-----------------------------------------------------------------

myfail msg = do
    inp <- getInput
    setInput ('x':inp)
    anyToken
    fail msg

parser2 = pa <|> pb <|> pc <|> myfail "sorry, doesn't parse"

test2 = parse parser2 "test2" "d'oh"
--------------------------------------------------------------------------

*FailTest> test2
Left "test2" (line 1, column 1):
sorry, doesn't parse

But that probably does more harm than good.
>
> My guess is that Parsec keeps these messages in an internal state, to use
> them whenever needed. My question is, how can I clear those error messages
> and only show the string I pass to fail?



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

Message: 5
Date: Sat, 6 Jun 2009 09:26:14 -0300
From: Giuliano Vilela <giulian...@gmail.com>
Subject: [Haskell-beginners] Clearing Parsec error messages
To: beginners@haskell.org
Message-ID:
        <4086423f0906060526p6f7f77c9ua5ac7d3567b95...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

On Sat, Jun 6, 2009 at 8:36 AM, Daniel Fischer <daniel.is.fisc...@web.de>wrote:

> Am Samstag 06 Juni 2009 02:05:13 schrieb Giuliano Vilela:
> > Hi all,
> >
> > In a Parsec project I used the *fail* parser, wanting to show a message
> to
> > the user and halt the parsing process. That's okay, but the error message
> > showed included some other "unexpected" and "expecting" messages that did
> > not seem related to the fail.
>
> I suppose your parser is not
>
> do return 'a'
>   fail "No dice"
>
> but rather something like
>
> do commonPreamble
>   foo <|> bar <|> baz <|> fail message
>
> and fail is only called if none of the possibilities succeed?
>


Close, but not quite. I'm actually using the Parsec monad with my own state
to build a symbol table during parsing (for a Pascal sub-language I
mentioned earlier in this list). So the fail is deep in the "recursion
chain", but it's something like what you mentioned above. It seemed to me
that *fail* was the best way to report a error, like "undefined type
identifier used".



> Then each of the failing parsers foo, bar and baz may add messages what
> input would have
> allowed them to proceed:
> ---------------------------------
> module FailTest where
>
> import Text.ParserCombinators.Parsec
>
> pa = char 'a'
>
> pb = char 'b'
>
> pc = char 'c'
>
> parser1 = pa <|> pb <|> pc <|> fail "Sorry, no parse"
>
> test1 = parse parser1 "test1" "d'oh"
>
> ------------------------------------------------------------
>
> *FailTest> test1
> Left "test1" (line 1, column 1):
> unexpected "d"
> expecting "a", "b" or "c"
> Sorry, no parse
>
> That's probably the kind of output you get. But I'd say the messages are
> very much related
> to the fail, most likely it's better to keep them.



Nice, I understand now how those messages are built. But, as you can see,
the errors I mentioned won't be related to the parsing itself. That's why
those "expected" and "unexpected" messages are undesirable.



>
> But if you absolutely want to get rid of them, you need a custom fail that
> consumes some
> input to remove the earlier expect messages. To avoid breaking the actual
> input or falling
> afoul of end of input, first inject a dummy token into the input, then
> consume that, and
> only thereafter fail:
> -----------------------------------------------------------------
>
> myfail msg = do
>    inp <- getInput
>    setInput ('x':inp)
>    anyToken
>    fail msg
>
> parser2 = pa <|> pb <|> pc <|> myfail "sorry, doesn't parse"
>
> test2 = parse parser2 "test2" "d'oh"
> --------------------------------------------------------------------------
>
> *FailTest> test2
> Left "test2" (line 1, column 1):
> sorry, doesn't parse


That worked :)

But thinking about it now, I see my solution probably isn't optimal. In some
cases, I will report type errors even when there is bad syntax further in
the source, which is not common behavior. You got any suggestions for my use
case?

The source code for the interpreter is here:
http://code.google.com/p/hpascal/ (pretty immature, my group just started
writing it) if you want to take a look. Important files are: Parsing.hs (the
parser itself) and TypeChecker.hs (parsers that access the internal monad
state and build the table).





-- 
[]'s

Giuliano Vilela.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20090606/6fb995ef/attachment-0001.html

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

Message: 6
Date: Sat, 6 Jun 2009 17:11:41 +0200
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] Clearing Parsec error messages
To: beginners@haskell.org
Message-ID: <200906061711.41644.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="iso-8859-15"

Am Samstag 06 Juni 2009 14:26:14 schrieb Giuliano Vilela:
> On Sat, Jun 6, 2009 at 8:36 AM, Daniel Fischer 
> <daniel.is.fisc...@web.de>wrote:
> > Am Samstag 06 Juni 2009 02:05:13 schrieb Giuliano Vilela:
>
> Close, but not quite. I'm actually using the Parsec monad with my own state
> to build a symbol table during parsing (for a Pascal sub-language I
> mentioned earlier in this list). So the fail is deep in the "recursion
> chain", but it's something like what you mentioned above. It seemed to me
> that *fail* was the best way to report a error, like "undefined type
> identifier used".

Ah, I see.
You successfully parsed a list of syntactically correct declarations, then 
check if 
they're semantically correct (using only known types, in this case) and if that 
fails, you 
really don't want to know under which circumstances you could have parsed more 
declarations :)

>
> But thinking about it now, I see my solution probably isn't optimal. In
> some cases, I will report type errors even when there is bad syntax further
> in the source, which is not common behavior. You got any suggestions for my
> use case?

If you don't want a "die on first error" strategy, add a "list of encountered 
errors" 
component to your user state and log all encountered errors.

data ParsingState = PS
    { symTbl :: SymbolTable
    , typeTbl :: TypeTable
    , errs :: [SyntaxError]
    }

data SyntaxError
    = UnknownType SourcePos String
    | UnknownOperator SourcePos String
    | MissingSemicolon SourcePos
    | ...

parseType = do
    typeId <- Tk.identifier
    tTable <- typeT
    case mlookup typeId tTable of
      Nothing -> return (BadType typeId)
      Just typeV -> return (GoodType typeId typeV)

varDeclaration = do
    varIdL <- Tk.commaSep1 Tk.identifier
    Tk.symbol ":"
    pos <- getPosition
    tp <- parseType
    case tp of
      BadType typeName -> do 
            logError (UnknownType pos typeName)
            return (VarDecl varIdL typeName)
      GoodType typeName typeV -> do
            forM_ varIdL (\vi -> insert vi into symbol table)
            return (VarDecl varIdL typeName)

When inserting variables into the symbol table, you should check whether it's 
already 
there, you don't want to parse

var
x, y : integer;
z, x : boolean;

without error.

I don't know what you will finally want to parse, but you should think about 
local 
variables with the same name as one in an enclosing scope early.

Finally,

realProgram = do
    prog <- program
    errs <- errorList
    if null errs
      then return prog
      else failWithErrors errs


>
> The source code for the interpreter is here:
> http://code.google.com/p/hpascal/ (pretty immature, my group just started
> writing it) if you want to take a look. Important files are: Parsing.hs
> (the parser itself) and TypeChecker.hs (parsers that access the internal
> monad state and build the table).

Hope that helps,
Daniel



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

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


End of Beginners Digest, Vol 12, Issue 3
****************************************

Reply via email to