{-# LANGUAGE RecordWildCards, CPP #-}
module HIE.Bios.Environment (initSession, getRuntimeGhcLibDir, getRuntimeGhcVersion, makeDynFlagsAbsolute, makeTargetsAbsolute, getCacheDir, addCmdOpts) where
import CoreMonad (liftIO)
import GHC (GhcMonad)
import qualified GHC as G
import qualified DriverPhases as G
import qualified Util as G
import DynFlags
import Control.Applicative
import Control.Monad (void)
import System.Directory
import System.FilePath
import System.Environment (lookupEnv)
import qualified Crypto.Hash.SHA1 as H
import qualified Data.ByteString.Char8 as B
import Data.ByteString.Base16
import Data.List
import Data.Char (isSpace)
import Text.ParserCombinators.ReadP hiding (optional)
import HIE.Bios.Types
import HIE.Bios.Ghc.Gap
initSession :: (GhcMonad m)
=> ComponentOptions
-> m [G.Target]
initSession :: ComponentOptions -> m [Target]
initSession ComponentOptions {..} = do
DynFlags
df <- m DynFlags
forall (m :: * -> *). GhcMonad m => m DynFlags
G.getSessionDynFlags
let opts_hash :: FilePath
opts_hash = ByteString -> FilePath
B.unpack (ByteString -> FilePath) -> ByteString -> FilePath
forall a b. (a -> b) -> a -> b
$ ByteString -> ByteString
encode (ByteString -> ByteString) -> ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ Ctx -> ByteString
H.finalize (Ctx -> ByteString) -> Ctx -> ByteString
forall a b. (a -> b) -> a -> b
$ Ctx -> [ByteString] -> Ctx
H.updates Ctx
H.init ((FilePath -> ByteString) -> [FilePath] -> [ByteString]
forall a b. (a -> b) -> [a] -> [b]
map FilePath -> ByteString
B.pack [FilePath]
componentOptions)
FilePath
cache_dir <- IO FilePath -> m FilePath
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO FilePath -> m FilePath) -> IO FilePath -> m FilePath
forall a b. (a -> b) -> a -> b
$ FilePath -> IO FilePath
getCacheDir FilePath
opts_hash
(df' :: DynFlags
df', targets :: [Target]
targets) <- [FilePath] -> DynFlags -> m (DynFlags, [Target])
forall (m :: * -> *).
GhcMonad m =>
[FilePath] -> DynFlags -> m (DynFlags, [Target])
addCmdOpts [FilePath]
componentOptions DynFlags
df
let df'' :: DynFlags
df'' = FilePath -> DynFlags -> DynFlags
makeDynFlagsAbsolute FilePath
componentRoot DynFlags
df'
m [InstalledUnitId] -> m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (m [InstalledUnitId] -> m ()) -> m [InstalledUnitId] -> m ()
forall a b. (a -> b) -> a -> b
$ DynFlags -> m [InstalledUnitId]
forall (m :: * -> *). GhcMonad m => DynFlags -> m [InstalledUnitId]
G.setSessionDynFlags
(DynFlags -> DynFlags
disableOptimisation
(DynFlags -> DynFlags) -> DynFlags -> DynFlags
forall a b. (a -> b) -> a -> b
$ DynFlags -> DynFlags
setIgnoreInterfacePragmas
(DynFlags -> DynFlags) -> DynFlags -> DynFlags
forall a b. (a -> b) -> a -> b
$ Maybe FilePath -> DynFlags -> DynFlags
writeInterfaceFiles (FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just FilePath
cache_dir)
(DynFlags -> DynFlags) -> DynFlags -> DynFlags
forall a b. (a -> b) -> a -> b
$ Int -> DynFlags -> DynFlags
setVerbosity 0
(DynFlags -> DynFlags) -> DynFlags -> DynFlags
forall a b. (a -> b) -> a -> b
$ DynFlags -> DynFlags
setLinkerOptions DynFlags
df''
)
let targets' :: [Target]
targets' = FilePath -> [Target] -> [Target]
makeTargetsAbsolute FilePath
componentRoot [Target]
targets
m ()
forall (m :: * -> *). GhcMonad m => m ()
unsetLogAction
[Target] -> m [Target]
forall (m :: * -> *) a. Monad m => a -> m a
return [Target]
targets'
makeTargetsAbsolute :: FilePath -> [G.Target] -> [G.Target]
makeTargetsAbsolute :: FilePath -> [Target] -> [Target]
makeTargetsAbsolute wdir :: FilePath
wdir = (Target -> Target) -> [Target] -> [Target]
forall a b. (a -> b) -> [a] -> [b]
map (\target :: Target
target -> Target
target {targetId :: TargetId
G.targetId = FilePath -> TargetId -> TargetId
makeTargetIdAbsolute FilePath
wdir (Target -> TargetId
G.targetId Target
target)})
makeTargetIdAbsolute :: FilePath -> G.TargetId -> G.TargetId
makeTargetIdAbsolute :: FilePath -> TargetId -> TargetId
makeTargetIdAbsolute wdir :: FilePath
wdir (G.TargetFile fp :: FilePath
fp phase :: Maybe Phase
phase) = FilePath -> Maybe Phase -> TargetId
G.TargetFile (FilePath -> FilePath -> FilePath
prependIfRelative FilePath
wdir FilePath
fp) Maybe Phase
phase
makeTargetIdAbsolute _ tid :: TargetId
tid = TargetId
tid
getRuntimeGhcLibDir :: Cradle a
-> IO (CradleLoadResult FilePath)
getRuntimeGhcLibDir :: Cradle a -> IO (CradleLoadResult FilePath)
getRuntimeGhcLibDir cradle :: Cradle a
cradle = do
Maybe FilePath
maybeNixLibDir <- FilePath -> IO (Maybe FilePath)
lookupEnv "NIX_GHC_LIBDIR"
case Maybe FilePath
maybeNixLibDir of
Just ld :: FilePath
ld -> CradleLoadResult FilePath -> IO (CradleLoadResult FilePath)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (FilePath -> CradleLoadResult FilePath
forall r. r -> CradleLoadResult r
CradleSuccess FilePath
ld)
Nothing -> (CradleLoadResult FilePath -> CradleLoadResult FilePath)
-> IO (CradleLoadResult FilePath) -> IO (CradleLoadResult FilePath)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((FilePath -> FilePath)
-> CradleLoadResult FilePath -> CradleLoadResult FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap FilePath -> FilePath
trim) (IO (CradleLoadResult FilePath) -> IO (CradleLoadResult FilePath))
-> IO (CradleLoadResult FilePath) -> IO (CradleLoadResult FilePath)
forall a b. (a -> b) -> a -> b
$
CradleAction a -> [FilePath] -> IO (CradleLoadResult FilePath)
forall a.
CradleAction a -> [FilePath] -> IO (CradleLoadResult FilePath)
runGhcCmd (Cradle a -> CradleAction a
forall a. Cradle a -> CradleAction a
cradleOptsProg Cradle a
cradle) ["--print-libdir"]
getRuntimeGhcVersion :: Cradle a
-> IO (CradleLoadResult String)
getRuntimeGhcVersion :: Cradle a -> IO (CradleLoadResult FilePath)
getRuntimeGhcVersion cradle :: Cradle a
cradle =
(CradleLoadResult FilePath -> CradleLoadResult FilePath)
-> IO (CradleLoadResult FilePath) -> IO (CradleLoadResult FilePath)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((FilePath -> FilePath)
-> CradleLoadResult FilePath -> CradleLoadResult FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap FilePath -> FilePath
trim) (IO (CradleLoadResult FilePath) -> IO (CradleLoadResult FilePath))
-> IO (CradleLoadResult FilePath) -> IO (CradleLoadResult FilePath)
forall a b. (a -> b) -> a -> b
$ CradleAction a -> [FilePath] -> IO (CradleLoadResult FilePath)
forall a.
CradleAction a -> [FilePath] -> IO (CradleLoadResult FilePath)
runGhcCmd (Cradle a -> CradleAction a
forall a. Cradle a -> CradleAction a
cradleOptsProg Cradle a
cradle) ["--numeric-version"]
cacheDir :: String
cacheDir :: FilePath
cacheDir = "hie-bios"
getCacheDir :: FilePath -> IO FilePath
getCacheDir :: FilePath -> IO FilePath
getCacheDir fp :: FilePath
fp = do
Maybe FilePath
mbEnvCacheDirectory <- FilePath -> IO (Maybe FilePath)
lookupEnv "HIE_BIOS_CACHE_DIR"
FilePath
cacheBaseDir <- IO FilePath
-> (FilePath -> IO FilePath) -> Maybe FilePath -> IO FilePath
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (XdgDirectory -> FilePath -> IO FilePath
getXdgDirectory XdgDirectory
XdgCache FilePath
cacheDir) FilePath -> IO FilePath
forall (m :: * -> *) a. Monad m => a -> m a
return
Maybe FilePath
mbEnvCacheDirectory
FilePath -> IO FilePath
forall (m :: * -> *) a. Monad m => a -> m a
return (FilePath
cacheBaseDir FilePath -> FilePath -> FilePath
</> FilePath
fp)
setLinkerOptions :: DynFlags -> DynFlags
setLinkerOptions :: DynFlags -> DynFlags
setLinkerOptions df :: DynFlags
df = DynFlags
df {
ghcLink :: GhcLink
ghcLink = GhcLink
LinkInMemory
, hscTarget :: HscTarget
hscTarget = HscTarget
HscNothing
, ghcMode :: GhcMode
ghcMode = GhcMode
CompManager
}
setIgnoreInterfacePragmas :: DynFlags -> DynFlags
setIgnoreInterfacePragmas :: DynFlags -> DynFlags
setIgnoreInterfacePragmas df :: DynFlags
df = DynFlags -> GeneralFlag -> DynFlags
gopt_set DynFlags
df GeneralFlag
Opt_IgnoreInterfacePragmas
setVerbosity :: Int -> DynFlags -> DynFlags
setVerbosity :: Int -> DynFlags -> DynFlags
setVerbosity n :: Int
n df :: DynFlags
df = DynFlags
df { verbosity :: Int
verbosity = Int
n }
writeInterfaceFiles :: Maybe FilePath -> DynFlags -> DynFlags
writeInterfaceFiles :: Maybe FilePath -> DynFlags -> DynFlags
writeInterfaceFiles Nothing df :: DynFlags
df = DynFlags
df
writeInterfaceFiles (Just hi_dir :: FilePath
hi_dir) df :: DynFlags
df = FilePath -> DynFlags -> DynFlags
setHiDir FilePath
hi_dir (DynFlags -> GeneralFlag -> DynFlags
gopt_set DynFlags
df GeneralFlag
Opt_WriteInterface)
setHiDir :: FilePath -> DynFlags -> DynFlags
setHiDir :: FilePath -> DynFlags -> DynFlags
setHiDir f :: FilePath
f d :: DynFlags
d = DynFlags
d { hiDir :: Maybe FilePath
hiDir = FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just FilePath
f}
addCmdOpts :: (GhcMonad m)
=> [String] -> DynFlags -> m (DynFlags, [G.Target])
addCmdOpts :: [FilePath] -> DynFlags -> m (DynFlags, [Target])
addCmdOpts cmdOpts :: [FilePath]
cmdOpts df1 :: DynFlags
df1 = do
(df2 :: DynFlags
df2, leftovers' :: [Located FilePath]
leftovers', _warns :: [Warn]
_warns) <- DynFlags
-> [Located FilePath] -> m (DynFlags, [Located FilePath], [Warn])
forall (m :: * -> *).
MonadIO m =>
DynFlags
-> [Located FilePath] -> m (DynFlags, [Located FilePath], [Warn])
G.parseDynamicFlags DynFlags
df1 ((FilePath -> Located FilePath) -> [FilePath] -> [Located FilePath]
forall a b. (a -> b) -> [a] -> [b]
map FilePath -> Located FilePath
forall a. HasSrcSpan a => SrcSpanLess a -> a
G.noLoc [FilePath]
cmdOpts)
[FilePath]
additionalTargets <- [[FilePath]] -> [FilePath]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[FilePath]] -> [FilePath]) -> m [[FilePath]] -> m [FilePath]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (FilePath -> m [FilePath]) -> [FilePath] -> m [[FilePath]]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (IO [FilePath] -> m [FilePath]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [FilePath] -> m [FilePath])
-> (FilePath -> IO [FilePath]) -> FilePath -> m [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO [FilePath]
getTargetsFromGhciScript) (DynFlags -> [FilePath]
ghciScripts DynFlags
df2)
let leftovers :: [Located FilePath]
leftovers = [Located FilePath]
leftovers' [Located FilePath] -> [Located FilePath] -> [Located FilePath]
forall a. [a] -> [a] -> [a]
++ (FilePath -> Located FilePath) -> [FilePath] -> [Located FilePath]
forall a b. (a -> b) -> [a] -> [b]
map FilePath -> Located FilePath
forall a. HasSrcSpan a => SrcSpanLess a -> a
G.noLoc [FilePath]
additionalTargets
let
normalise_hyp :: FilePath -> FilePath
normalise_hyp fp :: FilePath
fp
| Bool
strt_dot_sl Bool -> Bool -> Bool
&& "-" FilePath -> FilePath -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` FilePath
nfp = FilePath
cur_dir FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
nfp
| Bool
otherwise = FilePath
nfp
where
#if defined(mingw32_HOST_OS)
strt_dot_sl = "./" `isPrefixOf` fp || ".\\" `isPrefixOf` fp
#else
strt_dot_sl :: Bool
strt_dot_sl = "./" FilePath -> FilePath -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` FilePath
fp
#endif
cur_dir :: FilePath
cur_dir = '.' Char -> FilePath -> FilePath
forall a. a -> [a] -> [a]
: [Char
pathSeparator]
nfp :: FilePath
nfp = FilePath -> FilePath
normalise FilePath
fp
normal_fileish_paths :: [FilePath]
normal_fileish_paths = (Located FilePath -> FilePath) -> [Located FilePath] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map (FilePath -> FilePath
normalise_hyp (FilePath -> FilePath)
-> (Located FilePath -> FilePath) -> Located FilePath -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Located FilePath -> FilePath
forall a. HasSrcSpan a => a -> SrcSpanLess a
G.unLoc) [Located FilePath]
leftovers
let
(srcs :: [(FilePath, Maybe Phase)]
srcs, objs :: [FilePath]
objs) = [FilePath]
-> [(FilePath, Maybe Phase)]
-> [FilePath]
-> ([(FilePath, Maybe Phase)], [FilePath])
partition_args [FilePath]
normal_fileish_paths [] []
df3 :: DynFlags
df3 = DynFlags
df2 { ldInputs :: [Option]
ldInputs = (FilePath -> Option) -> [FilePath] -> [Option]
forall a b. (a -> b) -> [a] -> [b]
map (FilePath -> FilePath -> Option
FileOption "") [FilePath]
objs [Option] -> [Option] -> [Option]
forall a. [a] -> [a] -> [a]
++ DynFlags -> [Option]
ldInputs DynFlags
df2 }
[Target]
ts <- ((FilePath, Maybe Phase) -> m Target)
-> [(FilePath, Maybe Phase)] -> m [Target]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((FilePath -> Maybe Phase -> m Target)
-> (FilePath, Maybe Phase) -> m Target
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry FilePath -> Maybe Phase -> m Target
forall (m :: * -> *).
GhcMonad m =>
FilePath -> Maybe Phase -> m Target
G.guessTarget) [(FilePath, Maybe Phase)]
srcs
(DynFlags, [Target]) -> m (DynFlags, [Target])
forall (m :: * -> *) a. Monad m => a -> m a
return (DynFlags
df3, [Target]
ts)
makeDynFlagsAbsolute :: FilePath -> DynFlags -> DynFlags
makeDynFlagsAbsolute :: FilePath -> DynFlags -> DynFlags
makeDynFlagsAbsolute work_dir :: FilePath
work_dir df :: DynFlags
df =
(FilePath -> FilePath) -> DynFlags -> DynFlags
mapOverIncludePaths (FilePath -> FilePath -> FilePath
prependIfRelative FilePath
work_dir)
(DynFlags -> DynFlags) -> DynFlags -> DynFlags
forall a b. (a -> b) -> a -> b
$ DynFlags
df
{ importPaths :: [FilePath]
importPaths = (FilePath -> FilePath) -> [FilePath] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map (FilePath -> FilePath -> FilePath
prependIfRelative FilePath
work_dir) (DynFlags -> [FilePath]
importPaths DynFlags
df)
, packageDBFlags :: [PackageDBFlag]
packageDBFlags =
let makePackageDbAbsolute :: PackageDBFlag -> PackageDBFlag
makePackageDbAbsolute (PackageDB pkgConfRef :: PkgConfRef
pkgConfRef) = PkgConfRef -> PackageDBFlag
PackageDB
(PkgConfRef -> PackageDBFlag) -> PkgConfRef -> PackageDBFlag
forall a b. (a -> b) -> a -> b
$ case PkgConfRef
pkgConfRef of
PkgConfFile fp :: FilePath
fp -> FilePath -> PkgConfRef
PkgConfFile (FilePath -> FilePath -> FilePath
prependIfRelative FilePath
work_dir FilePath
fp)
conf :: PkgConfRef
conf -> PkgConfRef
conf
makePackageDbAbsolute db :: PackageDBFlag
db = PackageDBFlag
db
in (PackageDBFlag -> PackageDBFlag)
-> [PackageDBFlag] -> [PackageDBFlag]
forall a b. (a -> b) -> [a] -> [b]
map PackageDBFlag -> PackageDBFlag
makePackageDbAbsolute (DynFlags -> [PackageDBFlag]
packageDBFlags DynFlags
df)
}
prependIfRelative :: FilePath -> FilePath -> FilePath
prependIfRelative :: FilePath -> FilePath -> FilePath
prependIfRelative wdir :: FilePath
wdir f :: FilePath
f
| FilePath -> Bool
isAbsolute FilePath
f = FilePath
f
| Bool
otherwise = FilePath
wdir FilePath -> FilePath -> FilePath
</> FilePath
f
partition_args :: [String] -> [(String, Maybe G.Phase)] -> [String]
-> ([(String, Maybe G.Phase)], [String])
partition_args :: [FilePath]
-> [(FilePath, Maybe Phase)]
-> [FilePath]
-> ([(FilePath, Maybe Phase)], [FilePath])
partition_args [] srcs :: [(FilePath, Maybe Phase)]
srcs objs :: [FilePath]
objs = ([(FilePath, Maybe Phase)] -> [(FilePath, Maybe Phase)]
forall a. [a] -> [a]
reverse [(FilePath, Maybe Phase)]
srcs, [FilePath] -> [FilePath]
forall a. [a] -> [a]
reverse [FilePath]
objs)
partition_args ("-x":suff :: FilePath
suff:args :: [FilePath]
args) srcs :: [(FilePath, Maybe Phase)]
srcs objs :: [FilePath]
objs
| FilePath
"none" <- FilePath
suff = [FilePath]
-> [(FilePath, Maybe Phase)]
-> [FilePath]
-> ([(FilePath, Maybe Phase)], [FilePath])
partition_args [FilePath]
args [(FilePath, Maybe Phase)]
srcs [FilePath]
objs
| Phase
G.StopLn <- Phase
phase = [FilePath]
-> [(FilePath, Maybe Phase)]
-> [FilePath]
-> ([(FilePath, Maybe Phase)], [FilePath])
partition_args [FilePath]
args [(FilePath, Maybe Phase)]
srcs ([FilePath]
slurp [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [FilePath]
objs)
| Bool
otherwise = [FilePath]
-> [(FilePath, Maybe Phase)]
-> [FilePath]
-> ([(FilePath, Maybe Phase)], [FilePath])
partition_args [FilePath]
rest ([(FilePath, Maybe Phase)]
these_srcs [(FilePath, Maybe Phase)]
-> [(FilePath, Maybe Phase)] -> [(FilePath, Maybe Phase)]
forall a. [a] -> [a] -> [a]
++ [(FilePath, Maybe Phase)]
srcs) [FilePath]
objs
where phase :: Phase
phase = FilePath -> Phase
G.startPhase FilePath
suff
(slurp :: [FilePath]
slurp,rest :: [FilePath]
rest) = (FilePath -> Bool) -> [FilePath] -> ([FilePath], [FilePath])
forall a. (a -> Bool) -> [a] -> ([a], [a])
break (FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== "-x") [FilePath]
args
these_srcs :: [(FilePath, Maybe Phase)]
these_srcs = [FilePath] -> [Maybe Phase] -> [(FilePath, Maybe Phase)]
forall a b. [a] -> [b] -> [(a, b)]
zip [FilePath]
slurp (Maybe Phase -> [Maybe Phase]
forall a. a -> [a]
repeat (Phase -> Maybe Phase
forall a. a -> Maybe a
Just Phase
phase))
partition_args (arg :: FilePath
arg:args :: [FilePath]
args) srcs :: [(FilePath, Maybe Phase)]
srcs objs :: [FilePath]
objs
| FilePath -> Bool
looks_like_an_input FilePath
arg = [FilePath]
-> [(FilePath, Maybe Phase)]
-> [FilePath]
-> ([(FilePath, Maybe Phase)], [FilePath])
partition_args [FilePath]
args ((FilePath
arg,Maybe Phase
forall a. Maybe a
Nothing)(FilePath, Maybe Phase)
-> [(FilePath, Maybe Phase)] -> [(FilePath, Maybe Phase)]
forall a. a -> [a] -> [a]
:[(FilePath, Maybe Phase)]
srcs) [FilePath]
objs
| Bool
otherwise = [FilePath]
-> [(FilePath, Maybe Phase)]
-> [FilePath]
-> ([(FilePath, Maybe Phase)], [FilePath])
partition_args [FilePath]
args [(FilePath, Maybe Phase)]
srcs (FilePath
argFilePath -> [FilePath] -> [FilePath]
forall a. a -> [a] -> [a]
:[FilePath]
objs)
looks_like_an_input :: String -> Bool
looks_like_an_input :: FilePath -> Bool
looks_like_an_input m :: FilePath
m = FilePath -> Bool
G.isSourceFilename FilePath
m
Bool -> Bool -> Bool
|| FilePath -> Bool
G.looksLikeModuleName FilePath
m
Bool -> Bool -> Bool
|| "-" FilePath -> FilePath -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` FilePath
m
Bool -> Bool -> Bool
|| Bool -> Bool
not (FilePath -> Bool
hasExtension FilePath
m)
disableOptimisation :: DynFlags -> DynFlags
disableOptimisation :: DynFlags -> DynFlags
disableOptimisation df :: DynFlags
df = Int -> DynFlags -> DynFlags
updOptLevel 0 DynFlags
df
getTargetsFromGhciScript :: FilePath -> IO [String]
getTargetsFromGhciScript :: FilePath -> IO [FilePath]
getTargetsFromGhciScript script :: FilePath
script = do
[FilePath]
contents <- FilePath -> [FilePath]
lines (FilePath -> [FilePath]) -> IO FilePath -> IO [FilePath]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FilePath -> IO FilePath
readFile FilePath
script
let parseGhciLine :: FilePath -> [FilePath]
parseGhciLine = (([FilePath], FilePath) -> [FilePath])
-> [([FilePath], FilePath)] -> [FilePath]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap ([FilePath], FilePath) -> [FilePath]
forall a b. (a, b) -> a
fst ([([FilePath], FilePath)] -> [FilePath])
-> (FilePath -> [([FilePath], FilePath)]) -> FilePath -> [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (([FilePath], FilePath) -> Bool)
-> [([FilePath], FilePath)] -> [([FilePath], FilePath)]
forall a. (a -> Bool) -> [a] -> [a]
filter (FilePath -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (FilePath -> Bool)
-> (([FilePath], FilePath) -> FilePath)
-> ([FilePath], FilePath)
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([FilePath], FilePath) -> FilePath
forall a b. (a, b) -> b
snd) ([([FilePath], FilePath)] -> [([FilePath], FilePath)])
-> (FilePath -> [([FilePath], FilePath)])
-> FilePath
-> [([FilePath], FilePath)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ReadP [FilePath] -> FilePath -> [([FilePath], FilePath)]
forall a. ReadP a -> ReadS a
readP_to_S ReadP [FilePath]
parser
[FilePath] -> IO [FilePath]
forall (m :: * -> *) a. Monad m => a -> m a
return ([FilePath] -> IO [FilePath]) -> [FilePath] -> IO [FilePath]
forall a b. (a -> b) -> a -> b
$ (FilePath -> [FilePath]) -> [FilePath] -> [FilePath]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap FilePath -> [FilePath]
parseGhciLine [FilePath]
contents
parser :: ReadP [String]
parser :: ReadP [FilePath]
parser = do
FilePath
_ <- FilePath -> ReadP FilePath
string ":add" ReadP FilePath -> ReadP FilePath -> ReadP FilePath
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ReadP FilePath
space1
ReadP FilePath
scriptword ReadP FilePath -> ReadP FilePath -> ReadP [FilePath]
forall a sep. ReadP a -> ReadP sep -> ReadP [a]
`sepBy` ReadP FilePath
space1
space1 :: ReadP [Char]
space1 :: ReadP FilePath
space1 = ReadP Char -> ReadP FilePath
forall a. ReadP a -> ReadP [a]
many1 (Char -> ReadP Char
char ' ')
scriptword :: ReadP String
scriptword :: ReadP FilePath
scriptword = ReadP FilePath
quoted ReadP FilePath -> ReadP FilePath -> ReadP FilePath
forall a. ReadP a -> ReadP a -> ReadP a
<++ ReadP FilePath
value
quoted :: ReadP String
quoted :: ReadP FilePath
quoted = do
Char
_ <- Char -> ReadP Char
char '"'
ReadP Char -> ReadP Char -> ReadP FilePath
forall a sep. ReadP a -> ReadP sep -> ReadP [a]
manyTill (Char -> ReadP Char
escaped '"' ReadP Char -> ReadP Char -> ReadP Char
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ReadP Char
anyToken) (ReadP Char -> ReadP FilePath) -> ReadP Char -> ReadP FilePath
forall a b. (a -> b) -> a -> b
$ Char -> ReadP Char
char '"'
escaped :: Char -> ReadP Char
escaped :: Char -> ReadP Char
escaped c :: Char
c = Char
c Char -> ReadP FilePath -> ReadP Char
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ FilePath -> ReadP FilePath
string ("\\" FilePath -> FilePath -> FilePath
forall a. Semigroup a => a -> a -> a
<> [Char
c])
value :: ReadP String
value :: ReadP FilePath
value = ReadP Char -> ReadP FilePath
forall a. ReadP a -> ReadP [a]
many1 ((Char -> Bool) -> ReadP Char
satisfy (Bool -> Bool
not (Bool -> Bool) -> (Char -> Bool) -> Char -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Bool
isSpace))
anyToken :: ReadP Char
anyToken :: ReadP Char
anyToken = (Char -> Bool) -> ReadP Char
satisfy ((Char -> Bool) -> ReadP Char) -> (Char -> Bool) -> ReadP Char
forall a b. (a -> b) -> a -> b
$ Bool -> Char -> Bool
forall a b. a -> b -> a
const Bool
True
trim :: String -> String
trim :: FilePath -> FilePath
trim = (Char -> Bool) -> FilePath -> FilePath
forall a. (a -> Bool) -> [a] -> [a]
dropWhileEnd Char -> Bool
isSpace