Re: [Haskell-cafe] "Write Yourself a Scheme in 48 Hours"

2007-02-02 Thread Shannon -jj Behrens

On 2/1/07, Bryan O'Sullivan <[EMAIL PROTECTED]> wrote:

Shannon -jj Behrens wrote:
> I'm going through the "Write Yourself a Scheme in 48 Hours"
> <http://halogen.note.amherst.edu/~jdtang/scheme_in_48/tutorial/overview.html>
>
> tutorial.  I like it a lot, but I have some concerns.  Are the
> exercises in the tutorial known to be solvable by mere mortals?

The answer seems to be "yes, iff the mortals in question have grasped
the basics of monads, so they can fill in the gaps in the exposition."

> For instance:
>
> "Rewrite parseNumber using...explicit sequencing with the >>= operator"
> 
http://halogen.note.amherst.edu/~jdtang/scheme_in_48/tutorial/parser.html#symbols
>
> There aren't any examples of using >>= previous to this question.

There's a peculiar mixture of assumptions in the article.  He treats
monads breezily, as if they're a given; but pattern matching (much more
basic) receives some rather more detailed exposition.  And he glosses
over ">>", but doesn't mention the rewrite rule from "a<-x" to "x>>=\a->".

So don't beat yourself up.  The tutorial is missing a few bits and pieces.


Thanks.  That's all I needed to hear :)

--
http://jjinux.blogspot.com/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] "Write Yourself a Scheme in 48 Hours"

2007-02-01 Thread Shannon -jj Behrens

I'm going through the "Write Yourself a Scheme in 48 Hours"

tutorial.  I like it a lot, but I have some concerns.  Are the
exercises in the tutorial known to be solvable by mere mortals?

For instance:

"Rewrite parseNumber using...explicit sequencing with the >>= operator"
http://halogen.note.amherst.edu/~jdtang/scheme_in_48/tutorial/parser.html#symbols

There aren't any examples of using >>= previous to this question.
Furthermore, the link to the Standard Prelude is not helpful because
there aren't any examples of how to use >>=.

Furthermore, consider the exercise:

"Change parseNumber to support the Scheme standard for different
bases. You may find the readOct and readHex functions useful."
http://halogen.note.amherst.edu/~jdtang/scheme_in_48/tutorial/parser.html#symbols

I struggled against this for a couple hours last night.  How is the
reader supposed to figure out readOct, which is part of ReadS, without
understanding the whole ReadS business?  If the reader does understand
the ReadS business, he probably already understands Haskell far better
than the tutorial seems to suggest.  I eventually figured out how to
write:

parseHexNumber = do char '#'
   char 'x'
   s <- many1 (oneOf "0123456789abcdefABCDEF")
   case readHex s of
 [(n,"")] -> return n

but it was no small feat.  Furthermore, it was only possible because I
had already spent so much time trying to understand "A Gentle
Introduction to Haskell".  Worst of all, once I had it all
implemented, the parser *from* the tutorial:

parseExpr :: Parser LispVal
parseExpr = parseAtom
   <|> parseString
   <|> parseNumber

led to some surprising results.  It turns out that "#o9", which should be
an invalid attempt at an octal number, is getting parsed as an atom.
There's a whole layer of difficulty that seems insurmountable by mere
mortals like me using just this tutorial and minimal reference usage.

What am I missing?  Is it really solvable by mere mortals who don't
already know Haskell, the Parsec module, etc.?

Thanks,
-jj

--
http://jjinux.blogspot.com/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Translating C to English Using Haskell

2006-08-03 Thread Shannon -jj Behrens

I've written a two-part series for "Linux Journal" called "Translating C to
English Using Haskell".  Here are links to the two parts:

http://www.linuxjournal.com/article/9096
http://www.linuxjournal.com/article/9242

The catchline is:

Write a program in Haskell that translates C type declarations into English.
Manually translate the Haskell into English.

I've tried very hard to make it an entertaining article for Haskell newbies, so
if your head exploded when you tried to read "A Gentle Introduction to
Haskell", give my article a shot!

A special thank you goes to all the members of this who helped me when
I was writing the article!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] request for co-development: improving Data.CharEncoding module

2006-05-26 Thread Shannon -jj Behrens

On 5/26/06, Bulat Ziganshin <[EMAIL PROTECTED]> wrote:

Hello Haskell,

