[Haskell-cafe] Reading open data types

Benja Fallenstein benja.fallenstein at gmail.com
Wed Jun 13 10:12:25 EDT 2007


Hi all,

We've had a discussion on #haskell about how we can make a function
that reads in serialized values of an open data type, such as

class (Show a, Read a) => MyClass a where
    typeTag :: a -> String
    ... operations on the open data type...

data Obj = forall a. MyClass a => Obj { unObj :: a }

We would like to write a function like,

oread :: String -> Obj

The problem here is that unlike with 'read,' the calling context of
'oread' does not fix the implementation of Read that we want to use.
The best we've been able to come up with was to build a table that
maps type names to types:

type TypeTable = Map String Obj

oread :: TypeTable -> String -> Obj
oread types s = Obj $ read repr `asTypeOf` unObj (types ! tag) where
    tag = takeWhile (/= ' ') s
    repr = drop 1 $ dropWhile (/= ' ') s

instance Show Obj where
    show (Obj x) = typeTag x ++ " " ++ show x

As far as we can see, we'll have to create this table manually,
without support from the compiler. My suggestion would be to put the
code constructing the table for each module at the top of that module,
to keep it together with the exports and imports, like this:

module Foo.Foo (export1, export2, fooFooTypes) where

import Foo.Bar
import Foo.Baz
import Data.Map

fooFooTypes = fooBarTypes `union` fooBazTypes `union` fromList
    [ ("Foo.Foo.Ty1", Obj (undefined :: Ty1))
    , ("Foo.Foo.Ty2", Obj (undefined :: Ty2)) ]

However, this is still kind of boring. Is there a better way? If not,
would it be a good idea to have compiler support for building this
kind of type table?

Thanks,
- Benja


More information about the Haskell-Cafe mailing list