newSession gone from GHC API
humasect
humasect at gmail.com
Mon Sep 29 11:19:56 EDT 2008
Also to make Located String in the simple way:
import SrcLoc
L noSrcSpan "-hidir ../build"
also make sure to "import MonadUtils" for that version of liftIO.
I have converted the graphical/opengl/openal shell for the project I am
working on successfully, let me know if you have questions!
-lyndon
2008/9/29 Claus Reinke <claus.reinke at talk21.com>
I just noticed that newSession has been removed from the GHC API.
>> Unfortunately, this breaks nearly all examples on the web:
>> http://www.haskell.org/haskellwiki/GHC/As_a_library
>> http://hackage.haskell.org/trac/ghc/wiki/Commentary/Compiler/API
>> Could someone fix those up, to show the new style of interaction? Also
>> are the breaking changes to newSession in GHC 6.10, or only in GHC Head?
>>
>
> Thomas said he was working on a conversion guide, but
> delayed by travelling:
>
> http://www.haskell.org/pipermail/cvs-ghc/2008-September/045361.html
>
> Meanwhile, since you're somewhat familar with haddock, his
> patches to port haddock to the new api may help (I used them
> to figure out where to look for more info;). Or, if you prefer
> smaller examples, have a look at
>
> http://www.cs.kent.ac.uk/~cr3/toolbox/haskell/syb-utils/examples/GhcApiSybTesting.hs
>
> which I patched recently (diff below). Mostly, you'll be looking for
> runGhc, dropping session parameters, changing dynamic flags from
> String to Located String, and splitting checkModule into separate
> phases (there's a class that simplifies access via the old record selector
> functions). Possibly other small things, like using liftIO to
> do IO in the Ghc monads.
>
> Hth,
> Claus
>
> $ darcs changes -v -p 'new Ghc Api' | sed 's/\[_.._\]\[_._\]$//'
> diffing dir...
> Mon Sep 22 20:01:02 GMT Daylight Time 2008 claus.reinke at talk21.com
> * adapt example to new Ghc Api
> {
> hunk ./examples/GhcApiSybTesting.hs 15
> +import SrcLoc
> +import MonadUtils
> hunk ./examples/GhcApiSybTesting.hs 35
> -main = defaultErrorHandler defaultDynFlags $ do
> - s <- newSession (Just libdir)
> - flags <- getSessionDynFlags s
> - (flags,_,_) <- parseDynamicFlags flags ["-package ghc"]
> +main = defaultErrorHandler defaultDynFlags $
> + runGhc (Just libdir) $ do
> + flags <- getSessionDynFlags
> + (flags,_,_) <- parseDynamicFlags flags [noLoc "-package ghc"]
> hunk ./examples/GhcApiSybTesting.hs 40
> - setSessionDynFlags s flags{ hscTarget=HscInterpreted }
> - addTarget s =<< guessTarget source Nothing
> - load s LoadAllTargets
> - unqual <- getPrintUnqual s
> + setSessionDynFlags flags{ hscTarget=HscInterpreted }
> + addTarget =<< guessTarget source Nothing
> + load LoadAllTargets
> + unqual <- getPrintUnqual
> + {-
> hunk ./examples/GhcApiSybTesting.hs 50
> + -}
> + tcm <- typecheckModule =<< parseModule (mkModuleName modName)
> + doSomething unqual tcm
> hunk ./examples/GhcApiSybTesting.hs 63
> - doSomething unqual cm = do
> - let parsed = parsedSource cm
> - renamed = renamedSource cm
> - typechecked = typecheckedSource cm
> + doSomething unqual tcm = liftIO $ do
> + let parsed = parsedSource tcm
> + renamed = renamedSource tcm
> + typechecked = typecheckedSource tcm
> hunk ./examples/GhcApiSybTesting.hs 84
> - maybe (putStrLn "no typechecked source")
> - (printForUser stdout unqual . shown TypeChecker)
> typechecked
> + printForUser stdout unqual $ shown TypeChecker typechecked
>
> }
>
> _______________________________________________
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users at haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/glasgow-haskell-users/attachments/20080929/4a85bc98/attachment.htm
More information about the Glasgow-haskell-users
mailing list