[Haskell-cafe] Interactive Haskell and hs-plugins

Keean Schupke k.schupke at imperial.ac.uk
Tue Nov 1 12:02:10 EST 2005


The symbols must be exported from the main program... I think you can 
pass the linker an option to force it to export symbols.

    Keean.

Fraser Wilson wrote:

> Hi there,
>
> I would like to use evaluate arbitrary expressions in the context of a 
> mixed-language (Ada, Haskell and about twelve lines of C glue) 
> applications.  Is it possible to use dynload from hs-plugins to load a 
> module that references symbols in the loading program?
>
> For example, the application contains a Haskell module that looks a 
> bit like this:
>
> > module TestKeys.NamedObject where
> >    tt :: Int
> >    tt = 2
>
> I want the application to be able to offer the following sort of 
> interaction:
>
> haskell> tt
> 2
> haskell>
>
> But what actually happens is this:
>
> haskell> tt
> test_haskell3: /tmp/MDnum15633.o: unknown symbol 
> `TestKeysziNamedObject_tt_closure'
> test_haskell3: user error (resolveObjs failed with <<False>>)
>
> Compiling Haskell code in advance works (i.e. if I create and compile 
> a module that evalutes tt and link it in, everything runs fine).
>
> This is how I try to evaluate the expression:
>
> > evaluate :: String -> IO ()
> > evaluate "" = return ()
> > evaluate e = do writeFile "temp.hs" fileContents
> >         status <- makeWith "LeanderStub.hs" "temp.hs" ["-c"]
> >         case status of MakeSuccess code path -> loadAndEval path
> >                    MakeFailure error     -> print error
> >     where fileContents = "module Temp where\n\
> >                          \   result = " ++ e ++ "\n"
> >
> > loadAndEval :: FilePath -> IO ()
> > loadAndEval path = do mv <- dynload path [] [] "result"
> >               case mv of
> >                    LoadFailure msg -> print msg
> >                LoadSuccess _ v -> putStrLn v
>
> LeanderStub.hs is a module containing the necessary imports for the 
> expression to evaluate in the right context.
>
> I was hoping that passing "-c" to makeWith would create an object file 
> whose missing dependencies would be resolved when it was loaded into 
> an application which contained them.  Is this a dumb expectation?  The 
> alternative -- linking to the entire application for each expression 
> evaluated -- seems a bit over the top, and I can't see how state would 
> be maintained.
>
> I originally used unsafeEval_, but this has the same problem.
>
> I can't help but think that this must have been done before.  Any 
> advice?  If you know Guile, then the equivalent of gh_repl is what I'm 
> really after.
>
> cheers,
> Fraser.
>
>------------------------------------------------------------------------
>
>_______________________________________________
>Haskell-Cafe mailing list
>Haskell-Cafe at haskell.org
>http://www.haskell.org/mailman/listinfo/haskell-cafe
>  
>



More information about the Haskell-Cafe mailing list