[Template-haskell] How to extract name and type of exported
functions in modules
Oscar Finnsson
oscar.finnsson at gmail.com
Fri Oct 16 13:47:27 EDT 2009
Hi,
I'm trying to extract the names and types of exported functions in a module.
At the moment I've managed to get a list of all functions in a module
but I can't seem to figure out how to get their types.
Lets say I got the module
module Foo where
foo1 :: String -> String
foo1 value = value
foo2 = "hej"
and then in anothor module...
module Bar where
bar = $(getAllFunctions "<some-path>/Foo.hs")
At the moment I got getAllFunctions returning ["foo1","foo2"], but I
would really like to get it to return [("foo1",AppT (ConT "String")
(ConT "String")), ("foo2",ConT "String")]
Using "parseModuleWithMode" from Language.Haskell.Exts I can get hold
of the names and the type signature of foo1 (since it's specified in
the source code) but I cannot get hold of the type signature of foo2
(since it's not specified in the source code).
Is there another way to get the names/signatures of exported functions
from a module other than using parseModuleWithMode so the developer
writing the Foo-module isn't forced to explicitly supply type
signatures of the exported functions?
If I try "reify" to get information about the functions I get the error message:
"foo1 is not in scope at a reify"
This seems to be a known bug about reify (reported here
http://hackage.haskell.org/trac/ghc/ticket/2339). My problem is that I
cannot use the workaround since I don't know the name of the
functions.
Another disadvantage with this approach is that "getAllFunctions" must
have access to the source code of the module and that I must supply
the path the the module. If possible I would like to have code such as
bar = $(getAllFunctions "Foo")
instead of "<come-path>/Foo.hs".
Regards,
Oscar Finnsson
More information about the template-haskell
mailing list