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.  Closure (Matthew J. Williams)
   2.  Q) Using Data.Binary to parse a packet (Yang, Chul-Woong)
   3. Re:  Q) Using Data.Binary to parse a packet (Bjoern Brandenburg)
   4. Re:  Q) Using Data.Binary to parse a packet (Brent Yorgey)
   5. Re:  Closure (Magnus Therning)
   6.  type class question from Ternary Trees (MH)
   7. Re:  Closure (Matthew J. Williams)
   8. Re:  Closure (Brent Yorgey)
   9. Re:  type class question from Ternary Trees (Chadda? Fouch?)
  10.  MonadRandom or Control.Monad.Random (Michael P Mossey)


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

Message: 1
Date: Wed, 29 Jul 2009 02:02:40 +0100
From: "Matthew J. Williams" <matthewjwillia...@googlemail.com>
Subject: [Haskell-beginners] Closure
To: beginners@haskell.org
Message-ID: <4a6f9f92.0a04d00a.37e5.ffff8...@mx.google.com>
Content-Type: text/plain; charset="us-ascii"; format=flowed

Good morning

What is a closure and, what purpose does it serve?

        Sincerely,
        MJW



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

Message: 2
Date: Wed, 29 Jul 2009 09:19:39 +0900
From: "Yang, Chul-Woong" <cwy...@aranetworks.com>
Subject: [Haskell-beginners] Q) Using Data.Binary to parse a packet
To: beginners@haskell.org
Message-ID: <4a6f959b.20...@aranetworks.com>
Content-Type: text/plain; charset=EUC-KR

Dear Haskellers.

I would like to build simple UDP server application.
To parse a packet, I decide to use Data.Binary as followings:

data Packet = Packet {
foo :: Word16,
bar :: Word16,
baz :: Word32
} deriving (Show, Eq)

instance Binary Packet where
get = do
foo <- get :: Get Word16
bar <- get :: Get Word16
baz <- get :: Get Word32
return (Packet foo bar baz)
-- omitting put because we're now just receiving only

serveUDP port handlerfunc = withSocketsDo $
do
...
procMessages sock
where procMessages sock = do
(msg, _, addr) <- recvFrom sock 10240
handlerfunc addr msg
procMessages sock

myHandler addr msg = do
putStrLn $ decode (Data.ByteString.Lazy.Char8.Pack msg)

run = serveUDP "8080" myHandler


But, running it and sending sample udp packet results in following
exception.

*Main> run
Loading package syb ... linking ... done.
Loading package base-3.0.3.1 ... linking ... done.
Loading package array-0.2.0.0 ... linking ... done.
Loading package containers-0.2.0.1 ... linking ... done.
Loading package bytestring-0.9.1.4 ... linking ... done.
Loading package parsec-2.1.0.1 ... linking ... done.
Loading package network-2.2.1 ... linking ... done.
Loading package binary-0.5.0.1 ... linking ... done.
*** Exception: too few bytes. Failed reading at byte position 9
*Main>

Why and what can I do for this? Thanks in advance.

Chul-Woong Yang




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

Message: 3
Date: Tue, 28 Jul 2009 19:44:00 -0700
From: Bjoern Brandenburg <bbb....@gmail.com>
Subject: Re: [Haskell-beginners] Q) Using Data.Binary to parse a
        packet
To: "Yang, Chul-Woong" <cwy...@aranetworks.com>
Cc: beginners@haskell.org
Message-ID:
        <7ba288b20907281944m1e367041j653e633ba0cf9...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

2009/7/28 Yang, Chul-Woong <cwy...@aranetworks.com>:
> *** Exception: too few bytes. Failed reading at byte position 9
> *Main>
>
> Why and what can I do for this? Thanks in advance.

The Get monad is complaining that you are trying to read more than 8
bytes from a buffer of length 8. Presumably you are sending packets of
that size?

If you want to handle such errors (and you should), you could either
first test the length of the incoming message or use exception
handling to catch the exception in myHandler.

- Björn


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

Message: 4
Date: Wed, 29 Jul 2009 00:26:32 -0400
From: Brent Yorgey <byor...@seas.upenn.edu>
Subject: Re: [Haskell-beginners] Q) Using Data.Binary to parse a
        packet
To: beginners@haskell.org
Message-ID: <20090729042632.ga31...@seas.upenn.edu>
Content-Type: text/plain; charset=us-ascii

