"eval" in ghc(i)?

Donald Bruce Stewart dons at cse.unsw.edu.au
Wed May 3 20:51:50 EDT 2006


lemmih:
> On 5/4/06, Donald Bruce Stewart <dons at cse.unsw.edu.au> wrote:
> >geoffw:
> >>
> >>       I have an application written in OCaml that I'm interested in
> >>       porting over to Haskell, and I was wondering what the best way to 
> >replace
> >> the following OCaml function would be:
> >>
> >> Toploop.initialize_toplevel_env();;
> >>
> >> let eval txt = let lb = (Lexing.from_string txt) in
> >>  let phr = !Toploop.parse_toplevel_phrase lb in
> >>  Toploop.execute_phrase true Format.std_formatter phr;;
> >>
> >> eval "let add1 x = x +1;;";;
> >> eval "add1 2;;";;
> >>
> >> Where I would like to be able to "eval" Haskell-code instead.  It looks
> >> like I might be able to achieve something like this using hs-plugins,
> >> but it looks a bit more complex.  Is hs-plugins the best choice for this
> >> kind of "meta"-programming?  I'm pretty sure Template Haskell will not
> >> work for me, at least as I understand it I can only manipulate program
> >> fragments that will be compiled later and as such that it will not be
> >> possible to execute them until the next "phase".
> >
> >You can do some forms of runtime metaprogrammign with hs-plugins, yes.
> >E.g.
> >
> >Prelude System.Eval.Haskell> v <- eval "1 + 2 :: Int" [] :: IO (Maybe Int)
> >Prelude System.Eval.Haskell> v
> >Just 3
> >
> >Prelude System.Eval.Haskell> mf <- eval "\\x -> x + 1 :: Int" [] :: IO 
> >(Maybe (Int -> Int))
> >Prelude System.Eval.Haskell> let f = fromJust mf
> >Prelude System.Eval.Haskell> :t f
> >f :: Int -> Int
> >Prelude System.Eval.Haskell> f 7
> >8
> >
> >So if your program critically relies on this its possible to do.
> 
> You can also use the GHC library:
> Prelude> :m GHC
> Prelude GHC> GHC.init (Just 
> "/home/david/coding/haskell/ghc/usr/lib/ghc-6.5")
> Prelude GHC> session <- newSession Interactive
> Prelude GHC> setSessionDynFlags session =<< initPackages =<<
> getSessionDynFlags session
> Prelude GHC> setContext session [] [mkModule "Prelude"]
> Prelude GHC> runStmt session "let add1 x = x + 1"
> Prelude GHC> runStmt session "add1 2"
> 3
> Prelude GHC> :q
> Leaving GHCi.

It strikes me that we should be aiming for an interface like something 
approaching the various ML top levels, with ghc-api. That is, we
shouldn't need to deal with setting up package contexts and so on.

/me ponders an api ...

Something like:

    > GHC.Top.init
    > f <- run "let add1 x = x + 1"
    > f 7
    8

Lemmih, any ideas on whether it would be possible to simplify and
abstract over some of the details ? Do we need a SoC project... :)

-- Don


More information about the Glasgow-haskell-users mailing list