Instancing "Typeable" for monad transformers?

Is there any reasonable way to do this if I want to cast a monadic value? For example:
castState :: (Typeable a, Typeable s, Typeable1 m, Typeable b) => a -> Maybe (StateT s m b) castState = Data.Typeable.cast
None of the common monad transformers declare instances of Typeable, so I don't know if the concept itself even works. The use case here is one of my library users wants to return an Iteratee from code running in "hint", which requires any extracted values be typeable. My first attempt at an extension-free instance is something like this:
import Data.Enumerator import Data.Typeable
instance (Typeable a, Typeable1 m) => Typeable1 (Iteratee a m) where typeOf1 i = rep where typed :: (a -> b) -> b -> a -> a typed _ _ a = a
ia :: a -> Iteratee a m b ia = undefined
im :: m c -> Iteratee a m b im = undefined
rep = mkTyConApp (mkTyCon "Data.Enumerator.Iteratee") [tyA, tyM] tyA = typeOf (typed ia i undefined) tyM = typeOf1 (typed im i undefined)
which, besides being ugly, I have no idea if it's correct.

On Tue, Feb 1, 2011 at 10:02 PM, John Millikin
Is there any reasonable way to do this if I want to cast a monadic value? For example:
castState :: (Typeable a, Typeable s, Typeable1 m, Typeable b) => a -> Maybe (StateT s m b) castState = Data.Typeable.cast
None of the common monad transformers declare instances of Typeable, so I don't know if the concept itself even works.
The use case here is one of my library users wants to return an Iteratee from code running in "hint", which requires any extracted values be typeable. My first attempt at an extension-free instance is something like this:
I don't know if this helps in your case, but I get around this by having the actual interpreted type be 'State1 -> State2 -> Result', where the States are the arguments to run the monad stack, and Result is what happens when you run it. Then I mangle the input from the user (which should be 'MyMonad val') by wrapping a 'run' function around it so now it has the non-monadic type. Then I just run the function 'interpret' returns as a sub-monad: pull my state, pass it to run, and re-inject the state it returns or rethrow any exceptions it returns. Should work, as long as you can do the 'sub-run' thing (is there an official name for that?), it's certainly possibly with all the "standard" monads but I don't know about iteratee.

I would happily supply a patch to add the Typeable (and the few Data
instances that can be made) to transformers. I had to make similar ones in
my comonad-transformers package anyways.
-Edward Kmett
On Wed, Feb 2, 2011 at 1:02 AM, John Millikin
Is there any reasonable way to do this if I want to cast a monadic value? For example:
castState :: (Typeable a, Typeable s, Typeable1 m, Typeable b) => a -> Maybe (StateT s m b) castState = Data.Typeable.cast
None of the common monad transformers declare instances of Typeable, so I don't know if the concept itself even works.
The use case here is one of my library users wants to return an Iteratee from code running in "hint", which requires any extracted values be typeable. My first attempt at an extension-free instance is something like this:
import Data.Enumerator import Data.Typeable
instance (Typeable a, Typeable1 m) => Typeable1 (Iteratee a m) where typeOf1 i = rep where typed :: (a -> b) -> b -> a -> a typed _ _ a = a
ia :: a -> Iteratee a m b ia = undefined
im :: m c -> Iteratee a m b im = undefined
rep = mkTyConApp (mkTyCon "Data.Enumerator.Iteratee") [tyA, tyM] tyA = typeOf (typed ia i undefined) tyM = typeOf1 (typed im i undefined)
which, besides being ugly, I have no idea if it's correct.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Can you just wrap it? Something like this:
-- put your monad type here
type M a = Iteratee ... a
data W a = W (Iteratee ... a) deriving Typeable
unW (W x) = x
toDynW :: Typeable a => M a -> Dynamic
toDynW x = toDynamic (W x)
castM :: (Typeable x, Typeable a) => x -> Maybe (M a)
castM = unW . cast
-- ryan
On Tue, Feb 1, 2011 at 10:02 PM, John Millikin
Is there any reasonable way to do this if I want to cast a monadic value? For example:
castState :: (Typeable a, Typeable s, Typeable1 m, Typeable b) => a -> Maybe (StateT s m b) castState = Data.Typeable.cast
None of the common monad transformers declare instances of Typeable, so I don't know if the concept itself even works.
The use case here is one of my library users wants to return an Iteratee from code running in "hint", which requires any extracted values be typeable. My first attempt at an extension-free instance is something like this:
import Data.Enumerator import Data.Typeable
instance (Typeable a, Typeable1 m) => Typeable1 (Iteratee a m) where typeOf1 i = rep where typed :: (a -> b) -> b -> a -> a typed _ _ a = a
ia :: a -> Iteratee a m b ia = undefined
im :: m c -> Iteratee a m b im = undefined
rep = mkTyConApp (mkTyCon "Data.Enumerator.Iteratee") [tyA, tyM] tyA = typeOf (typed ia i undefined) tyM = typeOf1 (typed im i undefined)
which, besides being ugly, I have no idea if it's correct.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (4)
-
Edward Kmett
-
Evan Laforge
-
John Millikin
-
Ryan Ingram