On Wed, Jul 29, 2009 at 09:19:39AM +0900, Yang, Chul-Woong wrote:
> 
> data Packet = Packet {
> foo :: Word16,
> bar :: Word16,
> baz :: Word32
> } deriving (Show, Eq)
> 
> instance Binary Packet where
> get = do
> foo <- get :: Get Word16
> bar <- get :: Get Word16
> baz <- get :: Get Word32
> return (Packet foo bar baz)
> -- omitting put because we're now just receiving only

By the way, I have nothing to contribute towards solving your actual
problem, but I wanted to point out that you can write this Binary
instance much more simply.  First of all, you can just write

> instance Binary Packet where
>   get = do
>     foo <- get
>     bar <- get
>     baz <- get
>     return (Packet foo bar baz)

and through the magic of type inference, Haskell will figure out the
right instances to use based on the fact that you use foo, bar, and
baz as arguments to Packet, which expects certain types.  (Although
having the type signatures there as documentation is not a terrible
idea.)

But actually, we can do even better:

> import Control.Applicative
>
> instance Binary Packet where
>   get = Packet <$> get <*> get <*> get

Amazing! =) This is exactly the sort of thing Applicative is for.  It
lets us program in an "applicative" style where we apply functions to
arguments, where the arguments are computed in some sort of context
that may have "effects".  Monads give us the power to decide which
monadic actions to run next based on the results of a previous action,
but we don't need that power here: we are always going to run 'get'
three times and put the results in a Packet.  Using Applicative lets
us avoid giving names to the results of the calls to get.

-Brent


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

Message: 5
Date: Wed, 29 Jul 2009 08:37:46 +0100
From: Magnus Therning <mag...@therning.org>
Subject: Re: [Haskell-beginners] Closure
To: "Matthew J. Williams" <matthewjwillia...@googlemail.com>
Cc: beginners@haskell.org
Message-ID:
        <e040b520907290037v3cbcc191w44191fd39ce7b...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

On Wed, Jul 29, 2009 at 2:02 AM, Matthew J.
Williams<matthewjwillia...@googlemail.com> wrote:
> Good morning
>
> What is a closure and, what purpose does it serve?

This seems like a good explanation: http://www.haskell.org/haskellwiki/Closure

/M

-- 
Magnus Therning                        (OpenPGP: 0xAB4DFBA4)
magnus@therning.org          Jabber: magnus@therning.org
http://therning.org/magnus         identi.ca|twitter: magthe


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

Message: 6
Date: Wed, 29 Jul 2009 10:28:41 -0400
From: MH <mha...@gmail.com>
Subject: [Haskell-beginners] type class question from Ternary Trees
To: beginners@haskell.org
Message-ID:
        <648da0750907290728t1aa2b8bdr96b870846a419...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

I am going over ternary tree library and it all looks clear to me with
exception of the method below. Could you please explain to me how to
read this:

data TernarySet a = Node !a !(TernarySet a) !(TernarySet a) !(TernarySet a)
                  | Null !(TernarySet a)
                  | End                deriving (Show, Eq)

instance Binary a => Binary (TernarySet a) where
...... skipped

   get = do  ---first call to get
        tag <- getWord8
        case tag of
            _ | tag < 8 ->
                do
                    ch <- get   --- second call to get
                    l <- if tag `testBit` 2 then get else return End
---third call to get
                    e <- if tag `testBit` 1 then get else return End
                    h <- if tag `testBit` 0 then get else return End
                    return (Node ch l e h)
            8 -> return (Null End)

           .......skipped
What I don't understand here is recursive(?) call to 'get'. The first
'get' as I understand is an instance implementation of get from Binary
module.
What is 'ch <- get' (the second call) and 'get' inside 'if tag
`testBit` 2 then get ...' (the third call)?
tag <- getWord8 reads word8 from monad, then ch <- get reads what
(just a copy of tag???)?
Is get inside if ..then else statements is a look ahead get calls, to
read next word8?
Please provide more details if possible.
Thanks a lot.

Malik


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

Message: 7
Date: Wed, 29 Jul 2009 21:11:02 +0100
From: "Matthew J. Williams" <matthewjwillia...@googlemail.com>
Subject: Re: [Haskell-beginners] Closure
To: beginners@haskell.org
Message-ID: <4a70acb7.1c07d00a.389e.ffff9...@mx.google.com>
Content-Type: text/plain; charset="us-ascii"; format=flowed


>Williams<matthewjwillia...@googlemail.com> wrote:
> > Good morning
> >
> > What is a closure and, what purpose does it serve?
>
>This seems like a good explanation: http://www.haskell.org/haskellwiki/Closure
>
>/M
>
>Williams<matthewjwillia...@googlemail.com> wrote:
How does a closure differ from a binding? An example or two would be nice. :-)

         Sincerely,
         MJW  



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