i plan to publish new version of Streams library on next week (see
http://haskell.org/haskellwiki/Library/Streams if you still don't know
about it :) ). one of it's current drawbacks is lack of support for
file encodings other than UTF-8 and Latin-1. if someone can work on
this support, it will widen usage area of the library

i attached to letter current version of this module. it uses monadic
approach to encoding and decoding: each encoder is just a function
that performs monadic PutChar action via calls to monadic PutByte
action, and decoder in the same fashion translates each call to
GetChar into calls to GetByte. this allows to use encoders in various
environments - for monadic i/o, string conversion and so on

this module requires two improvements - first, support for other UTF
encodings; second, raising an exception in situations when data can't
be encoded (such as char > '\255' for Latin-1) or decoded (bad UTF
bytes sequence). if you are going to work on this module, please write
about this here - to avoid overlapping of work


I wonder if it helps any to "steal" this code from Python and
translate it into Haskell.

/me goes back to lurking.

-jj
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: request for code review

2006-03-15 Thread Shannon -jj Behrens
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 <[EMAIL PROTECTED]> wrote:
> 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-
>
>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: request for code review

2006-03-14 Thread Shannon -jj Behrens
On 3/14/06, Benjamin Franksen <[EMAIL PROTECTED]> 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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: request for code review

2006-03-13 Thread Shannon -jj Behrens
On 3/12/06, Lennart Augustsson <[EMAIL PROTECTED]> wrote:
> Shannon -jj Behrens wrote:
> > lexString ('*':cs) = (classifyString "*", cs)
> > lexString (c:cs) = (classifyString [c], cs)
>
> The first line isn't needed, it does the same as the second line.

Good eye!  You are correct.

Thanks,
-jj
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: request for code review

2006-03-13 Thread Shannon -jj Behrens
On 3/12/06, Einar Karttunen  wrote:
> 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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: request for code review

2006-03-12 Thread Shannon -jj Behrens
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 <[EMAIL PROTECTED]>
   Date: Fri Feb 17 00:03:38 PST 2006
-}

import Char (isSpace, isAlphaNum, isDigit)
import Control.Monad.State

-- |> is like a UNIX pipe.
infixl 9 |>
x |> f = f x

data TokenType = Identifier | Qualifier | Type | Symbol Char
  deriving (Show, Eq)

data Token = Token {
  tokenType :: TokenType,
  tokenValue :: String
} deriving Show

data ParseContext = ParseContext {
  input :: String,-- The input that has not been parsed yet.
  output :: [String], -- A list of strings in the reverse order of that which
  -- they should be printed (e.g. [" a dog.", "I have"]).
  currTok :: Token,   -- The current token, if defined.
  stack :: [Token]-- A stack of tokens we haven't dealt with yet.
} deriving Show

-- For convenience:
currTokType :: ParseContext -> TokenType
currTokType ctx = ctx |> currTok |> tokenType

currTokValue :: ParseContext -> String
currTokValue ctx = ctx |> currTok |> tokenValue

-- Start a new State ParseContext given an input string.
createParseContext :: String -> ParseContext
createParseContext input =
  ParseContext {input = input, output = [], stack = []}

-- Create the final output string given a ParseContext.
consolidateOutput :: ParseContext -> String
consolidateOutput ctx =
  ctx |> output |> reverse |> concat

-- "Write" to a ParseContext's output.
writeOutput :: String -> State ParseContext ()
writeOutput s = modify (\ctx -> ctx {output = s : output ctx})

-- Return the top token on the stack.
stackTop :: ParseContext -> Token
stackTop ctx = ctx |> stack |> head

-- Pop the stack.
pop :: State ParseContext ()
pop = modify (\ctx -> ctx {stack = ctx |> stack |> tail})

-- Write the value of the top of the stack and then pop it.
popAndWrite :: State ParseContext ()
popAndWrite = do
  top <- gets stackTop
  writeOutput (tokenValue top)
  pop

-- Classify a string into a Token.
classifyString :: String -> Token
classifyString "const"  = Token Qualifier "read-only"
classifyString "*"  = Token (Symbol '*') "pointer to"
classifyString [c]
  | not (isAlphaNum c)  = Token (Symbol c) [c]
classifyString s= Token tokType s
  where
tokType = case s of
  "volatile" -> Qualifier
  x | x `elem` ["void", "char", "signed", "unsigned", "short",
"int", "long", "float", "double", "struct",
"union", "enum"] -> Type
  x -> Identifier

