
Hi,
I'm working on another article like
http://www.linuxjournal.com/article/8850. This time, I'm taking an
exercise out of "Expert C Programming: Deep C Secrets" and
translating it into Haskell. The program translates C type
declarations into English. I would greatly appreciate some code
review. I'd prefer to look like an idiot in front of you guys rather
than in front of everyone in the world! ;)
Please understand, I am not a Haskell expert! Therefore, please make
your suggestions simple enough that I can actually accomplish them!
By the way, my code *mostly* follows the code laid out in the book. I
don't use a lexer or a parser or greatly improve on his algorithm.
I'd like the Haskell and C versions to be similar so that they can be
compared.
The C version is:
http://www.cs.may.ie/~jpower/Courses/compilers/labs/lab3/parse_decl.c
The Haskell version is below.
Thanks!
-jj
{- Translate C type declarations into English.
This exercise was taken from "Expert C Programming: Deep C Secrets", p. 84.
Example: echo -n "int *p;" | runhugs cdecl.hs
Name: Shannon -jj Behrens

Hi, You seem to like let a lot, whereas I hardly ever use them. In general I find where a lot more readable. (disclaimer, all notes untested, may not compile, may be wrong) Also, most haskell programs use $ instead of |>
-- For convenience: currTokType :: ParseContext -> TokenType currTokType ctx = ctx |> currTok |> tokenType
this could be written as: tokenType $ currTok $ ctx or even more succinctly, using points free style as:
currTokType = tokenType . currTok
writeOutput s = \ctx -> let newOutput = s : (output ctx) in ctx {output=newOutput}
why not?
writeOutput s ctx = ctx{output = s : output ctx}
shorter, no lambda (the argument is moved), no where, less code more obvious, and also some redundant brackets have been removed.
stackTop ctx = let (x:xs) = stack ctx in x stackTop ctx = head ctx
pop ctx = let (x:xs) = stack ctx in ctx {stack=xs}
ctx{stack = tail (stack ctx)}
classifyString s@(c:[]) | not (isAlphaNum c) = Token (Symbol c) s
classifyString s@[c] means the same thing (a one element list)
classifyString s = Token (whichType s) s where whichType "volatile" = Qualifier
isType "volatile" = Qualifier isType x | x `elem` ["void","char","signed" ...] = Type isType x = Identifier -- getting a bit bored here, so less suggestions from now on :) -- but if you send off a second draft i'll take another look -- i guess most things are done consistently
if ctx |> currTokValue |> (!! 0) |> isDigit
(!! 0) is head Biggest thing is |> is not a standard Haskell pattern, its usually either ($) or (.). Also where is great, and case statements are usually used less. Thanks Neil

Hi, can someone please point me at some code to read in the lines for a file - a working example ? I've have checked the tutorials on the wiki (some broken links) but couldn't find anything. - and my "The craft of functiional programming" doesn't have an example either ! thanks Rich

Hi
do x <- readFile "test.txt"
print (length (lines x))
That prints out the number of lines in a file, but once you have done
lines x, you can do anything you want to the lines
Thanks
Neil
On 3/5/06, Richard Gooding
Hi,
can someone please point me at some code to read in the lines for a file - a working example ?
I've have checked the tutorials on the wiki (some broken links) but couldn't find anything. - and my "The craft of functiional programming" doesn't have an example either !
thanks Rich _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 2006 March 05 Sunday 05:43, Shannon -jj Behrens wrote:
classifyString s = Token (whichType s) s where whichType "volatile" = Qualifier whichType "void" = Type whichType "char" = Type whichType "signed" = Type whichType "unsigned" = Type whichType "short" = Type whichType "int" = Type whichType "long" = Type whichType "float" = Type whichType "double" = Type whichType "struct" = Type whichType "union" = Type whichType "enum" = Type whichType _ = Identifier
whichType doesn't need to be a function. classifyString s = Token whichType s where whichType = case s of "volatile" -> Qualifier "void" -> Type "char" -> Type "signed" -> Type "unsigned" -> Type "short" -> Type "int" -> Type "long" -> Type "float" -> Type "double" -> Type "struct" -> Type "union" -> Type "enum" -> Type _ -> Identifier

