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. Re:  More Deserialization Woes (Yitzchak Gale)
   2. Re:  More Deserialization Woes (Yitzchak Gale)
   3.  Right-associating infix application operators (Tom Hobbs)
   4.  Right-associating infix application operators (Tom Hobbs)
   5. Re: Fwd: [Haskell-beginners] More Deserialization Woes
      (Daniel Fischer)
   6. Re:  Right-associating infix application operators
      (Antoine Latter)


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

Message: 1
Date: Tue, 6 Jul 2010 13:07:29 +0300
From: Yitzchak Gale <g...@sefer.org>
Subject: Re: [Haskell-beginners] More Deserialization Woes
To: Tom Hobbs <tvho...@googlemail.com>
Cc: beginners@haskell.org
Message-ID:
        <aanlktilbstluzi0dw4dekcj89mbxhn5kxdcg3tahb...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

Tom Hobbs wrote:
> I've been reading through various tutorials and they all put IO as the
> outermost monad, like you suggest.  However, I don't think that's what I
> want.

It is definitely what you want.

> ...am I in a niche where my requirement makes sense

No, you are doing something quite routine.

> or does my requirement make no sense

Your requirement is fine, and you would have no trouble
satisfying it with IO as your outer type.

But there are two basic approaches to dealing with failure:
returning a pure value that indicates the failure, like Maybe
or Either, or throwing an exception in IO that is not reflected
in the type. Since you are using Data.Binary for deserialization,
that is designed to use the second method. So rather than
spending more time on how to structure your types to indicate
failure, let's leave that aside for now and focus on how to do
deserialization. Error processing will automatically happen the
way you say - if anything goes really wrong in the middle, an
exception will be thrown and the entire operation will terminate
immediately. Later on, you can learn how to catch the exception
and do something other than end your program with the
standard error message.

> readNames 0 _ = []
> readNames n h = do
>   length <- fmap (fromIntegral . runGet getWord32be) $ L.hGet h 4
>   name <- L.hGet h length
>   (UTF.toString name) : readNames (n-1) h

Besides the type errors, which others have been helping you with,
(and another minor point - avoid using "length" as a variable name,
it is the name of one of the most commonly used Prelude functions),
let's look at the whole approach.

You are ping-ponging back and forth here between the Get monad
and manually reading ByteStrings from the handle.

The idea of the Get monad is to give a complete description
of your serialization format. Then, reading the ByteStrings will be
driven by your serialization format - just the right number of bytes
will automatically be read off the wire at each stage.

Here is the serialization format (note that we're not reading anything
here, just describing the format):

readNames :: Int -> Get [String]
readNames n = replicateM n $ do
  len <- getWord32be
  name <- getByteString len
  return $ UTF8.toString name

Now, in your "main" function (whose type is IO ()), you can
write:

  names <- fmap (runGet $ readNames n) $ L.hGetContents h

That will read bytes off the wire lazily, just the right number
of bytes to deserialize n names.

Of course, that will leave your handle in an unusable state.
If you have more to read after that, you have a few options.
Best is to combine everything you need to read out of
that handle into a single Get monad object that describes
the entire deserialization. Another (messier) approach is to use
runGetState instead of runGet - that gives you, in addition
to the deserialized data, a lazy ByteString that represents
additional bytes that can later be read off the handle.

Regards,
Yitz


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

Message: 2
Date: Tue, 6 Jul 2010 13:58:38 +0300
From: Yitzchak Gale <g...@sefer.org>
Subject: Re: [Haskell-beginners] More Deserialization Woes
To: Tom Hobbs <tvho...@googlemail.com>
Cc: beginners@haskell.org
Message-ID:
        <aanlktilypf1dajh5c6vvewoa-9q0b7pxfyfuv6ous...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

I wrote:
> readNames :: Int -> Get [String]
> readNames n = replicateM n $ do
>  len <- getWord32be
>  name <- getByteString len
>  return $ UTF8.toString name

Sorry, there's a type error there. You need to
convert the Word32 to an Int:

  name <- getByteString $ fromIntegral len

Regards,
Yitz


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

Message: 3
Date: Tue, 6 Jul 2010 12:00:33 +0100
From: Tom Hobbs <tvho...@googlemail.com>
Subject: [Haskell-beginners] Right-associating infix application
        operators
