Dynamic typing of polymorphic functions

Alfonso Acosta wrote:
mapSY :: (Typeable a, Typeable b) => (a -> b) -> Signal a -> Signal b mapSY f (Signal primSig) = Signal (PrimSignal (MapSY (toDyn f) primSig))
The following process would be really useful but its compilation obviously fails:
mapSnd :: Signal (a, a) -> Signal a mapSnd = mapSY snd
Could not deduce (Typeable a) from the context () arising from a use of `mapSY' Possible fix: add (Typeable a) to the context of the type signature for `mapSnd'
It seems the compiler's complaint is reasonable. The signature of the mapSY function says that mapSY may only be applied _provided_ that type variables 'a' and 'b' are instantiated to the types that are members of Typeable. That is, mapSY has a condition on its use. When you write
mapSndInt :: Signal (Int, Int) -> Signal Int mapSndInt = mapSY (snd :: (Int, Int) -> Int)
the condition is satisfied: 'a' and 'b' are instantiated to Int, and Int is a member of Typeable. The definition of mapSnd has no constraint. The compiler is upset: mapSY requires a condition, and mapSnd does not provide any, and there is no obvious way how an obligation Typeable a could have been satisfied otherwise. So, writing
mapSnd :: Typeable a => Signal (a, a) -> Signal a mapSnd = mapSY snd
is the logical thing to do.
Well, strangely enough, adding the "Typeable a" constraint hushed GHC but an error was instead triggered at runtime.
Perhaps the latter is the real problem. If one switches to dynamic typing, the type errors show up as run-time errors. I believe the typing of eval is a bit odd (and also not very useful). The following code seems to work. It also shows how to apply a polymorphic function, pairing, to to signals of any type. Here's a test:
signal3 = cons const0 (cons const0 const1) *Foo> :t signal3 signal3 :: Signal (Int, (Int, Float))
test1 = mapSnd signal3 test1 :: Signal (Int, Float) test12 = beval test1 *Foo> :t test12 test12 :: (Int, Float) *Foo> test12 (0,1.0)
{-# OPTIONS -fglasgow-exts #-} module Foo where import Data.Typeable import Data.Dynamic -- the phantom type parameter makes signal typing consistent newtype Signal a = Signal PrimSignal newtype PrimSignal = PrimSignal (Proc (PrimSignal)) data Proc input = MapSY Dynamic -- The processing function input -- The process input -- the rest of the processes are omitted | Const Dynamic | Cons Dynamic input input eval :: PrimSignal -> Dynamic -- evaluates the output of a process for one input eval (PrimSignal (MapSY dynF dynIn)) = dynApp dynF (eval dynIn) eval (PrimSignal (Cons cns a1 a2)) = dynApp (dynApp cns (eval a1)) (eval a2) eval (PrimSignal (Const inp)) = inp -- better eval beval :: Typeable a => Signal a -> a beval (Signal s) = maybe undefined id (fromDynamic (eval s)) -- sample signals const0 :: Signal Int const0 = Signal (PrimSignal (Const (toDyn (0::Int)))) const1 :: Signal Float const1 = Signal (PrimSignal (Const (toDyn (1::Float)))) -- the map process constructor mapSY :: (Typeable a, Typeable b) => (a -> b) -> Signal a -> Signal b mapSY f (Signal primSig) = Signal (PrimSignal (MapSY (toDyn f) primSig)) add1 :: Signal Int -> Signal Int add1 = mapSY ((+1) :: Int -> Int) mapSndInt :: Signal (Int, Int) -> Signal Int mapSndInt = mapSY (snd :: (Int, Int) -> Int) -- it is important to give the signature to (,) below: we pack the cons -- function of the right type! cons :: forall a b. (Typeable a, Typeable b) => Signal a -> Signal b -> Signal (a,b) cons (Signal sig1) (Signal sig2) = Signal (PrimSignal (Cons (toDyn ((,)::a->b->(a,b))) sig1 sig2)) mapSnd :: (Typeable a, Typeable b) => Signal (b, a) -> Signal a mapSnd = mapSY snd signal3 = cons const0 (cons const0 const1) -- *Foo> :t signal3 -- signal3 :: Signal (Int, (Int, Float)) test1 = mapSnd signal3 -- test1 :: Signal (Int, Float) test11 = let Signal s = test1 in eval s -- *Foo> test11 -- <<(Int,Float)>> -- Too bad. But we can do better. test12 = beval test1 {- *Foo> :t test12 test12 :: (Int, Float) *Foo> test12 (0,1.0) -}

Hi Oleg!
Thanks a lot for your answer, you turn out to end up solving every
problem I get stuck in :)
This bit was the essential part of it.
On Dec 20, 2007 11:47 AM,
-- it is important to give the signature to (,) below: we pack the cons -- function of the right type! cons :: forall a b. (Typeable a, Typeable b) => Signal a -> Signal b -> Signal (a,b) cons (Signal sig1) (Signal sig2) = Signal (PrimSignal (Cons (toDyn ((,)::a->b->(a,b))) sig1 sig2))
mapSnd :: (Typeable a, Typeable b) => Signal (b, a) -> Signal a mapSnd = mapSY snd

