[Haskell-cafe] Re: Knot tying vs monads

ChrisK haskell at list.mightyreason.com
Mon Nov 19 12:27:13 EST 2007


 The data dependency is circular.  The "case e of" Str and Brk are not-circular:
 layout examines the input parameters to determine column'.  Then column'
 is used to compute columnOut and s'.  Then the current data is
 prepended to s'.  The Blo case is the circular one.  Pushing the circular
 definitions in to this case (and using the mapSnd helper) results in:

>     layout :: [Pretty] -> (Int,String) -> (Int,String)
>     layout [] columnIn'sIn'pair = columnIn'sIn'pair
>     layout (e:es) (!columnIn,sIn) =
>       case e of
>         Str n str -> mapSnd (showString str) $ layout es (columnIn+n,sIn)
>         Brk n | columnIn + n + breakDist es after <= margin ->
>                   mapSnd (prepend n ' ') $ layout es (columnIn+n,sIn)
>               | 0 <= startColumn ->
>                   mapSnd (('\n':).prepend startColumn ' ') $ layout es (startColumn,sIn)
>               | otherwise -> mapSnd ('\n':) $ layout es (0,sIn)
>         Blo _n  indent es' -> let startColumn' = indent + columnIn
>                                   after' = breakDist es after
>                                   (columnOut,s') = layout es (column',sIn)
>                                   (column',sOut) = block startColumn' after' es' (columnIn,s')
>                               in (columnOut,sOut)
>
> mapSnd f (a,b) = (a,f b)

The circular usage of column' and s' can be unwound by "importing Control.Monad.Fix(fix)"
and writing a definition with "fix" that explicitly feeds back the s':

>         Blo _n  indent es' -> let startColumn' = indent + columnIn
>                                   after' = breakDist es after
>                                   withS ~(_,s') = let (column',sOut) = block startColumn' after' es' (columnIn,s')
>                                                       (columnOut,s'') = layout es (column',sIn)
>                                                   in ((columnOut,sOut),s'')
>                                   in fst (fix withS)

In withS above, the column' is created by the call to block and consumed by the call to layout.
The s'' is fed back to become s' by the use of fix.  The actual answer is the fst component.

It is also possible to avoid the lazy '~' matching by using "snd":

>         Blo _n  indent es' -> let startColumn' = indent + columnIn
>                                   after' = breakDist es after
>                                   withS ans's' = let (column',sOut) = block startColumn' after' es' (columnIn,snd ans's')
>                                                      (columnOut,s'') = layout es (column',sIn)
>                                                  in ((columnOut,sOut),s'')
>                                   in fst (fix withS)
>

Whether any of these three versions is clearer to the previous message is a matter of taste.

Cheers,
  Chris



More information about the Haskell-Cafe mailing list