-- Read the next token into currTok.
getToken :: State ParseContext ()
getToken = modify getToken'
  where
getToken' ctx@(ParseContext {input = s}) =
  ctx {currTok = token, input = theRest}
  where
(token, theRest) = s |> lstrip |> lexString
lstrip s = dropWhile isSpace s

-- Read a token.  Return it and the left-over portion of the string.
lexString :: String -> (Token, String)
lexString s@(c:cs) | isAlphaNum c = (token, theRest)
  where
(tokString, theRest) = span isAlphaNum s
token = classifyString tokString
lexString ('*':cs) = (classifyString "*", cs)
lexString (c:cs) = (classifyString [c], cs)

-- Put tokens on the stack until we reach the first identifier.
readToFirstIdentifier :: State ParseContext ()
readToFirstIdentifier = do
  getToken
  pushUntilIdentifier
  afterIdentifier <- get
  let s = identifier ++ " is "
  identifier = currTokValue afterIdentifier in
put (afterIdentifier {output = [s]})
  getToken

-- Keep pushing tokens until we hit an identifier.
pushUntilIdentifier :: State ParseContext ()
pushUntilIdentifier = do
  ctx <- get
  if currTokType ctx == Identifier
t

Re: [Haskell-cafe] |> vs. $ (was: request for code review)

2006-03-08 Thread Shannon -jj Behrens
On 3/8/06, Shannon -jj Behrens <[EMAIL PROTECTED]> wrote:
> On 3/8/06, Jared Updike <[EMAIL PROTECTED]> wrote:
> > > I suspect you guys are right.  I had always thought of states as
> > > being "isomorphic" to integers (i.e. you can be in state 0, state 1,
> > > ... state n), not as contexts (you have this input, that output, and
> > > this token stack), am I wrong?
> >
> > You're thinking of a state machine, I think, which is not quite what a
> > state monad would do here. (I have nightmares of writing a
> > state-machine parser in assembly like I did in an EE class once...
> > ouch).
> >
> > >  I suspect I need to spend more time
> > > trying to understand the state monad.  I must admit that I baulked
> > > the last time I tried to squeeze it into my head.  I'll just need to
> > > try again ;)
> >
> > Here's the way I like to think about state in imperative
> > programs---it's hard because it's not something you can get far away
> > from enough to see, usually.
> >
> > In imperative programs, the value of a variable 'a' at one point is
> > not always the value of the variable 'a' at another point later in the
> > code. In some sense, each statement that gets executed is passed the
> > entire state of the machine (the world) implicitly, and then when the
> > statement ends, it passes the state of the world on to the next
> > statement. If you want to access the value of the variable 'a', then
> > 'a' gets looked up in the environment/state.
> > In C/C++/Java/C#/Python/Perl, etc. this is done for you automatically
> > and efficiently. It's just the way the machine works. But you don't
> > have the choice to change this or, as someone put it, "overload the
> > semicolon".
> >
> > In Haskell none of this variable-mutating, state-passing **can**
> > occur, so it gets created from scratch, and voila, we have the State
> > Monad. It makes it sound like a lot more work than it should be just
> > to do something that comes for free in most other languages, but in
> > these languages, you can't overload the semicolon! And if you could,
> > who knows what could go wrong at runtime (imagine Perl with semicolon
> > overloading... I bet some day they will do this just because they
> > can...). In Haskell, everything is watched over by the type system, so
> > the parts of your program that explicitly need to munge state are
> > isolated with the some type tag, e.g. ParseContext, while the rest of
> > your program is "normal" and pure and functional.
> >
> > The problem with monads is not that they are "advanced" but that they
> > are so painfully and subtly abstract (I was going to say "subtly
> > simple" but maybe they aren't for most working non-Haskell
> > programmers...). (It just so happens that you **can** do amazing,
> > convenient, efficient, magic and otherwise advanced things with them,
> > especially with the libraries.) Another problem is that everyone has
> > different ways of explaining them or trying to define what they are (a
> > way of sequencing computation? or a type constructor? or a type
> > class?). Of course, they are all those things, which makes it even
> > more confusing. At a certain point, though, I think they just
> > subconciously click and boom, now you get it.
> >
> > Anyway, if your goal is to get people to understand Haskell, then see
> > if you can use monads to simplify things. If your goal is to do a
> > straight translation of the C code, don't worry about monads.
>
> Dude, that was a friggin' awesome email!  I'm trying to figure out how
> I can just copy it wholesale into the article ;)  I've been struggling
> with Haskell for long enough that my knowledge is now snowballing
> downhill.  Everything you said made sense 100%.

