Request: Open Module Resolution
S. Alexander Jacobson
alex at alexjacobson.com
Thu May 5 12:38:11 EDT 2005
On Wed, 4 May 2005, Simon Marlow wrote:
> 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
Oh, this is great! Then let me be more precise in my request:
I am looking for a way for the user to provide a function to handle
NotFound results. I want the user to be able to supply a function
that wraps findModule (with the exact same type signature).
> 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).
So the wrapper function can let the default findModule function
operate and only handle the case where findModule returns NotFound.
The key point here is I'd like a way to do this that doesn't requiring
recompiling GHC every time you change the wrapper function.
And I'd like the ability to reuse these user findModule functions
with multiple Haskell compilers.
Is this possible?
-Alex-
______________________________________________________________
S. Alexander Jacobson tel:917-770-6565 http://alexjacobson.com
On Wed, 4 May 2005, Simon Marlow wrote:
> 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
> _______________________________________________
> Libraries mailing list
> Libraries at haskell.org
> http://www.haskell.org/mailman/listinfo/libraries
>
More information about the Libraries
mailing list