Send Beginners mailing list submissions to
        [email protected]

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
        [email protected]

You can reach the person managing the list at
        [email protected]

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


Today's Topics:

   1.  More Context for Failures (Data.Aeson) (Darrin Thompson)
   2. Re:  More Context for Failures (Data.Aeson) (Brent Yorgey)
   3. Re:  More Context for Failures (Data.Aeson) (Brent Yorgey)
   4.  A  tree code (bahad?r altan)
   5. Re:  A tree code (AbdulSattar Mohammed)


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

Message: 1
Date: Thu, 23 Feb 2012 14:21:25 -0500
From: Darrin Thompson <[email protected]>
Subject: [Haskell-beginners] More Context for Failures (Data.Aeson)
To: [email protected]
Message-ID:
        <CABe4vZVy82-Ly05kGhLs6pvDjU+u6JD=_qscayfb8_78t50...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

I had a problem last night where I was parsing a lot of non-trivial
and annoyingly inconsistent json. These json documents have a very bad
habit of replacing lists with single objects when a particular
document contains a singleton list, which is maddening, but I can work
around it when I know to expect it. That's just one example of the
kinds of failures due to inconsistent documents.

My parsing code looks like this:

(Data.Aeson, btw)

instance FromJSON Whatever where
 parseJSON (Object o) = do
   a <- parseSomething o
   b <- parseSomethingElse o
   c <- ...
   andManyMore <- ...
   return $ Whatever a b c ...
 parseJSON _ = fail "dude"