Yes, having read more, I can see clearly that the State monad was what
I was looking for.  Consider:

<http://www.nomaware.com/monads/html/statemonad.html>
A pure functional language cannot update values in place because it
violates referential transparency. A common idiom to simulate such
stateful computations is to "thread" a state parameter through a
sequence of functions...This approach works, but such code can be
error-prone, messy and difficult to maintain. The State monad hides
the threading of the state parameter inside the binding operation,
simultaneously making the code easier to write, easier to read and
easier to modify.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] |> vs. $ (was: request for code review)

2006-03-08 Thread Shannon -jj Behrens
On 3/8/06, Jared Updike <[EMAIL PROTECTED]> wrote:
> > I suspect you guys are right.  I had always thought of states as
> > being "isomorphic" to integers (i.e. you can be in state 0, state 1,
> > ... state n), not as contexts (you have this input, that output, and
> > this token stack), am I wrong?
>
> You're thinking of a state machine, I think, which is not quite what a
> state monad would do here. (I have nightmares of writing a
> state-machine parser in assembly like I did in an EE class once...
> ouch).
>
> >  I suspect I need to spend more time
> > trying to understand the state monad.  I must admit that I baulked
> > the last time I tried to squeeze it into my head.  I'll just need to
> > try again ;)
>
> Here's the way I like to think about state in imperative
> programs---it's hard because it's not something you can get far away
> from enough to see, usually.
>
> In imperative programs, the value of a variable 'a' at one point is
> not always the value of the variable 'a' at another point later in the
> code. In some sense, each statement that gets executed is passed the
> entire state of the machine (the world) implicitly, and then when the
> statement ends, it passes the state of the world on to the next
> statement. If you want to access the value of the variable 'a', then
> 'a' gets looked up in the environment/state.
> In C/C++/Java/C#/Python/Perl, etc. this is done for you automatically
> and efficiently. It's just the way the machine works. But you don't
> have the choice to change this or, as someone put it, "overload the
> semicolon".
>
> In Haskell none of this variable-mutating, state-passing **can**
> occur, so it gets created from scratch, and voila, we have the State
> Monad. It makes it sound like a lot more work than it should be just
> to do something that comes for free in most other languages, but in
> these languages, you can't overload the semicolon! And if you could,
> who knows what could go wrong at runtime (imagine Perl with semicolon
> overloading... I bet some day they will do this just because they
> can...). In Haskell, everything is watched over by the type system, so
> the parts of your program that explicitly need to munge state are
> isolated with the some type tag, e.g. ParseContext, while the rest of
> your program is "normal" and pure and functional.
>
> The problem with monads is not that they are "advanced" but that they
> are so painfully and subtly abstract (I was going to say "subtly
> simple" but maybe they aren't for most working non-Haskell
> programmers...). (It just so happens that you **can** do amazing,
> convenient, efficient, magic and otherwise advanced things with them,
> especially with the libraries.) Another problem is that everyone has
> different ways of explaining them or trying to define what they are (a
> way of sequencing computation? or a type constructor? or a type
> class?). Of course, they are all those things, which makes it even
> more confusing. At a certain point, though, I think they just
> subconciously click and boom, now you get it.
>
> Anyway, if your goal is to get people to understand Haskell, then see
> if you can use monads to simplify things. If your goal is to do a
> straight translation of the C code, don't worry about monads.

Dude, that was a friggin' awesome email!  I'm trying to figure out how
I can just copy it wholesale into the article ;)  I've been struggling
with Haskell for long enough that my knowledge is now snowballing
downhill.  Everything you said made sense 100%.

Nice!
-jj
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] |> vs. $ (was: request for code review)

2006-03-08 Thread Shannon -jj Behrens
First of all, thank you all so much for taking the time to help me
with this exercise!  My hope is that once I'm able to understand it,
my understanding can come through in the article I write.

> Brian Hulley:
> In the pipe in the 'otherwise' branch, at the moment you have to
> assume that each of the transformations can successfully be done.
> What happens if getToken can't get a token because there are no more
> tokens left?  To solve this problem you could use a monad such as
> Maybe, to encapsulate the strategy "keep going as long as no
> problems have been encountered so far" eg:

