X-Git-Url: https://git.stderr.nl/gitweb?a=blobdiff_plain;f=c%CE%BBash%2FCLasH%2FUtils%2FGhcTools.hs;h=0c8c55980acbffd6ec6be06af544453f2b21f192;hb=9a431787ceb299b15106b0dfd07701913cf2b515;hp=9c5038cfd42586ba8ccd6c7b1aca998d06a8b7b7;hpb=ec4378a8a765c5a064b5cbed347b40c353c778a0;p=matthijs%2Fmaster-project%2Fc%CE%BBash.git diff --git "a/c\316\273ash/CLasH/Utils/GhcTools.hs" "b/c\316\273ash/CLasH/Utils/GhcTools.hs" index 9c5038c..0c8c559 100644 --- "a/c\316\273ash/CLasH/Utils/GhcTools.hs" +++ "b/c\316\273ash/CLasH/Utils/GhcTools.hs" @@ -1,15 +1,23 @@ -module GhcTools where +{-# LANGUAGE ScopedTypeVariables #-} + +module CLasH.Utils.GhcTools where + -- Standard modules +import qualified Monad import qualified System.IO.Unsafe -- GHC API -import qualified GHC -import qualified GHC.Paths +import qualified Annotations +import qualified CoreSyn import qualified DynFlags -import qualified TcRnMonad -import qualified MonadUtils import qualified HscTypes -import qualified PrelNames +import qualified GHC +import qualified Name +import qualified Serialized +import qualified Var + +-- Local Imports +import CLasH.Translator.Annotations -- Change a DynFlag from within the Ghc monad. Strangely enough there seems to -- be no standard function to do exactly this. @@ -26,19 +34,93 @@ setDynFlag dflag = do -- don't have side effects themselves (Or rather, that don't use -- unsafePerformIO themselves, since normal side effectful function would -- just return an IO monad when they are evaluated). -unsafeRunGhc :: GHC.Ghc a -> a -unsafeRunGhc m = - System.IO.Unsafe.unsafePerformIO $ - GHC.runGhc (Just GHC.Paths.libdir) $ do +unsafeRunGhc :: FilePath -> GHC.Ghc a -> a +unsafeRunGhc libDir m = + System.IO.Unsafe.unsafePerformIO $ do + GHC.runGhc (Just libDir) $ do dflags <- GHC.getSessionDynFlags GHC.setSessionDynFlags dflags m + +-- | Loads the given files and turns it into a core module +loadModules :: + FilePath -- ^ The GHC Library directory + -> [String] -- ^ The files that need to be loaded + -> (HscTypes.CoreModule -> GHC.Ghc (Maybe CoreSyn.CoreBndr)) -- ^ The TopEntity finder + -> (HscTypes.CoreModule -> GHC.Ghc (Maybe CoreSyn.CoreBndr)) -- ^ The InitState finder + -> (HscTypes.CoreModule -> GHC.Ghc (Maybe CoreSyn.CoreExpr)) -- ^ The TestInput finder + -> IO ( [HscTypes.CoreModule] + , [Maybe CoreSyn.CoreBndr] + , [Maybe CoreSyn.CoreBndr] + , [Maybe CoreSyn.CoreExpr] + , HscTypes.HscEnv + ) -- ^ ( The loaded modules, the TopEntity, the InitState, the TestInput + -- , The Environment corresponding of the loaded modules + -- ) +loadModules libdir filenames topEntLoc initSLoc testLoc = + GHC.defaultErrorHandler DynFlags.defaultDynFlags $ do + GHC.runGhc (Just libdir) $ do + dflags <- GHC.getSessionDynFlags + GHC.setSessionDynFlags dflags + cores <- mapM GHC.compileToCoreModule filenames + env <- GHC.getSession + top_entity <- mapM topEntLoc cores + init_state <- mapM initSLoc cores + test_input <- mapM testLoc cores + return (cores, top_entity, init_state, test_input, env) + +findBind :: + GHC.GhcMonad m => + (Var.Var -> m Bool) + -> HscTypes.CoreModule + -> m (Maybe CoreSyn.CoreBndr) +findBind criteria core = do + binders <- findBinder criteria core + case binders of + [] -> return Nothing + bndrs -> return $ Just $ fst $ head bndrs + +findExpr :: + GHC.GhcMonad m => + (Var.Var -> m Bool) + -> HscTypes.CoreModule + -> m (Maybe CoreSyn.CoreExpr) +findExpr criteria core = do + binders <- findBinder criteria core + case binders of + [] -> return Nothing + bndrs -> return $ Just $ snd $ head bndrs + +-- | Find a binder in module according to a certain criteria +findBinder :: + GHC.GhcMonad m => + (Var.Var -> m Bool) -- ^ The criteria to filter the binders on + -> HscTypes.CoreModule -- ^ The module to be inspected + -> m [(CoreSyn.CoreBndr, CoreSyn.CoreExpr)] -- ^ The binders to meet the criteria +findBinder criteria core = do + let binds = CoreSyn.flattenBinds $ HscTypes.cm_binds core + critbinds <- Monad.filterM (criteria . fst) binds + return critbinds + +-- | Determine if a binder has an Annotation meeting a certain criteria +hasCLasHAnnotation :: + GHC.GhcMonad m => + (CLasHAnn -> Bool) -- ^ The criteria the Annotation has to meet + -> Var.Var -- ^ The Binder + -> m Bool -- ^ Indicates if binder has the Annotation +hasCLasHAnnotation clashAnn var = do + let deserializer = Serialized.deserializeWithData + let target = Annotations.NamedTarget (Var.varName var) + (anns :: [CLasHAnn]) <- GHC.findGlobalAnns deserializer target + let annEnts = filter clashAnn anns + case annEnts of + [] -> return False + xs -> return True -runTcM :: TcRnMonad.TcM a -> IO a -runTcM thing_inside = do - GHC.runGhc (Just GHC.Paths.libdir) $ do - dflags <- GHC.getSessionDynFlags - GHC.setSessionDynFlags dflags - env <- GHC.getSession - HscTypes.ioMsgMaybe . MonadUtils.liftIO . TcRnMonad.initTcPrintErrors env PrelNames.iNTERACTIVE $ do - thing_inside +-- | Determine if a binder has a certain name +hasVarName :: + GHC.GhcMonad m => + String -- ^ The name the binder has to have + -> Var.Var -- ^ The Binder + -> m Bool -- ^ Indicate if the binder has the name +hasVarName lookfor bind = return $ lookfor == (Name.occNameString $ Name.nameOccName $ Name.getName bind)