I tried defining a parametrized state transformer using HBC, starting with
these definitions (all standard):

> newtype StateM m s a = StateM (s -> m (a,s))

> instance (Monad m) => Monad (StateM m s) where
>  -- return :: a -> StateM m s a
>  -- (>>=)  :: StateM m s a -> (a -> StateM m s b) -> StateM m s b
>  return a       = StateM (\s -> return (a,s))
>  StateM x >>= f = StateM (\s -> do (a,s') <-x s; case f a of StateM y-> y s')

> instance (MonadZero m) => MonadZero (StateM m s) where
>  -- zero :: StateM m s a
>  zero = StateM (\ _ -> zero)

> instance (MonadPlus m) => MonadPlus (StateM m s) where
>  -- (++) :: StateM m s a -> StateM m s a -> StateM m s a
>  StateM x ++ StateM y = StateM (\ s -> x s ++ y s)

  Now, in the literature, we often see the following definitions of the state
transformer monad class (and instance):

> class (Monad m) => STM m s where
>       update  :: (s -> s) -> m s
>       set     :: s -> m s
>       fetch   :: m s
>       set s   =  update (\_ -> s)

> instance (Monad m) => STM (StateM m s) s where
>       -- update :: (Monad m) => (s -> s) -> StateM m s s
>       update f = StateM (\s -> return (s, f s))

  Note that this class accepts two parameters and thus will not be accepted by
a Haskell 1.3 compiler.

  At first, I got around this by taking advantage of the fact that HBC allows
overlapping class instances, fixing the state s and defining the particular
state monads that I wanted (in different modules), e.g.:

> class (Monad m) => STM m where
>       update  :: (String -> String) -> m String
>       set     :: String -> m String
>       fetch   :: m String
>       set s   =  update (\_ -> s)

  ...etc.  This worked fine.

  Then, just for the hell of it, I defined STM as above, but universally
quantified the state type in the method signatures and pretended there was no
second parameter in the class definition:

> class (Monad m) => STM m where
>       update  :: (s -> s) -> m s
>       set     :: s -> m s
>       fetch   :: m s
>       set s   =  update (\_ -> s)
>       fetch   =  update id

  I figured that this would give me overloading ambiguities (or unification
errors) because I thought that making the state a class parameter must imply a
different level of quantification of s (or something).  Otherwise, why
explicitly make it a class parameter?  There must be a reason.

  To my surprise, it worked.  I repeated the procedure for a reader monad, and
defined a parser:

> type Parser a = ReaderM (StateM [] String) Loc a
> type LocS     = [(Loc,String)]
> data Loc      = Loc { line, col :: !Int }

> item  :: Parser String
> item  =  do   x:_ <- update tail
>               return x

  At this point, I had the vague idea that the compiler would not be able to
find the right overloading for the use of update above, but this module
compiles without error.

  I always thought that you need multi-parameter classes to define
parametrized monads.  Apparently I was wrong.  Is there some limitation to
this approach that I haven't encountered yet?

--------------------------------------------------------------------------
Frank Christoph                 Next Solution Co.       Tel: 0424-98-1811
[EMAIL PROTECTED]                              Fax: 0424-98-1500



Reply via email to