I can see where you're going with the Maybe monad, and it does make
sense.  However, I see Maybe as a "hammer" for a nail I wasn't
really all that interested in nailing ;)  It's true that getToken
might fail.  Most of the program isn't prepared to handle errors
gracefully, but neither was the C version.  That's okay.  If
anything, handling it as an exception and printing out a generic
error message would be more than enough.

Aside from the better error handling, I fear the Maybe monad isn't
buying much.

> Bulat Ziganshin:
> what you need here, imho, is a state monad.

> Danil Fischer
> I'd use a State-monad, say

I suspect you guys are right.  I had always thought of states as
being "isomorphic" to integers (i.e. you can be in state 0, state 1,
... state n), not as contexts (you have this input, that output, and
this token stack), am I wrong?  I suspect I need to spend more time
trying to understand the state monad.  I must admit that I baulked
the last time I tried to squeeze it into my head.  I'll just need to
try again ;)

> but if you'd done it monadically from
> the start, you'd probably chosen a different design

I specifically chose not to have a radically different design
because I wanted to maintain the "nature" of the original C code.
Naturally, if I were to try to do this from scratch, I'd use a
powerful lexer and parser.  However, the beauty of this code (i.e.
the original C code) is that it works without *needing* to use or
understand such powerful tools.

> As another method, I've hacked up a translation by parsing a
> declaration and creating a customized Show-instance.

Yeah, I thought of that too, but decided against if for the reason
given above.

Think of camping--sometimes it's fun to "rough it".  Sometimes it
can be fun to solve this problem without powerful tools.  Maybe I'm
just being silly ;)

> "In My Egotistical Opinion, most people's C programs should be
> indented six feet downward and covered with dirt."

Yeah, yeah ;)

I'm mostly a Python guy, so you're preaching to the choir ;)

Thanks again, guys!!!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] |> vs. $ (was: request for code review)

2006-03-07 Thread Shannon -jj Behrens
I did think of using a monad, but being relatively new to Haskell, I
was confused about a few things.  Let's start by looking at one of my
simpler functions:

-- Keep pushing tokens until we hit an identifier.
pushUntilIdentifier :: ParseContextTransformation
pushUntilIdentifier ctx
  | currTokType ctx == Identifier = ctx
  | otherwise =
  let newStack = (currTok ctx) : (stack ctx) in
(ctx {stack=newStack}) |>
getToken |>
pushUntilIdentifier

The function itself is a ParseContextTransformation.  It takes a
context, transforms it, and returns it.  Most of the pipelines in the
whole application are ParseContextTransformations, and the |> (or $ or
.) are ways of tying them together.  My questions concerning Monads
are in this example are:

1. Monads apply a strategy to computation.  For instance, the list
monad applies the strategy, "Try it with each of my members."  What
part of my code is the strategy?

2. Monads are containers that wrap a value.  For instance, the Maybe
monad can wrap any value, or it can wrap no value and just be Nothing.
 What part of my code is the thing being wrapped, and what part is
"extra data" stored in the Monad itself?

So I guess:

3. Is the ParseContext the monad or the thing being wrapped?

4. How do I divide the code between the functions on the right side of
>>= and the functions in the monad itself?  The functions on the right
side of >>= operate on the stuff inside the monad, and the functions
in the monad itself operate on the stuff in the monad.

5. How does the ParseContextTransformation relate?

It is because I did not understand the answers to these questions that
I thought maybe a monad might not be appropriate.  However, I surely
could be wrong.  Afterall, ParseContext, ParseContextTransformation,
and |> are all *inspired* by what I knew about monads.

Thanks for your help!

-jj

On 3/7/06, Brian Hulley <[EMAIL PROTECTED]> wrote:
> Brian Hulley wrote:
> > translate :: (Monad m) => String -> m String
> > translate = do
> >   createParseContext
> >   readToFirstIdentifier
> >   dealWithDeclarator
> >   consolidateOutput
>
> The type signature above doesn't match the do block. It would either have to
> be changed to something like:
>
> translate :: Control.Monad.State.MonadState String m => m ()
>
> (storing the string in the monad's state instead of using a monad which
> returns it) or the do block could be replaced with the >>= operator as
> below, to thread the returned string between the components of the "pipe":
>
> translate :: Monad m => String -> m String
> translate x =
>   return x >>=
>   createParseContext >>=
>   readToFirstIdentifier >>=
>  dealWithDeclarator >>=
>  consolidateOutput
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] |> vs. $ (was: request for code review)

