
{-# LANGUAGE ScopedTypeVariables #-}
Data.Dynamic gives a passable impression of adding support for dynamically typed code and runtime typing to GHC, without changing the basic statically typed, all types known at runtime nature of the language. Note that Data.Dynamic relies upon two things: it relies upon a concrete representation of types, given by TypeRep, and a primitive which has to be provided by the compiler to actually implement fromDynamic. (In GHC it uses unsafeCoerce# which is already available, but you could imagine providing other primitives). In principle TypeReps could be derived by hand, although if you do so you can break everything by providing invalid instances. In practice we'd rather the compiler did it for us and guaranteed safety. You can do all sorts of things with Dynamic, but the general pattern is that data which has some fixed, known type, can be passed through a chunk of code which doesn't know its type (wrapped in Dynamic) and then eventually consumed by another piece of code which *does* know the type, and can unwrap it. The consuming code has to know the type to unwrap it, although it can 'guess' various alternatives if it wants, and thus type safety is preserved. One thing which you can't obviously do is write Read or Show instances for Dynamic. So can we pass Dynamic data over the wire? If not, Dynamic is limited to the context of "within a single program", and can't be used over the network between cooperating programs, or in file formats, etc. You can try this:
import Data.Typeable
data SerialisedDynamic = SD TypeRep String deriving (Show)
freeze :: (Show a, Typeable a) => a -> SerialisedDynamic freeze x = SD (typeOf x) (show x)
thaw :: forall a . (Read a, Typeable a) => SerialisedDynamic -> Maybe a thaw (SD t s) = if typeOf (undefined :: a) == t then Just (read s) else Nothing
This is close, and works as far as it goes. It is a limited reimplementation of Dynamic which uses show/read instead of unsafeCoerce#. As such it is pure haskell (but relies on Typeable instances). 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 think of any reason why there can't be a Read instance for TypeRep, but it would be a bit tricky with the current TypeRep because of the way its implemented, I think. You need to take care about globally qualified types and might want to use package names like ghc does in its linking phase, but those are definitely surmountable problems. Having said all that, I'm not sure how useful this really is. Most of the time you could use this, you could equally just pass around the String and 'read' it once you get to the place where you want to use the value. Practical over-the-wire protocols necessarily have some kind of tagging mechanism, and all this adds is a global "tag table" for Typeable types via TypeRep. Jules

Hello Jules, Tuesday, May 13, 2008, 9:39:12 PM, you wrote:
This is close, and works as far as it goes. It is a limited reimplementation of Dynamic which uses show/read instead of
there are gread/gshow funcs. don't know how these works, though :) -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

On Tue, May 13, 2008 at 7:39 PM, Jules Bean
One thing which you can't obviously do is write Read or Show instances for Dynamic. So can we pass Dynamic data over the wire? If not, Dynamic is limited to the context of "within a single program", and can't be used over the network between cooperating programs, or in file formats, etc.
I've never used hs-plugins, but if I recall properly, it includes its own implementation of TypeRep (and consequently Dynamic) in order to overcome the serialization problem you have mentioned.

I use a trick like this to allow saving of dynamics into ho files for jhc, the same thing will work for network connections. see Info.Info for the data type, and Info.Binary for the binary serialization routines. http://repetae.net/dw/darcsweb.cgi?r=jhc;a=tree;f=/Info John -- John Meacham - ⑆repetae.net⑆john⑈

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@stillpsycho.net http://www.stillpsycho.net ... Real programs don't eat cache.
participants (5)
-
Alfonso Acosta
-
Bulat Ziganshin
-
Gökhan San
-
John Meacham
-
Jules Bean