Request: Open Module Resolution

Simon Marlow simonmar at microsoft.com
Wed May 4 05:26:49 EDT 2005


On 03 May 2005 23:01, S. Alexander Jacobson wrote:

> Proposal:
> 
> 1. Define a standard resolver module
> 
>    module Resolve where
> 
>    type Resolver = Args -> ModuleName -> IO HaskellSource
>    resolve::Resolver
> 
> 2. Require that Haskell compilers allow users to supply resolvers
> e.g.
> 
>    ghci -r ../../Resolve.hs

That requires compile-time code generation and execution (i.e. template
haskell), so I can't see all compilers implementing it.

Instead, let me point you at the place in GHC to insert your resolver.
In the module Finder, we have:

findModule :: HscEnv -> Module -> Bool -> IO FindResult

data FindResult
  = Found ModLocation PackageIdH
	-- the module was found
  | PackageHidden PackageId
	-- for an explicit source import: the package containing the
module is
	-- not exposed.
  | ModuleHidden  PackageId
	-- for an explicit source import: the package containing the
module is
	-- exposed, but the module itself is hidden.
  | NotFound [FilePath]
	-- the module was not found, the specified places were searched.

You can almost replace findModule with your own resolver.  However, the
question is what do you do for modules like "Prelude": it sounds like
you'll need to have pre-compiled code for all the standard libraries
around (I assume you want to avoid using packages).

Cheers,
	Simon


More information about the Libraries mailing list