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

Shannon -jj Behrens jjinux at gmail.com
Tue Mar 7 14:52:01 EST 2006


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 <brianh at metamilk.com> 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


More information about the Haskell-Cafe mailing list