[Template-haskell] How to extract name and type of exported functions in modules

Simon Peyton-Jones simonpj at microsoft.com
Tue Oct 20 10:38:33 EDT 2009


[ccing ghc-users]

| I'm trying to extract the names and types of exported functions in a module.

Quite a reasonable request.  But it's not conveniently possible at the moment.  Here's what you can do in the Q monad:

class (Monad m, Functor m) => Quasi m where
	-- Fresh names
  qNewName :: String -> m Name

	-- Error reporting and recovery
  qReport  :: Bool -> String -> m ()	-- Report an error (True) or warning (False)
					-- ...but carry on; use 'fail' to stop
  qRecover :: m a -> m a -> m a		-- Recover from the monadic 'fail'
					-- The first arg is the error handler
 
	-- Inspect the type-checker's environment
  qReify :: Name -> m Info
  qLocation :: m Loc

	-- Input/output (dangerous)
  qRunIO :: IO a -> m a

But you want one more function:

  qReifyModule :: String -> m ModuleInfo

where ModuleInfo is something like:

data ModuleInfo = MI { mi_exports :: [Name]
                     , ... instances,rules, etc }

Then you could use qReify to get info about a particular thing.


This would not be hard in principle, the details need thought.  For example, if module exports T( C1, C2), where C1, C2 are constructors of T which also has constructors C3, C4, what should appear in mi_exports?  Should mi_exports reflect the structure of the export list (see the AvailInfo type in GHC).

What is the info for an instance?
Do we need a way to ask for all the instances of a class (or rules for a function) regardless of what module those instances come from?   etc


Does this ring bells for anyone else?  Would someone like to write the spec?  Are there other reify-related things that we need?

Simon

| -----Original Message-----
| From: template-haskell-bounces at haskell.org [mailto:template-haskell-
| bounces at haskell.org] On Behalf Of Oscar Finnsson
| Sent: 16 October 2009 18:47
| To: template-haskell at haskell.org
| Subject: [Template-haskell] How to extract name and type of exported functions in
| modules
| 
| 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
| _______________________________________________
| template-haskell mailing list
| template-haskell at haskell.org
| http://www.haskell.org/mailman/listinfo/template-haskell



More information about the template-haskell mailing list