Fw: Modification of State Transformer

Scott J. jscott@planetinternet.be
Mon, 12 Aug 2002 21:08:47 +0200


----- Original Message -----
From: "Scott J." <jscott@planetinternet.be>
To: "Shawn P. Garbett" <Shawn@Garbett.org>
Sent: Monday, August 12, 2002 9:04 PM
Subject: Re: Modification of State Transformer


> I 'm sorry,
>
> What I meant was discussion about the state transformer ST s a itself. And
> how it works. What does mean the second inner forall loop and so on. I
can't
> find explanations of this in the Haskell library.
>
> Regards
>
> Scott
> ----- Original Message -----
> From: "Shawn P. Garbett" <Shawn@Garbett.org>
> To: "Scott J." <jscott@planetinternet.be>
> Cc: <haskell-cafe@haskell.org>
> Sent: Monday, August 12, 2002 4:19 PM
> Subject: Re: Modification of State Transformer
>
>
> > -----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-----
> > _______________________________________________
> > Haskell-Cafe mailing list
> > Haskell-Cafe@haskell.org
> > http://www.haskell.org/mailman/listinfo/haskell-cafe
> >
>