[Haskell-beginners] How to construct complex string

Stephen Tetley stephen.tetley at gmail.com
Fri Aug 9 00:18:28 CEST 2013


Hi Martin

The example is actually in the test directory - DotTest.hs.

> data Dot a = Dot { unDot :: Int -> ([GraphElement],Int,a) }

This is the monad in which you build syntax - when the code is run it is
pretty printed into a String.

This particular monad is a combination of the Writer monad - it accumulates
a list of GraphicElement and a state monad - Int is passed around and
incremented so it can generate variable names:

As separate pieces the monads are:

> data State a = State { unState :: Int -> (Int, a) }

i.e. a function from state of type `Int` to a tuple of state and a
polymorphic answer (Int,a).

> data Writer a = Writer { unWriter :: ([GraphElement],a) }

i.e. a tuple of GraphElement's accumulated in a list and a polymorphic
answer.

Once you have a "declaration" of a monad you also have to provide an
instance of the monad class so you can use the do-notation,
in the Dotgen code the instance is:

instance Monad Dot where
  return a = Dot $ \ uq -> ([],uq,a)
  m >>= k  = Dot $ \ uq -> case unDot m uq of
               (g1,uq',r) -> case unDot (k r) uq' of
                       (g2,uq2,r2) -> (g1 ++ g2,uq2,r2)

This is a bit complicated as it is a combination of the monadic operation
of both the State and Writer monad. With luck for just generating commands
(and not generating fresh variables) you should be able to manage with only
a Writer monad. There is one already in the monads package (mtl) in the
Platform.

The main part of the Dotgen library are the functions `edge`, `node`,
(.->.) etc. which build Dot commands. In `edge` you can see a single
command being built `[GraphEdge from to attrs]` in the first cell of the
answer tuple:

-- | 'edge' generates an edge between two 'NodeId's, with attributes.
edge      :: NodeId -> NodeId -> [(String,String)] -> Dot ()
edge  from to attrs = Dot (\ uq -> ( [ GraphEdge from to attrs ],uq,()))


Because no fresh variables are generated, the state `uq` (read as "unique")
is returned unaltered in the answer tuple along with the void answer `()`.

The other key part of the library is the so-called "run function" which
evaluates monadic expressions - here the run function is called showDot:

-- 'showDot' renders a dot graph as a 'String'.
showDot :: Dot a -> String
showDot (Dot dm) = case dm 0 of
            (elems,_,_) -> "digraph G {\n" ++ unlines (map showGraphElement
elems) ++ "\n}\n"


showDot unwraps `dm` from the Dot data type. As dm is a function ` Int ->
([GraphElement],Int,a) ` it needs to be applied to the initial state - here
0. This produces the answer 3-tuple, where we are only interested in the
accumulated list of dot commands (the first cell). This list of commands is
pretty printed into legal Dot syntax.

Hope this helps somewhat.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/beginners/attachments/20130808/56ac2be3/attachment.htm>


More information about the Beginners mailing list