Message: 8
Date: Wed, 29 Jul 2009 16:24:42 -0400
From: Brent Yorgey <byor...@seas.upenn.edu>
Subject: Re: [Haskell-beginners] Closure
To: beginners@haskell.org
Message-ID: <20090729202442.ga8...@seas.upenn.edu>
Content-Type: text/plain; charset=us-ascii

On Wed, Jul 29, 2009 at 09:11:02PM +0100, Matthew J. Williams wrote:
>
>> Williams<matthewjwillia...@googlemail.com> wrote:
>> > Good morning
>> >
>> > What is a closure and, what purpose does it serve?
>>
>> This seems like a good explanation: 
>> http://www.haskell.org/haskellwiki/Closure
>>
>> /M
>>
>> Williams<matthewjwillia...@googlemail.com> wrote:
> How does a closure differ from a binding? An example or two would be nice. :-)

A closure is essentially a binding, *together with* the enclosing
environment---the idea being that the binding may refer (via free
variables) to things in its environment.  The ability to have closures
is absolutely crucial to having first-class functions.

For example, consider this function:

  mkAdder :: Int -> (Int -> Int)
  mkAdder y = \x -> x + y

mkAdder takes an Int as an argument, and returns a function (Int ->
Int) as a result.  But take a look at the function it returns: \x -> x
+ y has a free variable (y) which refers to its environment.  So
really what you get when you call mkAdder with a particular argument
(say, 3) is a closure, containing the function \x -> x + y together
with the environment (y = 3).  

Of course, hopefully you have realized that mkAdder is really just
(+), written in a funny way!  So this isn't a contrived example;
closures are quite fundamental in Haskell.

With that said, on some level the idea of a closure is really just an
implementation detail---I wouldn't say that understanding it is of
fundamental importance in learning Haskell.  But learning things never
hurts (except when it does).

Hope this helps!
-Brent


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

Message: 9
Date: Wed, 29 Jul 2009 23:39:36 +0200
From: Chadda? Fouch? <chaddai.fou...@gmail.com>
Subject: Re: [Haskell-beginners] type class question from Ternary
        Trees
To: MH <mha...@gmail.com>
Cc: beginners@haskell.org
Message-ID:
        <e9350eaf0907291439q296d6355q62ae206792447...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

On Wed, Jul 29, 2009 at 4:28 PM, MH<mha...@gmail.com> wrote:
> I am going over ternary tree library and it all looks clear to me with
> exception of the method below.
>
> <cut>
>
> What I don't understand here is recursive(?) call to 'get'. The first
> 'get' as I understand is an instance implementation of get from Binary
> module.

get is a method of the Binary typeclass, it is an action in the Get
monad. A "Get a" action can be run against a bytestring to transform a
binary code into an Haskell value of type a. A Binary instance
describe how to encode (with put) to binary records and decode (with
get) from binary records a specific type, here "TernarySet a".

Here you have the definition of get for a ternary tree, the get inside
this definition are call to get for the right type, not always the
same, for instance in :

> ch <- get

This get is of type "Get a" (of TernarySet _a_), this can be inferred
because ch is later used in "Node ch l e h". Similarly l, e and h are
determined to be of type "TernarySet a" and so the gets in :

> l <- if tag `testBit` 2 then get else return End
> e <- if tag `testBit` 1 then get else return End
> h <- if tag `testBit` 0 then get else return End

are of type "Get (TernarySet a)" and so they recursively call the get
we're defining (that is no surprise since this type is recursive).

getWord8 is one of the primitive provided by Binary, though you could
use get instead, it would often be unclear or need a type annotation
(like here).

If you have experienced the read function, this is the same idea,
though a little bit more advanced (one of these things you can't
easily do with object : be polymorphic on the return type).

Binary can achieve pretty good performances in good cases, sometimes
only limited by the speed of your hardware.

-- 
Jedaï


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

Message: 10
Date: Thu, 30 Jul 2009 17:04:54 -0700
From: Michael P Mossey <m...@alumni.caltech.edu>
Subject: [Haskell-beginners] MonadRandom or Control.Monad.Random
To: beginners@haskell.org
Message-ID: <4a723526.2030...@alumni.caltech.edu>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

Where can I find MonadRandom or Control.Monad.Random to install? It doesn't 
seem 
to be a system library, I can't find it with cabal or Hoogle.

Thanks,
Mike


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

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


End of Beginners Digest, Vol 13, Issue 18
*****************************************

Reply via email to