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.  computing multiple attributes in Happy (kak dod)
   2. Re:  functional parser type error (Brent Yorgey)
   3.  De-serialising with minimal code noise and       fluff...
      possible? (Sean Charles)
   4. Re:  De-serialising with minimal code noise and fluff...
      possible? (David McBride)


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

Message: 1
Date: Tue, 3 Apr 2012 18:17:46 +0530
From: kak dod <kak.dod2...@gmail.com>
Subject: [Haskell-beginners] computing multiple attributes in Happy
To: beginners@haskell.org
Message-ID:
        <CAJ4=wngkcaqjipt88_gcxm77efnnxy0h78k2em2hx8dgwrl...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

Hello,
I am trying out the happy parser.
Take the second example Binary to Decimal given on the happy site:
http://www.haskell.org/happy/doc/html/sec-AttributeGrammarExample.html

This example computes the decimal value equivalent to the given binary
string.

I want to modify it so that along with the decimal value, it should compute
a list of data values, like MyLeft, MyRight.
I have modified the grammar given on the site as shown below (in the end).

What I want to do is generate a list of MyLeft, MyRight such that MyLeft
denotes 0 and MyRight denotes 1.
So, if my input is "1011\n" then I expect the list attribute to be:
[MyRight, Myleft, MyRight, MyRight]

The happy compiles this thing without any problem, ghci compiles and loads
it correctly. But when I run the following command I always get only the
decimal value and not the list:

So my questions are:

   1. *How shall one compute, access multiple attributes in happy first? **(use
   in Haskell code, write to file etc)*
   2. *How shall one access any one or multiple of the computed attributes
   in GHCi then?*
   3. *Am I computing the list correctly?
   *


Thanks in advance.
     kak

Here is my happy grammar code:
-----------------------------
{
module BitsParser (parse) where
test = parse "1011\n"

-- how to write the list attribute to a file here?

data Dirs = MyLeft | MyRight deriving Show
fun a b = a^b
}

%tokentype { Char }

%token minus { '-' }
%token plus  { '+' }
%token one   { '1' }
%token zero  { '0' }
%token newline { '\n' }

%attributetype { Attrs }
%attribute value { Integer }
%attribute pos   { Int }
%attribute list   { [Dirs] }

%name parse start

%%

start
   : num newline { $$ = $1 }

num
   : bits        { $$ = $1       ; $1.pos = 0 ; $1.list = [] }
   | plus bits   { $$ = $2       ; $2.pos = 0 ; $2.list = [] }
   | minus bits  { $$ = negate $2; $2.pos = 0 ; $2.list = [] }

bits
   : bit         { $$ = $1
                 ; $1.pos = $$.pos ; $1.list =  $$.list
                 }

   | bits bit    { $$ = $1 + $2 ; $$.list = $1.list ++ $2.list
                 ; $1.pos = $$.pos + 1
                 ; $2.pos = $$.pos
                 }

bit
   : zero        { $$ = 0 ; $$.list = [MyLeft] }
   | one         { $$ = fun 2 ($$.pos) ; $$.list = [MyRight] }

{
happyError = error "parse error"
}
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120403/f988d5e6/attachment-0001.htm>

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

Message: 2
Date: Tue, 3 Apr 2012 14:02:22 -0400
From: Brent Yorgey <byor...@seas.upenn.edu>
Subject: Re: [Haskell-beginners] functional parser type error
To: beginners@haskell.org
Message-ID: <20120403180222.ga1...@seas.upenn.edu>
Content-Type: text/plain; charset=us-ascii

On Mon, Apr 02, 2012 at 09:58:31PM +0100, felipe zapata wrote:
> Hi.
> 
> I'm Following the book of Programming in haskell written by Graham Hutton.
> In Chapter number 8 there is a discussion about functional parsers and it
> is defined a functional Parser item and some basic parsers as follow

How is the Parser type defined?  The problem may be that you need to
make Parser a newtype, and write a Monad instance for it -- if Parser is
defined as a type synonym, then there will be a default Monad instance
used (the one for functions) but that is not the one you want.

-Brent



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

Message: 3
Date: Tue, 03 Apr 2012 23:26:55 +0100
From: Sean Charles <s...@objitsu.com>
Subject: [Haskell-beginners] De-serialising with minimal code noise
        and     fluff... possible?
To: beginners@haskell.org
Message-ID: <4f7b792f.7060...@objitsu.com>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

Hi list,

to further my haskell skills I decided to produce my own raw MySQL 
connection. So far I can connect to the server and extract the handshake 
initialisation packet (HIP) and create the client authentication packet. 
Once I've figured out how to implement the salting and hashing I have a 
chance of starting a session. Not a problem, just got to do it. I want a 
module that I can use for simple DBMS I/O that doesn't use libmysql or 
odbc as sometimes these things just refuse to install on certain 
platform / architecture combinations!

