[Haskell-cafe] How to define a Monad instance

Thiago Negri evohunz at gmail.com
Tue Jul 31 18:13:34 CEST 2012


Thanks for the reply Ryan.

That's exactly the type of thing I was trying to do: use the
syntactical sugar of do-notation to express some replacement rules.

Why am I doing this?

A long time ago, when I was learning C, I did a small project
(spaghetti code) to encrypt text files in some user-defined language.
It supported exact replacement (char -> char) and some other stuff
that I called "sessions" of encryption and masked string replacement.

The sessions can be turned on or off at the same time of matching a
char, e.g. the user could define that when the char 'a' was matched
inside the session "foo", it will change it to a 'b', turn off the
session "foo" and turn on the sessions "bar" and "baz".

So, I'm trying to create a similar thing in Haskell.

In my view, it fits in the Monad class, as I'm doing pattern matching
and replacing at the same time as sequencing other things like
changing the state of the replacement machine.

The char-to-char replacement is the first step.

I'll try your exercises later, when I get home.

Thanks,
Thiago.

2012/7/31 Ryan Ingram <ryani.spam at gmail.com>:
> A couple typos:
>
> instance Monad Replacer1 where
> ->
> instance Monad (Replacer1 k) where
>
>
> instance Monad Replacer2 k where
> ->
> instance Monad (Replacer2 k) where
>
> I haven't tested any of this code, so you may have to fix some minor type
> errors.
>
>
> On Mon, Jul 30, 2012 at 10:38 PM, Ryan Ingram <ryani.spam at gmail.com> wrote:
>>
>> To take this a step further, if what you really want is the syntax sugar
>> for do-notation (and I understand that, I love sweet, sweet syntactical
>> sugar), you are probably implementing a Writer monad over some monoid.
>>
>> Here's two data structures that can encode this type;
>>
>> data Replacer1 k a = Replacer1 (k -> Maybe k) a
>> data Replacer2 k a = Replacer2 [(k,k)] a
>>
>> instance Monad Replacer1 where
>>     return x = Replacer1 (\_ -> Nothing) x
>>     Replacer1 ka a >>= f = result where
>>         Replacer1 kb b = f a
>>         result = Replacer1 (\x -> ka x `mplus` kb x) b
>>
>> (!>) :: Eq k => k -> k -> Replacer1 k ()
>> x !> y = Replacer1 (\k -> if k == x then Just y else Nothing) ()
>>
>> replace1 :: Replacer1 k () -> [k] -> [k]    -- look ma, no Eq requirement!
>> replace1 (Replacer k ()) = map (\x -> fromMaybe x $ k x) -- from
>> Data.Maybe
>>
>> table1 :: Replacer1 Char ()
>> table1 = do
>>     'a' !> 'b'
>>     'A' !> 'B'
>>
>> test = replace1 table1 "All I want"
>>
>> -- Exercise: what changes if we switch ka and kb in the result of (>>=)?
>> When does it matter?
>>
>> -- Exercises for you to implement:
>> instance Monad Replacer2 k where
>> replacer :: Eq k => Replacer2 k -> [k] -> [k]
>> ($>) :: k -> k -> Replacer2 k
>>
>> -- Exercise: Lets make use of the fact that we're a monad!
>> --
>> -- What if the operator !> had a different type?
>> -- (!>) :: Eq k => k -> k -> Replacer k Integer
>> -- which returns the count of replacements done.
>> --
>> -- table3 = do
>> --     count <- 'a' !> 'b'
>> --     when (count > 3) ('A' !> 'B')
>> --     return ()
>> --
>> -- Do any of the data structures I've given work?  Why or why not?
>> -- Can you come up with a way to implement this?
>>
>>   -- ryan
>>
>>
>> On Sat, Jul 28, 2012 at 10:07 AM, Steffen Schuldenzucker
>> <sschuldenzucker at uni-bonn.de> wrote:
>>>
>>> On 07/28/2012 03:35 PM, Thiago Negri wrote:
>>> > [...]
>>>
>>>> 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 TableDefinition a is like [(a, a)].
>>>
>>>> [...]
>>>
>>> >
>>>>
>>>> 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)))
>>>
>>>
>>> Yes, but monads aren't just about sequencing. I like to see a monad as a
>>> generalized computation (e.g. nondeterministic, involving IO, involving
>>> state etc). Therefore, you should ask yourself if TableDefinition can be
>>> seen as some kind of abstract "computation". In particular, can you
>>> "execute" a computation and "extract" its result? as in
>>>
>>>   do
>>>     r <- Match 'a' 'c' Restart
>>>     if r == 'y' then Restart else Match 2 3 (Match 3 4 Restart)
>>>
>>> Doesn't immediately make sense to me. In particular think about the
>>> different possible result types of a TableDefinition computation.
>>>
>>> If all you want is sequencing, you might be looking for a Monoid instance
>>> instead, corresponding to the Monoid instance of [b], where b=(a,a) here.
>>>
>>>>  [...]
>>>
>>> >
>>>>
>>>> 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. :(
>>>
>>>
>>> The desugaring of the example looks like this:
>>>
>>>   ('a' :> 'b') >> ('A' :> 'B')
>>>
>>> Only (>>) is used, but not (>>=) (i.e. results are always discarded). If
>>> this is the only case that makes sense, you're probably looking for a Monoid
>>> instead (see above)
>>>
>>> -- Steffen
>>>
>>>
>>> _______________________________________________
>>> Haskell-Cafe mailing list
>>> Haskell-Cafe at haskell.org
>>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
>>
>



More information about the Haskell-Cafe mailing list