[Haskell-cafe] How to define a Monad instance

Thiago Negri evohunz at gmail.com
Sat Jul 28 15:35:40 CEST 2012


Hello.

I'm trying to understand Monads. In order to do so, I decided to
create my own Monad for a simple domain-specific language.
The idea is to define a way to describe a multi-value replacement
inside do-notation.

Example of a function doing what I want (without Monads):

replaceAll :: (a -> Maybe a) -> [a] -> [a]
replaceAll f xs = go f xs []
  where go :: (a -> Maybe a) -> [a] -> [a] -> [a]
        go _ [] acc = acc
        go f (x:xs) acc = let acc' = acc ++ [fromMaybe x (f x)] in
acc' `seq` go f xs acc'

Example of a replacement table:

table :: Char -> Maybe Char
table x = case x of
                'a' -> Just 'b'
                'A' -> Just 'B'
                _   -> Nothing

Example of use:

\> replaceAll table "All I want"
"Bll I wbnt"


Now, want I tried to do...
As Monads are used for sequencing, first thing I did was to define the
following data type:

data TableDefinition a = Match a a (TableDefinition a) | Restart

So, to create a replacement table:

table' :: TableDefinition Char
table' =
        Match 'a' 'b'
        (Match 'A' 'B'
         Restart)

It look like a Monad (for me), as I can sequence any number of
replacement values:

table'' :: TableDefinition Char
table'' = Match 'a' 'c'
         (Match 'c' 'a'
         (Match 'b' 'e'
         (Match 'e' 'b'
          Restart)))

In order to run the replacement over a list, I've defined the
following function:

runTable :: Eq a => TableDefinition a -> [a] -> [a]
runTable t = go t t []
  where go _ _             acc []        = acc
        go s Restart       acc (x:xs)    = let acc' = (acc ++ [x]) in
                                               acc' `seq` go s s acc' xs
        go s (Match a b m) acc ci@(x:xs) | x == a    = let acc' = (acc
++ [b]) in
                                                           acc' `seq`
go s m acc' xs
                                         | otherwise = go s m acc ci

The result is still the same:

\> runTable table' "All I want"
"Bll I wbnt"

I'd like to define the same data structure as:

newTable :: TableDefinition Char
newTable = do
        'a' :> 'b'
        'A' :> 'B'

But I can't figure a way to define a Monad instance for that. :(

Can you help me?

Thanks,
Thiago.



More information about the Haskell-Cafe mailing list