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

Brian Hulley brianh at metamilk.com
Tue Mar 7 17:07:52 EST 2006


Shannon -jj Behrens wrote:
> 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?

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:

type ParseContextTransformation = ParseContext -> Maybe ParseContext

pushUntilIdentifier :: ParseContextTransformation
pushUntilIdentifier ctx
   | currTokType ctx == Identifier = Just ctx
   | otherwise =
      let newStack = (currTok ctx) : (stack ctx) in
            return  ctx{stack=newStack} >>=
            getToken >>=
            pushUntilIdentifier

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

lexString :: String -> (Maybe Token, String)
lexString s@(c:cs) | isAlphaNum c =
  let (tokString, theRest) = span isAlphaNum s
      token = classifyString tokString in
     (Just token, theRest)
lexString ('*':cs) = (Just $ classifyString "*", cs)
lexString (c:cs) = (Just $ classifyString (c:[]), cs)
lexString [] = (Nothing, [])  -- can now deal with this case

lexString is itself a candidate for a monadic computation on a state monad 
where the state is the string and Maybe Token is the return type, but it 
depends on how much you want to "monadify" your code...

>
> 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?

Using the Maybe monad as above, it is the monad's "return type". For any 
monad m, m a means "the monad m returning a value of type a" so Maybe 
ParseContext means "a Maybe monad returning a value of type ParseContext". I 
think "stored in the monad itself" would usually refer to the case where you 
use some sort of state monad where the ParseContext would be the state but 
AFAIK this wouldn't be the most natural way to structure this sort of 
application.

>
> 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.

Using the Maybe monad you could access the result by:

toplevel :: String -> IO ()
toplevel s = case translate s of
                        Just s' -> putStrLn s'
                        Nothing -> putStrLn "Error translating"

where translate and each of its component functions are changed to return 
their results via the Maybe monad.

>
> 5. How does the ParseContextTransformation relate?

I just modified ParseContextTransformation so that the resulting 
ParseContext is returned via the Maybe monad to allow for failure in any of 
the transformation steps. You'd need to also change createParseContext to 
return Maybe ParseContext etc.

There are more advanced ways of using monads, eg where you use Monad m => 
instead of hardcoding the Maybe monad into the result, but it probably makes 
more sense to understand monads using concrete examples first. The tutorials 
give more info on these advanced monadic ways (and are certainly far better 
than me at explaining them).

Hope this helps,
Brian.




More information about the Haskell-Cafe mailing list