[Haskell-cafe] Type-level lambdas in Haskell? ( was Multiparameter class error)

oleg at pobox.com oleg at pobox.com
Wed Feb 21 23:00:56 EST 2007


Alfonso Acosta wrote:

> class Synchronous s f1 f2 |  s -> f1, s -> f2  where
>  mapSY          :: f1 a b -> s a -> s b
>  delaySY        :: a  -> s a -> s a
>  zipWithSY     :: f2 a b c-> s a -> s b -> s c
>
> The goal of this class is to extend the name of the following
> functions (which BTW are already present in a working library and for
> that reason _it is a must_ that their types remain untouched) ...
>
> mapSY  :: (a->b) -> Signal a -> Signal b
> delaySY :: a -> Signal a -> Signal b -> Signal c
> zipWithSY :: (a->b->c) -> Signal a -> Signal b -> Signal c
>
> .. accepting these definitions as well
>
> mapSY :: (HDPrimType a, HDPrimType b) => 
>    HDFun (a->b) -> HDSignal a -> HDSignal b 
> delaySY :: HDPrimType a => a -> HDSignal a -> HDSignal a
> zipWithSY :: (HDPrimType a, HDPrimType b, HDPrimType c) => HDFun
> (a->b->c) -> HDSignal a -> HDSignal b -> HDSignal c


First of all, the design already exhibits the problem: 
	delaySY :: HDPrimType a => a -> HDSignal a -> HDSignal a
cannot be made _at all_ the member of an instantiated Synchronous
class. The reason is that in the class definition 

> class Synchronous s f1 f2 |  s -> f1, s -> f2  where
>  delaySY        :: a  -> s a -> s a

the function delaySY is declared *fully* polymorphic over 'a' -- there
are no constraints on a and no restrictions. However,

> delaySY :: HDPrimType a => a -> HDSignal a -> HDSignal a

shows that 'a' is constrained to satisfy the HDPrimType a. 
That's the problem: the latter function is not generic enough. 
The problem is described (and solved) in a message `Restricted
Datatypes Now'
  http://www.haskell.org/pipermail/haskell-prime/2006-February/000498.html

I'm not certain if there is a compelling reason to place mapSY,
delaySY and zipWithSY in the same class. If not, the following is the
solution to the problem. Both sets of mapSY, delaySY and zipWithSY are
unified in overloaded functions:

{-# OPTIONS -fglasgow-exts -fallow-undecidable-instances #-}

module SY where

class SynchronousM arg1 s a b | s a b -> arg1 where
 mapSY          :: arg1 -> s a -> s b

class SynchronousD s a where
 delaySY        :: a  -> s a -> s a

class SynchronousZ arg1 s a b c | s a b c -> arg1  where
 zipWithSY     :: arg1 -> s a -> s b -> s c


-- stubs
newtype Signal a = Signal a
newtype HDSignal a = HDSignal a
newtype HDFun a = HDFun a

class HDPrimType a where 
    cnv :: a -> a; cnv = id
           
instance HDPrimType Int  
instance HDPrimType Bool

-- (not so) Grand Unification

instance SynchronousM (a->b) Signal a b where
 mapSY f (Signal x) = Signal (f x)

instance (HDPrimType a, HDPrimType b)
    => SynchronousM (HDFun (a->b)) HDSignal a b where
 mapSY  (HDFun f) (HDSignal x) = HDSignal (cnv . f . cnv $ x)


instance SynchronousD Signal a where
 delaySY _ = id

instance HDPrimType a => SynchronousD HDSignal a where
 delaySY _ (HDSignal x) = HDSignal (cnv x)


instance SynchronousZ (a->b->c) Signal a b c  where
 zipWithSY f (Signal x) (Signal y) = Signal (f x y)

instance (HDPrimType a, HDPrimType b, HDPrimType c) =>
    SynchronousZ (HDFun (a->b->c)) HDSignal a b c  where
 zipWithSY (HDFun f) (HDSignal x) (HDSignal y) = 
     HDSignal (cnv (f (cnv x) (cnv y)))


More information about the Haskell-Cafe mailing list