Did anyone with knowledge of Associated Types pursue this solution?

Where did you get this from.  My haskell-cafe mail folder doesn't seem
to have the thread you are replying to.


Sorry I replied from gmane; I should have included a link to the original thread, but I really expected gmane to do that. The thread is at:

http://www.haskell.org/pipermail/haskell-cafe/2006-December/020615.html


It doesn't work with GHC head, and I can't really do anything about that.
Mostly curiosity.

The main reason this doesn't work with the head is because the
implementation of associated type *synonyms* (as opposed to associated
data types) is still incomplete.  (See also
<http://haskell.org/haskellwiki/GHC/Indexed_types>.) We are working at the implementation, but I just relocated from New York to Sydney, which
is why not much happened in the last two months.

But I also don't quite understand the intention of this code:


I will try to fill in the details, but surely it is all expanded in the original thread.

The idea is that we have an indexed/effectful monad where bind and return have a parameterized type:

class WitnessMonad m where
  (>>=) :: m a b x -> (x -> m b c y) -> m a c y
  return :: x -> m a a x

We can produce instances of WitnessMonad from an existing Monad using an adaptor

newtype WitnessAdaptor m a b x = W {unW::m x}
instance Monad m => WitnessMonad (WitnessAdaptor m)

And rebind the do syntax to our WitnessMonad.
But using vanilla Monads via this trick requires to lift and unlift every monadic action with the adaptor. An example in the IO monad:

test1 :: IO String
test1 = unW$ do
  msg <- W getLine
  W$ putStrLn "Thanks!"
  return msg

From here on the intent was on producing a solution using ATs that hides this explicit wrapping. I don't really know the details of the proposed solution.

Thanks
pepe

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

Reply via email to