Alfonso Acosta wrote:
dynApp allows to apply a Dynamic function to a Dynamic argument:
dynApp :: Dynamic -> Dynamic -> Dynamic
I don't seem to find a way (without modifying Data.Dynamic itself) to code this function
This is not very difficult if we have a well-delineated (and still infinite) type universe: to be precise, if we know the signature of our type terms. That is usually a reasonable assumption. The trick is to build a function that is an inverse of typeOf: given a TypeRep, we wish to find its representative, a value whose type has the given TypeRep. We use the result of this inverse function (to be called reflect) when applying fromDynamic. We know that writing of reflect is possible because we know the syntax of the type language (by assumption) and because Haskell luckily is inconsistent as a logic and so every type is populated. The code below borrows most of the machinery from the type-checker/typed-compiler http://okmij.org/ftp/Haskell/staged/IncopeTypecheck.hs which may be entitled 'How to program hypothetical proofs', as the long title comments explain. The above code essentially implements dynApp, which is called there typecheck_app. We adapt that code below. We assume that our type universe is described by the following syntax data Type = Bool | Int | Type -> Type Regarding the previous problem: the following bit
-- it is important to give the signature to (,) below: we pack the cons -- function of the right type! cons :: forall a b. (Typeable a, Typeable b) => Signal a -> Signal b -> Signal (a,b) cons (Signal sig1) (Signal sig2) = Signal (PrimSignal (Cons (toDyn ((,)::a->b->(a,b))) sig1 sig2))
was indeed essential. One of the main lessons of our APLAS paper was the realization that things become significantly simpler if we do more work at the value production site. We could not have implemented typed Partial Evaluation or typed CPS so simply. The latter usually considered to require significantly complex type systems, beyond the reach of the mainstream languages. Incidentally, that paper promotes a different way of building typed DSL (the final tagless way). http://okmij.org/ftp/papers/tagless-final-APLAS.pdf http://www.cs.rutgers.edu/~ccshan/tagless/talk.pdf http://www.cs.rutgers.edu/~ccshan/quote/language.pdf I was thinking that perhaps that method might be beneficial to your application. I don't know your DSL language well enough to be able to tell though... {-# OPTIONS -fglasgow-exts -W #-} module DA where import Data.Typeable import Data.Dynamic data Dyn = forall a. Typeable a => Dyn a -- Check to see if a term represents a function. If so, -- return terms that witness the type of the argument and of the body reflect_fn :: TypeRep -> Maybe (Dyn, Dyn) reflect_fn tfun | (con,[arg1,arg2]) <- splitTyConApp tfun, con == arrowTyCon = Just (reflect arg1, reflect arg2) reflect_fn _ = Nothing arrowTyCon = typeRepTyCon (typeOf (undefined::Int->Int)) -- reflect typerep to a type (witness). The inverse of typeOf. reflect :: TypeRep -> Dyn reflect x | x == typeOf (undefined::Int) = Dyn (undefined::Int) reflect x | x == typeOf (undefined::Bool) = Dyn (undefined::Bool) reflect x | Just (Dyn e1, Dyn e2) <- reflect_fn x = let mkfun :: a -> b -> (a->b); mkfun = undefined in Dyn (mkfun e1 e2) -- the re-implementation of dynApply mydynApply :: Dynamic -> Dynamic -> Maybe Dynamic mydynApply e1 e2 | let tfun = dynTypeRep e1, let targ = dynTypeRep e2, Just tres <- funResultTy tfun targ, Dyn a <- reflect targ, Dyn b <- reflect tres, Just e1' <- fromDynamic e1, Just e2' <- fromDynamic e2 `asTypeOf` (Just a) = return $ toDyn (e1' e2' `asTypeOf` b) mydynApply e1 e2 = fail $ unwords ["Bad App, of types ",show (dynTypeRep e1),"and", show (dynTypeRep e2)] test1 :: Maybe Bool test1 = mydynApply (toDyn not) (toDyn False) >>= fromDynamic -- Just True test2 :: Maybe Bool test2 = mydynApply (toDyn not) (toDyn (1::Int)) >>= fromDynamic -- Nothing test3 :: Maybe Int test3 = mydynApply (toDyn ((+)::Int->Int->Int)) (toDyn (1::Int)) >>= (\f -> mydynApply f (toDyn (2::Int))) >>= fromDynamic -- Just 3
participants (2)
-
Alfonso Acosta
-
oleg@okmij.org