Skip to content
Snippets Groups Projects
Commit 098e969b authored by Potato Hatsue's avatar Potato Hatsue Committed by Sylvain Henry
Browse files

Re-export some 'Way' related functions in DynFlags

parent ded498ef
No related branches found
No related tags found
1 merge request!2Re-export some 'Way' related functions in DynFlags
......@@ -120,7 +120,9 @@ library
if impl(ghc >= 9.0)
hs-source-dirs: src
exposed-modules: Outputable
exposed-modules: Outputable DynFlags
build-depends:
containers >= 0.6.0 && <= 0.6.5
reexported-modules:
GHC.Rename.Bind as RnBinds
, GHC.Rename.Env as RnEnv
......@@ -347,7 +349,7 @@ library
, GHC.Driver.Main as HscMain
, GHC.Driver.Make as GhcMake
, GHC.Driver.Hooks as Hooks
, GHC.Driver.Session as DynFlags
-- , GHC.Driver.Session as DynFlags
, GHC.Driver.Phases as DriverPhases
, GHC.Driver.Pipeline as DriverPipeline
, GHC.Driver.Pipeline.Monad as PipelineMonad
......
{-# LANGUAGE CPP #-}
module DynFlags
( module GHC.Driver.Session,
Way(..),
wayRTSOnly,
wayGeneralFlags,
wayUnsetGeneralFlags,
buildTag,
dynamicGhc,
hostFullWays,
interpWays,
)
where
import Data.Set (Set)
import GHC.Driver.Session
#if MIN_VERSION_GLASGOW_HASKELL(9,2,0,0)
import GHC.Platform.Ways
#else
import GHC.Driver.Ways
#endif
buildTag :: DynFlags -> String
buildTag = waysBuildTag . ways
dynamicGhc :: Bool
dynamicGhc = hostIsDynamic
interpWays :: Set Way
interpWays = hostFullWays
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment