Re: Modification of State Transformer

"Shawn P. Garbett"
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

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.
This list is great. The implementation in the ST module solves the problem and I understand how it works. Shawn -- You're in a maze of twisty little statements, all alike. Public Key available from http://www.garbett.org/public-key

Hi,
I invite you then to explain what happens with every step.
The use of "forall" is misleading and fast to be misunderstood: I mention
here the inner forall's.
Thx
Scott
----- Original Message -----
From: "Shawn P. Garbett"
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.
This list is great. The implementation in the ST module solves the problem and I understand how it works.
Shawn
-- You're in a maze of twisty little statements, all alike. Public Key available from http://www.garbett.org/public-key _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

-----BEGIN PGP SIGNED MESSAGE----- Hash: SHA1 On Sunday 11 August 2002 07:26 pm, Scott J. wrote:
Hi,
I invite you then to explain what happens with every step.
The use of "forall" is misleading and fast to be misunderstood: I mention here the inner forall's.
Thx
Scott
This list is great. The implementation in the ST module solves the problem and I understand how it works.
Shawn
Given the level of detailed explanations to date, I don't see the point. But I'll go ahead and do so anyway, by summarizing what I've learned from the previous posts. I had read the example in Bird'd book on state transformers. The definition of state however was a fixed type in the examples. Wanting to extend the definition and make it more general I was trying to figure out how to modify the type. Bird's definition was: newtype St a = MkSt (State -> (a,State)) type State = type I had attempted to extend the type as follows newtype St a s = MkSt (s -> (a,s)) This died in the compiler when declaring this type as an instance of 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 ghc returned the following (referencing the instance line): Couldn't match `*' against `* -> *' Expected kind: (* -> *) -> * Inferred kind: (* -> * -> *) -> * When checking kinds in `Monad St' In the instance declaration for `Monad St' When a type constructor has an argument it has a type of `* -> *'. When a type constructor has two arguments it has a type of `* -> * -> *'. This construction of the type can be extended to n arguments by having the number of `->' match the n arguments of type and the `*' be n+1. The class definition of Monad contains the following: class Monad m where return :: a -> m a (>>=) :: m a -> (a -> m b) -> m b So the class of St a s needs reduction from `* -> * -> *' to `* -> *' to fit the single argument type constructor of the Monad class. By using (St a) which causes the type constructor to be of type `(* -> *) -> *'. Since `(* -> *)' can be used as `*', by creation of another type. This because equivalent to `* -> *'. The only thing left is reversing the order so that the result type is of the correct form in the Monad usage. I.e, in my initial ordering the `return' of the Monad would end up returning something of type `s' which is not particularly useful, since type `a' is the desired return type from the transformer. So the corrected version of State becomes: newtype St s a = MkSt (s -> (a, s)) instance Monad (St s) where ... Shawn Garbett - -- You're in a maze of twisty little statements, all alike. Public Key available from http://www.garbett.org/public-key -----BEGIN PGP SIGNATURE----- Version: GnuPG v1.0.7 (GNU/Linux) iD8DBQE9V8P4DtpPjAQxZ6ARAq0VAJ9toEiEm+d58vgbKEofzXBISyXrEACfasbc eaEg2zVi9y90vk+fXKGSrt0= =OrwN -----END PGP SIGNATURE-----
participants (3)
-
Jon Cast
-
Scott J.
-
Shawn P. Garbett