[Haskell-cafe] GHC Api typechecking

Phyx lonetiger at gmail.com
Sun Apr 18 06:01:36 EDT 2010


Hi,

I checked out how Hint is doing it, but unfortunately they're calling a function in the GHC api's interactive part to typecheck a single statement, much like :t in ghci,
So I can't use it to typecheck whole modules.
I've tried working around not being able to construct a TargetId but ran into another wall.
I can't find anyway to do dependency analysis on the in-memory target, so the dependency graph would be empty which is ofcourse a big problem.

Does anyone know if Leksah uses the GHC api for typechecking? And if it only gives type errors after you save a file?

The code I've been trying is

typeCheckStringOnly :: String -> IO (ApiResults Bool)
typeCheckStringOnly contents = handleSourceError processErrors $
 runGhc (Just libdir) $ do
    buffer <- liftIO $ stringToStringBuffer contents
    clock  <- liftIO getClockTime
    dflags <- getSessionDynFlags
    setSessionDynFlags dflags
    let srcLoc   = mkSrcLoc (mkFastString "internal:string") 1 1
        dynFlag  = defaultDynFlags 
        state    = mkPState buffer srcLoc dynFlag
        parsed   = unP Parser.parseModule state
        pkgId    = stringToPackageId "internal"
        name     = mkModuleName "Unknown"
        mod'     = mkModule pkgId name
        location = ModLocation Nothing "" ""
        summary  = ModSummary mod' HsSrcFile location clock Nothing [] [] "" dynFlag Nothing
    (\a->setSession $ a { hsc_mod_graph = [summary] }) =<< getSession
    case parsed of
       PFailed _ _        -> return $ ApiOk False
       POk newstate mdata -> do let module' = ParsedModule summary mdata
                                check <- typecheckModule module'
                                return $ ApiOk True

this fails with a ghc panic

: panic! (the 'impossible' happened)
  (GHC version 6.12.1 for i386-unknown-mingw32):
        no package state yet: call GHC.setSessionDynFlags

Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug

:(

Cheers,
Phyx

-----Original Message-----
From: Gwern Branwen [mailto:gwern0 at gmail.com] 
Sent: Saturday, April 17, 2010 20:59
To: Phyx
Subject: Re: [Haskell-cafe] GHC Api typechecking

On Sat, Apr 17, 2010 at 1:49 PM, Phyx <lonetiger at gmail.com> wrote:
> Hi all, I was wondering if someone knows how to do the following:
>
>
>
> I’m looking to typecheck a string using the GHC Api, where I run into
> problems is that I need to construct a Target, but the TargetId only seem to
> reference physical files.
>
>
>
> Ofcourse I can write the string to a file and typecheck that file, but I
> would like to do it all in memory and avoid IO if possible.
>
>
>
> Does anyone know if this is possible?
>
>
>
> For the record I’m trying to create the target as follows
>
>
>
> createTarget :: String -> IO Target
>
> createTarget content =
>
>  do clock  <- getClockTime
>
>     buffer <- stringToStringBuffer content
>
>     return $ Target { targetId           = TargetModule (mkModuleName
> "string:internal") ß problem
>
>                     , targetAllowObjCode = True
>
>                     , targetContents     = Just (buffer,clock)
>
>                     }
>
>
>
> typeCheckStringOnly :: String -> IO (ApiResults Bool)
>
> typeCheckStringOnly contents = handleSourceError processErrors $
>
> runGhc (Just libdir) $ do
>
>     dflags <- getSessionDynFlags
>
>     setSessionDynFlags dflags
>
>     target <- liftIO $ createTarget contents
>
>     addTarget target
>
>     load LoadAllTargets
>
>     let modName = mkModuleName "string:internal" ß problem again, don’t know
> how to create the dependency graph then.
>
>     graph <- depanal [modName] True
>
>     (\a->setSession $ a { hsc_mod_graph = graph }) =<< getSession
>
>     value <- fmap typecheckedSource (typeCheck modName)
>
>     return $ ApiOk True
>
>
>
> Cheers,
>
> Phyx

Have you looked at how the Hint package does things?

-- 
gwern



More information about the Haskell-Cafe mailing list