On 08/21/2011 05:33 AM, Felipe Almeida Lessa wrote:
On Sat, Aug 20, 2011 at 6:26 PM, Tom Schouten<t...@zwizwa.be>  wrote:
data Kl i o = forall s. Kl s (i ->    s ->    (s, o))

This is an Arrow.  At first I wondered if there was also an associated
Monad, hence the iso function.
Given

   data Kl i o = forall s. Kl s (i ->    s ->    (s, o))

   instance ArrrowApply KI where
     ...

then 'ArrowMonad KI' [1] is a monad isomorphic to

   data KIM o = forall s. KIM s (s ->  (s, o))

Is this what you are looking for?

Yes, but I run into the same problem.


data Kl i o = forall s. Kl (i -> s -> (s, o))

-- OK
instance Category Kl where
  id = Kl $ \ i () -> ((), i)
  (.) (Kl u2) (Kl u1) = (Kl u12) where
    u12 a (s1, s2) = ((s1',s2'), c) where
      (s1', b) = u1 a s1
      (s2', c) = u2 b s2

-- OK
instance Arrow Kl where
  arr f = Kl $ \i () -> ((), f i)
  first (Kl u) = (Kl u') where
    u' (i, x) s = (s', (o, x)) where
      (s', o) = u i s

-- Can't make this work.  The problem seems to be the same as before:
-- there's no way to require that the hidden types of both Kl
-- constructors are the same.
instance ArrowApply Kl where
  app = Kl $ \((Kl f), a) -> f a


_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to