Request: Open Module Resolution

S. Alexander Jacobson alex at alexjacobson.com
Mon May 9 20:09:14 EDT 2005


On Fri, 6 May 2005, Simon Marlow wrote:

> Certainly.  But there's no easy way to say this:  I think you're going
> to have to do it yourself (or find some kind soul to do it).  Of course
> we'll incorporate the changes as long as they don't break anything else.

Ok, any reason the code below wouldn't work?

Usage:

  $ resolve ghci MyModule.hs Also.lhs -i ../myPath

It attempts to retrieve all the imports of MyModule.hs and Also.hs 
from the Internet into a __Resolved__ directory designated in a 
configuration file.  It then calls the rest of the command line 
adding in the __Resolved__ directory e.g. it calls:

  system $ "ghci MyModule.hs Also.hs -i ../myPath -i __Resolved__"

Here is the strawman wrapper code (I haven't written any 
actual Resolver yet)

   module Wrap where
   import System
   import System.Cmd
   import Language.Haskell.Syntax
   import Language.Haskell.Parser
   import qualified Resolver
   import Text.Regex
   import Maybe

   getFileNames = return . filter (isJust .  matchRegex (mkRegex ".*\\.l?hs$"))
   readFile' x = catch (readFile x) (\_->return "")
   getFileImports fileName = readFile' fileName >>= (return.getParsedImports.parseModule)
   getParsedImports (ParseFailed _ _) = []
   getParsedImports (ParseOk (HsModule _ _ _ imports _)) = map (modName.importModule) imports
   modName (Module name) = name
   getAllImports args= getFileNames args >>= mapM getFileImports  >>= (return.concat)
   doResolves conf args = getAllImports args >>= mapM (Resolver.resolve conf)

   main = do
          args <- getArgs
          conf <- (catch (getEnv "RESOLVECONF") (\_->return "")) >>= Resolver.readConf
          doResolves conf args
          system $ unwords args ++ " -i " ++ (Resolver.getBaseDir conf)

-Alex-

PS I love that Haskell makes this sort of "shell scripting" so easy!!!

______________________________________________________________
S. Alexander Jacobson tel:917-770-6565 http://alexjacobson.com







> On 05 May 2005 17:38, S. Alexander Jacobson wrote:
>
>> 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?
>
> Certainly.  But there's no easy way to say this:  I think you're going
> to have to do it yourself (or find some kind soul to do it).  Of course
> we'll incorporate the changes as long as they don't break anything else.
>
> Cheers,
> 	Simon
>



More information about the Libraries mailing list