[Haskell-cafe] Dynamic typing of polymorphic functions

Alfonso Acosta alfonso.acosta at gmail.com
Wed Dec 19 06:23:52 EST 2007


Hi all,

As some of you might remember I'm working on a EDSL which models
process networks (A process can simply be viewed as a box which has a
number of input and output signals and makes computations over them).

A simple example of the processes implemented is MapSY, which is
similar to Haskell's well-known map function.  It takes a signal and a
processing function as arguments and applies that function the signal.

Following Lava's approach, a specifically designed Signal type hides
and "secretly" forwards the structure of the network. Such structure
is logically an untyped graph. For that reason, the processing
functions associated to the different processes are kept in Dynamic
form.

A very simplified  implementation could be:

------

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


eval :: Proc Dynamic -> Dynamic
-- evaluates the output of a process for one input
eval (MapSY dynF dynIn) = dynApp dynF dynIn


-- 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))


-----

OK, If you managed to read until this point, you might have noticed
that, due to the monomorphism restriction implied by Data.Typeable, it
is impossible to build polymorphic processes.

The approach works nicely for monomorphic processes though:

add1 :: Signal Int -> Signal Int
add1 = mapSY ((+1) :: Int -> Int)

mapSndInt :: Signal (Int, Int) -> Signal Int
mapSndInt = mapSY (snd :: (Int, Int) -> Int)

But it does not work for building polymorphic processes.

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'

Again, due to the monomorphism restriction of the Typeable class, the
compiler's suggestion of adding a Typeable context didn't work. (Well,
strangely enough, adding the "Typeable a" constraint hushed GHC but an
error was instead triggered at runtime).


I must admit I'm totally stuck with this problem. My two options are:

1) Forcing the user to define mapSnd & friends for each combination of
types (which can hardly be considered an acceptable solution)
2) Think of a change in the internal representation of signals which
made polymorphic processes possible. Polymorphic processes don't have
to
    be necessarily definable by the user. They should be happy enough
with a few polymorphic primitives (mapSnd would be one of them).

  * Maybe an implementation of unsafe dynamics using unsafeCoerce
which allowed applying polymorphic functions to monomorphic values for
specific safe cases?


I would really appreciate any suggestions or remarks regarding my
problem/design.

Thanks in advance,

Alfonso Acosta


More information about the Haskell-Cafe mailing list