So, here's my problem: I kind of understand monads, I can use them and 
appreciate what/why they are useful etc. but my current implementation 
of reading the HIP into the type I created (shown next) appears to me at 
least to be plain clunky, ugly and inelegant compared to ninja haskell 
code I've read and one day hope to match, here's my code... apologies 
for the length of the post but I hope it's interesting to some!

data PktHIP = PktHIP
               { hipProtoVer :: Int
               , hipSvrVer   :: String
               , hipThreadId :: Int
               , hipScramble :: BS.ByteString
               , hipSvrCaps  :: Integer
               , hipSvrLang  :: Int
               , hipSvrStat  :: Int
               , hipScramLen :: Int
               , hipPlugin   :: String
               } deriving(Show)

and reading it...

getHIP :: Handle -> IO PktHIP
getHIP h = do
   ver <- streamInt h 1
   str <- getNTS h
   tid <- streamInt h 4
   buf <- BS.hGet h 8
   BS.hGet h 1 -- filler
   scap1 <- streamInt h 2
   slang <- streamInt h 1
   sstat <- streamInt h 2
   scap2 <- streamInt h 2
   scrln <- streamInt h 1
   BS.hGet h 10 -- filler
   scram <- getNTS h
   -- todo: there *has* to be a more concise way of doing this?
   return $
     PktHIP { hipProtoVer = ver
            , hipSvrVer   = str
            , hipThreadId = tid
            , hipScramble = buf
            , hipSvrCaps  = fromIntegral scap1 -- scap2 << 2 ? TODO!
            , hipSvrLang  = slang
            , hipSvrStat  = sstat
            , hipScramLen = scrln
            , hipPlugin   = scram
            }

-- Extract an N byte Int value from the input stream
streamInt :: Handle -> Int -> IO Int
streamInt h len = liftM bsVal $ BS.hGet h len

bsVal :: BS.ByteString -> Int
bsVal = BS.foldr' (\byte total ->  fromEnum byte + (shiftL total 8)) 0

-- Get a Null-Terminated String
getNTS :: Handle -> IO String
getNTS h = streamInt h 1 >>= \b -> getString h "" b
            where
              getString :: Handle -> String -> Int -> IO String
              getString h acc c
                | c == 0  = return $ reverse acc
                | otherwise = streamInt h 1 >>= getString h ((chr c):acc)


Then I read about the Data.Binary package and the Get monad and got this 
far...

readHIP :: Get (Maybe PktHIP)
readHIP = do
   return (Nothing)

I looked at the example on this page: 
http://www.haskell.org/haskellwiki/DealingWithBinaryData , I stopped 
because I realised that the Get monad was only going to mean I ended up 
with very similarly structured code and probably  a lot of it. I know 
the PktHIP has lots of fields but even so I am convinced it can be 
reduced and re-factored into much more beautiful code that I know how to 
write so far.

I've tried to reason about it and I can "see" that there is a function 
out there that takes a Handle and "a record modifier function" and I can 
see also that it might be time for me to create my first Monad type ever
IIUC, by implementing >>=, >> and return and I make use of the many 
monad centric modules that exist but I also am under the impression that 
I can add as many other functions to my Monad class as I need to do what 
I need to do, is that correct?

I would therefore like some way to create an initial "thing" that 
contains the handle passed in to the function so that the >>= 
invocations can be as clean as possible because somewhere in my mind I 
can feel code resembling something like this:

getHIP :: Handle -> MyMonad PktHIP
getHIP h = do    -- science fiction code starts now!

     let rs = ... --- record state monad thing with "h" and "PktHIP"

     getInt 1 rs hipProtoVer >>
     getNTS   rs hipSvrVer >>
     getInt 4 rs hipThreadId >>
     getBS  8 rs hipScramble >>
     skip 1 >>
        :
        : ...etc
     return $ theHIP

getInt :: Int -> ST ? -> (PktHIP -> PktHIP) -> MyMonad PktHIP
getInt len state fmod = do
     val <- readStream ("h from state") len
let state' = modify state by setting field "fmod" to "val"
        return state'

Problems / things I am clueless about how to do here

   |1| how to create "something" that each >>= can modify (state monad 
instance?)
   |2| how to put the Handle "h" somewhere it can be read on each read 
action
   |3| everything else!!!

So, any ideas, examples etc. would be most enlightening and gratefully 
absorbed!
Sean Charles.
:)




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

Message: 4
Date: Tue, 3 Apr 2012 21:20:21 -0400
From: David McBride <toa...@gmail.com>
Subject: Re: [Haskell-beginners] De-serialising with minimal code
        noise and fluff... possible?
