Reflective capabilities of Haskell (cont'd)

I am trying to port a programme written in Maude, which is a reflective language based on rewriting logic ( http://maude.cs.uiuc.edu/ ), to Haskell. I thought using Template Haskell might be a good idea, but I got stuck and now I am wondering if this is really possible in Haskell. Let me give an example of a Maude module defining the function last over a list of Peano numbers. fmod LAST is sorts Peano PeanoList . op 0 : -> Peano [ctor] . op s : Peano -> Peano [ctor] . op [] : -> PeanoList [ctor] . op cons : Peano PeanoList -> PeanoList [ctor] . op last : PeanoList -> Peano . vars X Y : Peano . var Xs : PeanoList . eq last(cons(X,[])) = X . eq last(cons(X,cons(Y,Xs))) = last(cons(Y,Xs)) . endfm So, last(cons(s(0),cons(s(s(0)),cons(s(s(s(0))),[])))) would reduce to s(s(s(0))). The cool thing about Maude is, that terms, modules, ... can be lifted to the meta level. For example: upModule('LAST, false) would yield fmod 'LAST is including 'BOOL . sorts 'Peano ; 'PeanoList . none op '0 : nil -> 'Peano [ctor] . op '`[`] : nil -> 'PeanoList [ctor] . op 'cons : 'Peano 'PeanoList -> 'PeanoList [ctor] . op 'last : 'PeanoList -> 'Peano [none] . op 's : 'Peano -> 'Peano [ctor] . none eq 'last['cons['X:Peano,'`[`].PeanoList]] = 'X:Peano [none] . eq 'last['cons['X:Peano,'cons['Y:Peano,'Xs:PeanoList]]] = last['cons[ 'Y:Peano,'Xs:PeanoList]] [none] . endfm I also have access, e.g. to the defined type constructors. So upOpDecls('LAST,false). yields op '0 : nil -> 'Peano [ctor] . op '`[`] : nil -> 'PeanoList [ctor] . op 'cons : 'Peano 'PeanoList -> 'PeanoList [ctor] . op 'last : 'PeanoList -> 'Peano [none] . op 's : 'Peano -> 'Peano [ctor] . Given an arbitrary function, I have access to its definition, its types and the type constructors, all as ADTs. Is this possible with Template Haskell, or in some other way? Thanks a lot, Martin

Hello,
Data.Typeable gives you most of what you want except for access to
function bodies.
-Jeff
On Tue, Mar 11, 2008 at 6:17 AM, Martin Hofmann
I am trying to port a programme written in Maude, which is a reflective language based on rewriting logic ( http://maude.cs.uiuc.edu/ ), to Haskell. I thought using Template Haskell might be a good idea, but I got stuck and now I am wondering if this is really possible in Haskell. Let me give an example of a Maude module defining the function last over a list of Peano numbers.
fmod LAST is sorts Peano PeanoList .
op 0 : -> Peano [ctor] . op s : Peano -> Peano [ctor] .
op [] : -> PeanoList [ctor] . op cons : Peano PeanoList -> PeanoList [ctor] .
op last : PeanoList -> Peano .
vars X Y : Peano . var Xs : PeanoList .
eq last(cons(X,[])) = X . eq last(cons(X,cons(Y,Xs))) = last(cons(Y,Xs)) .
endfm
So, last(cons(s(0),cons(s(s(0)),cons(s(s(s(0))),[])))) would reduce to s(s(s(0))). The cool thing about Maude is, that terms, modules, ... can be lifted to the meta level. For example:
upModule('LAST, false)
would yield
fmod 'LAST is including 'BOOL . sorts 'Peano ; 'PeanoList . none op '0 : nil -> 'Peano [ctor] . op '`[`] : nil -> 'PeanoList [ctor] . op 'cons : 'Peano 'PeanoList -> 'PeanoList [ctor] . op 'last : 'PeanoList -> 'Peano [none] . op 's : 'Peano -> 'Peano [ctor] . none eq 'last['cons['X:Peano,'`[`].PeanoList]] = 'X:Peano [none] . eq 'last['cons['X:Peano,'cons['Y:Peano,'Xs:PeanoList]]] = last['cons[ 'Y:Peano,'Xs:PeanoList]] [none] . endfm
I also have access, e.g. to the defined type constructors.
So upOpDecls('LAST,false).
yields
op '0 : nil -> 'Peano [ctor] . op '`[`] : nil -> 'PeanoList [ctor] . op 'cons : 'Peano 'PeanoList -> 'PeanoList [ctor] . op 'last : 'PeanoList -> 'Peano [none] . op 's : 'Peano -> 'Peano [ctor] .
Given an arbitrary function, I have access to its definition, its types and the type constructors, all as ADTs.
Is this possible with Template Haskell, or in some other way?
Thanks a lot,
Martin
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Data.Typeable gives you most of what you want except for access to function bodies.
Thanks a lot, this helps a bit, but access to function bodies is exactly what I need. Or being more precise, I need the functionality of ghci's command ':t'. So functions that behave as follows, where everything is of course meta-represented in some way as ADT: Prelude Data.Typeable> typeOf (\a -> (Just (a:""))) (\a -> (Just (a:""))) :: Char -> Maybe [Char] Prelude Data.Typeable> getDomain $ typeOf (\a -> (Just (a:""))) [Char] Prelude Data.Typeable>getCodomain $ typeOf (\a -> (Just (a:""))) (Maybe [Char]) Prelude Data.Typeable>getTypeConstructors (Maybe [Char]) [ (Just) :: [Char] -> Maybe [Char] , (Nothing) :: Maybe [Char] ] Prelude Data.Typeable>getTypeConstructors [Char] [ (:) :: Char -> [Char] -> [Char] , ([]) :: [Char] ] I am much obliged for any kind of hint. Cheers, Martin

Hello,
Thanks a lot, this helps a bit, but access to function bodies is exactly what I need. Or being more precise, I need the functionality of ghci's command ':t'. So functions that behave as follows, where everything is of course meta-represented in some way as ADT:
Prelude Data.Typeable> typeOf (\a -> (Just (a:""))) (\a -> (Just (a:""))) :: Char -> Maybe [Char]
Prelude Data.Typeable> getDomain $ typeOf (\a -> (Just (a:""))) [Char]
Prelude Data.Typeable>getCodomain $ typeOf (\a -> (Just (a:""))) (Maybe [Char])
Data.Typeable should allow for all of the previous.
Prelude Data.Typeable>getTypeConstructors (Maybe [Char]) [ (Just) :: [Char] -> Maybe [Char] , (Nothing) :: Maybe [Char] ]
Prelude Data.Typeable>getTypeConstructors [Char] [ (:) :: Char -> [Char] -> [Char] , ([]) :: [Char] ]
Data.Generics allows you to do this (to a certain extent), i.e. there is a function dataTypeConstrs :: DataType -> [Constr] -Jeff --- This e-mail may contain confidential and/or privileged information. If you are not the intended recipient (or have received this e-mail in error) please notify the sender immediately and destroy this e-mail. Any unauthorized copying, disclosure or distribution of the material in this e-mail is strictly forbidden.

Hello,
Prelude Data.Typeable> typeOf (\a -> (Just (a:""))) (\a -> (Just (a:""))) :: Char -> Maybe [Char]
Prelude Data.Typeable> getDomain $ typeOf (\a -> (Just (a:""))) [Char]
Prelude Data.Typeable>getCodomain $ typeOf (\a -> (Just (a:""))) (Maybe [Char])
Data.Typeable should allow for all of the previous.
Prelude Data.Typeable>getTypeConstructors (Maybe [Char]) [ (Just) :: [Char] -> Maybe [Char] , (Nothing) :: Maybe [Char] ]
Prelude Data.Typeable>getTypeConstructors [Char] [ (:) :: Char -> [Char] -> [Char] , ([]) :: [Char] ]
Data.Generics allows you to do this (to a certain extent), i.e. there is a function
dataTypeConstrs :: DataType -> [Constr]
It might be hard, or even impossible, to get Data.Typeable and Data.Generics to play with each other. There seems to be no good way of converting a Data.Typeable.TypeRep to a Data.Generics.Basics.DataType. Another option might be to use Language.Haskell.Parser and Language.Haskell.Syntax, but I have little experience with this and am not sure if you'll be able to do what you want. -Jeff --- This e-mail may contain confidential and/or privileged information. If you are not the intended recipient (or have received this e-mail in error) please notify the sender immediately and destroy this e-mail. Any unauthorized copying, disclosure or distribution of the material in this e-mail is strictly forbidden.

On Wed, 2008-03-12 at 15:59 -0400, Jeff Polakow wrote:
Data.Generics allows you to do this (to a certain extent), i.e. there is a function
dataTypeConstrs :: DataType -> [Constr]
It might be hard, or even impossible, to get Data.Typeable and Data.Generics to play with each other. There seems to be no good way of converting a Data.Typeable.TypeRep to a Data.Generics.Basics.DataType.
Another option might be to use Language.Haskell.Parser and Language.Haskell.Syntax, but I have little experience with this and am not sure if you'll be able to do what you want.
On Wed, 2008-03-12 at 23:08 -0700, oleg@okmij.org wrote:
Thanks a lot, this helps a bit, but access to function bodies is exactly what I need Then perhaps you might like the method of reconstructing bodies (of possibly compiled) functions http://okmij.org/ftp/Computation/Generative.html#diff-th in the form of AST -- the template Haskell AST. The reconstructed bodies of functions can be arbitrarily manipulated (e.g., _symbolically_ differentiated or algebraically simplified) and then converted `back' to the compiled code.
Thanks for the hints, they all seem to be promising, at least for some part of my problem. I'll try it out whether I can put them together. Cheers, Martin
participants (3)
-
jeff p
-
Jeff Polakow
-
Martin Hofmann