lifting functions to tuples?

oleg at pobox.com oleg at pobox.com
Wed Nov 19 17:25:19 EST 2003


The problem:

liftTup f (a, b) = (f a, f b)

of the signature
	liftTup:: ?? -> (a,b) -> (c,d)

Again, it is possible to write this in Haskell with common extensions

> {-# OPTIONS -fglasgow-exts #-}

> import Data.Dynamic
> import Data.Maybe

> liftp f (a,b) = ((fromJust . fromDynamic . f . toDyn) a,
>                  (fromJust . fromDynamic . f . toDyn) b)                

*Main> :t liftp
forall a2 a a3 a1.
(Typeable a, Typeable a1, Typeable a2, Typeable a3) =>
(Dynamic -> Dynamic) -> (a1, a3) -> (a, a2)


> f1 x | isJust (fromDynamic x::(Maybe Int)) 
>     = let y = fromJust $ fromDynamic x in toDyn $ (toEnum (y + 1)::Char)
> f1 x | isJust (fromDynamic x::(Maybe Float))
>     = let y::Float = fromJust $ fromDynamic x in toDyn $ (round(y + 1)::Int)
> f1 x = x

*Main> liftp f1 (65::Int,1.0::Float) :: (Char,Int)
('B',2)

> f2 x | isJust (fromDynamic x::(Maybe Bool)) 
>     = let y = fromJust $ fromDynamic x 
>       in toDyn $ ((toEnum (if y then 42 else 65))::Char)
> f2 x | isJust (fromDynamic x::(Maybe ()))
>     = let () = fromJust $ fromDynamic x in toDyn $ (2.5::Float)
> f2 x = x

*Main> liftp f2 (True,()) :: (Char,Float)
('*',2.5)
*Main> liftp f2 (False,()) :: (Char,Float)
('A',2.5)
*Main> liftp f2 (False,1::Int) :: (Char,Int)
('A',1)

As has been discussed on this list on many occasions, Dynamic (and the
accompanied safe coerce) can be implemented in Haskell98 plus
existentials and multi-parameter classes with functional dependencies.

As a matter of fact, translating (a,b) into (c,d) doesn' seem to be
much different than the generic mapping. I think Strafunsky can
express such a transformation trivially. Right?



More information about the Haskell mailing list