Reflection API for Haskell.

Krasimir Angelov kr.angelov at gmail.com
Thu Mar 30 06:30:23 EST 2006


Hello Guys,

I am interested in having better Reflection API for Haskell. Currently
we have Typeable and Data classes which provide some pieces of
information about the data types at runtime. The (typeOf :: Typeable a
=> a -> TypeRep) method provides runtime information about the type of
a given variable. The (dataTypeOf :: Data a => a -> DataType) provides
almost the same information but with some extras. There is some
overlap between the TypeRep and DataType types. Some pieces of
information you can get from the TypeRep, other from the DataType and
some other from both of them. There is also an information which is
inaccessible from either TypeRep and DataType. Here is a list of the
differences:

- TypeRep contains both the TyCon and the arguments given to it.
DataType contains only the name of the TyCon. The TyCon name is
duplicated in TypeRep and in DataType.
- DataType contains the DataRep structure which gives us an
information about the available data structures. This is the only way
to access them.
- The Constr type represents data constructors at runtime. It has
information about the constructor name, the record selectors and the
fixity (prefix/infix). Unfortunately there isn't any information about
the types of its arguments.

What I would like to see is a better Reflection API with clear
interface. My proposal is:

-- * Type representations
TypeRep -- abstract, instance of: Eq, Show, Typeable
TyCon -- abstract, instance of: Eq, Show, Typeable
DataCon   -- abstract, instance of: Eq, Show, Typeable

-- * Construction of type representations
mkTyCon       :: String  -> Arity -> [DataCon] -> Fixity -> TyCon
mkTyConVar  :: Int -> Arity -> TyCon
mkTyVar      :: Int -> TypeRep
mkTyConApp :: TyCon   -> [TypeRep] -> TypeRep
mkDataCon   :: String -> [TypeRep] -> TypeRep -> [String] -> Fixity -> DataCon

-- * Fixity representation
Fixity(..)        -- instance of: Eq, Show, Typeable
defaultFixity  :: Fixity

-- * Observation of type representations
typeRepTyCon :: TypeRep -> TyCon
typeRepArgs    :: TypeRep -> [TypeRep]

-- * Observation of type constructors
tyConString       :: TyCon   -> String
tyConArity         :: TyCon   -> Int
tyConDataCons  :: TypeCon -> [DataCon]
tyConFixity        :: TyCon   -> Fixity

-- * Observation of data constructors
dataConString  :: DataCon -> String
dataConArgs    :: DataCon -> [TypeRep]
dataConResult :: DataCon -> TypeRep
dataConFields :: DataCon -> [String]
dataConFixity  :: DataCon -> Fixity

The above API is just a reorganization of the existing API but with
some extensions:

- In the existing API there is no way to get the TyCon fixity and
arity. In the new one there are the tyConFixity and tyConArity
functions.
- The data constructors are available from the tyConDataCons function.
There isn't need for the separated DataType and DataRep types.
- The DataCon arguments and the result type are available from the
dataConArgs and dataConResult functions.
- Since the type can be polymorphic we need to have representation for
type variables. For that reason there are the mkTyVar and mkTyConVar
functions.

The new API can be used for both the Dynamic data type implementation
and for the generic programming API. The additional information can be
used for many kinds of serialization libraries where you would like to
be sure that you are deserialising data with the same structure as
those used in your program. In addition if you have stored the data
type meta information you can have many kinds of generic tools that
can read/write the data without need to have the same types defined in
the application.

What do you think about this kind of generalization of the existing
API in the standard package?

Cheers,
  Krasimir


More information about the Libraries mailing list