Hi,
Thanks to everyone who reviewed my code and submitted comments the
first time! I've updated the code and transitioned to using the State
monad. Perhaps controversially, I've continued to use |> in a bunch
of places that the monad didn't get rid of because I think it's more
readable, but I'm still open for argument on this topic. Using the
monad didn't make the code any shorter, but it kind of "felt" better,
once I figured out how to use it. Figuring out how to use execState
to get into and out of "monad-ity" was the hardest part, because it's
mentioned in so few of the examples. I think it's fair to say, of
course, that using a monad has increased the complexity, but I can
still read what I wrote. I've posted my code below for additional
comments.
Thanks again!
-jj
{- Translate C type declarations into English.
This exercise was taken from "Expert C Programming: Deep C Secrets", p. 84.
Example: echo -n "int *p;" | runhugs cdecl.hs
Name: Shannon -jj Behrens
Hi,
I'm working on another article like http://www.linuxjournal.com/article/8850. This time, I'm taking an exercise out of "Expert C Programming: Deep C Secrets" and translating it into Haskell. The program translates C type declarations into English. I would greatly appreciate some code review. I'd prefer to look like an idiot in front of you guys rather than in front of everyone in the world! ;)
Please understand, I am not a Haskell expert! Therefore, please make your suggestions simple enough that I can actually accomplish them!
By the way, my code *mostly* follows the code laid out in the book. I don't use a lexer or a parser or greatly improve on his algorithm. I'd like the Haskell and C versions to be similar so that they can be compared.
The C version is: http://www.cs.may.ie/~jpower/Courses/compilers/labs/lab3/parse_decl.c
The Haskell version is below. [snip]

On 12.03 01:47, Shannon -jj Behrens wrote:
monad. Perhaps controversially, I've continued to use |> in a bunch of places that the monad didn't get rid of because I think it's more readable, but I'm still open for argument on this topic. Using the
What about using (>>>) from Control.Arrow?
-- For convenience: currTokType :: ParseContext -> TokenType currTokType ctx = ctx |> currTok |> tokenType
currTokType = currTok >>> tokenType
currTokValue :: ParseContext -> String currTokValue ctx = ctx |> currTok |> tokenValue
currTokValue = currTok >>> tokenValue
-- Create the final output string given a ParseContext. consolidateOutput :: ParseContext -> String consolidateOutput ctx = ctx |> output |> reverse |> concat
consolidateOutput = output >>> reverse >>> concat and so on. - Einar Karttunen

On 3/12/06, Einar Karttunen
On 12.03 01:47, Shannon -jj Behrens wrote:
monad. Perhaps controversially, I've continued to use |> in a bunch of places that the monad didn't get rid of because I think it's more readable, but I'm still open for argument on this topic. Using the
What about using (>>>) from Control.Arrow?
-- For convenience: currTokType :: ParseContext -> TokenType currTokType ctx = ctx |> currTok |> tokenType
currTokType = currTok >>> tokenType
currTokValue :: ParseContext -> String currTokValue ctx = ctx |> currTok |> tokenValue
currTokValue = currTok >>> tokenValue
-- Create the final output string given a ParseContext. consolidateOutput :: ParseContext -> String consolidateOutput ctx = ctx |> output |> reverse |> concat
consolidateOutput = output >>> reverse >>> concat
and so on.
I'm sorry, I looked at Arrow.hs, and I just don't understand. The State monad is working just fine. I'm only using |> as a replacement for $ because I find it more readable to read left to right than right to left. Arrows looks like a replacement for monads. Are you saying I should drop my use of the State monad? If so, why? I like the readability of the do syntax. Are you saying that >>> can be used as a reversed version of $? Thanks for your patiences with my ignorance ;) Thanks, -jj

On Mon, Mar 13, 2006 at 06:48:51PM -0800, Shannon -jj Behrens wrote:
consolidateOutput = output >>> reverse >>> concat
and so on.
Are you saying that >>> can be used as a reversed version of $?
For the (->) instance of Arrow, (>>>) is simply reversed function composition, (>>>) = flip (.). Using Arrows for such a simple thing as function composition can be quite confusing, especially for beginners. Best regards Tomasz -- I am searching for programmers who are good at least in (Haskell || ML) && (Linux || FreeBSD || math) for work in Warsaw, Poland

Shannon -jj Behrens wrote:
I'm only using |> as a replacement for $ because I find it more readable to read left to right than right to left.
You can see this in two different ways, I think. Imagine the following: (+1) (*2) 3 This is not legal Haskell because it gets parsed as: ((+1) (*2)) 3 To avoid this problem, we can add our own brackets: (+1) ((*2) 3) Speaking loosely, $ is an alternative to the brackets, so we can also write: (+1) $ (*2) 3 We get the answer 7 whether we use brackets or $. If $ is going to be an alternative to brackets, we would be a bit surprised if the evaluation order changed. At the same time, it's true that if you think of this as a Unix pipe, the evaluation order is the wrong way round. We are evaluating right to left. Arrows are meant to be like Unix pipes. The whole idea is that you build up pipelines (and networks) of arrows. Usefully for you, functions are a kind of arrow, so you get the arrow operators automatically. As expected ((+1) >>> (*2)) 3 gives 8 and not 7.
Arrows looks like a replacement for monads. Are you saying I should drop my use of the State monad? If so, why? I like the readability of the do syntax.
Okay, now it's my turn to ask a question. :-) I've read about arrows, and while I think I see what they do, I'm not sure why they are seen as so special that they even get new syntax. This question of Shannon's is exactly the point I struggle with. I can see that the arrow operators might be useful with functions, but are they useful for other things too? For example, as monads are one kind of arrow, I thought I would make some of the I/O functions into arrows and see what happened. The result was pretty much the same as using the monad, except slightly less convenient. I've been trying to use the arrow interface to HXT, but I don't see why it works better with arrows rather than functions. The arrows all do various transformations on the XML, but isn't that the idea of a function? Couldn't processTopDown, for example, be a function that maps an input XML tree to an output one, and takes a lambda expression which is to be applied to each node? Thanks, Pete

On Tuesday 14 March 2006 14:46, Pete Chown wrote:
Shannon -jj Behrens wrote:
Arrows looks like a replacement for monads. Are you saying I should drop my use of the State monad? If so, why? I like the readability of the do syntax.
Okay, now it's my turn to ask a question. :-) I've read about arrows, and while I think I see what they do, I'm not sure why they are seen as so special that they even get new syntax. This question of Shannon's is exactly the point I struggle with. I can see that the arrow operators might be useful with functions, but are they useful for other things too?
Yes, http://www.haskell.org/arrows/biblio.html lists a number of papers describing non-trivial applications of Arrows, that is, Arrows other than (->). I found the exposition in http://www.haskell.org/yale/papers/oxford02/ to be quite readable.
For example, as monads are one kind of arrow, I thought I would make some of the I/O functions into arrows and see what happened. The result was pretty much the same as using the monad, except slightly less convenient.
You can write monadic code without ever using the syntax sugar, and get along. However, do-notation is convenient. OTOH, I am told that programming with Arrows is really quite inconvenient w/o the syntax sugar. Cheers, Ben

On 3/14/06, Benjamin Franksen
On Tuesday 14 March 2006 14:46, Pete Chown wrote:
Shannon -jj Behrens wrote:
Arrows looks like a replacement for monads. Are you saying I should drop my use of the State monad? If so, why? I like the readability of the do syntax.
Okay, now it's my turn to ask a question. :-) I've read about arrows, and while I think I see what they do, I'm not sure why they are seen as so special that they even get new syntax. This question of Shannon's is exactly the point I struggle with. I can see that the arrow operators might be useful with functions, but are they useful for other things too?
Yes, http://www.haskell.org/arrows/biblio.html lists a number of papers describing non-trivial applications of Arrows, that is, Arrows other than (->). I found the exposition in http://www.haskell.org/yale/papers/oxford02/ to be quite readable.
For example, as monads are one kind of arrow, I thought I would make some of the I/O functions into arrows and see what happened. The result was pretty much the same as using the monad, except slightly less convenient.
You can write monadic code without ever using the syntax sugar, and get along. However, do-notation is convenient. OTOH, I am told that programming with Arrows is really quite inconvenient w/o the syntax sugar.
Well, forgive me for my newbie-ness: o How important is it that I switch from using the State monad to using arrows? o How important is it that I switch from using |> or $ to using arrows? (It seems that using arrows just to replace |> or $ is like using a sledge hammer to drive a thumb tack.) o How much will this increase the "conceptual complexity" of my program--i.e. how much time am I going to have to spend explaining it in my article? o How much will this improve the readability or decrease the amount of code in my program? Thanks! -jj

"Shannon -jj Behrens"
o How important is it that I switch from using the State monad to using arrows?
Not at all.
o How important is it that I switch from using |> or $ to using arrows?
Not at all.
(It seems that using arrows just to replace |> or $ is like using a sledge hammer to drive a thumb tack.)
Exactly so.
o How much will this increase the "conceptual complexity" of my program--i.e. how much time am I going to have to spend explaining it in my article?
By a significant amount. Some might even argue that using monads is overkill... (Although in this case monads may indeed be justified.)
o How much will this improve the readability or decrease the amount of code in my program?
Not at all.
Thanks!
Not at all! :-) Regards, Malcolm

Hi, I disagree with most people on this, since I am in general principle opposed to monads on the grounds that I don't understand them :)
o How important is it that I switch from using the State monad to using arrows? I don't understand either monads or arrows
o How important is it that I switch from using |> or $ to using arrows? |> is pure functional programming. $ is pure functional programming. It just so happens that the idiom you are more used to |> is not the one most functional programmers are used to.
If a solution can be done in a purely functional way, do so. If a function requires monads, use them. If you just want to do entirely functional things in a monadic way then use Java :) Disclaimer: I hate monads, everyone will disagree with me. Thanks Neil

On Tuesday 14 March 2006 20:58, you wrote:
On 3/14/06, Benjamin Franksen
wrote: On Tuesday 14 March 2006 14:46, Pete Chown wrote:
Shannon -jj Behrens wrote:
Arrows looks like a replacement for monads. Are you saying I should drop my use of the State monad? If so, why? I like the readability of the do syntax.
Okay, now it's my turn to ask a question. :-) I've read about arrows, and while I think I see what they do, I'm not sure why they are seen as so special that they even get new syntax. This question of Shannon's is exactly the point I struggle with. I can see that the arrow operators might be useful with functions, but are they useful for other things too?
Yes, http://www.haskell.org/arrows/biblio.html lists a number of papers describing non-trivial applications of Arrows, that is, Arrows other than (->). I found the exposition in http://www.haskell.org/yale/papers/oxford02/ to be quite readable.
For example, as monads are one kind of arrow, I thought I would make some of the I/O functions into arrows and see what happened. The result was pretty much the same as using the monad, except slightly less convenient.
You can write monadic code without ever using the syntax sugar, and get along. However, do-notation is convenient. OTOH, I am told that programming with Arrows is really quite inconvenient w/o the syntax sugar.
Well, forgive me for my newbie-ness:
o How important is it that I switch from using the State monad to using arrows? o How important is it that I switch from using |> or $ to using arrows? (It seems that using arrows just to replace |> or $ is like using a sledge hammer to drive a thumb tack.) o How much will this increase the "conceptual complexity" of my program--i.e. how much time am I going to have to spend explaining it in my article? o How much will this improve the readability or decrease the amount of code in my program?
Thanks! -jj