In my code I might have 10 sub parsers so any of them might fail. When
the parser fails I see a failure message like "expected [a] but got
Object" and no additional context. And of course if I was in a
language with a stack I could just look at the stack. (And I'd be
miserable in other ways. So I'm not exactly complaining...) These
documents are long enough that I burned a lot of time comparing Aeson
dumps looking for where I got an object instead of an array.

Wouldn't it be neato if I could do this...

instance FromJSON Whatever where
 parseJSON (Object o) = do
   a <- failureContext "branchA" $ parseSomething o
   b <- failureContext "branchB" parseSomethingElse o
   return $ Whatever a b
 parseJSON _ = fail "dude"

Now when it dies, the error message will be "branchB: expected [a] but
got Object".

This seems like a useful utility. Does it already exist and I don't
know it? Would it be easy to write? I'm a little bit out of my depth
here. I've never tried to handle exceptions in Haskell before.

Seems like it would be something like:

failureContext :: (MonadIOSomething m) => String -> m a -> m a
failureContext errorContextName = -- Catch exceptions and rewrite messages
--  or wrap the exception in something and rethrow like Erlang or Java

-- 
Darrin



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

Message: 2
Date: Thu, 23 Feb 2012 14:51:57 -0500
From: Brent Yorgey <[email protected]>
Subject: Re: [Haskell-beginners] More Context for Failures
        (Data.Aeson)
To: [email protected]
Message-ID: <[email protected]>
Content-Type: text/plain; charset=us-ascii

On Thu, Feb 23, 2012 at 02:21:25PM -0500, Darrin Thompson wrote:
> 
> Wouldn't it be neato if I could do this...
> 
> instance FromJSON Whatever where
>  parseJSON (Object o) = do
>    a <- failureContext "branchA" $ parseSomething o
>    b <- failureContext "branchB" parseSomethingElse o
>    return $ Whatever a b
>  parseJSON _ = fail "dude"
> 
> Now when it dies, the error message will be "branchB: expected [a] but
> got Object".

What immediately comes to mind would be to use ReaderT [String] along
with the 'local' method to maintain an explicit stack of parsing
contexts.  However, parseJSON is not polymorphic in the monad used --
so there's no way to use ReaderT in the implementation of parseJSON
methods.

However, parseJSON returns a 'Parser' which is defined like this:

-- | Failure continuation.
type Failure f r   = String -> f r
-- | Success continuation.
type Success a f r = a -> f r

-- | A continuation-based parser type.
newtype Parser a = Parser {
      runParser :: forall f r.
                   Failure f r
                -> Success a f r
                -> f r
    }

So I think it is possible to leverage the "failure continuation" to do
what you want.  In particular,

  failureContext :: String -> Parser a -> Parser a
  failureContext branch p = Parser (\f s -> runParser p (f . (++ (branch ++ ": 
"))) s)

Untested but I'm pretty sure it will work.  The idea is that
'failureContext' transforms a parser by modifying its "failure
continuation" to first tack the current branch onto the front of the
error message.  These can be stacked just like you would expect.

Argh, I just realized that this *would* work except that
Data.Aeson.Types.Internal does not export the Parser constructor!  In
fact, the aeson package also does not export the
Data.Aeson.Types.Internal module at all.  So to make this work you
would have to build your own customized version of aeson.  This is not
too difficult (cabal unpack aeson; cd aeson; export more stuff; bump
version number in cabal file; cabal install) but if this is something
you want to release then obviously you can't have it depending on a
customized version of aeson.  If it's just an internal tool though,
this may work fine.  Of course, you can also submit a patch to the
aeson maintainer adding the relevant exports.

-Brent



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

Message: 3
Date: Thu, 23 Feb 2012 20:22:37 -0500
From: Brent Yorgey <[email protected]>
Subject: Re: [Haskell-beginners] More Context for Failures
        (Data.Aeson)
To: [email protected]
Message-ID: <[email protected]>
Content-Type: text/plain; charset=us-ascii

On Thu, Feb 23, 2012 at 02:51:57PM -0500, Brent Yorgey wrote:
> 
>   failureContext :: String -> Parser a -> Parser a
>   failureContext branch p = Parser (\f s -> runParser p (f . (++(branch ++ ": 
> "))) s)

Whoops, of course that should be

  ((branch ++ ": ") ++)

instead of

  (++ (branch ++ ": "))

to put the branch tag on the beginning instead of the end of the
message.

-Brent



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

Message: 4
Date: Fri, 24 Feb 2012 04:50:48 +0000 (GMT)
From: bahad?r altan <[email protected]>
Subject: [Haskell-beginners] A  tree code
To: "[email protected]" <[email protected]>
Message-ID:
        <[email protected]>
Content-Type: text/plain; charset="iso-8859-1"

Hello. There is a code below and I couldn't understand it myself. Could you 
help me with that please? ?I especially have no idea about "data Tree alpha = 
Empty |?Node?" part.


data Tree alpha = Empty |?Node ( alpha ,Tree alpha , Tree alpha )
x = Node (1,Node (2,Empty ,Empty),Node(3,Empty ,Empty))
y = Node(3,Empty ,Empty)

Thanks in advance
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120224/4ffc33ba/attachment-0001.htm>

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

Message: 5
Date: Fri, 24 Feb 2012 10:46:54 +0530
From: AbdulSattar Mohammed <[email protected]>
Subject: Re: [Haskell-beginners] A tree code
To: bahad?r altan <[email protected]>,        [email protected]
Message-ID:
        <ca+mxqh9bfydqx_dxqyoyczlpqcwsbw+4xze-8xwnnwri9ni...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

Hello bahadyr,

Before going into data Tree alpha, consider a simpler version,  tree that
stores only an integer in it.

Now, a (binary) tree will consist of nodes. A node can be an Empty node or
store an integer and link to two other nodes (a left one and a right one).
So, basically we have only two types of nodes. We represent this in this
way:

data Node = Empty
          | ValueNode Int, Node, Node -- An integer, a left node and a
right node

We construct this node this way:
n = Empty --creates an empty node
n = ValueNode 3, Empty, Empty -- A node containing only one value
n = ValueNode 3, (Node 4 Empty Empty), (Node 5 Empty Empty) -- 3 with left
4 and right 5

This has a limitation: we can store only integers in it. Let's remove that
limitation by using Type Variables.
Instead of saying that Node stores only Int, we must say that Node needs a
Type first, then it stores values of that type in it.

So, instead of just:

data Node

we have

data Node a = Empty -- a is the type variable

Now, Node uses that a instead of Int

data Node a = Empty
            | ValueNode a, (Node a), (Node a)

(Node a), (Node a) tell that the left and right of the trees must be of
type (Node a) i.e. it cannot left cannot have an Int while right has a
Char. The whole tree holds the same type.

The creation of objects is same as above. The types of x and y would now be x
:: Node Int, y::Node Int

We can now have:
c = ValueNode ("haskell", Empty, Empty) too.

Hope you are clear on this and welcome to Haskell!

On Fri, Feb 24, 2012 at 10:20 AM, bahad?r altan <[email protected]> wrote:
> Hello. There is a code below and I couldn't understand it myself. Could
you
> help me with that please?  I especially have no idea about "data Tree
alpha
> = Empty | Node " part.
>
>
> data Tree alpha = Empty | Node ( alpha ,Tree alpha , Tree alpha )
> x = Node (1,Node (2,Empty ,Empty),Node(3,Empty ,Empty))
> y = Node(3,Empty ,Empty)
>
> Thanks in advance
>
> _______________________________________________
> Beginners mailing list
> [email protected]
> http://www.haskell.org/mailman/listinfo/beginners
>

-- 
Warm Regards,

AbdulSattar Mohammed
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120224/a64eeea6/attachment-0001.htm>

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

_______________________________________________
Beginners mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 44, Issue 23
*****************************************

Reply via email to