To: beginners@haskell.org
Message-ID:
        <aanlktimdikn59ib1ey1mrczul8ok95se3pdo8mxpi...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

In people's responses to my serialization questions, I've seen them using $.

I didn't know what it was so I've looked it up.  Can someone please confirm
my understanding of what it does, please?

According to http://en.wikibooks.org/wiki/Haskell/Practical_monads, after
the second code sample in the "Return Values" section, it seems to suggest
that $ is only used to avoid using so many brackets.  Which seems to make
sense, but looking at it's definition in Prelude I really can't see why it's
useful.

Yitz gave me the code;

fmap (runGet $ readNames n) $ L.hGetContents h

So can I rewrite this without the $ like this?

fmap (runGet (readNames n)) (L.hGetContents h)

Is there any additional benefit to using $ than just not having to write as
many brackets?

Thanks,

Tom
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20100706/b3f56bae/attachment-0001.html

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

Message: 4
Date: Tue, 6 Jul 2010 12:00:33 +0100
From: Tom Hobbs <tvho...@googlemail.com>
Subject: [Haskell-beginners] Right-associating infix application
        operators
To: beginners@haskell.org
Message-ID:
        <aanlktimhlgcqbzuwplgwmpyk8etouggun7rke5lzu...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

In people's responses to my serialization questions, I've seen them using $.

I didn't know what it was so I've looked it up.  Can someone please confirm
my understanding of what it does, please?

According to http://en.wikibooks.org/wiki/Haskell/Practical_monads, after
the second code sample in the "Return Values" section, it seems to suggest
that $ is only used to avoid using so many brackets.  Which seems to make
sense, but looking at it's definition in Prelude I really can't see why it's
useful.

Yitz gave me the code;

fmap (runGet $ readNames n) $ L.hGetContents h

So can I rewrite this without the $ like this?

fmap (runGet (readNames n)) (L.hGetContents h)

Is there any additional benefit to using $ than just not having to write as
many brackets?

Thanks,

Tom
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20100706/e772e9c1/attachment-0001.html

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

Message: 5
Date: Tue, 6 Jul 2010 13:01:59 +0200
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: Fwd: [Haskell-beginners] More Deserialization Woes
To: Tom Hobbs <tvho...@googlemail.com>
Cc: beginners@haskell.org
Message-ID: <201007061302.00199.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="utf-8"

On Tuesday 06 July 2010 12:06:53, Tom Hobbs wrote:
> On Tue, Jul 6, 2010 at 10:42 AM, Daniel Fischer 
<daniel.is.fisc...@web.de>wrote:
> > Nevertheless, IO (Maybe [String]) is, I believe, the appropriate type.
>
> I accept that you guys have most likely forgotten more about Haskell
> than I know,

Well, we're here to change that :)

> but can you explain to me why this is the appropriate type?

For one thing, because main's type is IO (), so ultimately you will have IO 
as the outermost Monad.
If you must seriously intertwine I/O with pure computations, using a Monad-
transformer with IO as the innermost Monad would be appropriate, but 
(admittedly I took just a cursory glance at what you try to do) that didn't 
seem the case here.
If I/O needn't be woven into the computation that strongly, it's better to 
keep I/O and computations as separate as possible (makes refactoring 
easier, for example), that usually means you have a small IO-wrapper 
calling pure functions to work with the data gotten from IO.

But as Yitz pointed out, deserialisation throws exceptions if things go 
wrong, so

IO [String]

could be more appropriate.

>
> Note to self: I think I've got the answer to this at the end of this
> email!
>
> > > However, the result of "IO [Just "a", Just "b", Nothing, Nothing]"
> > > would signify that communication failed halfway through and would
> > > not make sense in my context.  This is what the advice seems to be
> > > suggesting I write.  But in this case, I'd prefer to return
> > > "Nothing" to signify that a problem occurred.
> >
> > You can do that by applying sequence (at the type [Maybe String] ->
> > Maybe [String]).
> >
> > Say you have
> >
> > ping0 :: args -> IO [Maybe String]
> >
> > then you'd use
> >
> > ping :: args -> IO (Maybe [String])
> >  ping = fmap sequence ping0
>
> Okay, I've looked at the definition of sequence in Prelude and I think I
> understand what's going on.  I need to experiment with it first before I
> fully get it.

