Modification of State Transformer

Jon Cast jcast@ou.edu
Thu, 08 Aug 2002 17:33:10 -0500


"Shawn P. Garbett" <listman@garbett.org> wrote:
> I'm trying to modify Richard Bird's state transformer. The example
> in his book (_Introduction_to_Functional_Programming_using_Haskell_)
> has State defined as a explicit type.

> I.e. Here's the relevant snippet:

> -- State transformer definition

> newtype St a = MkSt (State -> (a, State))
> type State   = Int

> -- State transformer applied to state
> apply             :: St a -> State -> (a, State)
> apply (MkSt f) s  = f s

> -- State monad

> instance Monad St where
>   return x  = MkSt f where f s = (x,s)
>   p >>= q   = MkSt f where f s = apply (q x) s'
>                                  where (x, s') = apply p s
> -----------------------------------------

> What I want is something like this, so that the state transformer
> has a generic state type:

Btw: This has already been done, in GHC: see the ST module in GHC's
library
<http://www.haskell.org/ghc/docs/latest/html/base/Control.Monad.ST.html>.
To answer your specific question, though:

> newtype St a s = MkSt (s -> (a, s))

These are in the wrong order (see below); you want:

> newtype St s a = MkSt (s -> (a, s))

> apply             :: St a s -> s -> (a, s)
> apply (MkSt f) s  = f s

Again, s/St a s/St s a/.

> instance Monad St where
>   return x  = MkSt f where f s = (x,s)
>   p >>= q   = MkSt f where f s = apply (q x) s'
>                                  where (x, s') = apply p s
> -----------------------------------------------------------
> The trouble occurs on the instance line
>     Couldn't match `*' against `* -> *'
>         Expected kind: (* -> *) -> *
>         Inferred kind: (* -> * -> *) -> *
>     When checking kinds in `Monad St'
>     In the instance declaration for `Monad St'
> Failed, modules loaded: none.

Right.  The problem here is that St is a type constructor with two
arguments (i.e., of kind (* -> * -> *)), whereas Monad wants a type
constructor with one argument (i.e., of kind (* -> *)).  Hence the
error.  This is the same type of error you'd get if you tried to
declare an instance for `Eq Tree', where `Tree' is a standard
(polymorphic) BST.  The way you solve that is to instantiate `Eq (Tree
a)', and it's the same thing here: instantiate `Monad (St s)'.
Of course, you need to switch the order of the arguments to St first
(as done above), so Haskell knows `s' is a the state type, not the
result type.

HTH

Jon Cast