[Haskell-beginners] help
haskell-beginners at iorange.fastmail.fm
haskell-beginners at iorange.fastmail.fm
Tue Nov 18 17:20:47 EST 2008
On Tue, 18 Nov 2008 17:12:57 -0500 (EST), beginners-request at haskell.org
said:
> Send Beginners mailing list submissions to
> beginners at 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-request at haskell.org
>
> You can reach the person managing the list at
> beginners-owner at 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: Profiling haskell code (Brent Yorgey)
> 2. Parsing arithmentic expressions (Glurk)
> 3. Re: Parsing arithmentic expressions (Bernie Pope)
> 4. RE: Profiling haskell code (Sayali Kulkarni)
> 5. Re: Profiling haskell code (Brent Yorgey)
> 6. Type polymorphism with size (Michael Snoyman)
> 7. Re: Type polymorphism with size (Brent Yorgey)
> 8. Re: Type polymorphism with size (Michael Snoyman)
>
>
> ----------------------------------------------------------------------
>
> Message: 1
> Date: Fri, 14 Nov 2008 15:53:34 -0500
> From: Brent Yorgey <byorgey at seas.upenn.edu>
> Subject: Re: [Haskell-beginners] Profiling haskell code
> To: beginners at haskell.org
> Message-ID: <20081114205334.GA30261 at seas.upenn.edu>
> Content-Type: text/plain; charset=us-ascii
>
> >
> > quicksort [ ] = [ ]
> >
> > quicksort (x : xs) = quicksort larger ++ [x ] ++ quicksort smaller
> >
> >
> > where
> >
> >
> > smaller = [a | a <- xs, a <= x ]
> >
> >
> > larger = [b | b <- xs, b > x ]
> >
> >
> >
> >
> >
> > When I compile the code with the following command :
> >
> >
> >
> > $ ghc --make Project.hs -prof -auto-all
> >
> > Then I tested it with the following command :
> >
> > $ Project +RTS -p
> >
> > It generates the .hi and the .o file but I cannot get the .prof file.
> >
> > Please let me know if any of the steps is missing or where could I check
> > my profiling info.
> >
>
> Hi Sayali,
>
> Is the code shown above *everything* in your Project.hs file? You
> will also need a main function for it to actually do anything. If
> there is more to your Project.hs file that you have not shown, could
> you send the complete version?
>
> Do you get any errors? Does Project produce the output that you expect?
>
> -Brent
>
>
> ------------------------------
>
> Message: 2
> Date: Sun, 16 Nov 2008 00:15:29 +0000 (UTC)
> From: Glurk <streborg at hotmail.com>
> Subject: [Haskell-beginners] Parsing arithmentic expressions
> To: beginners at haskell.org
> Message-ID: <loom.20081115T235851-940 at post.gmane.org>
> Content-Type: text/plain; charset=us-ascii
>
> Hi,
>
> I'm just trying to learn how to use Parsec and am experimenting with
> parsing
> arithmetic expressions.
>
> This article gives a good example ->
> http://www.haskell.org/haskellwiki/Parsing_expressions_and_statements
>
> However, like most other examples I could find, the grammar for the
> expression
> doesn't take operator precedence into account, and allows for expressions
> of
> any size by defining expr recursively, eg :-
>
> expr ::= var | const | ( expr ) | unop expr | expr duop expr
>
> So, you can keep extending the expression by adding another operator and
> expression.
>
> The data to hold the expression is then very easily derived :-
>
> data Expr = Var String | Con Bool | Uno Unop Expr | Duo Duop Expr Expr
>
> The grammar I want to parse is slightly different in that it allows for
> operator precendence. Part of the grammar is something like :-
>
> expression = SimpleExpression {relation SimpleExpression}.
> SimpleExpression = ["+"|"-"] term {AddOperator term}.
>
> So, instead of recursively defining expression, it is made up of
> multiples
> occurrences of SimpleExpression joined together with Relation operators.
>
> Where I am confused is how I should best represent this stucture in my
> data.
> Should I have something like :-
>
> data Expr = Expr SimpleExpr [(RelOp, SimpleExpression)]
>
> ie, an initial SimpleExpr, followed by a list of operator and
> SimpleExpression
> pairs.
>
> I haven't seen any example similar to this, so I was wondering if I'm
> going
> down the wrong track ?
>
> Perhaps another alternative is to modify the grammar somehow ?
>
> I guess, the question is, in general how do you handle such repeated
> elements
> as definied in an EBNF grammar, in structuring your data ?
>
> Any advice appreciated !
>
> Thanks :)
>
>
>
> ------------------------------
>
> Message: 3
> Date: Mon, 17 Nov 2008 16:35:02 +1100
> From: Bernie Pope <bjpop at csse.unimelb.edu.au>
> Subject: Re: [Haskell-beginners] Parsing arithmentic expressions
> To: Glurk <streborg at hotmail.com>
> Cc: beginners at haskell.org
> Message-ID: <57383C16-16DD-4032-9CBC-5D6CC27A6E6E at csse.unimelb.edu.au>
> Content-Type: text/plain; charset=US-ASCII; format=flowed; delsp=yes
>
> Hi,
>
> Have you seen the buildExpressionParser combinator in Parsec?
>
> http://legacy.cs.uu.nl/daan/download/parsec/parsec.html#buildExpressionParser
>
> It allows you to specify precedence and associativity for operator
> parsers declaratively, and it generally saves you from lots of
> refactoring in the grammar.
>
> You could probably stick with the straightforward data representation
> of expressions.
>
> Cheers,
> Bernie.
>
> On 16/11/2008, at 11:15 AM, Glurk wrote:
>
> > Hi,
> >
> > I'm just trying to learn how to use Parsec and am experimenting with
> > parsing
> > arithmetic expressions.
> >
> > This article gives a good example ->
> > http://www.haskell.org/haskellwiki/Parsing_expressions_and_statements
> >
> > However, like most other examples I could find, the grammar for the
> > expression
> > doesn't take operator precedence into account, and allows for
> > expressions of
> > any size by defining expr recursively, eg :-
> >
> > expr ::= var | const | ( expr ) | unop expr | expr duop expr
> >
> > So, you can keep extending the expression by adding another operator
> > and
> > expression.
> >
> > The data to hold the expression is then very easily derived :-
> >
> > data Expr = Var String | Con Bool | Uno Unop Expr | Duo Duop Expr Expr
> >
> > The grammar I want to parse is slightly different in that it allows
> > for
> > operator precendence. Part of the grammar is something like :-
> >
> > expression = SimpleExpression {relation SimpleExpression}.
> > SimpleExpression = ["+"|"-"] term {AddOperator term}.
> >
> > So, instead of recursively defining expression, it is made up of
> > multiples
> > occurrences of SimpleExpression joined together with Relation
> > operators.
> >
> > Where I am confused is how I should best represent this stucture in
> > my data.
> > Should I have something like :-
> >
> > data Expr = Expr SimpleExpr [(RelOp, SimpleExpression)]
> >
> > ie, an initial SimpleExpr, followed by a list of operator and
> > SimpleExpression
> > pairs.
> >
> > I haven't seen any example similar to this, so I was wondering if
> > I'm going
> > down the wrong track ?
> >
> > Perhaps another alternative is to modify the grammar somehow ?
> >
> > I guess, the question is, in general how do you handle such repeated
> > elements
> > as definied in an EBNF grammar, in structuring your data ?
> >
> > Any advice appreciated !
> >
> > Thanks :)
> >
> > _______________________________________________
> > Beginners mailing list
> > Beginners at haskell.org
> > http://www.haskell.org/mailman/listinfo/beginners
>
>
>
> ------------------------------
>
> Message: 4
> Date: Mon, 17 Nov 2008 09:35:26 +0530
> From: "Sayali Kulkarni" <Sayali.Kulkarni at kpitcummins.com>
> Subject: RE: [Haskell-beginners] Profiling haskell code
> To: "Brent Yorgey" <byorgey at seas.upenn.edu>, <beginners at haskell.org>
> Message-ID: <82C3BC9106BCE149B63464D79D0A22FD0761A60E at sohm.kpit.com>
> Content-Type: text/plain; charset="us-ascii"
>
> Hello Brent,
>
> I just have written a quick sort program.
> There is nothing more in the code than that I have shown.
>
> What is it about the main function?
> What do I need to do in the main function?
>
> I do not get any errors.
> And I get the expected output. The only thing that I am stuck at is that
> I do not get the ".prof" file which will give me the profile details of
> the code.
>
> Also it would be great if you could through a light on whether there is
> any other method to profile a code in Haskell?
>
> Regards,
> Sayali.
>
> -----Original Message-----
> From: beginners-bounces at haskell.org
> [mailto:beginners-bounces at haskell.org] On Behalf Of Brent Yorgey
> Sent: Saturday, November 15, 2008 2:24 AM
> To: beginners at haskell.org
> Subject: Re: [Haskell-beginners] Profiling haskell code
>
> >
> > quicksort [ ] = [ ]
> >
> > quicksort (x : xs) = quicksort larger ++ [x ] ++ quicksort smaller
> >
> >
> > where
> >
> >
> > smaller = [a | a <- xs, a <= x ]
> >
> >
> > larger = [b | b <- xs, b > x ]
> >
> >
> >
> >
> >
> > When I compile the code with the following command :
> >
> >
> >
> > $ ghc --make Project.hs -prof -auto-all
> >
> > Then I tested it with the following command :
> >
> > $ Project +RTS -p
> >
> > It generates the .hi and the .o file but I cannot get the .prof file.
> >
> > Please let me know if any of the steps is missing or where could I
> check
> > my profiling info.
> >
>
> Hi Sayali,
>
> Is the code shown above *everything* in your Project.hs file? You
> will also need a main function for it to actually do anything. If
> there is more to your Project.hs file that you have not shown, could
> you send the complete version?
>
> Do you get any errors? Does Project produce the output that you expect?
>
> -Brent
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>
>
> ------------------------------
>
> Message: 5
> Date: Mon, 17 Nov 2008 09:07:57 -0500
> From: Brent Yorgey <byorgey at seas.upenn.edu>
> Subject: Re: [Haskell-beginners] Profiling haskell code
> To: beginners at haskell.org
> Message-ID: <20081117140757.GA13235 at seas.upenn.edu>
> Content-Type: text/plain; charset=us-ascii
>
> On Mon, Nov 17, 2008 at 09:35:26AM +0530, Sayali Kulkarni wrote:
> > Hello Brent,
> >
> > I just have written a quick sort program.
> > There is nothing more in the code than that I have shown.
> >
> > What is it about the main function?
> > What do I need to do in the main function?
> >
> > I do not get any errors.
> > And I get the expected output. The only thing that I am stuck at is that
> > I do not get the ".prof" file which will give me the profile details of
> > the code.
> >
> > Also it would be great if you could through a light on whether there is
> > any other method to profile a code in Haskell?
> >
> > Regards,
> > Sayali.
>
> Hi Sayali,
>
> Just writing a quicksort function by itself is fine if you want to
> test it interactively in ghci. But if you want to profile it you will
> have to make an executable, which means you will need a 'main'
> function which says what to do when the program is run. Your main
> function might look something like this:
>
> main = do print "Sorting..."
> print (length (quicksort (reverse [1..1000000])))
> print "Done!"
>
> Of course, sorting a list in reverse order might not be a very
> representative task; you might also want to look into the
> System.Random module to generate a list of a million random elements
> and sort that.
>
> -Brent
>
> >
> > -----Original Message-----
> > From: beginners-bounces at haskell.org
> > [mailto:beginners-bounces at haskell.org] On Behalf Of Brent Yorgey
> > Sent: Saturday, November 15, 2008 2:24 AM
> > To: beginners at haskell.org
> > Subject: Re: [Haskell-beginners] Profiling haskell code
> >
> > >
> > > quicksort [ ] = [ ]
> > >
> > > quicksort (x : xs) = quicksort larger ++ [x ] ++ quicksort smaller
> > >
> > >
> > > where
> > >
> > >
> > > smaller = [a | a <- xs, a <= x ]
> > >
> > >
> > > larger = [b | b <- xs, b > x ]
> > >
> > >
> > >
> > >
> > >
> > > When I compile the code with the following command :
> > >
> > >
> > >
> > > $ ghc --make Project.hs -prof -auto-all
> > >
> > > Then I tested it with the following command :
> > >
> > > $ Project +RTS -p
> > >
> > > It generates the .hi and the .o file but I cannot get the .prof file.
> > >
> > > Please let me know if any of the steps is missing or where could I
> > check
> > > my profiling info.
> > >
> >
> > Hi Sayali,
> >
> > Is the code shown above *everything* in your Project.hs file? You
> > will also need a main function for it to actually do anything. If
> > there is more to your Project.hs file that you have not shown, could
> > you send the complete version?
> >
> > Do you get any errors? Does Project produce the output that you expect?
> >
> > -Brent
> > _______________________________________________
> > Beginners mailing list
> > Beginners at haskell.org
> > http://www.haskell.org/mailman/listinfo/beginners
> >
>
>
> ------------------------------
>
> Message: 6
> Date: Tue, 18 Nov 2008 10:02:20 -0800
> From: "Michael Snoyman" <michael at snoyman.com>
> Subject: [Haskell-beginners] Type polymorphism with size
> To: beginners at haskell.org
> Message-ID:
> <29bf512f0811181002k7ea715f3o8d797aae6a4b3855 at mail.gmail.com>
> Content-Type: text/plain; charset="utf-8"
>
> I am trying to write some code to read flat files from a mainframe
> system.
> This includes some character fields. This is a fixed width file, so each
> field will have a consistent length between records, but there are fields
> of
> different length within a record. For example, I might have a "name"
> field
> length 20 and an eye color field length 5.
>
> I am trying to use the binary library to read in this file. I've written
> a
> binary type, MFChar2, for reading in a 2-length character field. It is
> defined as such (you can safely ignore the ebcdicToAscii piece, it is
> just
> doing character conversion):
>
> data MFChar2 = MFChar2 [Word8]
> instance Binary MFChar2 where
> put = undefined
> get = do ebcdic <- replicateM 2 getWord8
> return $ MFChar2 $ map ebcdicToAscii ebcdic
>
> What I would like to do is have some kind of generic "MFChar" data type
> which could take any character length, but I can't figure out how to do
> it.
> Any help would be appreciated.
>
> Thanks,
> Michael
> -------------- next part --------------
> An HTML attachment was scrubbed...
> URL:
> http://www.haskell.org/pipermail/beginners/attachments/20081118/3349841f/attachment-0001.htm
>
> ------------------------------
>
> Message: 7
> Date: Tue, 18 Nov 2008 14:18:22 -0500
> From: Brent Yorgey <byorgey at seas.upenn.edu>
> Subject: Re: [Haskell-beginners] Type polymorphism with size
> To: beginners at haskell.org
> Message-ID: <20081118191822.GA9270 at seas.upenn.edu>
> Content-Type: text/plain; charset=us-ascii
>
> On Tue, Nov 18, 2008 at 10:02:20AM -0800, Michael Snoyman wrote:
> > I am trying to write some code to read flat files from a mainframe system.
> > This includes some character fields. This is a fixed width file, so each
> > field will have a consistent length between records, but there are fields of
> > different length within a record. For example, I might have a "name" field
> > length 20 and an eye color field length 5.
> >
> > I am trying to use the binary library to read in this file. I've written a
> > binary type, MFChar2, for reading in a 2-length character field. It is
> > defined as such (you can safely ignore the ebcdicToAscii piece, it is just
> > doing character conversion):
> >
> > data MFChar2 = MFChar2 [Word8]
> > instance Binary MFChar2 where
> > put = undefined
> > get = do ebcdic <- replicateM 2 getWord8
> > return $ MFChar2 $ map ebcdicToAscii ebcdic
> >
> > What I would like to do is have some kind of generic "MFChar" data type
> > which could take any character length, but I can't figure out how to do it.
> > Any help would be appreciated.
>
> Hm, interesting! The problem is that 'get' does not take any
> arguments, so must determine what to do from the type at which it is
> called. So the number of words to be read needs to be in the type.
> We can't put actual Int values in a type -- but there is actually a
> way to do what you want, by encoding natural numbers at the type
> level! I don't know whether this really belongs on a 'beginners' list
> but I couldn't resist. =)
>
>
> data Z -- the type representing zero
> data S n -- the type representing the successor of another natural
>
> -- for example, Z, S Z, and S (S Z) are types representing
> -- zero, one, and two.
>
> -- the n is for a type-level natural representing the length of the list.
> data MFChar n = MFChar [Word8]
>
> -- add a Word8 to the beginning of an MFChar, resulting in an MFChar
> -- one word longer
> mfCons :: Word8 -> MFChar n -> MFChar (S n)
> mfCons w (MFChar ws) = MFChar (w:ws)
>
> instance Binary (MFChar Z) where
> get = return $ MFChar []
>
> instance (Binary (MFChar n)) => Binary (MFChar (S n)) where
> get = do ebcdic <- getWord8
> rest <- get -- the correct type of get is
> -- inferred due to the use of mfCons below
> return $ mfCons (ebcdicToAscii ebcdic) rest
>
>
> Now if you wanted to read a field with 20 chars, you can use
>
> get :: Get (MFChar (S (S (S ... 20 S's ... Z))))
>
> Ugly, I know. You could make it slightly more bearable by defining
> some type synonyms at the top of your program like
>
> type Five = S (S (S (S (S Z))))
> type Ten = S (S (S (S (S Five))))
>
> and so on. Then you can just say get :: Get (MFChar Ten) or whatever.
>
> This is untested but it (or something close to it) ought to work. Of
> course, you may well ask yourself whether this contortion is really
> worth it. Maybe it is, maybe it isn't, but I can't think of a better
> way to do it in Haskell. In a dependently typed language such as
> Agda, we could just put regular old natural numbers in the types,
> instead of going through contortions to encode natural numbers as
> types as we have to do here. So I guess the real answer to your
> question is "use a dependently typed language". =)
>
> If you have problems getting this to work or more questions, feel free
> to ask!
>
> -Brent
>
>
> ------------------------------
>
> Message: 8
> Date: Tue, 18 Nov 2008 14:18:46 -0800
> From: "Michael Snoyman" <michael at snoyman.com>
> Subject: Re: [Haskell-beginners] Type polymorphism with size
> To: "Brent Yorgey" <byorgey at seas.upenn.edu>
> Cc: beginners at haskell.org
> Message-ID:
> <29bf512f0811181418v4698d586u979454b051de85da at mail.gmail.com>
> Content-Type: text/plain; charset="utf-8"
>
> On Tue, Nov 18, 2008 at 11:18 AM, Brent Yorgey
> <byorgey at seas.upenn.edu>wrote:
>
> > Hm, interesting! The problem is that 'get' does not take any
> > arguments, so must determine what to do from the type at which it is
> > called. So the number of words to be read needs to be in the type.
> > We can't put actual Int values in a type -- but there is actually a
> > way to do what you want, by encoding natural numbers at the type
> > level! I don't know whether this really belongs on a 'beginners' list
> > but I couldn't resist. =)
> >
> >
> > data Z -- the type representing zero
> > data S n -- the type representing the successor of another natural
> >
> > -- for example, Z, S Z, and S (S Z) are types representing
> > -- zero, one, and two.
> >
> > -- the n is for a type-level natural representing the length of the list.
> > data MFChar n = MFChar [Word8]
> >
> > -- add a Word8 to the beginning of an MFChar, resulting in an MFChar
> > -- one word longer
> > mfCons :: Word8 -> MFChar n -> MFChar (S n)
> > mfCons w (MFChar ws) = MFChar (w:ws)
> >
> > instance Binary (MFChar Z) where
> > get = return $ MFChar []
> >
> > instance (Binary (MFChar n)) => Binary (MFChar (S n)) where
> > get = do ebcdic <- getWord8
> > rest <- get -- the correct type of get is
> > -- inferred due to the use of mfCons below
> > return $ mfCons (ebcdicToAscii ebcdic) rest
> >
> >
> > Now if you wanted to read a field with 20 chars, you can use
> >
> > get :: Get (MFChar (S (S (S ... 20 S's ... Z))))
> >
> > Ugly, I know. You could make it slightly more bearable by defining
> > some type synonyms at the top of your program like
> >
> > type Five = S (S (S (S (S Z))))
> > type Ten = S (S (S (S (S Five))))
> >
> > and so on. Then you can just say get :: Get (MFChar Ten) or whatever.
> >
> > This is untested but it (or something close to it) ought to work. Of
> > course, you may well ask yourself whether this contortion is really
> > worth it. Maybe it is, maybe it isn't, but I can't think of a better
> > way to do it in Haskell. In a dependently typed language such as
> > Agda, we could just put regular old natural numbers in the types,
> > instead of going through contortions to encode natural numbers as
> > types as we have to do here. So I guess the real answer to your
> > question is "use a dependently typed language". =)
> >
> > If you have problems getting this to work or more questions, feel free
> > to ask!
> >
>
> Very interesting solution to the problem. I tried it out and it works
> perfectly... but it's just too much of a hack for my tastes (no offense;
> I
> think it was very cool). I thought about it a bit and realized what I
> really
> want is a way to deal with tuples of the same type, which led to this
> kind
> of implementation.
>
> class RepTuple a b | a -> b where
> toList :: a -> [b]
> tMap :: (b -> b) -> a -> a
>
> instance RepTuple (a, a) a where
> toList (a, b) = [a, b]
> tMap f (a, b) = (f a, f b)
>
> And so on and so forth for every kind of tuple. Of course, this runs into
> the issue of the single case, for which I used the OneTuple library
> (actually, I wrote my own right now, but I intend to just use the
> OneTuple
> library).
>
> I can then do something like this (which I have tested and works):
>
> data MFChar w = MFChar w
> deriving Eq
> instance (RepTuple w a, Integral a) => Show (MFChar w) where
> show (MFChar ws) = map (chr . fromIntegral) $ toList ws
> instance (Integral a, Binary w, RepTuple w a) => Binary (MFChar w) where
> put = undefined
> get = do ebcdic <- get
> let ascii = tMap ebcdicToAscii ebcdic
> return $ MFChar ascii
>
> type MFChar1 = MFChar (OneTuple Word8)
> type MFChar2 = MFChar (Word8, Word8)
> type MFChar4 = MFChar (Word8, Word8, Word8, Word8)
> type MFChar5 = MFChar (Word8, Word8, Word8, Word8, Word8)
> type MFChar10 = MFChar (Word8, Word8, Word8, Word8, Word8,
> Word8, Word8, Word8, Word8, Word8)
>
> If I wanted, I could do away with the tMap function and just include the
> ebcdicToAscii step in the show instance.
>
> Michael
> -------------- next part --------------
> An HTML attachment was scrubbed...
> URL:
> http://www.haskell.org/pipermail/beginners/attachments/20081118/8a75bca1/attachment.htm
>
> ------------------------------
>
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>
>
> End of Beginners Digest, Vol 5, Issue 10
> ****************************************
--
israel orange
iorange at fastmail.fm
More information about the Beginners
mailing list