2006-03-06 Thread Shannon -jj Behrens
By the way, thanks for everyone's comments so far!  They're very helpful!

> 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

Concerning:

-- |> is like a UNIX pipe.
infixl 9 |>
x |> f = f x

I find "ctx |> currTok |> tokenType" to be more readable than
"tokenType $ currTok $ ctx" because you're not reading the code in
reverse.  That's my primary complaint with "." and "$".  That's
especially the case when I'm spreading the code over multiple lines:

-- Translate a C type declaration into English.
translate :: String -> String
translate s =
  s |>
  createParseContext |>
  readToFirstIdentifier |>
  dealWithDeclarator |>
  consolidateOutput

I prefer |> for readability, but I understand that it can be bad to
spring new constructs on programmers in the middle of a program, and
I'm totally in favor of following standard Haskell idioms.  Does
anyone else have strong opinions one way or the other?  It seems like
most of my program is centered around pipes of "|>", so it's an
important issue.

Thanks!
-jj
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] request for code review

2006-03-05 Thread 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.

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 <[EMAIL PROTECTED]>
   Date: Fri Feb 17 00:03:38 PST 2006
-}

import Char (isSpace, isAlphaNum, isDigit)

-- |> is like a UNIX pipe.
infixl 9 |>
x |> f = f x

data TokenType = Identifier | Qualifier | Type | Symbol Char
  deriving (Show, Eq)

data Token = Token {
  tokenType :: TokenType,
  tokenValue :: String
} deriving Show

data ParseContext = ParseContext {
  input :: String,-- The input that has not been parsed yet.
  output :: [String], -- A list of strings in the reverse order of that which
  -- they should be printed (e.g. [" a dog.", "I have"]).
  currTok :: Token,   -- The current token, if defined.
  stack :: [Token]-- A stack of tokens we haven't dealt with yet.
} deriving Show

-- For convenience:
currTokType :: ParseContext -> TokenType
currTokType ctx = ctx |> currTok |> tokenType

currTokValue :: ParseContext -> String
currTokValue ctx = ctx |> currTok |> tokenValue

type ParseContextTransformation = ParseContext -> ParseContext

-- Start a new ParseContext given an input string.
createParseContext :: String -> ParseContext
createParseContext input = ParseContext {input=input, output=[], stack=[]}

-- Create the final output string given a ParseContext.
consolidateOutput :: ParseContext -> String
consolidateOutput ctx = ctx |> output |> reverse |> concat

{- "Write" to a ParseContext's output.  The API is a bit strange.
   (writeOutput s) is itself a ParseContextTransformation which you can apply
   to ParseContexts.  Strange but convenient.
-}
writeOutput :: String -> ParseContextTransformation
writeOutput s = \ctx ->
  let newOutput = s : (output ctx) in
ctx {output=newOutput}

-- Return the top token on the stack.
stackTop :: ParseContext -> Token
stackTop ctx =
  let (x:xs) = stack ctx in x

-- Pop the stack.
pop :: ParseContextTransformation
pop ctx =
  let (x:xs) = stack ctx in ctx {stack=xs}

-- Write the value of the top of the stack and then pop it.
popAndWrite :: ParseContextTransformation
popAndWrite ctx =
  ctx |>
  ((stackTop ctx) |>
   tokenValue |>
   writeOutput) |>
  pop

-- Classify a string into a Token.
classifyString :: String -> Token
classifyString "const"  = Token Qualifier "read-only"
classifyString "*"  = Token (Symbol '*') "pointer to"
classifyString s@(c:[])
  | not (isAlphaNum c)  = Token (Symbol c) s
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

-- Read the next token into currTok.
getToken :: ParseContextTransformation
getToken ctx@(ParseContext {input=s}) =
  let lstrip s = dropWhile isSpace s
  (token, theRest) = s |> lstrip |> lexString in
ctx {currTok=token, input=theRest}

-- Read a token.  Return it and the left-over portion of the string.
lexString :: String -> (Token, String)
lexString s@(c:cs) | isAlphaNum c =
  let (tokString, theRest) = span isAlphaNum s
  token = classifyString tokString in
(token, theRest)
lexString ('*':cs) = (classifyString "*", cs)
lexString (c:cs) = (classifyString (c:[]), cs)

--