[Haskell-cafe] Data.Dynamic over the wire

Gökhan San gsan at stillpsycho.net
Wed May 14 17:23:39 EDT 2008


Hi,

> {-# LANGUAGE ExistentialQuantification, ScopedTypeVariables #-}

Following the related discussion on #haskell, I ended up writing the below
code (thanks to the suggestions). This is for a genetic programming 
library, but the usage would be similar. It also (de)serializes
TypeRep.

I'm a haskell newbie, so feel free to report any awkwardness. :-)

> module Main (main) where

> import Data.Typeable

Dyn holds either the data or the serialized version of it.
This is for performance reasons. Local functions will return 'D x' 
values, deserializing any 'S t s' they encounter in the process. 
When Dyn is shown and read (transmitted?), it becomes a string again.

Function names can be stored in the string version, and a lookup table
could be used to map to actual functions.

> data Dyn = forall a. (Typeable a, Show a) => D a | S TypeRep String

> dynTypeRep         :: Dyn -> TypeRep
> dynTypeRep (D x)   = typeOf x
> dynTypeRep (S t _) = t

> fromDyn         :: forall a. (Typeable a, Read a) => Dyn -> Maybe a
> fromDyn (D x)   = cast x
> fromDyn (S t s) = if typeOf (undefined :: a) == t 
>                   then Just (read s)
>                   else Nothing

The above version would be more useful, but 'S t s' can't be cast
into a type other than the one represented by t. (We don't need this
anyway.)

> fromDyn'         :: (Typeable a, Read a) => Dyn -> a
> fromDyn' (D x)   = case xa of Nothing -> error "Typecast failed!"
>                               Just a  -> a
>     where xa = cast x
> fromDyn' (S t s) = read s

Rep is the intermediate type used while (de)serializing Typeable. I couldn't
think of a way for reading TypeRep with the current implementation of show.

> newtype Rep = R (String, [Rep]) deriving (Read, Show)

> toRep   :: TypeRep -> Rep
> toRep t = R (show con, map toRep args)
>           where (con, args) = splitTyConApp t

> fromRep                 :: Rep -> TypeRep
> fromRep (R (con, args)) = mkTyConApp (mkTyCon con) $ map fromRep args

> instance Show Dyn where
>     show (D x)   = show (toRep (typeOf x), show x)
>     show (S t s) = show (toRep t, s)

> instance Read Dyn where
>     readsPrec d                    = (map toS) . rP
>         where toS ((rep, str), s') = (S (fromRep rep) str, s')
>               rP                   = (readsPrec d) :: ReadS (Rep, String)

Below are some examples. I'm looking for a practical way to define functions
that work over several types more easily. The functionality should be like
type classes for runtime.

> add5 :: Dyn -> Dyn
> add5 dx | dynTypeRep dx == typeOf (undefined :: Int) =
>             D (fromDyn' dx + 5 :: Int)
>         | dynTypeRep dx == typeOf (undefined :: Double) =
>             D (fromDyn' dx + 5 :: Double)

> main :: IO ()
> main = do 
>   let dd = D ([(1 :: Int, "test")])
>       ds = (read $ show dd) :: Dyn
>       di = D (2 :: Int)
>       df = D (2 :: Double)
>       daf = add5 df
>       dai = add5 di
>   print dd
>   print ds -- Should be identical
>   print (daf, dynTypeRep daf) -- 7.0
>   print (dai, dynTypeRep dai) -- 7


On Tuesday May 13 2008, Jules Bean wrote:
> You can't finish it off because you can't derive a 'Read' instance for
> SD, because there is no read instance for TypeRep. Off-hand I can't

-- 

Gokhan San
gsan at stillpsycho.net
http://www.stillpsycho.net

... Real programs don't eat cache.
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 189 bytes
Desc: This is a digitally signed message part.
Url : http://www.haskell.org/pipermail/haskell-cafe/attachments/20080514/3a7133b4/attachment.bin


More information about the Haskell-Cafe mailing list