On Tuesday 14 March 2006 20:58, you wrote:
On 3/14/06, Benjamin Franksen
wrote: On Tuesday 14 March 2006 14:46, Pete Chown wrote:
Shannon -jj Behrens wrote:
Arrows looks like a replacement for monads. Are you saying I should drop my use of the State monad? If so, why? I like the readability of the do syntax.
Okay, now it's my turn to ask a question. :-) I've read about arrows, and while I think I see what they do, I'm not sure why they are seen as so special that they even get new syntax. This question of Shannon's is exactly the point I struggle with. I can see that the arrow operators might be useful with functions, but are they useful for other things too?
Yes, http://www.haskell.org/arrows/biblio.html lists a number of papers describing non-trivial applications of Arrows, that is, Arrows other than (->). I found the exposition in http://www.haskell.org/yale/papers/oxford02/ to be quite readable.
For example, as monads are one kind of arrow, I thought I would make some of the I/O functions into arrows and see what happened. The result was pretty much the same as using the monad, except slightly less convenient.
You can write monadic code without ever using the syntax sugar, and get along. However, do-notation is convenient. OTOH, I am told that programming with Arrows is really quite inconvenient w/o the syntax sugar.
Well, forgive me for my newbie-ness:
o How important is it that I switch from using the State monad to using arrows?
I can see no good reason to do it.
o How important is it that I switch from using |> or $ to using arrows?
Not important. Arrows are just another way to structure a program. However, they have been designed for cases where a monad can /not/ be applied, such as e.g. self-optimizing parser combinators.
(It seems that using arrows just to replace |> or $ is like using a sledge hammer to drive a thumb tack.)
Yes.
o How much will this increase the "conceptual complexity" of my program--i.e. how much time am I going to have to spend explaining it in my article?
A lot, so I'd say leave it alone. I would use either plain function application or --perhaps-- a state monad.
o How much will this improve the readability or decrease the amount of code in my program?
See above. I don't think you gain anything by using (>>>). However, I still recommend using function application ($) instead of inverse application (|>) because this closer to idiomatic Haskell. Besides, readability depends on how proficient the reader is. People who regularly program using Arrows may find it easy to read. I don't and have more difficulty understanding it than e.g. monadic code. Cheers, Ben

