0

I am trying to get the CORE of all modules in a package (I am using base-4.9.0.0 as an example).

Following the examples here on SO and the Haskell wiki I managed to come up with the following function:

compileToSimpleCore otherincludes path = GHC.runGhc (Just libdir) $ do
    dynflags <- GHC.getSessionDynFlags
    _ <- GHC.setSessionDynFlags dynflags { includePaths = otherincludes ++ includePaths dynflags}
        -- set all files in package as compilation targets
        -- This fixes the issue of not finding an import
    targets <- mapM (`GHC.guessTarget` Nothing) (path:otherincludes)
    GHC.setTargets targets
    _ <- GHC.load GHC.LoadAllTargets
    modSum <- GHC.getModSummary $ GHC.mkModuleName path
    p <- GHC.parseModule modSum
    t <- GHC.typecheckModule p
    d <- GHC.desugarModule t
    l <- GHC.loadModule d
    n <- GHC.getNamesInScope
    c <- return $ GHC.coreModule d
    let guts = mg_binds c
    let modName = GHC.moduleNameString $ GHC.moduleName $ mg_module c
    return guts

I get the following errors:

base-4.9.0.0/Control/Arrow.hs:3:16:
    unknown flag in  {-# OPTIONS_GHC #-} pragma: -Wno-inline-rule-shadowing

base-4.9.0.0/Data/Typeable/Internal.hs:13:14:
    Unsupported extension: TypeApplications

Question

Is there an easy way to get all the extensions used in the package (maybe going through the cabal file?)

Also, I'm guessing I am missing a flag for the pragma errors but not sure what I am missing.

UPDATE

So the above problems where fixed by using base-4.8.2.0 as a test case.

I now hit 2 problems:

  • .hsc files are not handled in any way by my function above so the whole process halts. I fixed this (temporarily) by manually doing hsc2hs for all the .hsc files in the pacakge.

  • Internal modules of the package are not visible:

     Could not find module ‘Control.Monad.ST.Imp’
     it is a hidden module in the package ‘base-4.8.2.0’
     Use -v to see a list of the files searched for.
    

CODE

I know is a long shot but if anyone can help me or at least for future reference here is the code updated code I've been using (mostly an adaptation of LiquidHaskell).

-- initial env is Nothing (empty)
compileToCore :: FilePath -> Package -> IO ModGuts
compileToCore target pkg = runEngingeGhc Nothing pkg $ getGhcInfo target

-- | Set up the GHC environment
runEngingeGhc :: Maybe HscEnv -> Package -> GHC.Ghc a -> IO a
runEngingeGhc hscEnv pkg act =
  GHC.defaultErrorHandler defaultFatalMessager defaultFlushOut $
    GHC.runGhc (Just libdir) $ do
      maybe (return ()) GHC.setSession hscEnv
      df <- GHC.getSessionDynFlags
      let df' = df { importPaths  = nub $ includeDirs pkg ++ importPaths df
                    , libraryPaths = nub $ includeDirs pkg ++ libraryPaths df
                  , includePaths = nub $ includeDirs pkg ++ includePaths df
                  , packageFlags = [ ExposePackage (PackageArg "ghc")
                                                    (ModRenaming True [])
                                    , ExposePackage (PackageArg "ghc-paths")
                                                    (ModRenaming True [])]
                                    ++ packageFlags df
                    , ghcLink      = NoLink
                    -- , hscTarget    = HscInterpreted -- HscNothing
                    , ghcMode      = CompManager
                    }
      _ <- GHC.setSessionDynFlags df'
      _ <- liftIO $ initPackages df'
      GHC.defaultCleanupHandler df' act


getGhcInfo :: FilePath -> GHC.Ghc ModGuts
getGhcInfo target = do
  -- paths <- importPaths <$> GHC.getSessionDynFlags
  -- find and Load Targets
  GHC.setTargets . return =<< GHC.guessTarget target Nothing
  impNames <- allDepNames <$> GHC.depanal [] False
  GHC.load GHC.LoadAllTargets
  makeModGuts target


-- get the dependencies
allDepNames :: [ModSummary] -> [String] -- from LiquidH
allDepNames = concatMap (map declNameString . ms_textual_imps)

declNameString :: GHC.Located (GHC.ImportDecl GHC.RdrName) -> String -- from LiquidH
declNameString = GHC.moduleNameString . GHC.unLoc . GHC.ideclName . GHC.unLoc

makeModGuts :: FilePath -> GHC.Ghc ModGuts
makeModGuts f = do
  modGraph <- GHC.getModuleGraph
  case find (\m -> not (isBootSummary m) && f == msHsFilePath m) modGraph of
    Just modSummary -> do
      parsed   <- GHC.parseModule modSummary
      modGuts  <- GHC.coreModule <$> (GHC.desugarModule =<< GHC.typecheckModule parsed)
      return $! modGuts
    Nothing ->
      panic "Ghc Interface: Unable to get GhcModGuts"
Community
  • 1
  • 1
aesadde
  • 439
  • 3
  • 9
  • 1
    Are you using GHC 8.0? You need to use GHC 8.0 (or later) to use the `TypeApplications` extension. – ErikR May 24 '16 at 11:23
  • Indeed, thanks. I am using GHC 7.10.3. I changed to use base-4.8.2.0 as a test and now the extension and problems seem to have disappeared. I still have problem with the include though. I tried to manually add the `include` dir of the package to the dyn flags but I'm wondering if there is an easier way to do this? – aesadde May 24 '16 at 11:32
  • Well - AFAIK `base` is a tricky package to build. There is no cabal file for it. It's built by scripts in the GHC bindist. – ErikR May 24 '16 at 12:24
  • I see thanks! I'll report here if I manage to do something about it! But at least, `base` does have a [cabal file](http://hackage.haskell.org/package/base-4.8.2.0/base.cabal) – aesadde May 24 '16 at 13:44

0 Answers0