[Haskell-cafe] segfault when using ghc api

Anthonin Bonnefoy anthonin.bonnefoy at gmail.com
Sun Feb 27 15:24:01 CET 2011


Hi,

The first argument of runGhc takes the directory where GHC's library
are. You can use the ghc-paths module
(http://hackage.haskell.org/package/ghc-paths ) for this.

Just install ghc-paths with cabal, import Ghc.Paths and call runGhc
with (Just libdir), it should get past the segfault.

On Sun, Feb 27, 2011 at 10:51 AM, Edward Amsden <eca7215 at cs.rit.edu> wrote:
> I'm trying to run the following code. I'm not at all sure it's
> correct, it's based off of a bit of poking around in the ghc api.
> Running it with a command line argument like "show (5 + 2)" gives me a
> segmentation fault. Poking around with gdb and following the steps at
> http://hackage.haskell.org/trac/ghc/wiki/Debugging/CompiledCode yields
> precisely nothing, as even the "disassemble" command complains "No
> function contains program counter for selected frame."
>
> Any ideas?
>
> == code ==
> module Main where
>
> import GHC
> import DynFlags
> import Data.Dynamic
> import System
>
> evalString :: Typeable a => String -> IO (Maybe a)
> evalString s = defaultErrorHandler defaultDynFlags $ runGhc Nothing $ do
>  dynflags <- getSessionDynFlags
>  setSessionDynFlags $ dynflags
>  target <- guessTarget "Prelude" Nothing
>  setTargets [target]
>  load LoadAllTargets
>
>  dyn <- dynCompileExpr s
>  return $ fromDynamic dyn
>
> main = do
>  (s:_) <- getArgs
>  e <- evalString s
>  putStrLn $ maybe "oops" id e
>
> --
> Edward Amsden
> Undergraduate
> Computer Science
> Rochester Institute of Technology
> www.edwardamsden.com
>
> _______________________________________________
> 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