To: Sean Charles <s...@objitsu.com>
Cc: beginners@haskell.org
Message-ID:
        <can+tr43a1frpfaqcupodp2cpm7m_vnrupowxc2jmcx3mtj_...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

You're on the right track, and yes you can do what you want to do.
I'll explain by rewriting some of your code to use the state monad.

{-# LANGUAGE GeneralizedNewtypeDeriving #-}
import Data.Binary
import Control.Monad.State as S
import IO
import qualified Data.ByteString as BS
import Data.Bits (shiftL)
import Data.Char (chr)

newtype MyMonad a = MyMonad (StateT Handle IO a)
  deriving (Functor, Monad, MonadState Handle, MonadIO)

runMyMonad :: MyMonad b -> Handle -> IO b
runMyMonad (MyMonad proc) = fmap fst . runStateT proc

What the above code does, is sets up a state, which in this case just
holds a handle (but it could have been any user defined state).  It
uses ghc's newtype deriving extension to get the common instances that
you'll need.  This is generally way easier than writing the instances
yourself.  It wraps it in a newtype which you can call whatever you
want to make things simpler when you are thinking about the types
involved.

For the rest of the code I'm just going to rewrite your code with
"'"'s  behind them to denote that they are changed.

streamInt' len = S.get >>= \h -> liftIO $ liftM bsVal $ BS.hGet h len
hGet' len = S.get >>= \h -> liftIO $ BS.hGet h len
getNTS' = S.get >>= liftIO . getNTS  -- basically just your functions
with a liftIO in front, and a call to get to get the handle from your
state monad.

getHIP' :: Handle -> IO PktHIP
getHIP' = runMyMonad getHIP''
  where
    getHIP'' :: MyMonad PktHIP
    getHIP'' = do
      ver <- streamInt' 1
      str <- getNTS'
      tid <- streamInt' 4
      buf <- hGet' 8
      hGet' 1 -- filler
      scap1 <- streamInt' 2
      slang <- streamInt' 1
      sstat <- streamInt' 2
      scap2 <- streamInt' 2
      scrln <- streamInt' 1
      hGet' 10 -- filler
      scram <- getNTS'
      return $ PktHIP
                  { hipProtoVer = ver
                    , hipSvrVer   = str
                    , hipThreadId = tid
                    , hipScramble = buf
                    , hipSvrCaps  = fromIntegral scap1 -- scap2 << 2 ? TODO!
                    , hipSvrLang  = slang
                    , hipSvrStat  = sstat
                    , hipScramLen = scrln
                    , hipPlugin   = scram
                    }


This function is the same as yours, except that it doesn't need to
worry about handles.

And right about this point you are saying, wait a second this code is
still long.  If you were using more than just a single handle, you
could fit a lot more in that state.  There's another thing you can do
that I'm aware of to squeeze a little more brevity out of your code.
That is called applicatives.  Instead of writing getHIP in monadic
style, you can do it in applicative.  Well actually you can almost do
it in applicative style, because your structure does not quite match
up with the data you are retrieving.  It would look something like
this (untested):

import Control.Applicative

getHIP h = PktHIP <$> streamInt h 1 <*> getNTS h <*> streamInt h 4 <*>
... etc ... <*> getNTS h

<$> is just another word for fmap.  If the types of your records match
up (or you can coerce them ie for hipSvrCaps would be "<*>
(fromIntegral <$> streamInt h 2) <*>" you can put it all in one big
line or two.

If you have any other questions, let me know.

On Tue, Apr 3, 2012 at 6:26 PM, Sean Charles <s...@objitsu.com> wrote:
> Hi list,
>
> to further my haskell skills I decided to produce my own raw MySQL
> connection. So far I can connect to the server and extract the handshake
> initialisation packet (HIP) and create the client authentication packet.
> Once I've figured out how to implement the salting and hashing I have a
> chance of starting a session. Not a problem, just got to do it. I want a
> module that I can use for simple DBMS I/O that doesn't use libmysql or odbc
> as sometimes these things just refuse to install on certain platform /
> architecture combinations!
>
> So, here's my problem: I kind of understand monads, I can use them and
> appreciate what/why they are useful etc. but my current implementation of
> reading the HIP into the type I created (shown next) appears to me at least
> to be plain clunky, ugly and inelegant compared to ninja haskell code I've
> read and one day hope to match, here's my code... apologies for the length
> of the post but I hope it's interesting to some!
>
> data PktHIP = PktHIP
> ? ? ? ? ? ? ?{ hipProtoVer :: Int
> ? ? ? ? ? ? ?, hipSvrVer ? :: String
> ? ? ? ? ? ? ?, hipThreadId :: Int
> ? ? ? ? ? ? ?, hipScramble :: BS.ByteString
> ? ? ? ? ? ? ?, hipSvrCaps ?:: Integer
> ? ? ? ? ? ? ?, hipSvrLang ?:: Int
> ? ? ? ? ? ? ?, hipSvrStat ?:: Int
> ? ? ? ? ? ? ?, hipScramLen :: Int
> ? ? ? ? ? ? ?, hipPlugin ? :: String
> ? ? ? ? ? ? ?} deriving(Show)
>
> and reading it...
>
> getHIP :: Handle -> IO PktHIP
> getHIP h = do
> ?ver <- streamInt h 1
> ?str <- getNTS h
> ?tid <- streamInt h 4
> ?buf <- BS.hGet h 8
> ?BS.hGet h 1 -- filler
> ?scap1 <- streamInt h 2
> ?slang <- streamInt h 1
> ?sstat <- streamInt h 2
> ?scap2 <- streamInt h 2
> ?scrln <- streamInt h 1
> ?BS.hGet h 10 -- filler
> ?scram <- getNTS h
> ?-- todo: there *has* to be a more concise way of doing this?
> ?return $
> ? ?PktHIP { hipProtoVer = ver
> ? ? ? ? ? , hipSvrVer ? = str
> ? ? ? ? ? , hipThreadId = tid
> ? ? ? ? ? , hipScramble = buf
> ? ? ? ? ? , hipSvrCaps ?= fromIntegral scap1 -- scap2 << 2 ? TODO!
> ? ? ? ? ? , hipSvrLang ?= slang
> ? ? ? ? ? , hipSvrStat ?= sstat
> ? ? ? ? ? , hipScramLen = scrln
> ? ? ? ? ? , hipPlugin ? = scram
> ? ? ? ? ? }
>
> -- Extract an N byte Int value from the input stream
> streamInt :: Handle -> Int -> IO Int
> streamInt h len = liftM bsVal $ BS.hGet h len
>
> bsVal :: BS.ByteString -> Int
> bsVal = BS.foldr' (\byte total -> ?fromEnum byte + (shiftL total 8)) 0
>
> -- Get a Null-Terminated String
> getNTS :: Handle -> IO String
> getNTS h = streamInt h 1 >>= \b -> getString h "" b
> ? ? ? ? ? where
> ? ? ? ? ? ? getString :: Handle -> String -> Int -> IO String
> ? ? ? ? ? ? getString h acc c
> ? ? ? ? ? ? ? | c == 0 ?= return $ reverse acc
> ? ? ? ? ? ? ? | otherwise = streamInt h 1 >>= getString h ((chr c):acc)
>
>
> Then I read about the Data.Binary package and the Get monad and got this
> far...
>
> readHIP :: Get (Maybe PktHIP)
> readHIP = do
> ?return (Nothing)
>
> I looked at the example on this page:
> http://www.haskell.org/haskellwiki/DealingWithBinaryData , I stopped because
> I realised that the Get monad was only going to mean I ended up with very
> similarly structured code and probably ?a lot of it. I know the PktHIP has
> lots of fields but even so I am convinced it can be reduced and re-factored
> into much more beautiful code that I know how to write so far.
>
> I've tried to reason about it and I can "see" that there is a function out
> there that takes a Handle and "a record modifier function" and I can see
> also that it might be time for me to create my first Monad type ever
> IIUC, by implementing >>=, >> and return and I make use of the many monad
> centric modules that exist but I also am under the impression that I can add
> as many other functions to my Monad class as I need to do what I need to do,
> is that correct?
>
> I would therefore like some way to create an initial "thing" that contains
> the handle passed in to the function so that the >>= invocations can be as
> clean as possible because somewhere in my mind I can feel code resembling
> something like this:
>
> getHIP :: Handle -> MyMonad PktHIP
> getHIP h = do ? ?-- science fiction code starts now!
>
> ? ?let rs = ... --- record state monad thing with "h" and "PktHIP"
>
> ? ?getInt 1 rs hipProtoVer >>
> ? ?getNTS ? rs hipSvrVer >>
> ? ?getInt 4 rs hipThreadId >>
> ? ?getBS ?8 rs hipScramble >>
> ? ?skip 1 >>
> ? ? ? :
> ? ? ? : ...etc
> ? ?return $ theHIP
>
> getInt :: Int -> ST ? -> (PktHIP -> PktHIP) -> MyMonad PktHIP
> getInt len state fmod = do
> ? ?val <- readStream ("h from state") len
> let state' = modify state by setting field "fmod" to "val"
> ? ? ? return state'
>
> Problems / things I am clueless about how to do here
>
> ?|1| how to create "something" that each >>= can modify (state monad
> instance?)
> ?|2| how to put the Handle "h" somewhere it can be read on each read action
> ?|3| everything else!!!
>
> So, any ideas, examples etc. would be most enlightening and gratefully
> absorbed!
> Sean Charles.
> :)
>
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners



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

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


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

Reply via email to