On Wed, Mar 25, 2009 at 8:25 AM, Jonathan Cast
<[email protected]> wrote:
> On Wed, 2009-03-25 at 15:09 +0000, Simon Marlow wrote:
>> the ordering that the state monad expects
>> (and I can never remember which way around they are in Control.Monad.State).
>
> Really? I found it obvious once I figured out it how simple it made
> (>>=). With the order from Control.Monad.State (with constructors
> ignored):
>
> a >>= f = \ s -> case s a of
> (x, s') -> f x s'
>
> Reversing the order of the components of the result gives you
>
> a >>= f = \ s -> case s a of
> (s', x) -> f x s'
>
> which just looks weird.
However, if you are used to thinking in terms of type composition, s
-> (s, a) makes more sense, because it is effectively
(s ->) . (s,) . Identity
whose "functor-ness" is automatic via composition of functors:
newtype Identity a = Identity a
inIdentity f (Identity a) = Identity (f a)
instance Functor Identity where
fmap f = inIdentity f
instance Functor ((,) a) where
fmap f (a, x) = (a, f x)
instance Functor ((->) a) where
fmap f k a = f (k a)
newtype O f g x = O (f (g x))
inO f (O a) = O (f a)
instance (Functor f, Functor g) => Functor (O f g) where
fmap f = inO (fmap (fmap f))
-- or fmap = inO . fmap . fmap
-- not valid haskell, but if there were sections at the type level it would be.
type State s = (s ->) `O` (s,) `O` Identity
-- ryan
_______________________________________________
Haskell-Cafe mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/haskell-cafe