That's normal. The definition of sequence isn't immediately accessible.

>
> So if ping0 returns IO [Just "a", Just "b", Nothing] then then what
> would ping return?  IO (Just ["a", "b", ?]).  Nevermind, I can play with
> that and work it out later.

Prelude> sequence $ [Just (1 :: Int), Just 2, Just 3]
Just [1,2,3]
Prelude> sequence $ [Just (1 :: Int), Just 2, Nothing, Just 3]
Nothing

And sequence short-cuts when there's a Nothing:
Prelude> sequence $ [Just (1 :: Int), Just 2, Nothing, Just 3] ++ replicate 
1000000000 (Just 4)
Nothing
(0.00 secs, 0 bytes)
Prelude> sequence $ [Just (1 :: Int), Just 2, Nothing, Just 3] ++ repeat 
(Just 4)
Nothing
(0.01 secs, 0 bytes)

>
> Thinking to my requirement I think I'd want something more like;
>
> ping :: args -> IO (Maybe [String])
> ping args = fmap f ps
>                  where
>                  ps = ping0 args
>                  f | Nothing `elem` ps = Nothing
>
>                    | otherwise             = fmap sequence ps
>
> Or would I get this behaviour for free straight from the use of
> sequence?
>

Yes, sequence does that automatically for you :)
The problem is that sequence must traverse the entire list to know whether 
it'll return Nothing or (Just list) if there's no Nothing, so it can take a 
while if the list is long (and forever, if the list is infinite and doesn't 
contain a Nothing).

> > > Is it possible, to extract the values out of the IO monad so it can
> > > be used in pure functions.
> >
> > Yes, but you needn't (and shouldn't in general).
>
> Again, what is the why?
>
> My theory is that I want to get [String] from ping, and then (possibly)
> do lots of other things with it that don't require any kind of IO.  But
> maybe that's not true and I need to think a bit harder about what the
> caller is likely to do with the result from ping.  In terms of
> performance (memory footprint, speed of execution, etc) does "carrying
> around the IO monad" make much of a difference?
>
> <insert five minute reflective pause here>
>
> You're right.  I don't need to pull the [String] out of the IO monad.
>  Suprise, suprise, the general pattern is appropriate in my case. 
> Something clicked in my head when I re-read "pureStuff someValues" -
> this time is was a good click though!
>
> Please understand, I'm challenging you on the answers because I don't
> understand them, not because I think they're wrong!  :-)

I understand. I would've gone into more detail, but I was in a hurry :)

>
> Thanks again for the very quick and helpful answers!
>
> Tom


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

Message: 6
Date: Tue, 6 Jul 2010 06:10:06 -0500
From: Antoine Latter <aslat...@gmail.com>
Subject: Re: [Haskell-beginners] Right-associating infix application
        operators
To: Tom Hobbs <tvho...@googlemail.com>
Cc: beginners@haskell.org
Message-ID:
        <aanlktikfhphbjxg27uny_ro3lzb2peplbeothteqz...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

Hi Tom,

There are no additional benifits to the '$' function - you pretty much have
it.

Wait - one more. It can be used as a 'section' like any other binary
operator, so ($ 4) :: (Int -> a) -> a. But that doesn't come up a whole lot.
This is much like how (* 5) 6 == 30.

Antoine

On Jul 6, 2010 6:00 AM, "Tom Hobbs" <tvho...@googlemail.com> wrote:

In people's responses to my serialization questions, I've seen them using $.

I didn't know what it was so I've looked it up.  Can someone please confirm
my understanding of what it does, please?

According to http://en.wikibooks.org/wiki/Haskell/Practical_monads, after
the second code sample in the "Return Values" section, it seems to suggest
that $ is only used to avoid using so many brackets.  Which seems to make
sense, but looking at it's definition in Prelude I really can't see why it's
useful.

Yitz gave me the code;

fmap (runGet $ readNames n) $ L.hGetContents h

So can I rewrite this without the $ like this?

fmap (runGet (readNames n)) (L.hGetContents h)

Is there any additional benefit to using $ than just not having to write as
many brackets?

Thanks,

Tom

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20100706/3bac7e40/attachment.html

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

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


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

Reply via email to