Shannon -jj Behrens wrote:
o How important is it that I switch from using the State monad to using arrows?
Your problem seems to be naturally soved by the State monad, therefore you should use that.
o How important is it that I switch from using |> or $ to using arrows?
Unimportant. However, I'd recommend switching from application ($,|>) to composition (.,>>>) where possible. It's "more functional" and often easier to read.
o How much will this increase the "conceptual complexity" of my program
Not at all. You might define >>> locally as f >>> g = \x -> g (f x) or just pretend that this definition is contained in Control.Arrow due to a historical accident, thereby completely ignoring the existence of other arrows. Udo. -- Wo die Macht geistlos ist, ist der Geist machtlos. (aus einem Gipfelbuch)

Ok, with all the various opinions, I think I'll:
o Stick with the State monad.
o Switch from |> to $ and teach readers how to read it, "Think of 'f $
g $ x' as 'f of g of x' or 'f(g(x))'. From that point of view, it may
be helpful to read 'f $ g $ x' from right to left."
Unless there are any objections, with that one change, I'll consider
the coding done and move on to writing the article.
Thanks so much for all of your various opinions and suggestions! I
feel much more comfortable speaking from a position of authority
knowing that all of you have reviewed my code!
Best Regards,
-jj
On 3/15/06, Udo Stenzel
Shannon -jj Behrens wrote:
o How important is it that I switch from using the State monad to using arrows?
Your problem seems to be naturally soved by the State monad, therefore you should use that.
o How important is it that I switch from using |> or $ to using arrows?
Unimportant. However, I'd recommend switching from application ($,|>) to composition (.,>>>) where possible. It's "more functional" and often easier to read.
o How much will this increase the "conceptual complexity" of my program
Not at all. You might define >>> locally as
f >>> g = \x -> g (f x)
or just pretend that this definition is contained in Control.Arrow due to a historical accident, thereby completely ignoring the existence of other arrows.
Udo. -- Wo die Macht geistlos ist, ist der Geist machtlos. (aus einem Gipfelbuch)
-----BEGIN PGP SIGNATURE----- Version: GnuPG v1.4.1 (GNU/Linux)
iD8DBQFEF+f5c1ZCC9bsOpURAv2gAJwNirkt2yMFLlbTT9I2twUs3UcxdQCeKqx2 0FVTzx7VJEGtJexlGIJxero= =CPSW -----END PGP SIGNATURE-----
participants (12)
-
Benjamin Franksen
-
Brian Hulley
-
Einar Karttunen
-
Lennart Augustsson
-
Malcolm Wallace
-
Neil Mitchell
-
Pete Chown
-
Richard Gooding
-
Scott Turner
-
Shannon -jj Behrens
-
Tomasz Zielonka
-
Udo Stenzel