RE: Reflection API for Haskell.

I'm all for this. But I think the design needs a bit of work. Firstly, remember that TypeReps at the moment are designed for *ground types*, that is types with no free type variables. A ground type always starts with a type constructor. So one can start with typeOf to get a TyCon. The TyCon might not be an algebraic data type; that's why the DataType type in Data.Generics.Basics has a DataRep thing. You could add that. (You'd want to add FunRep.) I think you could probably get rid of dataTypeOf entirely, incidentally. When it comes to the types of data constructors, they have *quantified* types, so you need a way to bind the type variables. I don't see that in your design. [This relates to another missing feature of the current design which is that it can't represent higher rank types, e..g typeOf f where f :: (forall a. a->a) -> Int But allowing this would required not only a higher-rank TypeRep, but having instances of Typeable at for-all types, which is an entirely un-explored area. Let's leave that aside.] So for data constructors you have type variables in their types, and I think you' have to represent that explicitly, which would in turn mean that a TypeRep is not simply an application of a TyCon. (I'm not keen on "tycoon tyvars", which I guess is your fix. The water seems deeper here. Are you sure you could not get away without representations of the constructor argument types? After all, SYB has already shown how to write serialisers and deserialisers. Simon | -----Original Message----- | From: libraries-bounces@haskell.org [mailto:libraries-bounces@haskell.org] On Behalf Of Krasimir | Angelov | Sent: 30 March 2006 12:30 | To: Haskell Libraries | Subject: Reflection API for Haskell. | | 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 | _______________________________________________ | Libraries mailing list | Libraries@haskell.org | http://www.haskell.org/mailman/listinfo/libraries

Sure. The proposal isn't final. I already have found that it needs
extra work. As you said it will require representation for 'forall'.
The 'tyConArity' function is totally wrong, instead we will need
'tyConKind' function which have to return the complete type kind.
Another difficulty is that the following declarations:
data T1 = mkT1
data T2 = mkT2 T1 deriving Typeable
are correct with the existing Typeable but with the proposed
extensions we will need Typeable instance for T1 too. This is because
in order to represent the type of mkT2 :: T1 -> T2 we need the TypeRep
of T1 and hence we need Typeable T1. This will make the proposal
backward incompatible. Instead we can leave the DataCon representation
in the Data class but with some revisions.
2006/4/3, Simon Peyton-Jones
The water seems deeper here. Are you sure you could not get away without representations of the constructor argument types? After all, SYB has already shown how to write serialisers and deserialisers.
It isn't enough because I would like to be able to serialize/deserialize some Haskell values to BerkleyDB. The existing API is enough for that but the troubles come when I have to change the representation of any type. I would like to compare the current type representation with those stored in the database. In addition I would like to have generic tool that will be able read\write data from the database without need to have the same data types defined. This is necessary if you want to have an easy way to translate your exising data to the new representation. Cheers, Krasimir

After all,
SYB has already shown how to write serialisers and deserialisers.
It isn't enough because I would like to be able to serialize/deserialize some Haskell values to BerkleyDB. The existing API is enough for that but the troubles come when I have to change the representation of any type. I would like to compare the current type representation with those stored in the database. In addition I would like to have generic tool that will be able read\write data from the database without need to have the same data types defined. This is necessary if you want to have an easy way to translate your exising data to the new representation.
Cheers, Krasimir
A consistent reflection module is necessary. Reflection must be a module of Haskell not a kind of hack that works for certain types of data and in certain cases because, if we have reflection as a module, people will more easily port many ideas that come form other languages such are frameworks for industrial programming. I definitively support the need of reflection as a distinct feature in Haskell.
participants (3)
-
Alberto Gómez Corona
-
Krasimir Angelov
-
Simon Peyton-Jones