{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TemplateHaskell #-}
module Clash.GHC.LoadModules
  ( loadModules
  , ghcLibDir
  , setWantedLanguageExtensions
  )
where
#ifndef USE_GHC_PATHS
#ifndef TOOL_VERSION_ghc
#error TOOL_VERSION_ghc undefined
#endif
#endif
import           Clash.Annotations.Primitive     (HDL, PrimitiveGuard)
import           Clash.Annotations.TopEntity     (TopEntity (..))
import           Clash.Primitives.Types          (UnresolvedPrimitive)
import           Clash.Util                      (ClashException(..), pkgIdFromTypeable)
import qualified Clash.Util.Interpolate          as I
import           Control.Arrow                   (first, second)
import           Control.DeepSeq                 (deepseq)
import           Control.Exception               (SomeException, throw)
import           Control.Monad                   (forM, when)
#if MIN_VERSION_ghc(8,6,0)
import           Control.Exception               (throwIO)
#endif
import           Control.Monad.IO.Class          (liftIO)
import           Data.Char                       (isDigit)
import           Data.Generics.Uniplate.DataOnly (transform)
import           Data.Data                       (Data)
import           Data.Typeable                   (Typeable)
import           Data.List                       (foldl', nub)
import           Data.Maybe                      (catMaybes, listToMaybe, fromMaybe)
import qualified Data.Text                       as Text
import qualified Data.Time.Clock                 as Clock
import           Debug.Trace
import           Language.Haskell.TH.Syntax      (lift)
import           GHC.Stack                       (HasCallStack)
#ifdef USE_GHC_PATHS
import           GHC.Paths                       (libdir)
#else
import           System.Exit                     (ExitCode (..))
import           System.IO                       (hGetLine)
import           System.IO.Error                 (tryIOError)
import           System.Process                  (runInteractiveCommand,
                                                  waitForProcess)
#endif
import qualified Annotations
import qualified CoreFVs
import qualified CoreSyn
import qualified Digraph
#if MIN_VERSION_ghc(8,6,0)
import qualified DynamicLoading
#endif
import           DynFlags                        (GeneralFlag (..))
import qualified DynFlags
import qualified Exception
import qualified GHC
import qualified HscMain
import qualified HscTypes
import qualified MonadUtils
import qualified Panic
import qualified GhcPlugins                      (deserializeWithData, installedUnitIdString)
import qualified TcRnMonad
import qualified TcRnTypes
import qualified TidyPgm
import qualified Unique
import qualified UniqFM
import qualified FamInst
import qualified FamInstEnv
import qualified GHC.LanguageExtensions          as LangExt
import qualified Name
import qualified OccName
import           Outputable                      (ppr)
import qualified Outputable
import qualified UniqSet
import           Util (OverridingBool)
import qualified Var
import           Clash.GHC.GHC2Core                           (modNameM, qualifiedNameString')
import           Clash.GHC.LoadInterfaceFiles
  (loadExternalExprs, getUnresolvedPrimitives, loadExternalBinders,
   LoadedBinders(..))
import           Clash.GHCi.Common                            (checkMonoLocalBindsMod)
import           Clash.Util                                   (curLoc, noSrcSpan, reportTimeDiff
                                                              ,wantedLanguageExtensions, unwantedLanguageExtensions)
import           Clash.Annotations.BitRepresentation.Internal
  (DataRepr', dataReprAnnToDataRepr')
ghcLibDir :: IO FilePath
#ifdef USE_GHC_PATHS
ghcLibDir = return libdir
#else
ghcLibDir :: IO FilePath
ghcLibDir = do
  (Maybe FilePath
libDirM,ExitCode
exitCode) <- FilePath -> IO (Maybe FilePath, ExitCode)
getProcessOutput (FilePath -> IO (Maybe FilePath, ExitCode))
-> FilePath -> IO (Maybe FilePath, ExitCode)
forall a b. (a -> b) -> a -> b
$ FilePath
"ghc-" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ TOOL_VERSION_ghc ++ " --print-libdir"
  case ExitCode
exitCode of
     ExitCode
ExitSuccess   -> case Maybe FilePath
libDirM of
       Just FilePath
libDir -> FilePath -> IO FilePath
forall (m :: Type -> Type) a. Monad m => a -> m a
return FilePath
libDir
       Maybe FilePath
Nothing     -> FilePath -> IO FilePath
forall a. FilePath -> a
Panic.pgmError FilePath
noGHC
     ExitFailure Int
i -> case Int
i of
       Int
127         -> FilePath -> IO FilePath
forall a. FilePath -> a
Panic.pgmError FilePath
noGHC
       Int
i'          -> FilePath -> IO FilePath
forall a. FilePath -> a
Panic.pgmError (FilePath -> IO FilePath) -> FilePath -> IO FilePath
forall a b. (a -> b) -> a -> b
$ FilePath
"Calling GHC failed with error code: " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Int -> FilePath
forall a. Show a => a -> FilePath
show Int
i'
  where
    noGHC :: FilePath
noGHC = FilePath
"Clash needs the GHC compiler it was built with, ghc-" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ TOOL_VERSION_ghc ++
            FilePath
", but it was not found. Make sure its location is in your PATH variable."
getProcessOutput :: String -> IO (Maybe String, ExitCode)
getProcessOutput :: FilePath -> IO (Maybe FilePath, ExitCode)
getProcessOutput FilePath
command =
     
  do (Handle
_, Handle
pOut, Handle
_, ProcessHandle
handle) <- FilePath -> IO (Handle, Handle, Handle, ProcessHandle)
runInteractiveCommand FilePath
command
     
     ExitCode
exitCode <- ProcessHandle -> IO ExitCode
waitForProcess ProcessHandle
handle
     
     Maybe FilePath
output   <- (IOError -> Maybe FilePath)
-> (FilePath -> Maybe FilePath)
-> Either IOError FilePath
-> Maybe FilePath
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Maybe FilePath -> IOError -> Maybe FilePath
forall a b. a -> b -> a
const Maybe FilePath
forall a. Maybe a
Nothing) FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just (Either IOError FilePath -> Maybe FilePath)
-> IO (Either IOError FilePath) -> IO (Maybe FilePath)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> IO FilePath -> IO (Either IOError FilePath)
forall a. IO a -> IO (Either IOError a)
tryIOError (Handle -> IO FilePath
hGetLine Handle
pOut)
     
     (Maybe FilePath, ExitCode) -> IO (Maybe FilePath, ExitCode)
forall (m :: Type -> Type) a. Monad m => a -> m a
return (Maybe FilePath
output, ExitCode
exitCode)
#endif
loadExternalModule
  :: (HasCallStack, GHC.GhcMonad m)
  => HDL
  -> String
  
  
  -> m (Either
          SomeException
          ( [CoreSyn.CoreBndr]                     
          , FamInstEnv.FamInstEnv                  
          , GHC.ModuleName                         
          , LoadedBinders
          , [CoreSyn.CoreBind]                     
          ) )
loadExternalModule :: HDL
-> FilePath
-> m (Either
        SomeException
        ([CoreBndr], FamInstEnv, ModuleName, LoadedBinders, [CoreBind]))
loadExternalModule HDL
hdl FilePath
modName0 = m ([CoreBndr], FamInstEnv, ModuleName, LoadedBinders, [CoreBind])
-> m (Either
        SomeException
        ([CoreBndr], FamInstEnv, ModuleName, LoadedBinders, [CoreBind]))
forall (m :: Type -> Type) e a.
(ExceptionMonad m, Exception e) =>
m a -> m (Either e a)
Exception.gtry (m ([CoreBndr], FamInstEnv, ModuleName, LoadedBinders, [CoreBind])
 -> m (Either
         SomeException
         ([CoreBndr], FamInstEnv, ModuleName, LoadedBinders, [CoreBind])))
-> m ([CoreBndr], FamInstEnv, ModuleName, LoadedBinders,
      [CoreBind])
-> m (Either
        SomeException
        ([CoreBndr], FamInstEnv, ModuleName, LoadedBinders, [CoreBind]))
forall a b. (a -> b) -> a -> b
$ do
  let modName1 :: ModuleName
modName1 = FilePath -> ModuleName
GHC.mkModuleName FilePath
modName0
  Module
foundMod <- ModuleName -> Maybe FastString -> m Module
forall (m :: Type -> Type).
GhcMonad m =>
ModuleName -> Maybe FastString -> m Module
GHC.findModule ModuleName
modName1 Maybe FastString
forall a. Maybe a
Nothing
  let errMsg :: FilePath
errMsg = FilePath
"Internal error: found  module, but could not load it"
  ModuleInfo
modInfo <- ModuleInfo -> Maybe ModuleInfo -> ModuleInfo
forall a. a -> Maybe a -> a
fromMaybe (FilePath -> ModuleInfo
forall a. HasCallStack => FilePath -> a
error FilePath
errMsg) (Maybe ModuleInfo -> ModuleInfo)
-> m (Maybe ModuleInfo) -> m ModuleInfo
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (Module -> m (Maybe ModuleInfo)
forall (m :: Type -> Type).
GhcMonad m =>
Module -> m (Maybe ModuleInfo)
GHC.getModuleInfo Module
foundMod)
  [TyThing]
tyThings <- [Maybe TyThing] -> [TyThing]
forall a. [Maybe a] -> [a]
catMaybes ([Maybe TyThing] -> [TyThing]) -> m [Maybe TyThing] -> m [TyThing]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (Name -> m (Maybe TyThing)) -> [Name] -> m [Maybe TyThing]
forall (t :: Type -> Type) (m :: Type -> Type) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Name -> m (Maybe TyThing)
forall (m :: Type -> Type). GhcMonad m => Name -> m (Maybe TyThing)
GHC.lookupGlobalName (ModuleInfo -> [Name]
GHC.modInfoExports ModuleInfo
modInfo)
  let rootIds :: [CoreBndr]
rootIds = [CoreBndr
id_ | GHC.AnId CoreBndr
id_ <- [TyThing]
tyThings]
  LoadedBinders
loaded <- HDL -> [CoreBndr] -> m LoadedBinders
forall (m :: Type -> Type).
GhcMonad m =>
HDL -> [CoreBndr] -> m LoadedBinders
loadExternalBinders HDL
hdl [CoreBndr]
rootIds
  let allBinders :: [CoreBind]
allBinders = [(CoreBndr, CoreExpr)] -> [CoreBind]
makeRecursiveGroups (LoadedBinders -> [(CoreBndr, CoreExpr)]
lbBinders LoadedBinders
loaded)
  ([CoreBndr], FamInstEnv, ModuleName, LoadedBinders, [CoreBind])
-> m ([CoreBndr], FamInstEnv, ModuleName, LoadedBinders,
      [CoreBind])
forall (m :: Type -> Type) a. Monad m => a -> m a
return ([CoreBndr]
rootIds, FamInstEnv
FamInstEnv.emptyFamInstEnv, ModuleName
modName1, LoadedBinders
loaded, [CoreBind]
allBinders)
setupGhc
  :: GHC.GhcMonad m
  => OverridingBool
  -> Maybe GHC.DynFlags
  -> [FilePath]
  -> m ()
setupGhc :: OverridingBool -> Maybe DynFlags -> [FilePath] -> m ()
setupGhc OverridingBool
useColor Maybe DynFlags
dflagsM [FilePath]
idirs = do
  DynFlags
dflags <-
    case Maybe DynFlags
dflagsM of
      Just DynFlags
df -> DynFlags -> m DynFlags
forall (m :: Type -> Type) a. Monad m => a -> m a
return DynFlags
df
      Maybe DynFlags
Nothing -> do
#if MIN_VERSION_ghc(8,6,0)
        
        DynFlags
df <- do
          DynFlags
df <- m DynFlags
forall (m :: Type -> Type). GhcMonad m => m DynFlags
GHC.getSessionDynFlags
          [InstalledUnitId]
_ <- DynFlags -> m [InstalledUnitId]
forall (m :: Type -> Type).
GhcMonad m =>
DynFlags -> m [InstalledUnitId]
GHC.setSessionDynFlags DynFlags
df {pkgDatabase :: Maybe [(FilePath, [PackageConfig])]
DynFlags.pkgDatabase = Maybe [(FilePath, [PackageConfig])]
forall a. Maybe a
Nothing}
          m DynFlags
forall (m :: Type -> Type). GhcMonad m => m DynFlags
GHC.getSessionDynFlags
#else
        df <- GHC.getSessionDynFlags
#endif
        let df1 :: DynFlags
df1 = DynFlags -> DynFlags
setWantedLanguageExtensions DynFlags
df
            ghcTyLitNormPlugin :: ModuleName
ghcTyLitNormPlugin = FilePath -> ModuleName
GHC.mkModuleName FilePath
"GHC.TypeLits.Normalise"
            ghcTyLitExtrPlugin :: ModuleName
ghcTyLitExtrPlugin = FilePath -> ModuleName
GHC.mkModuleName FilePath
"GHC.TypeLits.Extra.Solver"
            ghcTyLitKNPlugin :: ModuleName
ghcTyLitKNPlugin   = FilePath -> ModuleName
GHC.mkModuleName FilePath
"GHC.TypeLits.KnownNat.Solver"
            dfPlug :: DynFlags
dfPlug = DynFlags
df1 { pluginModNames :: [ModuleName]
DynFlags.pluginModNames = [ModuleName] -> [ModuleName]
forall a. Eq a => [a] -> [a]
nub ([ModuleName] -> [ModuleName]) -> [ModuleName] -> [ModuleName]
forall a b. (a -> b) -> a -> b
$
                                ModuleName
ghcTyLitNormPlugin ModuleName -> [ModuleName] -> [ModuleName]
forall a. a -> [a] -> [a]
: ModuleName
ghcTyLitExtrPlugin ModuleName -> [ModuleName] -> [ModuleName]
forall a. a -> [a] -> [a]
:
                                ModuleName
ghcTyLitKNPlugin ModuleName -> [ModuleName] -> [ModuleName]
forall a. a -> [a] -> [a]
: DynFlags -> [ModuleName]
DynFlags.pluginModNames DynFlags
df1
                           , useColor :: OverridingBool
DynFlags.useColor = OverridingBool
useColor
                           , importPaths :: [FilePath]
DynFlags.importPaths = [FilePath]
idirs
                           }
        DynFlags -> m DynFlags
forall (m :: Type -> Type) a. Monad m => a -> m a
return DynFlags
dfPlug
  let dflags1 :: DynFlags
dflags1 = DynFlags
dflags
                  { optLevel :: Int
DynFlags.optLevel = Int
2
                  , ghcMode :: GhcMode
DynFlags.ghcMode  = GhcMode
GHC.CompManager
                  , ghcLink :: GhcLink
DynFlags.ghcLink  = GhcLink
GHC.LinkInMemory
                  , hscTarget :: HscTarget
DynFlags.hscTarget
                      = if Bool
DynFlags.rtsIsProfiled
                           then HscTarget
DynFlags.HscNothing
                           else DynFlags -> HscTarget
DynFlags.defaultObjectTarget (DynFlags -> HscTarget) -> DynFlags -> HscTarget
forall a b. (a -> b) -> a -> b
$
#if !MIN_VERSION_ghc(8,10,0)
                                  DynFlags.targetPlatform
#endif
                                    DynFlags
dflags
                  , reductionDepth :: IntWithInf
DynFlags.reductionDepth = IntWithInf
1000
                  }
  let dflags2 :: DynFlags
dflags2 = DynFlags -> DynFlags
unwantedOptimizationFlags DynFlags
dflags1
      ghcDynamic :: Bool
ghcDynamic = case FilePath -> [(FilePath, FilePath)] -> Maybe FilePath
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup FilePath
"GHC Dynamic" (DynFlags -> [(FilePath, FilePath)]
DynFlags.compilerInfo DynFlags
dflags) of
                    Just FilePath
"YES" -> Bool
True
                    Maybe FilePath
_          -> Bool
False
      dflags3 :: DynFlags
dflags3 = if Bool
ghcDynamic then DynFlags -> GeneralFlag -> DynFlags
DynFlags.gopt_set DynFlags
dflags2 GeneralFlag
DynFlags.Opt_BuildDynamicToo
                              else DynFlags
dflags2
  Bool -> m () -> m ()
forall (f :: Type -> Type). Applicative f => Bool -> f () -> f ()
when (GeneralFlag -> DynFlags -> Bool
DynFlags.gopt GeneralFlag
DynFlags.Opt_WorkerWrapper DynFlags
dflags3) (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$
    FilePath -> m () -> m ()
forall a. FilePath -> a -> a
trace
      ([FilePath] -> FilePath
unlines [FilePath
"WARNING:"
               ,FilePath
"`-fworker-wrapper` option is globally enabled, this can result in incorrect code."
               ,FilePath
"Are you compiling with `-O` or `-O2`? Consider adding `-fno-worker-wrapper`."
               ,FilePath
"`-fworker-wrapper` can be use in a diligent manner on a file-by-file basis"
               ,FilePath
"by using a `{-# OPTIONS_GHC -fworker-wrapper` #-} pragma."
               ])
      (() -> m ()
forall (m :: Type -> Type) a. Monad m => a -> m a
return ())
#if MIN_VERSION_ghc(8,6,0)
  HscEnv
hscenv <- m HscEnv
forall (m :: Type -> Type). GhcMonad m => m HscEnv
GHC.getSession
  DynFlags
dflags4 <- IO DynFlags -> m DynFlags
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
MonadUtils.liftIO (HscEnv -> DynFlags -> IO DynFlags
DynamicLoading.initializePlugins HscEnv
hscenv DynFlags
dflags3)
  [InstalledUnitId]
_ <- DynFlags -> m [InstalledUnitId]
forall (m :: Type -> Type).
GhcMonad m =>
DynFlags -> m [InstalledUnitId]
GHC.setSessionDynFlags DynFlags
dflags4
#else
  _ <- GHC.setSessionDynFlags dflags3
#endif
  () -> m ()
forall (m :: Type -> Type) a. Monad m => a -> m a
return ()
loadLocalModule
  :: GHC.GhcMonad m
  => HDL
  -> String
  
  
  -> m ( [CoreSyn.CoreBndr]                     
       , FamInstEnv.FamInstEnv                  
       , GHC.ModuleName                         
       , LoadedBinders
       , [CoreSyn.CoreBind]                     
       )
loadLocalModule :: HDL
-> FilePath
-> m ([CoreBndr], FamInstEnv, ModuleName, LoadedBinders,
      [CoreBind])
loadLocalModule HDL
hdl FilePath
modName = do
  Target
target <- FilePath -> Maybe Phase -> m Target
forall (m :: Type -> Type).
GhcMonad m =>
FilePath -> Maybe Phase -> m Target
GHC.guessTarget FilePath
modName Maybe Phase
forall a. Maybe a
Nothing
  [Target] -> m ()
forall (m :: Type -> Type). GhcMonad m => [Target] -> m ()
GHC.setTargets [Target
target]
  ModuleGraph
modGraph <- [ModuleName] -> Bool -> m ModuleGraph
forall (m :: Type -> Type).
GhcMonad m =>
[ModuleName] -> Bool -> m ModuleGraph
GHC.depanal [] Bool
False
#if MIN_VERSION_ghc(8,4,1)
  let modGraph' :: ModuleGraph
modGraph' = (ModSummary -> ModSummary) -> ModuleGraph -> ModuleGraph
GHC.mapMG ModSummary -> ModSummary
disableOptimizationsFlags ModuleGraph
modGraph
#else
  let modGraph' = map disableOptimizationsFlags modGraph
#endif
      
      
      modGraph2 :: [ModSummary]
modGraph2 = [SCC ModSummary] -> [ModSummary]
forall a. [SCC a] -> [a]
Digraph.flattenSCCs (Bool -> ModuleGraph -> Maybe ModuleName -> [SCC ModSummary]
GHC.topSortModuleGraph Bool
True ModuleGraph
modGraph' Maybe ModuleName
forall a. Maybe a
Nothing)
  IO () -> m ()
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ (ModSummary -> IO ()) -> [ModSummary] -> IO ()
forall (t :: Type -> Type) (m :: Type -> Type) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ ModSummary -> IO ()
checkMonoLocalBindsMod [ModSummary]
modGraph2
  [([CoreBind], FamInstEnv)]
tidiedMods <- [ModSummary]
-> (ModSummary -> m ([CoreBind], FamInstEnv))
-> m [([CoreBind], FamInstEnv)]
forall (t :: Type -> Type) (m :: Type -> Type) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM [ModSummary]
modGraph2 ((ModSummary -> m ([CoreBind], FamInstEnv))
 -> m [([CoreBind], FamInstEnv)])
-> (ModSummary -> m ([CoreBind], FamInstEnv))
-> m [([CoreBind], FamInstEnv)]
forall a b. (a -> b) -> a -> b
$ \ModSummary
m -> do
    DynFlags
oldDFlags <- m DynFlags
forall (m :: Type -> Type). GhcMonad m => m DynFlags
GHC.getSessionDynFlags
    ParsedModule
pMod  <- ModSummary -> m ParsedModule
forall (m :: Type -> Type).
GhcMonad m =>
ModSummary -> m ParsedModule
parseModule ModSummary
m
    [InstalledUnitId]
_ <- DynFlags -> m [InstalledUnitId]
forall (m :: Type -> Type).
GhcMonad m =>
DynFlags -> m [InstalledUnitId]
GHC.setSessionDynFlags (ModSummary -> DynFlags
GHC.ms_hspp_opts (ParsedModule -> ModSummary
GHC.pm_mod_summary ParsedModule
pMod))
    TypecheckedModule
tcMod <- ParsedModule -> m TypecheckedModule
forall (m :: Type -> Type).
GhcMonad m =>
ParsedModule -> m TypecheckedModule
GHC.typecheckModule (ParsedModule -> ParsedModule
removeStrictnessAnnotations ParsedModule
pMod)
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    TypecheckedModule
tcMod' <- TypecheckedModule -> m TypecheckedModule
forall mod (m :: Type -> Type).
(TypecheckedMod mod, GhcMonad m) =>
mod -> m mod
GHC.loadModule TypecheckedModule
tcMod
    ModGuts
dsMod <- (DesugaredModule -> ModGuts) -> m DesugaredModule -> m ModGuts
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap DesugaredModule -> ModGuts
forall m. DesugaredMod m => m -> ModGuts
GHC.coreModule (m DesugaredModule -> m ModGuts) -> m DesugaredModule -> m ModGuts
forall a b. (a -> b) -> a -> b
$ TypecheckedModule -> m DesugaredModule
forall (m :: Type -> Type).
GhcMonad m =>
TypecheckedModule -> m DesugaredModule
GHC.desugarModule TypecheckedModule
tcMod'
    HscEnv
hsc_env <- m HscEnv
forall (m :: Type -> Type). GhcMonad m => m HscEnv
GHC.getSession
#if MIN_VERSION_ghc(8,4,1)
    ModGuts
simpl_guts <- IO ModGuts -> m ModGuts
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
MonadUtils.liftIO (IO ModGuts -> m ModGuts) -> IO ModGuts -> m ModGuts
forall a b. (a -> b) -> a -> b
$ HscEnv -> [FilePath] -> ModGuts -> IO ModGuts
HscMain.hscSimplify HscEnv
hsc_env [] ModGuts
dsMod
#else
    simpl_guts <- MonadUtils.liftIO $ HscMain.hscSimplify hsc_env dsMod
#endif
    ModGuts -> m ()
forall (m :: Type -> Type). Monad m => ModGuts -> m ()
checkForInvalidPrelude ModGuts
simpl_guts
    (CgGuts
tidy_guts,ModDetails
_) <- IO (CgGuts, ModDetails) -> m (CgGuts, ModDetails)
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
MonadUtils.liftIO (IO (CgGuts, ModDetails) -> m (CgGuts, ModDetails))
-> IO (CgGuts, ModDetails) -> m (CgGuts, ModDetails)
forall a b. (a -> b) -> a -> b
$ HscEnv -> ModGuts -> IO (CgGuts, ModDetails)
TidyPgm.tidyProgram HscEnv
hsc_env ModGuts
simpl_guts
    let pgm :: [CoreBind]
pgm        = CgGuts -> [CoreBind]
HscTypes.cg_binds CgGuts
tidy_guts
    let modFamInstEnv :: FamInstEnv
modFamInstEnv = TcGblEnv -> FamInstEnv
TcRnTypes.tcg_fam_inst_env (TcGblEnv -> FamInstEnv) -> TcGblEnv -> FamInstEnv
forall a b. (a -> b) -> a -> b
$ (TcGblEnv, ModDetails) -> TcGblEnv
forall a b. (a, b) -> a
fst ((TcGblEnv, ModDetails) -> TcGblEnv)
-> (TcGblEnv, ModDetails) -> TcGblEnv
forall a b. (a -> b) -> a -> b
$ TypecheckedModule -> (TcGblEnv, ModDetails)
GHC.tm_internals_ TypecheckedModule
tcMod
    [InstalledUnitId]
_ <- DynFlags -> m [InstalledUnitId]
forall (m :: Type -> Type).
GhcMonad m =>
DynFlags -> m [InstalledUnitId]
GHC.setSessionDynFlags DynFlags
oldDFlags
    ([CoreBind], FamInstEnv) -> m ([CoreBind], FamInstEnv)
forall (m :: Type -> Type) a. Monad m => a -> m a
return ([CoreBind]
pgm,FamInstEnv
modFamInstEnv)
  let ([[CoreBind]]
binders,[FamInstEnv]
modFamInstEnvs) = [([CoreBind], FamInstEnv)] -> ([[CoreBind]], [FamInstEnv])
forall a b. [(a, b)] -> ([a], [b])
unzip [([CoreBind], FamInstEnv)]
tidiedMods
      binderIds :: [CoreBndr]
binderIds                = ((CoreBndr, CoreExpr) -> CoreBndr)
-> [(CoreBndr, CoreExpr)] -> [CoreBndr]
forall a b. (a -> b) -> [a] -> [b]
map (CoreBndr, CoreExpr) -> CoreBndr
forall a b. (a, b) -> a
fst ([CoreBind] -> [(CoreBndr, CoreExpr)]
forall b. [Bind b] -> [(b, Expr b)]
CoreSyn.flattenBinds ([[CoreBind]] -> [CoreBind]
forall (t :: Type -> Type) a. Foldable t => t [a] -> [a]
concat [[CoreBind]]
binders))
      plusFamInst :: FamInstEnv -> FamInstEnv -> FamInstEnv
plusFamInst FamInstEnv
f1 FamInstEnv
f2        = FamInstEnv -> [FamInst] -> FamInstEnv
FamInstEnv.extendFamInstEnvList FamInstEnv
f1 (FamInstEnv -> [FamInst]
FamInstEnv.famInstEnvElts FamInstEnv
f2)
      modFamInstEnvs' :: FamInstEnv
modFamInstEnvs'          = (FamInstEnv -> FamInstEnv -> FamInstEnv)
-> FamInstEnv -> [FamInstEnv] -> FamInstEnv
forall (t :: Type -> Type) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' FamInstEnv -> FamInstEnv -> FamInstEnv
plusFamInst FamInstEnv
FamInstEnv.emptyFamInstEnv [FamInstEnv]
modFamInstEnvs
      rootModule :: ModuleName
rootModule               = ModSummary -> ModuleName
GHC.ms_mod_name (ModSummary -> ModuleName)
-> ([ModSummary] -> ModSummary) -> [ModSummary] -> ModuleName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ModSummary] -> ModSummary
forall a. [a] -> a
last ([ModSummary] -> ModuleName) -> [ModSummary] -> ModuleName
forall a b. (a -> b) -> a -> b
$ [ModSummary]
modGraph2
  
  
  let rootIds :: [CoreBndr]
rootIds = ((CoreBndr, CoreExpr) -> CoreBndr)
-> [(CoreBndr, CoreExpr)] -> [CoreBndr]
forall a b. (a -> b) -> [a] -> [b]
map (CoreBndr, CoreExpr) -> CoreBndr
forall a b. (a, b) -> a
fst ([(CoreBndr, CoreExpr)] -> [CoreBndr])
-> ([CoreBind] -> [(CoreBndr, CoreExpr)])
-> [CoreBind]
-> [CoreBndr]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [CoreBind] -> [(CoreBndr, CoreExpr)]
forall b. [Bind b] -> [(b, Expr b)]
CoreSyn.flattenBinds ([CoreBind] -> [CoreBndr]) -> [CoreBind] -> [CoreBndr]
forall a b. (a -> b) -> a -> b
$ [[CoreBind]] -> [CoreBind]
forall a. [a] -> a
last [[CoreBind]]
binders
  LoadedBinders
loaded0 <- HDL -> UniqSet CoreBndr -> [CoreBind] -> m LoadedBinders
forall (m :: Type -> Type).
GhcMonad m =>
HDL -> UniqSet CoreBndr -> [CoreBind] -> m LoadedBinders
loadExternalExprs HDL
hdl ([CoreBndr] -> UniqSet CoreBndr
forall a. Uniquable a => [a] -> UniqSet a
UniqSet.mkUniqSet [CoreBndr]
binderIds) ([[CoreBind]] -> [CoreBind]
forall (t :: Type -> Type) a. Foldable t => t [a] -> [a]
concat [[CoreBind]]
binders)
  
  [Either UnresolvedPrimitive FilePath]
localPrims <- HDL -> [CoreBndr] -> m [Either UnresolvedPrimitive FilePath]
forall (m :: Type -> Type).
GhcMonad m =>
HDL -> [CoreBndr] -> m [Either UnresolvedPrimitive FilePath]
findPrimitiveAnnotations HDL
hdl [CoreBndr]
binderIds
  let loaded1 :: LoadedBinders
loaded1 = LoadedBinders
loaded0{lbPrims :: [Either UnresolvedPrimitive FilePath]
lbPrims=LoadedBinders -> [Either UnresolvedPrimitive FilePath]
lbPrims LoadedBinders
loaded0 [Either UnresolvedPrimitive FilePath]
-> [Either UnresolvedPrimitive FilePath]
-> [Either UnresolvedPrimitive FilePath]
forall a. [a] -> [a] -> [a]
++ [Either UnresolvedPrimitive FilePath]
localPrims}
  let allBinders :: [CoreBind]
allBinders = [[CoreBind]] -> [CoreBind]
forall (t :: Type -> Type) a. Foldable t => t [a] -> [a]
concat [[CoreBind]]
binders [CoreBind] -> [CoreBind] -> [CoreBind]
forall a. [a] -> [a] -> [a]
++ [(CoreBndr, CoreExpr)] -> [CoreBind]
makeRecursiveGroups (LoadedBinders -> [(CoreBndr, CoreExpr)]
lbBinders LoadedBinders
loaded0)
  ([CoreBndr], FamInstEnv, ModuleName, LoadedBinders, [CoreBind])
-> m ([CoreBndr], FamInstEnv, ModuleName, LoadedBinders,
      [CoreBind])
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure ([CoreBndr]
rootIds, FamInstEnv
modFamInstEnvs', ModuleName
rootModule, LoadedBinders
loaded1, [CoreBind]
allBinders)
loadModules
  :: OverridingBool
  
  -> HDL
  
  -> String
  
  -> Maybe (DynFlags.DynFlags)
  
  -> [FilePath]
  
  -> IO ( [CoreSyn.CoreBind]                     
        , [(CoreSyn.CoreBndr,Int)]               
        , [CoreSyn.CoreBndr]                     
        , FamInstEnv.FamInstEnvs
        , [( CoreSyn.CoreBndr                    
           , Maybe TopEntity                     
           , Maybe CoreSyn.CoreBndr)]            
        , [Either UnresolvedPrimitive FilePath]
        , [DataRepr']
        , [(Text.Text, PrimitiveGuard ())]
        )
loadModules :: OverridingBool
-> HDL
-> FilePath
-> Maybe DynFlags
-> [FilePath]
-> IO
     ([CoreBind], [(CoreBndr, Int)], [CoreBndr], FamInstEnvs,
      [(CoreBndr, Maybe TopEntity, Maybe CoreBndr)],
      [Either UnresolvedPrimitive FilePath], [DataRepr'],
      [(Text, PrimitiveGuard ())])
loadModules OverridingBool
useColor HDL
hdl FilePath
modName Maybe DynFlags
dflagsM [FilePath]
idirs = do
  FilePath
libDir <- IO FilePath -> IO FilePath
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
MonadUtils.liftIO IO FilePath
ghcLibDir
  UTCTime
startTime <- IO UTCTime
Clock.getCurrentTime
  Maybe FilePath
-> Ghc
     ([CoreBind], [(CoreBndr, Int)], [CoreBndr], FamInstEnvs,
      [(CoreBndr, Maybe TopEntity, Maybe CoreBndr)],
      [Either UnresolvedPrimitive FilePath], [DataRepr'],
      [(Text, PrimitiveGuard ())])
-> IO
     ([CoreBind], [(CoreBndr, Int)], [CoreBndr], FamInstEnvs,
      [(CoreBndr, Maybe TopEntity, Maybe CoreBndr)],
      [Either UnresolvedPrimitive FilePath], [DataRepr'],
      [(Text, PrimitiveGuard ())])
forall a. Maybe FilePath -> Ghc a -> IO a
GHC.runGhc (FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just FilePath
libDir) (Ghc
   ([CoreBind], [(CoreBndr, Int)], [CoreBndr], FamInstEnvs,
    [(CoreBndr, Maybe TopEntity, Maybe CoreBndr)],
    [Either UnresolvedPrimitive FilePath], [DataRepr'],
    [(Text, PrimitiveGuard ())])
 -> IO
      ([CoreBind], [(CoreBndr, Int)], [CoreBndr], FamInstEnvs,
       [(CoreBndr, Maybe TopEntity, Maybe CoreBndr)],
       [Either UnresolvedPrimitive FilePath], [DataRepr'],
       [(Text, PrimitiveGuard ())]))
-> Ghc
     ([CoreBind], [(CoreBndr, Int)], [CoreBndr], FamInstEnvs,
      [(CoreBndr, Maybe TopEntity, Maybe CoreBndr)],
      [Either UnresolvedPrimitive FilePath], [DataRepr'],
      [(Text, PrimitiveGuard ())])
-> IO
     ([CoreBind], [(CoreBndr, Int)], [CoreBndr], FamInstEnvs,
      [(CoreBndr, Maybe TopEntity, Maybe CoreBndr)],
      [Either UnresolvedPrimitive FilePath], [DataRepr'],
      [(Text, PrimitiveGuard ())])
forall a b. (a -> b) -> a -> b
$ do
    
    
    OverridingBool -> Maybe DynFlags -> [FilePath] -> Ghc ()
forall (m :: Type -> Type).
GhcMonad m =>
OverridingBool -> Maybe DynFlags -> [FilePath] -> m ()
setupGhc OverridingBool
useColor ((\DynFlags
d -> DynFlags
d{mainFunIs :: Maybe FilePath
GHC.mainFunIs=Maybe FilePath
forall a. Maybe a
Nothing}) (DynFlags -> DynFlags) -> Maybe DynFlags -> Maybe DynFlags
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe DynFlags
dflagsM) [FilePath]
idirs
    
    
    
    
    
    ([CoreBndr]
rootIds, FamInstEnv
modFamInstEnvs, ModuleName
rootModule, LoadedBinders{[Either UnresolvedPrimitive FilePath]
[(CoreBndr, Int)]
[(CoreBndr, CoreExpr)]
[CoreBndr]
[DataRepr']
lbReprs :: LoadedBinders -> [DataRepr']
lbUnlocatable :: LoadedBinders -> [CoreBndr]
lbClassOps :: LoadedBinders -> [(CoreBndr, Int)]
lbReprs :: [DataRepr']
lbPrims :: [Either UnresolvedPrimitive FilePath]
lbUnlocatable :: [CoreBndr]
lbClassOps :: [(CoreBndr, Int)]
lbBinders :: [(CoreBndr, CoreExpr)]
lbPrims :: LoadedBinders -> [Either UnresolvedPrimitive FilePath]
lbBinders :: LoadedBinders -> [(CoreBndr, CoreExpr)]
..}, [CoreBind]
allBinders) <-
      
      
      HDL
-> FilePath
-> Ghc
     (Either
        SomeException
        ([CoreBndr], FamInstEnv, ModuleName, LoadedBinders, [CoreBind]))
forall (m :: Type -> Type).
(HasCallStack, GhcMonad m) =>
HDL
-> FilePath
-> m (Either
        SomeException
        ([CoreBndr], FamInstEnv, ModuleName, LoadedBinders, [CoreBind]))
loadExternalModule HDL
hdl FilePath
modName Ghc
  (Either
     SomeException
     ([CoreBndr], FamInstEnv, ModuleName, LoadedBinders, [CoreBind]))
-> (Either
      SomeException
      ([CoreBndr], FamInstEnv, ModuleName, LoadedBinders, [CoreBind])
    -> Ghc
         ([CoreBndr], FamInstEnv, ModuleName, LoadedBinders, [CoreBind]))
-> Ghc
     ([CoreBndr], FamInstEnv, ModuleName, LoadedBinders, [CoreBind])
forall (m :: Type -> Type) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
        Left SomeException
_loadExternalErr -> HDL
-> FilePath
-> Ghc
     ([CoreBndr], FamInstEnv, ModuleName, LoadedBinders, [CoreBind])
forall (m :: Type -> Type).
GhcMonad m =>
HDL
-> FilePath
-> m ([CoreBndr], FamInstEnv, ModuleName, LoadedBinders,
      [CoreBind])
loadLocalModule HDL
hdl FilePath
modName
        Right ([CoreBndr], FamInstEnv, ModuleName, LoadedBinders, [CoreBind])
res -> ([CoreBndr], FamInstEnv, ModuleName, LoadedBinders, [CoreBind])
-> Ghc
     ([CoreBndr], FamInstEnv, ModuleName, LoadedBinders, [CoreBind])
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure ([CoreBndr], FamInstEnv, ModuleName, LoadedBinders, [CoreBind])
res
    let allBinderIds :: [CoreBndr]
allBinderIds = ((CoreBndr, CoreExpr) -> CoreBndr)
-> [(CoreBndr, CoreExpr)] -> [CoreBndr]
forall a b. (a -> b) -> [a] -> [b]
map (CoreBndr, CoreExpr) -> CoreBndr
forall a b. (a, b) -> a
fst ([CoreBind] -> [(CoreBndr, CoreExpr)]
forall b. [Bind b] -> [(b, Expr b)]
CoreSyn.flattenBinds [CoreBind]
allBinders)
    UTCTime
modTime <- UTCTime
startTime UTCTime -> Int -> Int
forall a b. NFData a => a -> b -> b
`deepseq` [CoreBndr] -> Int
forall (t :: Type -> Type) a. Foldable t => t a -> Int
length [CoreBndr]
allBinderIds Int -> Ghc UTCTime -> Ghc UTCTime
`seq` IO UTCTime -> Ghc UTCTime
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
MonadUtils.liftIO IO UTCTime
Clock.getCurrentTime
    let modStartDiff :: FilePath
modStartDiff = UTCTime -> UTCTime -> FilePath
reportTimeDiff UTCTime
modTime UTCTime
startTime
    IO () -> Ghc ()
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
MonadUtils.liftIO (IO () -> Ghc ()) -> IO () -> Ghc ()
forall a b. (a -> b) -> a -> b
$ FilePath -> IO ()
putStrLn (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ FilePath
"GHC: Parsing and optimising modules took: " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
modStartDiff
    UTCTime
extTime <- UTCTime
modTime UTCTime -> Int -> Int
forall a b. NFData a => a -> b -> b
`deepseq` [CoreBndr] -> Int
forall (t :: Type -> Type) a. Foldable t => t a -> Int
length [CoreBndr]
lbUnlocatable Int -> Ghc UTCTime -> Ghc UTCTime
forall a b. NFData a => a -> b -> b
`deepseq` IO UTCTime -> Ghc UTCTime
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
MonadUtils.liftIO IO UTCTime
Clock.getCurrentTime
    let extModDiff :: FilePath
extModDiff = UTCTime -> UTCTime -> FilePath
reportTimeDiff UTCTime
extTime UTCTime
modTime
    IO () -> Ghc ()
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
MonadUtils.liftIO (IO () -> Ghc ()) -> IO () -> Ghc ()
forall a b. (a -> b) -> a -> b
$ FilePath -> IO ()
putStrLn (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ FilePath
"GHC: Loading external modules from interface files took: " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
extModDiff
    
    
    HscEnv
hscEnv <- Ghc HscEnv
forall (m :: Type -> Type). GhcMonad m => m HscEnv
GHC.getSession
#if MIN_VERSION_ghc(8,6,0)
    FamInstEnvs
famInstEnvs <- do
      (Messages
msgs, Maybe FamInstEnvs
m) <- IO (Messages, Maybe FamInstEnvs)
-> Ghc (Messages, Maybe FamInstEnvs)
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
TcRnMonad.liftIO (IO (Messages, Maybe FamInstEnvs)
 -> Ghc (Messages, Maybe FamInstEnvs))
-> IO (Messages, Maybe FamInstEnvs)
-> Ghc (Messages, Maybe FamInstEnvs)
forall a b. (a -> b) -> a -> b
$ HscEnv -> TcM FamInstEnvs -> IO (Messages, Maybe FamInstEnvs)
forall a. HscEnv -> TcM a -> IO (Messages, Maybe a)
TcRnMonad.initTcInteractive HscEnv
hscEnv TcM FamInstEnvs
FamInst.tcGetFamInstEnvs
      case Maybe FamInstEnvs
m of
        Maybe FamInstEnvs
Nothing -> IO FamInstEnvs -> Ghc FamInstEnvs
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
TcRnMonad.liftIO (IO FamInstEnvs -> Ghc FamInstEnvs)
-> IO FamInstEnvs -> Ghc FamInstEnvs
forall a b. (a -> b) -> a -> b
$ SourceError -> IO FamInstEnvs
forall e a. Exception e => e -> IO a
throwIO (ErrorMessages -> SourceError
HscTypes.mkSrcErr (Messages -> ErrorMessages
forall a b. (a, b) -> b
snd Messages
msgs))
        Just FamInstEnvs
x  -> FamInstEnvs -> Ghc FamInstEnvs
forall (m :: Type -> Type) a. Monad m => a -> m a
return FamInstEnvs
x
#else
    famInstEnvs <- TcRnMonad.liftIO $ TcRnMonad.initTcForLookup hscEnv FamInst.tcGetFamInstEnvs
#endif
    
    
    
    [(CoreBndr, Maybe TopEntity)]
allSyn     <- ((CoreBndr, TopEntity) -> (CoreBndr, Maybe TopEntity))
-> [(CoreBndr, TopEntity)] -> [(CoreBndr, Maybe TopEntity)]
forall a b. (a -> b) -> [a] -> [b]
map ((TopEntity -> Maybe TopEntity)
-> (CoreBndr, TopEntity) -> (CoreBndr, Maybe TopEntity)
forall (a :: Type -> Type -> Type) b c d.
Arrow a =>
a b c -> a (d, b) (d, c)
second TopEntity -> Maybe TopEntity
forall a. a -> Maybe a
Just) ([(CoreBndr, TopEntity)] -> [(CoreBndr, Maybe TopEntity)])
-> Ghc [(CoreBndr, TopEntity)] -> Ghc [(CoreBndr, Maybe TopEntity)]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> [CoreBndr] -> Ghc [(CoreBndr, TopEntity)]
forall (m :: Type -> Type).
GhcMonad m =>
[CoreBndr] -> m [(CoreBndr, TopEntity)]
findSynthesizeAnnotations [CoreBndr]
allBinderIds
    [(CoreBndr, Maybe TopEntity)]
topSyn     <- ((CoreBndr, TopEntity) -> (CoreBndr, Maybe TopEntity))
-> [(CoreBndr, TopEntity)] -> [(CoreBndr, Maybe TopEntity)]
forall a b. (a -> b) -> [a] -> [b]
map ((TopEntity -> Maybe TopEntity)
-> (CoreBndr, TopEntity) -> (CoreBndr, Maybe TopEntity)
forall (a :: Type -> Type -> Type) b c d.
Arrow a =>
a b c -> a (d, b) (d, c)
second TopEntity -> Maybe TopEntity
forall a. a -> Maybe a
Just) ([(CoreBndr, TopEntity)] -> [(CoreBndr, Maybe TopEntity)])
-> Ghc [(CoreBndr, TopEntity)] -> Ghc [(CoreBndr, Maybe TopEntity)]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> [CoreBndr] -> Ghc [(CoreBndr, TopEntity)]
forall (m :: Type -> Type).
GhcMonad m =>
[CoreBndr] -> m [(CoreBndr, TopEntity)]
findSynthesizeAnnotations [CoreBndr]
rootIds
    [(CoreBndr, CoreBndr)]
benchAnn   <- [CoreBndr] -> Ghc [(CoreBndr, CoreBndr)]
forall (m :: Type -> Type).
GhcMonad m =>
[CoreBndr] -> m [(CoreBndr, CoreBndr)]
findTestBenchAnnotations [CoreBndr]
rootIds
    [DataRepr']
reprs'     <- Ghc [DataRepr']
forall (m :: Type -> Type). GhcMonad m => m [DataRepr']
findCustomReprAnnotations
    [(Text, PrimitiveGuard ())]
primGuards <- [CoreBndr] -> Ghc [(Text, PrimitiveGuard ())]
forall (m :: Type -> Type).
GhcMonad m =>
[CoreBndr] -> m [(Text, PrimitiveGuard ())]
findPrimitiveGuardAnnotations [CoreBndr]
allBinderIds
    let topEntityName :: FilePath
topEntityName = FilePath -> Maybe FilePath -> FilePath
forall a. a -> Maybe a -> a
fromMaybe FilePath
"topEntity" (DynFlags -> Maybe FilePath
GHC.mainFunIs (DynFlags -> Maybe FilePath) -> Maybe DynFlags -> Maybe FilePath
forall (m :: Type -> Type) a b. Monad m => (a -> m b) -> m a -> m b
=<< Maybe DynFlags
dflagsM)
        varNameString :: CoreBndr -> FilePath
varNameString = OccName -> FilePath
OccName.occNameString (OccName -> FilePath)
-> (CoreBndr -> OccName) -> CoreBndr -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name -> OccName
Name.nameOccName (Name -> OccName) -> (CoreBndr -> Name) -> CoreBndr -> OccName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CoreBndr -> Name
Var.varName
        topEntities :: [CoreBndr]
topEntities = (CoreBndr -> Bool) -> [CoreBndr] -> [CoreBndr]
forall a. (a -> Bool) -> [a] -> [a]
filter ((FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
==FilePath
topEntityName) (FilePath -> Bool) -> (CoreBndr -> FilePath) -> CoreBndr -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CoreBndr -> FilePath
varNameString) [CoreBndr]
rootIds
        benches :: [CoreBndr]
benches     = (CoreBndr -> Bool) -> [CoreBndr] -> [CoreBndr]
forall a. (a -> Bool) -> [a] -> [a]
filter ((FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
"testBench") (FilePath -> Bool) -> (CoreBndr -> FilePath) -> CoreBndr -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CoreBndr -> FilePath
varNameString) [CoreBndr]
rootIds
        mergeBench :: (CoreBndr, b) -> (CoreBndr, b, Maybe CoreBndr)
mergeBench (CoreBndr
x,b
y) = (CoreBndr
x,b
y,CoreBndr -> [(CoreBndr, CoreBndr)] -> Maybe CoreBndr
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup CoreBndr
x [(CoreBndr, CoreBndr)]
benchAnn)
        allSyn' :: [(CoreBndr, Maybe TopEntity, Maybe CoreBndr)]
allSyn'     = ((CoreBndr, Maybe TopEntity)
 -> (CoreBndr, Maybe TopEntity, Maybe CoreBndr))
-> [(CoreBndr, Maybe TopEntity)]
-> [(CoreBndr, Maybe TopEntity, Maybe CoreBndr)]
forall a b. (a -> b) -> [a] -> [b]
map (CoreBndr, Maybe TopEntity)
-> (CoreBndr, Maybe TopEntity, Maybe CoreBndr)
forall b. (CoreBndr, b) -> (CoreBndr, b, Maybe CoreBndr)
mergeBench [(CoreBndr, Maybe TopEntity)]
allSyn
    [(CoreBndr, Maybe TopEntity, Maybe CoreBndr)]
topEntities' <-
      case ([CoreBndr]
topEntities, [(CoreBndr, Maybe TopEntity)]
topSyn) of
        ([], []) ->
          let modName1 :: FilePath
modName1 = SDoc -> FilePath
Outputable.showSDocUnsafe (ModuleName -> SDoc
forall a. Outputable a => a -> SDoc
ppr ModuleName
rootModule) in
          if FilePath
topEntityName FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
/= FilePath
"topEntity" then
            FilePath -> Ghc [(CoreBndr, Maybe TopEntity, Maybe CoreBndr)]
forall a. FilePath -> a
Panic.pgmError [I.i|
              No top-level function called '#{topEntityName}' found. Did you
              forget to export it?
            |]
          else
            FilePath -> Ghc [(CoreBndr, Maybe TopEntity, Maybe CoreBndr)]
forall a. FilePath -> a
Panic.pgmError [I.i|
              No top-level function called 'topEntity' found, nor a function with
              a 'Synthesize' annotation in module #{modName1}. Did you forget to
              export them?
              For more information on 'Synthesize' annotations, check out the
              documentation of "Clash.Annotations.TopEntity".
            |]
        ([], [(CoreBndr, Maybe TopEntity)]
_) ->
          [(CoreBndr, Maybe TopEntity, Maybe CoreBndr)]
-> Ghc [(CoreBndr, Maybe TopEntity, Maybe CoreBndr)]
forall (m :: Type -> Type) a. Monad m => a -> m a
return [(CoreBndr, Maybe TopEntity, Maybe CoreBndr)]
allSyn'
        ([CoreBndr
x], [(CoreBndr, Maybe TopEntity)]
_) ->
          case CoreBndr
-> [(CoreBndr, Maybe TopEntity)] -> Maybe (Maybe TopEntity)
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup CoreBndr
x [(CoreBndr, Maybe TopEntity)]
topSyn of
            Maybe (Maybe TopEntity)
Nothing ->
              case CoreBndr -> [(CoreBndr, CoreBndr)] -> Maybe CoreBndr
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup CoreBndr
x [(CoreBndr, CoreBndr)]
benchAnn of
                Maybe CoreBndr
Nothing -> [(CoreBndr, Maybe TopEntity, Maybe CoreBndr)]
-> Ghc [(CoreBndr, Maybe TopEntity, Maybe CoreBndr)]
forall (m :: Type -> Type) a. Monad m => a -> m a
return ((CoreBndr
x,Maybe TopEntity
forall a. Maybe a
Nothing,[CoreBndr] -> Maybe CoreBndr
forall a. [a] -> Maybe a
listToMaybe [CoreBndr]
benches)(CoreBndr, Maybe TopEntity, Maybe CoreBndr)
-> [(CoreBndr, Maybe TopEntity, Maybe CoreBndr)]
-> [(CoreBndr, Maybe TopEntity, Maybe CoreBndr)]
forall a. a -> [a] -> [a]
:[(CoreBndr, Maybe TopEntity, Maybe CoreBndr)]
allSyn')
                Just CoreBndr
y  -> [(CoreBndr, Maybe TopEntity, Maybe CoreBndr)]
-> Ghc [(CoreBndr, Maybe TopEntity, Maybe CoreBndr)]
forall (m :: Type -> Type) a. Monad m => a -> m a
return ((CoreBndr
x,Maybe TopEntity
forall a. Maybe a
Nothing,CoreBndr -> Maybe CoreBndr
forall a. a -> Maybe a
Just CoreBndr
y)(CoreBndr, Maybe TopEntity, Maybe CoreBndr)
-> [(CoreBndr, Maybe TopEntity, Maybe CoreBndr)]
-> [(CoreBndr, Maybe TopEntity, Maybe CoreBndr)]
forall a. a -> [a] -> [a]
:[(CoreBndr, Maybe TopEntity, Maybe CoreBndr)]
allSyn')
            Just Maybe TopEntity
_ ->
              [(CoreBndr, Maybe TopEntity, Maybe CoreBndr)]
-> Ghc [(CoreBndr, Maybe TopEntity, Maybe CoreBndr)]
forall (m :: Type -> Type) a. Monad m => a -> m a
return [(CoreBndr, Maybe TopEntity, Maybe CoreBndr)]
allSyn'
        ([CoreBndr]
_, [(CoreBndr, Maybe TopEntity)]
_) ->
          FilePath -> Ghc [(CoreBndr, Maybe TopEntity, Maybe CoreBndr)]
forall a. FilePath -> a
Panic.pgmError (FilePath -> Ghc [(CoreBndr, Maybe TopEntity, Maybe CoreBndr)])
-> FilePath -> Ghc [(CoreBndr, Maybe TopEntity, Maybe CoreBndr)]
forall a b. (a -> b) -> a -> b
$ $(FilePath
curLoc) FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"Multiple 'topEntities' found."
    let reprs1 :: [DataRepr']
reprs1 = [DataRepr']
lbReprs [DataRepr'] -> [DataRepr'] -> [DataRepr']
forall a. [a] -> [a] -> [a]
++ [DataRepr']
reprs'
    UTCTime
annTime <-
      UTCTime
extTime
        UTCTime -> Int -> Int
forall a b. NFData a => a -> b -> b
`deepseq` [(CoreBndr, Maybe TopEntity, Maybe CoreBndr)] -> Int
forall (t :: Type -> Type) a. Foldable t => t a -> Int
length [(CoreBndr, Maybe TopEntity, Maybe CoreBndr)]
topEntities'
        Int
-> [Either UnresolvedPrimitive FilePath]
-> [Either UnresolvedPrimitive FilePath]
forall a b. NFData a => a -> b -> b
`deepseq` [Either UnresolvedPrimitive FilePath]
lbPrims
        [Either UnresolvedPrimitive FilePath] -> [DataRepr'] -> [DataRepr']
forall a b. NFData a => a -> b -> b
`deepseq` [DataRepr']
reprs1
        [DataRepr']
-> [(Text, PrimitiveGuard ())] -> [(Text, PrimitiveGuard ())]
forall a b. NFData a => a -> b -> b
`deepseq` [(Text, PrimitiveGuard ())]
primGuards
        [(Text, PrimitiveGuard ())] -> Ghc UTCTime -> Ghc UTCTime
forall a b. NFData a => a -> b -> b
`deepseq` IO UTCTime -> Ghc UTCTime
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
MonadUtils.liftIO IO UTCTime
Clock.getCurrentTime
    let annExtDiff :: FilePath
annExtDiff = UTCTime -> UTCTime -> FilePath
reportTimeDiff UTCTime
annTime UTCTime
extTime
    IO () -> Ghc ()
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
MonadUtils.liftIO (IO () -> Ghc ()) -> IO () -> Ghc ()
forall a b. (a -> b) -> a -> b
$ FilePath -> IO ()
putStrLn (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ FilePath
"GHC: Parsing annotations took: " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
annExtDiff
    ([CoreBind], [(CoreBndr, Int)], [CoreBndr], FamInstEnvs,
 [(CoreBndr, Maybe TopEntity, Maybe CoreBndr)],
 [Either UnresolvedPrimitive FilePath], [DataRepr'],
 [(Text, PrimitiveGuard ())])
-> Ghc
     ([CoreBind], [(CoreBndr, Int)], [CoreBndr], FamInstEnvs,
      [(CoreBndr, Maybe TopEntity, Maybe CoreBndr)],
      [Either UnresolvedPrimitive FilePath], [DataRepr'],
      [(Text, PrimitiveGuard ())])
forall (m :: Type -> Type) a. Monad m => a -> m a
return ( [CoreBind]
allBinders
           , [(CoreBndr, Int)]
lbClassOps
           , [CoreBndr]
lbUnlocatable
           , (FamInstEnvs -> FamInstEnv
forall a b. (a, b) -> a
fst FamInstEnvs
famInstEnvs, FamInstEnv
modFamInstEnvs)
           , [(CoreBndr, Maybe TopEntity, Maybe CoreBndr)]
topEntities'
           , [Either UnresolvedPrimitive FilePath]
lbPrims
           , [DataRepr']
reprs1
           , [(Text, PrimitiveGuard ())]
primGuards
           )
makeRecursiveGroups
  :: [(CoreSyn.CoreBndr,CoreSyn.CoreExpr)]
  -> [CoreSyn.CoreBind]
makeRecursiveGroups :: [(CoreBndr, CoreExpr)] -> [CoreBind]
makeRecursiveGroups
  = (SCC (CoreBndr, CoreExpr) -> CoreBind)
-> [SCC (CoreBndr, CoreExpr)] -> [CoreBind]
forall a b. (a -> b) -> [a] -> [b]
map SCC (CoreBndr, CoreExpr) -> CoreBind
makeBind
  ([SCC (CoreBndr, CoreExpr)] -> [CoreBind])
-> ([(CoreBndr, CoreExpr)] -> [SCC (CoreBndr, CoreExpr)])
-> [(CoreBndr, CoreExpr)]
-> [CoreBind]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Node Unique (CoreBndr, CoreExpr)] -> [SCC (CoreBndr, CoreExpr)]
forall key payload.
Uniquable key =>
[Node key payload] -> [SCC payload]
Digraph.stronglyConnCompFromEdgedVerticesUniq
  ([Node Unique (CoreBndr, CoreExpr)] -> [SCC (CoreBndr, CoreExpr)])
-> ([(CoreBndr, CoreExpr)] -> [Node Unique (CoreBndr, CoreExpr)])
-> [(CoreBndr, CoreExpr)]
-> [SCC (CoreBndr, CoreExpr)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((CoreBndr, CoreExpr) -> Node Unique (CoreBndr, CoreExpr))
-> [(CoreBndr, CoreExpr)] -> [Node Unique (CoreBndr, CoreExpr)]
forall a b. (a -> b) -> [a] -> [b]
map (CoreBndr, CoreExpr) -> Node Unique (CoreBndr, CoreExpr)
makeNode
  where
    makeNode
      :: (CoreSyn.CoreBndr,CoreSyn.CoreExpr)
      -> Digraph.Node Unique.Unique (CoreSyn.CoreBndr,CoreSyn.CoreExpr)
    makeNode :: (CoreBndr, CoreExpr) -> Node Unique (CoreBndr, CoreExpr)
makeNode (CoreBndr
b,CoreExpr
e) =
#if MIN_VERSION_ghc(8,4,1)
      (CoreBndr, CoreExpr)
-> Unique -> [Unique] -> Node Unique (CoreBndr, CoreExpr)
forall key payload. payload -> key -> [key] -> Node key payload
Digraph.DigraphNode
        (CoreBndr
b,CoreExpr
e)
        (CoreBndr -> Unique
Var.varUnique CoreBndr
b)
        (UniqSet CoreBndr -> [Unique]
forall elt. UniqSet elt -> [Unique]
UniqSet.nonDetKeysUniqSet (CoreExpr -> UniqSet CoreBndr
CoreFVs.exprFreeIds CoreExpr
e))
#else
      ((b,e)
      ,Var.varUnique b
      ,UniqSet.nonDetKeysUniqSet (CoreFVs.exprFreeIds e))
#endif
    makeBind
      :: Digraph.SCC (CoreSyn.CoreBndr,CoreSyn.CoreExpr)
      -> CoreSyn.CoreBind
    makeBind :: SCC (CoreBndr, CoreExpr) -> CoreBind
makeBind (Digraph.AcyclicSCC (CoreBndr
b,CoreExpr
e)) = CoreBndr -> CoreExpr -> CoreBind
forall b. b -> Expr b -> Bind b
CoreSyn.NonRec CoreBndr
b CoreExpr
e
    makeBind (Digraph.CyclicSCC [(CoreBndr, CoreExpr)]
bs)     = [(CoreBndr, CoreExpr)] -> CoreBind
forall b. [(b, Expr b)] -> Bind b
CoreSyn.Rec [(CoreBndr, CoreExpr)]
bs
errOnDuplicateAnnotations
  :: String
  
  -> [CoreSyn.CoreBndr]
  
  -> [[a]]
  
  -> [(CoreSyn.CoreBndr, a)]
errOnDuplicateAnnotations :: FilePath -> [CoreBndr] -> [[a]] -> [(CoreBndr, a)]
errOnDuplicateAnnotations FilePath
nm [CoreBndr]
bndrs [[a]]
anns =
  [(CoreBndr, [a])] -> [(CoreBndr, a)]
forall a. [(CoreBndr, [a])] -> [(CoreBndr, a)]
go ([CoreBndr] -> [[a]] -> [(CoreBndr, [a])]
forall a b. [a] -> [b] -> [(a, b)]
zip [CoreBndr]
bndrs [[a]]
anns)
 where
  go
    :: [(CoreSyn.CoreBndr, [a])]
    -> [(CoreSyn.CoreBndr, a)]
  go :: [(CoreBndr, [a])] -> [(CoreBndr, a)]
go []             = []
  go ((CoreBndr
_, []):[(CoreBndr, [a])]
ps)   = [(CoreBndr, [a])] -> [(CoreBndr, a)]
forall a. [(CoreBndr, [a])] -> [(CoreBndr, a)]
go [(CoreBndr, [a])]
ps
  go ((CoreBndr
b, [a
p]):[(CoreBndr, [a])]
ps)  = (CoreBndr
b, a
p) (CoreBndr, a) -> [(CoreBndr, a)] -> [(CoreBndr, a)]
forall a. a -> [a] -> [a]
: ([(CoreBndr, [a])] -> [(CoreBndr, a)]
forall a. [(CoreBndr, [a])] -> [(CoreBndr, a)]
go [(CoreBndr, [a])]
ps)
  go ((CoreBndr
b, [a]
_):[(CoreBndr, [a])]
_)  =
    FilePath -> [(CoreBndr, a)]
forall a. FilePath -> a
Panic.pgmError (FilePath -> [(CoreBndr, a)]) -> FilePath -> [(CoreBndr, a)]
forall a b. (a -> b) -> a -> b
$ FilePath
"The following value has multiple "
                  FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"'" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
nm FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"' annotations: "
                  FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ SDoc -> FilePath
Outputable.showSDocUnsafe (CoreBndr -> SDoc
forall a. Outputable a => a -> SDoc
ppr CoreBndr
b)
findAnnotationsByTargets
  :: GHC.GhcMonad m
  => Typeable a
  => Data a
  => [Annotations.AnnTarget Name.Name]
  -> m [[a]]
findAnnotationsByTargets :: [AnnTarget Name] -> m [[a]]
findAnnotationsByTargets [AnnTarget Name]
targets =
  (AnnTarget Name -> m [a]) -> [AnnTarget Name] -> m [[a]]
forall (t :: Type -> Type) (m :: Type -> Type) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (([Word8] -> a) -> AnnTarget Name -> m [a]
forall (m :: Type -> Type) a.
(GhcMonad m, Typeable a) =>
([Word8] -> a) -> AnnTarget Name -> m [a]
GHC.findGlobalAnns [Word8] -> a
forall a. Data a => [Word8] -> a
GhcPlugins.deserializeWithData) [AnnTarget Name]
targets
findAllModuleAnnotations
  :: GHC.GhcMonad m
  => Data a
  => Typeable a
  => m [a]
findAllModuleAnnotations :: m [a]
findAllModuleAnnotations = do
  HscEnv
hsc_env <- m HscEnv
forall (m :: Type -> Type). GhcMonad m => m HscEnv
GHC.getSession
  AnnEnv
ann_env <- IO AnnEnv -> m AnnEnv
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO AnnEnv -> m AnnEnv) -> IO AnnEnv -> m AnnEnv
forall a b. (a -> b) -> a -> b
$ HscEnv -> Maybe ModGuts -> IO AnnEnv
HscTypes.prepareAnnotations HscEnv
hsc_env Maybe ModGuts
forall a. Maybe a
Nothing
  [a] -> m [a]
forall (m :: Type -> Type) a. Monad m => a -> m a
return ([a] -> m [a]) -> [a] -> m [a]
forall a b. (a -> b) -> a -> b
$ [[a]] -> [a]
forall (t :: Type -> Type) a. Foldable t => t [a] -> [a]
concat
         ([[a]] -> [a]) -> [[a]] -> [a]
forall a b. (a -> b) -> a -> b
$ UniqFM [a] -> [[a]]
forall elt. UniqFM elt -> [elt]
UniqFM.nonDetEltsUFM
         (UniqFM [a] -> [[a]]) -> UniqFM [a] -> [[a]]
forall a b. (a -> b) -> a -> b
$ ([Word8] -> a) -> AnnEnv -> UniqFM [a]
forall a. Typeable a => ([Word8] -> a) -> AnnEnv -> UniqFM [a]
Annotations.deserializeAnns [Word8] -> a
forall a. Data a => [Word8] -> a
GhcPlugins.deserializeWithData AnnEnv
ann_env
findNamedAnnotations
  :: GHC.GhcMonad m
  => Data a
  => Typeable a
  => [CoreSyn.CoreBndr]
  -> m [[a]]
findNamedAnnotations :: [CoreBndr] -> m [[a]]
findNamedAnnotations [CoreBndr]
bndrs =
  [AnnTarget Name] -> m [[a]]
forall (m :: Type -> Type) a.
(GhcMonad m, Typeable a, Data a) =>
[AnnTarget Name] -> m [[a]]
findAnnotationsByTargets ((CoreBndr -> AnnTarget Name) -> [CoreBndr] -> [AnnTarget Name]
forall a b. (a -> b) -> [a] -> [b]
map (Name -> AnnTarget Name
forall name. name -> AnnTarget name
Annotations.NamedTarget (Name -> AnnTarget Name)
-> (CoreBndr -> Name) -> CoreBndr -> AnnTarget Name
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CoreBndr -> Name
Var.varName) [CoreBndr]
bndrs)
findPrimitiveGuardAnnotations
  :: GHC.GhcMonad m
  => [CoreSyn.CoreBndr]
  -> m [(Text.Text, (PrimitiveGuard ()))]
findPrimitiveGuardAnnotations :: [CoreBndr] -> m [(Text, PrimitiveGuard ())]
findPrimitiveGuardAnnotations [CoreBndr]
bndrs = do
  [[PrimitiveGuard ()]]
anns0 <- [CoreBndr] -> m [[PrimitiveGuard ()]]
forall (m :: Type -> Type) a.
(GhcMonad m, Data a, Typeable a) =>
[CoreBndr] -> m [[a]]
findNamedAnnotations [CoreBndr]
bndrs
  let anns1 :: [(CoreBndr, PrimitiveGuard ())]
anns1 = FilePath
-> [CoreBndr]
-> [[PrimitiveGuard ()]]
-> [(CoreBndr, PrimitiveGuard ())]
forall a. FilePath -> [CoreBndr] -> [[a]] -> [(CoreBndr, a)]
errOnDuplicateAnnotations FilePath
"PrimitiveGuard" [CoreBndr]
bndrs [[PrimitiveGuard ()]]
anns0
  [(Text, PrimitiveGuard ())] -> m [(Text, PrimitiveGuard ())]
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure (((CoreBndr, PrimitiveGuard ()) -> (Text, PrimitiveGuard ()))
-> [(CoreBndr, PrimitiveGuard ())] -> [(Text, PrimitiveGuard ())]
forall a b. (a -> b) -> [a] -> [b]
map ((CoreBndr -> Text)
-> (CoreBndr, PrimitiveGuard ()) -> (Text, PrimitiveGuard ())
forall (a :: Type -> Type -> Type) b c d.
Arrow a =>
a b c -> a (b, d) (c, d)
first (Name -> Text
qualifiedNameString' (Name -> Text) -> (CoreBndr -> Name) -> CoreBndr -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CoreBndr -> Name
Var.varName)) [(CoreBndr, PrimitiveGuard ())]
anns1)
findCustomReprAnnotations
  :: GHC.GhcMonad m
  => m [DataRepr']
findCustomReprAnnotations :: m [DataRepr']
findCustomReprAnnotations =
  (DataReprAnn -> DataRepr') -> [DataReprAnn] -> [DataRepr']
forall a b. (a -> b) -> [a] -> [b]
map DataReprAnn -> DataRepr'
dataReprAnnToDataRepr' ([DataReprAnn] -> [DataRepr']) -> m [DataReprAnn] -> m [DataRepr']
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> m [DataReprAnn]
forall (m :: Type -> Type) a.
(GhcMonad m, Data a, Typeable a) =>
m [a]
findAllModuleAnnotations
findSynthesizeAnnotations
  :: GHC.GhcMonad m
  => [CoreSyn.CoreBndr]
  -> m [(CoreSyn.CoreBndr, TopEntity)]
findSynthesizeAnnotations :: [CoreBndr] -> m [(CoreBndr, TopEntity)]
findSynthesizeAnnotations [CoreBndr]
bndrs = do
  [[TopEntity]]
anns <- [CoreBndr] -> m [[TopEntity]]
forall (m :: Type -> Type) a.
(GhcMonad m, Data a, Typeable a) =>
[CoreBndr] -> m [[a]]
findNamedAnnotations [CoreBndr]
bndrs
  [(CoreBndr, TopEntity)] -> m [(CoreBndr, TopEntity)]
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure (FilePath -> [CoreBndr] -> [[TopEntity]] -> [(CoreBndr, TopEntity)]
forall a. FilePath -> [CoreBndr] -> [[a]] -> [(CoreBndr, a)]
errOnDuplicateAnnotations FilePath
"Synthesize" [CoreBndr]
bndrs (([TopEntity] -> [TopEntity]) -> [[TopEntity]] -> [[TopEntity]]
forall a b. (a -> b) -> [a] -> [b]
map ((TopEntity -> Bool) -> [TopEntity] -> [TopEntity]
forall a. (a -> Bool) -> [a] -> [a]
filter TopEntity -> Bool
isSyn) [[TopEntity]]
anns))
 where
  isSyn :: TopEntity -> Bool
isSyn (Synthesize {}) = Bool
True
  isSyn TopEntity
_               = Bool
False
findTestBenchAnnotations
  :: GHC.GhcMonad m
  => [CoreSyn.CoreBndr]
  -> m [(CoreSyn.CoreBndr,CoreSyn.CoreBndr)]
findTestBenchAnnotations :: [CoreBndr] -> m [(CoreBndr, CoreBndr)]
findTestBenchAnnotations [CoreBndr]
bndrs = do
  [[TopEntity]]
anns0 <- [CoreBndr] -> m [[TopEntity]]
forall (m :: Type -> Type) a.
(GhcMonad m, Data a, Typeable a) =>
[CoreBndr] -> m [[a]]
findNamedAnnotations [CoreBndr]
bndrs
  let anns1 :: [[TopEntity]]
anns1 = ([TopEntity] -> [TopEntity]) -> [[TopEntity]] -> [[TopEntity]]
forall a b. (a -> b) -> [a] -> [b]
map ((TopEntity -> Bool) -> [TopEntity] -> [TopEntity]
forall a. (a -> Bool) -> [a] -> [a]
filter TopEntity -> Bool
isTB) [[TopEntity]]
anns0
      anns2 :: [(CoreBndr, TopEntity)]
anns2 = FilePath -> [CoreBndr] -> [[TopEntity]] -> [(CoreBndr, TopEntity)]
forall a. FilePath -> [CoreBndr] -> [[a]] -> [(CoreBndr, a)]
errOnDuplicateAnnotations FilePath
"TestBench" [CoreBndr]
bndrs [[TopEntity]]
anns1
  [(CoreBndr, CoreBndr)] -> m [(CoreBndr, CoreBndr)]
forall (m :: Type -> Type) a. Monad m => a -> m a
return (((CoreBndr, TopEntity) -> (CoreBndr, CoreBndr))
-> [(CoreBndr, TopEntity)] -> [(CoreBndr, CoreBndr)]
forall a b. (a -> b) -> [a] -> [b]
map ((TopEntity -> CoreBndr)
-> (CoreBndr, TopEntity) -> (CoreBndr, CoreBndr)
forall (a :: Type -> Type -> Type) b c d.
Arrow a =>
a b c -> a (d, b) (d, c)
second TopEntity -> CoreBndr
findTB) [(CoreBndr, TopEntity)]
anns2)
  where
    isTB :: TopEntity -> Bool
isTB (TestBench {}) = Bool
True
    isTB TopEntity
_              = Bool
False
    findTB :: TopEntity -> CoreSyn.CoreBndr
    findTB :: TopEntity -> CoreBndr
findTB (TestBench Name
tb) = case [CoreBndr] -> Maybe CoreBndr
forall a. [a] -> Maybe a
listToMaybe ((CoreBndr -> Bool) -> [CoreBndr] -> [CoreBndr]
forall a. (a -> Bool) -> [a] -> [a]
filter (Name -> CoreBndr -> Bool
forall a. Show a => a -> CoreBndr -> Bool
eqNm Name
tb) [CoreBndr]
bndrs) of
      Just CoreBndr
tb' -> CoreBndr
tb'
      Maybe CoreBndr
Nothing  -> FilePath -> CoreBndr
forall a. FilePath -> a
Panic.pgmError (FilePath -> CoreBndr) -> FilePath -> CoreBndr
forall a b. (a -> b) -> a -> b
$
        FilePath
"TestBench named: " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Name -> FilePath
forall a. Show a => a -> FilePath
show Name
tb FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" not found"
    findTB TopEntity
_ = FilePath -> CoreBndr
forall a. FilePath -> a
Panic.pgmError FilePath
"Unexpected Synthesize"
    eqNm :: a -> CoreBndr -> Bool
eqNm a
thNm CoreBndr
bndr = FilePath -> Text
Text.pack (a -> FilePath
forall a. Show a => a -> FilePath
show a
thNm) Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
qualNm
      where
        bndrNm :: Name
bndrNm  = CoreBndr -> Name
Var.varName CoreBndr
bndr
        qualNm :: Text
qualNm  = Text -> (Text -> Text) -> Maybe Text -> Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Text
occName (\Text
modName -> Text
modName Text -> Text -> Text
`Text.append` (Char
'.' Char -> Text -> Text
`Text.cons` Text
occName)) (Name -> Maybe Text
modNameM Name
bndrNm)
        occName :: Text
occName = FilePath -> Text
Text.pack (OccName -> FilePath
OccName.occNameString (Name -> OccName
Name.nameOccName Name
bndrNm))
findPrimitiveAnnotations
  :: GHC.GhcMonad m
  => HDL
  -> [CoreSyn.CoreBndr]
  -> m [Either UnresolvedPrimitive FilePath]
findPrimitiveAnnotations :: HDL -> [CoreBndr] -> m [Either UnresolvedPrimitive FilePath]
findPrimitiveAnnotations HDL
hdl [CoreBndr]
bndrs = do
  let
    annTargets :: [Maybe (AnnTarget name)]
annTargets =
     (Name -> Maybe (AnnTarget name))
-> [Name] -> [Maybe (AnnTarget name)]
forall a b. (a -> b) -> [a] -> [b]
map
       ((Module -> AnnTarget name)
-> Maybe Module -> Maybe (AnnTarget name)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap Module -> AnnTarget name
forall name. Module -> AnnTarget name
Annotations.ModuleTarget (Maybe Module -> Maybe (AnnTarget name))
-> (Name -> Maybe Module) -> Name -> Maybe (AnnTarget name)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name -> Maybe Module
Name.nameModule_maybe)
       ((CoreBndr -> Name) -> [CoreBndr] -> [Name]
forall a b. (a -> b) -> [a] -> [b]
map CoreBndr -> Name
Var.varName [CoreBndr]
bndrs)
  let
    targets :: [AnnTarget Name]
targets =
      ([Maybe (AnnTarget Name)] -> [AnnTarget Name]
forall a. [Maybe a] -> [a]
catMaybes [Maybe (AnnTarget Name)]
forall name. [Maybe (AnnTarget name)]
annTargets) [AnnTarget Name] -> [AnnTarget Name] -> [AnnTarget Name]
forall a. [a] -> [a] -> [a]
++
        ((CoreBndr -> AnnTarget Name) -> [CoreBndr] -> [AnnTarget Name]
forall a b. (a -> b) -> [a] -> [b]
map (Name -> AnnTarget Name
forall name. name -> AnnTarget name
Annotations.NamedTarget (Name -> AnnTarget Name)
-> (CoreBndr -> Name) -> CoreBndr -> AnnTarget Name
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CoreBndr -> Name
Var.varName) [CoreBndr]
bndrs)
  [[Primitive]]
anns <- [AnnTarget Name] -> m [[Primitive]]
forall (m :: Type -> Type) a.
(GhcMonad m, Typeable a, Data a) =>
[AnnTarget Name] -> m [[a]]
findAnnotationsByTargets [AnnTarget Name]
targets
  [[Either UnresolvedPrimitive FilePath]]
-> [Either UnresolvedPrimitive FilePath]
forall (t :: Type -> Type) a. Foldable t => t [a] -> [a]
concat ([[Either UnresolvedPrimitive FilePath]]
 -> [Either UnresolvedPrimitive FilePath])
-> m [[Either UnresolvedPrimitive FilePath]]
-> m [Either UnresolvedPrimitive FilePath]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$>
    ((AnnTarget Name, Primitive)
 -> m [Either UnresolvedPrimitive FilePath])
-> [(AnnTarget Name, Primitive)]
-> m [[Either UnresolvedPrimitive FilePath]]
forall (t :: Type -> Type) (m :: Type -> Type) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (HDL
-> (AnnTarget Name, Primitive)
-> m [Either UnresolvedPrimitive FilePath]
forall (m :: Type -> Type).
MonadIO m =>
HDL
-> (AnnTarget Name, Primitive)
-> m [Either UnresolvedPrimitive FilePath]
getUnresolvedPrimitives HDL
hdl)
    ([[(AnnTarget Name, Primitive)]] -> [(AnnTarget Name, Primitive)]
forall (t :: Type -> Type) a. Foldable t => t [a] -> [a]
concat ([[(AnnTarget Name, Primitive)]] -> [(AnnTarget Name, Primitive)])
-> [[(AnnTarget Name, Primitive)]] -> [(AnnTarget Name, Primitive)]
forall a b. (a -> b) -> a -> b
$ (AnnTarget Name -> [Primitive] -> [(AnnTarget Name, Primitive)])
-> [AnnTarget Name]
-> [[Primitive]]
-> [[(AnnTarget Name, Primitive)]]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (\AnnTarget Name
t -> (Primitive -> (AnnTarget Name, Primitive))
-> [Primitive] -> [(AnnTarget Name, Primitive)]
forall a b. (a -> b) -> [a] -> [b]
map ((,) AnnTarget Name
t)) [AnnTarget Name]
targets [[Primitive]]
anns)
parseModule :: GHC.GhcMonad m => GHC.ModSummary -> m GHC.ParsedModule
parseModule :: ModSummary -> m ParsedModule
parseModule ModSummary
modSum = do
  (GHC.ParsedModule ModSummary
pmModSum ParsedSource
pmParsedSource [FilePath]
extraSrc ApiAnns
anns) <-
    ModSummary -> m ParsedModule
forall (m :: Type -> Type).
GhcMonad m =>
ModSummary -> m ParsedModule
GHC.parseModule ModSummary
modSum
  ParsedModule -> m ParsedModule
forall (m :: Type -> Type) a. Monad m => a -> m a
return (ModSummary -> ParsedSource -> [FilePath] -> ApiAnns -> ParsedModule
GHC.ParsedModule
            (ModSummary -> ModSummary
disableOptimizationsFlags ModSummary
pmModSum)
            ParsedSource
pmParsedSource [FilePath]
extraSrc ApiAnns
anns)
disableOptimizationsFlags :: GHC.ModSummary -> GHC.ModSummary
disableOptimizationsFlags :: ModSummary -> ModSummary
disableOptimizationsFlags ms :: ModSummary
ms@(GHC.ModSummary {FilePath
[(Maybe FastString, Located ModuleName)]
Maybe UTCTime
Maybe HsParsedModule
Maybe StringBuffer
UTCTime
HscSource
ModLocation
Module
DynFlags
ms_mod :: ModSummary -> Module
ms_hsc_src :: ModSummary -> HscSource
ms_location :: ModSummary -> ModLocation
ms_hs_date :: ModSummary -> UTCTime
ms_obj_date :: ModSummary -> Maybe UTCTime
ms_iface_date :: ModSummary -> Maybe UTCTime
ms_hie_date :: ModSummary -> Maybe UTCTime
ms_srcimps :: ModSummary -> [(Maybe FastString, Located ModuleName)]
ms_textual_imps :: ModSummary -> [(Maybe FastString, Located ModuleName)]
ms_parsed_mod :: ModSummary -> Maybe HsParsedModule
ms_hspp_file :: ModSummary -> FilePath
ms_hspp_buf :: ModSummary -> Maybe StringBuffer
ms_hspp_buf :: Maybe StringBuffer
ms_hspp_opts :: DynFlags
ms_hspp_file :: FilePath
ms_parsed_mod :: Maybe HsParsedModule
ms_textual_imps :: [(Maybe FastString, Located ModuleName)]
ms_srcimps :: [(Maybe FastString, Located ModuleName)]
ms_hie_date :: Maybe UTCTime
ms_iface_date :: Maybe UTCTime
ms_obj_date :: Maybe UTCTime
ms_hs_date :: UTCTime
ms_location :: ModLocation
ms_hsc_src :: HscSource
ms_mod :: Module
ms_hspp_opts :: ModSummary -> DynFlags
..})
  = ModSummary
ms {ms_hspp_opts :: DynFlags
GHC.ms_hspp_opts = DynFlags
dflags}
  where
    dflags :: DynFlags
dflags = DynFlags -> DynFlags
unwantedOptimizationFlags (DynFlags
ms_hspp_opts
              { optLevel :: Int
DynFlags.optLevel = Int
2
              , reductionDepth :: IntWithInf
DynFlags.reductionDepth = IntWithInf
1000
              })
unwantedOptimizationFlags :: GHC.DynFlags -> GHC.DynFlags
unwantedOptimizationFlags :: DynFlags -> DynFlags
unwantedOptimizationFlags DynFlags
df =
  (DynFlags -> Extension -> DynFlags)
-> DynFlags -> [Extension] -> DynFlags
forall (t :: Type -> Type) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' DynFlags -> Extension -> DynFlags
DynFlags.xopt_unset
    ((DynFlags -> GeneralFlag -> DynFlags)
-> DynFlags -> [GeneralFlag] -> DynFlags
forall (t :: Type -> Type) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' DynFlags -> GeneralFlag -> DynFlags
DynFlags.gopt_unset DynFlags
df [GeneralFlag]
unwanted) [Extension]
unwantedLang
  where
    unwanted :: [GeneralFlag]
unwanted = [ GeneralFlag
Opt_LiberateCase 
               , GeneralFlag
Opt_SpecConstr 
               , GeneralFlag
Opt_IgnoreAsserts 
               , GeneralFlag
Opt_DoEtaReduction 
               , GeneralFlag
Opt_UnboxStrictFields 
               , GeneralFlag
Opt_UnboxSmallStrictFields 
#if !MIN_VERSION_ghc(8,6,0)
               , Opt_Vectorise 
               , Opt_VectorisationAvoidance 
#endif
               , GeneralFlag
Opt_RegsGraph 
               , GeneralFlag
Opt_RegsGraph 
               , GeneralFlag
Opt_PedanticBottoms 
               , GeneralFlag
Opt_LlvmTBAA 
               , GeneralFlag
Opt_CmmSink 
               , GeneralFlag
Opt_CmmElimCommonBlocks 
               , GeneralFlag
Opt_OmitYields 
               , GeneralFlag
Opt_IgnoreInterfacePragmas 
               , GeneralFlag
Opt_OmitInterfacePragmas 
               , GeneralFlag
Opt_IrrefutableTuples 
               , GeneralFlag
Opt_Loopification 
               , GeneralFlag
Opt_CprAnal 
               , GeneralFlag
Opt_FullLaziness 
               ]
    
    
    
    unwantedLang :: [Extension]
unwantedLang = [ Extension
LangExt.Strict
                   , Extension
LangExt.StrictData
                   ]
setWantedLanguageExtensions :: GHC.DynFlags -> GHC.DynFlags
setWantedLanguageExtensions :: DynFlags -> DynFlags
setWantedLanguageExtensions DynFlags
df =
   (DynFlags -> GeneralFlag -> DynFlags)
-> DynFlags -> [GeneralFlag] -> DynFlags
forall (t :: Type -> Type) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' DynFlags -> GeneralFlag -> DynFlags
DynFlags.gopt_set
    ((DynFlags -> Extension -> DynFlags)
-> DynFlags -> [Extension] -> DynFlags
forall (t :: Type -> Type) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' DynFlags -> Extension -> DynFlags
DynFlags.xopt_unset
      ((DynFlags -> Extension -> DynFlags)
-> DynFlags -> [Extension] -> DynFlags
forall (t :: Type -> Type) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' DynFlags -> Extension -> DynFlags
DynFlags.xopt_set DynFlags
df [Extension]
wantedLanguageExtensions) [Extension]
unwantedLanguageExtensions)
      [GeneralFlag]
wantedOptimizations
 where
  wantedOptimizations :: [GeneralFlag]
wantedOptimizations =
    [ GeneralFlag
Opt_CSE 
    , GeneralFlag
Opt_Specialise 
    , GeneralFlag
Opt_DoLambdaEtaExpansion 
    , GeneralFlag
Opt_CaseMerge 
    , GeneralFlag
Opt_DictsCheap 
    , GeneralFlag
Opt_ExposeAllUnfoldings 
    , GeneralFlag
Opt_ForceRecomp 
    , GeneralFlag
Opt_EnableRewriteRules 
    , GeneralFlag
Opt_SimplPreInlining 
    , GeneralFlag
Opt_StaticArgumentTransformation 
    , GeneralFlag
Opt_FloatIn 
    , GeneralFlag
Opt_DictsStrict 
    , GeneralFlag
Opt_DmdTxDictSel 
    , GeneralFlag
Opt_Strictness 
    , GeneralFlag
Opt_SpecialiseAggressively 
    , GeneralFlag
Opt_CrossModuleSpecialise 
    ]
removeStrictnessAnnotations ::
     GHC.ParsedModule
  -> GHC.ParsedModule
removeStrictnessAnnotations :: ParsedModule -> ParsedModule
removeStrictnessAnnotations ParsedModule
pm =
    ParsedModule
pm {pm_parsed_source :: ParsedSource
GHC.pm_parsed_source = (HsModule GhcPs -> HsModule GhcPs) -> ParsedSource -> ParsedSource
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap HsModule GhcPs -> HsModule GhcPs
rmPS (ParsedModule -> ParsedSource
GHC.pm_parsed_source ParsedModule
pm)}
  where
    
    rmPS :: HsModule GhcPs -> HsModule GhcPs
rmPS HsModule GhcPs
hsm = HsModule GhcPs
hsm {hsmodDecls :: [LHsDecl GhcPs]
GHC.hsmodDecls = ((LHsDecl GhcPs -> LHsDecl GhcPs)
-> [LHsDecl GhcPs] -> [LHsDecl GhcPs]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap ((LHsDecl GhcPs -> LHsDecl GhcPs)
 -> [LHsDecl GhcPs] -> [LHsDecl GhcPs])
-> ((HsDecl GhcPs -> HsDecl GhcPs)
    -> LHsDecl GhcPs -> LHsDecl GhcPs)
-> (HsDecl GhcPs -> HsDecl GhcPs)
-> [LHsDecl GhcPs]
-> [LHsDecl GhcPs]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (HsDecl GhcPs -> HsDecl GhcPs) -> LHsDecl GhcPs -> LHsDecl GhcPs
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap) HsDecl GhcPs -> HsDecl GhcPs
rmHSD (HsModule GhcPs -> [LHsDecl GhcPs]
forall pass. HsModule pass -> [LHsDecl pass]
GHC.hsmodDecls HsModule GhcPs
hsm)}
    
#if MIN_VERSION_ghc(8,6,0)
    rmHSD :: HsDecl GhcPs -> HsDecl GhcPs
rmHSD (GHC.TyClD XTyClD GhcPs
x TyClDecl GhcPs
tyClDecl) = XTyClD GhcPs -> TyClDecl GhcPs -> HsDecl GhcPs
forall p. XTyClD p -> TyClDecl p -> HsDecl p
GHC.TyClD XTyClD GhcPs
x (TyClDecl GhcPs -> TyClDecl GhcPs
rmTyClD TyClDecl GhcPs
tyClDecl)
#else
    rmHSD (GHC.TyClD tyClDecl) = GHC.TyClD (rmTyClD tyClDecl)
#endif
    rmHSD HsDecl GhcPs
hsd                  = HsDecl GhcPs
hsd
    
    rmTyClD :: TyClDecl GhcPs -> TyClDecl GhcPs
rmTyClD dc :: TyClDecl GhcPs
dc@(GHC.DataDecl {}) = TyClDecl GhcPs
dc {tcdDataDefn :: HsDataDefn GhcPs
GHC.tcdDataDefn = HsDataDefn GhcPs -> HsDataDefn GhcPs
rmDataDefn (TyClDecl GhcPs -> HsDataDefn GhcPs
forall pass. TyClDecl pass -> HsDataDefn pass
GHC.tcdDataDefn TyClDecl GhcPs
dc)}
    rmTyClD TyClDecl GhcPs
tyClD = TyClDecl GhcPs
tyClD
    
    rmDataDefn :: HsDataDefn GhcPs -> HsDataDefn GhcPs
rmDataDefn HsDataDefn GhcPs
hdf = HsDataDefn GhcPs
hdf {dd_cons :: [LConDecl GhcPs]
GHC.dd_cons = ((LConDecl GhcPs -> LConDecl GhcPs)
-> [LConDecl GhcPs] -> [LConDecl GhcPs]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap ((LConDecl GhcPs -> LConDecl GhcPs)
 -> [LConDecl GhcPs] -> [LConDecl GhcPs])
-> ((ConDecl GhcPs -> ConDecl GhcPs)
    -> LConDecl GhcPs -> LConDecl GhcPs)
-> (ConDecl GhcPs -> ConDecl GhcPs)
-> [LConDecl GhcPs]
-> [LConDecl GhcPs]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ConDecl GhcPs -> ConDecl GhcPs)
-> LConDecl GhcPs -> LConDecl GhcPs
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap) ConDecl GhcPs -> ConDecl GhcPs
rmCD (HsDataDefn GhcPs -> [LConDecl GhcPs]
forall pass. HsDataDefn pass -> [LConDecl pass]
GHC.dd_cons HsDataDefn GhcPs
hdf)}
    
#if MIN_VERSION_ghc(8,6,0)
    rmCD :: ConDecl GhcPs -> ConDecl GhcPs
rmCD gadt :: ConDecl GhcPs
gadt@(GHC.ConDeclGADT {}) = ConDecl GhcPs
gadt {con_res_ty :: LHsType GhcPs
GHC.con_res_ty = LHsType GhcPs -> LHsType GhcPs
rmHsType (ConDecl GhcPs -> LHsType GhcPs
forall pass. ConDecl pass -> LHsType pass
GHC.con_res_ty ConDecl GhcPs
gadt)
                                          ,con_args :: HsConDeclDetails GhcPs
GHC.con_args   = HsConDeclDetails GhcPs -> HsConDeclDetails GhcPs
forall (f :: Type -> Type) (f :: Type -> Type) (f :: Type -> Type).
(Functor f, Functor f, Functor f) =>
HsConDetails (LHsType GhcPs) (f (f (f (ConDeclField GhcPs))))
-> HsConDetails (LHsType GhcPs) (f (f (f (ConDeclField GhcPs))))
rmConDetails (ConDecl GhcPs -> HsConDeclDetails GhcPs
forall pass. ConDecl pass -> HsConDeclDetails pass
GHC.con_args ConDecl GhcPs
gadt)
                                          }
    rmCD h98 :: ConDecl GhcPs
h98@(GHC.ConDeclH98 {})   = ConDecl GhcPs
h98  {con_args :: HsConDeclDetails GhcPs
GHC.con_args = HsConDeclDetails GhcPs -> HsConDeclDetails GhcPs
forall (f :: Type -> Type) (f :: Type -> Type) (f :: Type -> Type).
(Functor f, Functor f, Functor f) =>
HsConDetails (LHsType GhcPs) (f (f (f (ConDeclField GhcPs))))
-> HsConDetails (LHsType GhcPs) (f (f (f (ConDeclField GhcPs))))
rmConDetails (ConDecl GhcPs -> HsConDeclDetails GhcPs
forall pass. ConDecl pass -> HsConDeclDetails pass
GHC.con_args ConDecl GhcPs
h98)}
    rmCD ConDecl GhcPs
xcon                      = ConDecl GhcPs
xcon
#else
    rmCD gadt@(GHC.ConDeclGADT {}) = gadt {GHC.con_type = rmSigType (GHC.con_type gadt)}
    rmCD h98@(GHC.ConDeclH98 {})   = h98  {GHC.con_details = rmConDetails (GHC.con_details h98)}
#endif
    
    
#if !MIN_VERSION_ghc(8,6,0)
    rmSigType hsIB = hsIB {GHC.hsib_body = rmHsType (GHC.hsib_body hsIB)}
#endif
    
    
    rmConDetails :: HsConDetails (LHsType GhcPs) (f (f (f (ConDeclField GhcPs))))
-> HsConDetails (LHsType GhcPs) (f (f (f (ConDeclField GhcPs))))
rmConDetails (GHC.PrefixCon [LHsType GhcPs]
args) = [LHsType GhcPs]
-> HsConDetails (LHsType GhcPs) (f (f (f (ConDeclField GhcPs))))
forall arg rec. [arg] -> HsConDetails arg rec
GHC.PrefixCon ((LHsType GhcPs -> LHsType GhcPs)
-> [LHsType GhcPs] -> [LHsType GhcPs]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap LHsType GhcPs -> LHsType GhcPs
rmHsType [LHsType GhcPs]
args)
    rmConDetails (GHC.RecCon f (f (f (ConDeclField GhcPs)))
rec)     = f (f (f (ConDeclField GhcPs)))
-> HsConDetails (LHsType GhcPs) (f (f (f (ConDeclField GhcPs))))
forall arg rec. rec -> HsConDetails arg rec
GHC.RecCon (((f (f (ConDeclField GhcPs)) -> f (f (ConDeclField GhcPs)))
-> f (f (f (ConDeclField GhcPs))) -> f (f (f (ConDeclField GhcPs)))
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap ((f (f (ConDeclField GhcPs)) -> f (f (ConDeclField GhcPs)))
 -> f (f (f (ConDeclField GhcPs)))
 -> f (f (f (ConDeclField GhcPs))))
-> ((ConDeclField GhcPs -> ConDeclField GhcPs)
    -> f (f (ConDeclField GhcPs)) -> f (f (ConDeclField GhcPs)))
-> (ConDeclField GhcPs -> ConDeclField GhcPs)
-> f (f (f (ConDeclField GhcPs)))
-> f (f (f (ConDeclField GhcPs)))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (f (ConDeclField GhcPs) -> f (ConDeclField GhcPs))
-> f (f (ConDeclField GhcPs)) -> f (f (ConDeclField GhcPs))
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap ((f (ConDeclField GhcPs) -> f (ConDeclField GhcPs))
 -> f (f (ConDeclField GhcPs)) -> f (f (ConDeclField GhcPs)))
-> ((ConDeclField GhcPs -> ConDeclField GhcPs)
    -> f (ConDeclField GhcPs) -> f (ConDeclField GhcPs))
-> (ConDeclField GhcPs -> ConDeclField GhcPs)
-> f (f (ConDeclField GhcPs))
-> f (f (ConDeclField GhcPs))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ConDeclField GhcPs -> ConDeclField GhcPs)
-> f (ConDeclField GhcPs) -> f (ConDeclField GhcPs)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap) ConDeclField GhcPs -> ConDeclField GhcPs
rmConDeclF f (f (f (ConDeclField GhcPs)))
rec)
    rmConDetails (GHC.InfixCon LHsType GhcPs
l LHsType GhcPs
r)   = LHsType GhcPs
-> LHsType GhcPs
-> HsConDetails (LHsType GhcPs) (f (f (f (ConDeclField GhcPs))))
forall arg rec. arg -> arg -> HsConDetails arg rec
GHC.InfixCon (LHsType GhcPs -> LHsType GhcPs
rmHsType LHsType GhcPs
l) (LHsType GhcPs -> LHsType GhcPs
rmHsType LHsType GhcPs
r)
    
    rmHsType :: LHsType GhcPs -> LHsType GhcPs
rmHsType = (LHsType GhcPs -> LHsType GhcPs) -> LHsType GhcPs -> LHsType GhcPs
forall on. Uniplate on => (on -> on) -> on -> on
transform LHsType GhcPs -> LHsType GhcPs
forall pass. LHsType pass -> LHsType pass
go
      where
#if MIN_VERSION_ghc(8,6,0)
        go :: LHsType pass -> LHsType pass
go (LHsType pass -> SrcSpanLess (LHsType pass)
forall a. HasSrcSpan a => a -> SrcSpanLess a
GHC.unLoc -> GHC.HsBangTy _ _ ty) = LHsType pass
ty
#else
        go (GHC.unLoc -> GHC.HsBangTy _ ty) = ty
#endif
        go LHsType pass
ty                               = LHsType pass
ty
    
    rmConDeclF :: ConDeclField GhcPs -> ConDeclField GhcPs
rmConDeclF ConDeclField GhcPs
cdf = ConDeclField GhcPs
cdf {cd_fld_type :: LHsType GhcPs
GHC.cd_fld_type = LHsType GhcPs -> LHsType GhcPs
rmHsType (ConDeclField GhcPs -> LHsType GhcPs
forall pass. ConDeclField pass -> LBangType pass
GHC.cd_fld_type ConDeclField GhcPs
cdf)}
preludePkgId :: String
preludePkgId :: FilePath
preludePkgId = $(lift $ pkgIdFromTypeable (undefined :: TopEntity))
checkForInvalidPrelude :: Monad m => HscTypes.ModGuts -> m ()
checkForInvalidPrelude :: ModGuts -> m ()
checkForInvalidPrelude ModGuts
guts =
  case (FilePath -> Bool) -> [FilePath] -> [FilePath]
forall a. (a -> Bool) -> [a] -> [a]
filter FilePath -> Bool
isWrongPrelude [FilePath]
pkgIds of
    []    -> () -> m ()
forall (m :: Type -> Type) a. Monad m => a -> m a
return ()
    (FilePath
x:[FilePath]
_) -> ClashException -> m ()
forall a e. Exception e => e -> a
throw (SrcSpan -> FilePath -> Maybe FilePath -> ClashException
ClashException SrcSpan
noSrcSpan (FilePath -> FilePath
msgWrongPrelude FilePath
x) Maybe FilePath
forall a. Maybe a
Nothing)
  where
    pkgs :: [(InstalledUnitId, Bool)]
pkgs = Dependencies -> [(InstalledUnitId, Bool)]
HscTypes.dep_pkgs (Dependencies -> [(InstalledUnitId, Bool)])
-> (ModGuts -> Dependencies)
-> ModGuts
-> [(InstalledUnitId, Bool)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ModGuts -> Dependencies
HscTypes.mg_deps (ModGuts -> [(InstalledUnitId, Bool)])
-> ModGuts -> [(InstalledUnitId, Bool)]
forall a b. (a -> b) -> a -> b
$ ModGuts
guts
    pkgIds :: [FilePath]
pkgIds = ((InstalledUnitId, Bool) -> FilePath)
-> [(InstalledUnitId, Bool)] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map (InstalledUnitId -> FilePath
GhcPlugins.installedUnitIdString (InstalledUnitId -> FilePath)
-> ((InstalledUnitId, Bool) -> InstalledUnitId)
-> (InstalledUnitId, Bool)
-> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (InstalledUnitId, Bool) -> InstalledUnitId
forall a b. (a, b) -> a
fst) [(InstalledUnitId, Bool)]
pkgs
    prelude :: FilePath
prelude = FilePath
"clash-prelude-"
    isPrelude :: FilePath -> Bool
isPrelude FilePath
pkg = case Int -> FilePath -> (FilePath, FilePath)
forall a. Int -> [a] -> ([a], [a])
splitAt (FilePath -> Int
forall (t :: Type -> Type) a. Foldable t => t a -> Int
length FilePath
prelude) FilePath
pkg of
      (FilePath
x,Char
y:FilePath
_) | FilePath
x FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
prelude Bool -> Bool -> Bool
&& Char -> Bool
isDigit Char
y -> Bool
True     
      (FilePath, FilePath)
_ -> Bool
False
    isWrongPrelude :: FilePath -> Bool
isWrongPrelude FilePath
pkg = FilePath -> Bool
isPrelude FilePath
pkg Bool -> Bool -> Bool
&& FilePath
pkg FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
/= FilePath
preludePkgId
    msgWrongPrelude :: FilePath -> FilePath
msgWrongPrelude FilePath
pkg = [FilePath] -> FilePath
unlines [FilePath
"Clash only works with the exact clash-prelude it was built with."
                                  ,FilePath
"Clash was built with: " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
preludePkgId
                                  ,FilePath
"So can't run with:    " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
pkg
                                  ]