[Haskell-cafe] Data.Dynamic over the wire

2008-05-13 Thread Jules Bean

 {-# 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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Data.Dynamic over the wire

2008-05-13 Thread Bulat Ziganshin
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,
 Bulatmailto:[EMAIL PROTECTED]

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Data.Dynamic over the wire

2008-05-13 Thread Alfonso Acosta
On Tue, May 13, 2008 at 7:39 PM, Jules Bean [EMAIL PROTECTED] wrote:
  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.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Data.Dynamic over the wire

2008-05-13 Thread John Meacham
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⑈
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe