{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TupleSections #-}
module HIE.Bios.Cradle (
findCradle
, loadCradle
, loadImplicitCradle
, yamlConfig
, defaultCradle
, isCabalCradle
, isStackCradle
, isDirectCradle
, isBiosCradle
, isNoneCradle
, isMultiCradle
, isDefaultCradle
, isOtherCradle
, getCradle
, readProcessWithOutputs
, readProcessWithCwd
, makeCradleResult
) where
import Control.Applicative ((<|>), optional)
import Data.Bifunctor (first)
import Control.DeepSeq
import Control.Exception (handleJust)
import qualified Data.Yaml as Yaml
import Data.Void
import Data.Char (isSpace)
import System.Exit
import System.Directory hiding (findFile)
import Colog.Core (LogAction (..), WithSeverity (..), Severity (..), (<&))
import Control.Monad
import Control.Monad.Extra (unlessM)
import Control.Monad.Trans.Cont
import Control.Monad.Trans.Maybe
import Control.Monad.IO.Class
import Data.Conduit.Process
import qualified Data.Conduit.Combinators as C
import qualified Data.Conduit as C
import qualified Data.Conduit.Text as C
import qualified Data.HashMap.Strict as Map
import Data.Maybe (fromMaybe, maybeToList)
import Data.List
import Data.List.Extra (trimEnd)
import Data.Ord (Down(..))
import qualified Data.Text as T
import System.Environment
import System.FilePath
import System.PosixCompat.Files
import System.Info.Extra (isWindows)
import System.IO (hClose, hGetContents, hSetBuffering, BufferMode(LineBuffering), withFile, IOMode(..))
import System.IO.Error (isPermissionError)
import System.IO.Temp
import HIE.Bios.Config
import HIE.Bios.Environment (getCacheDir)
import HIE.Bios.Types hiding (ActionName(..))
import HIE.Bios.Wrappers
import qualified HIE.Bios.Types as Types
import qualified HIE.Bios.Ghc.Gap as Gap
import GHC.Fingerprint (fingerprintString)
import GHC.ResponseFile (escapeArgs)
hie_bios_output :: String
hie_bios_output :: String
hie_bios_output = String
"HIE_BIOS_OUTPUT"
hie_bios_ghc :: String
hie_bios_ghc :: String
hie_bios_ghc = String
"HIE_BIOS_GHC"
hie_bios_ghc_args :: String
hie_bios_ghc_args :: String
hie_bios_ghc_args = String
"HIE_BIOS_GHC_ARGS"
hie_bios_arg :: String
hie_bios_arg :: String
hie_bios_arg = String
"HIE_BIOS_ARG"
hie_bios_deps :: String
hie_bios_deps :: String
hie_bios_deps = String
"HIE_BIOS_DEPS"
findCradle :: FilePath -> IO (Maybe FilePath)
findCradle :: String -> IO (Maybe String)
findCradle String
wfile = do
let wdir :: String
wdir = String -> String
takeDirectory String
wfile
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT (String -> MaybeT IO String
yamlConfig String
wdir)
loadCradle :: FilePath -> IO (Cradle Void)
loadCradle :: String -> IO (Cradle Void)
loadCradle = forall b a.
FromJSON b =>
(b -> Cradle a) -> String -> IO (Cradle a)
loadCradleWithOpts forall a. Void -> a
absurd
loadImplicitCradle :: Show a => FilePath -> IO (Cradle a)
loadImplicitCradle :: forall a. Show a => String -> IO (Cradle a)
loadImplicitCradle String
wfile = do
let wdir :: String
wdir = String -> String
takeDirectory String
wfile
Maybe (CradleConfig Void, String)
cfg <- forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT (forall a. String -> MaybeT IO (CradleConfig a, String)
implicitConfig String
wdir)
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ case Maybe (CradleConfig Void, String)
cfg of
Just (CradleConfig Void, String)
bc -> forall b a. (b -> Cradle a) -> (CradleConfig b, String) -> Cradle a
getCradle forall a. Void -> a
absurd (CradleConfig Void, String)
bc
Maybe (CradleConfig Void, String)
Nothing -> forall a. String -> Cradle a
defaultCradle String
wdir
loadCradleWithOpts :: (Yaml.FromJSON b) => (b -> Cradle a) -> FilePath -> IO (Cradle a)
loadCradleWithOpts :: forall b a.
FromJSON b =>
(b -> Cradle a) -> String -> IO (Cradle a)
loadCradleWithOpts b -> Cradle a
buildCustomCradle String
wfile = do
CradleConfig b
cradleConfig <- forall b. FromJSON b => String -> IO (CradleConfig b)
readCradleConfig String
wfile
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall b a. (b -> Cradle a) -> (CradleConfig b, String) -> Cradle a
getCradle b -> Cradle a
buildCustomCradle (CradleConfig b
cradleConfig, String -> String
takeDirectory String
wfile)
getCradle :: (b -> Cradle a) -> (CradleConfig b, FilePath) -> Cradle a
getCradle :: forall b a. (b -> Cradle a) -> (CradleConfig b, String) -> Cradle a
getCradle b -> Cradle a
buildCustomCradle (CradleConfig b
cc, String
wdir) = forall a. [String] -> Cradle a -> Cradle a
addCradleDeps [String]
cradleDeps forall a b. (a -> b) -> a -> b
$ case forall a. CradleConfig a -> CradleType a
cradleType CradleConfig b
cc of
Cabal CabalType{ cabalComponent :: CabalType -> Maybe String
cabalComponent = Maybe String
mc } -> forall a. String -> Maybe String -> Cradle a
cabalCradle String
wdir Maybe String
mc
CabalMulti CabalType
dc [(String, CabalType)]
ms ->
forall b a. (b -> Cradle a) -> (CradleConfig b, String) -> Cradle a
getCradle b -> Cradle a
buildCustomCradle
(forall a. [String] -> CradleType a -> CradleConfig a
CradleConfig [String]
cradleDeps
(forall a. [(String, CradleConfig a)] -> CradleType a
Multi [(String
p, forall a. [String] -> CradleType a -> CradleConfig a
CradleConfig [] (forall a. CabalType -> CradleType a
Cabal forall a b. (a -> b) -> a -> b
$ CabalType
dc forall a. Semigroup a => a -> a -> a
<> CabalType
c)) | (String
p, CabalType
c) <- [(String, CabalType)]
ms])
, String
wdir)
Stack StackType{ stackComponent :: StackType -> Maybe String
stackComponent = Maybe String
mc, stackYaml :: StackType -> Maybe String
stackYaml = Maybe String
syaml} ->
let
stackYamlConfig :: StackYaml
stackYamlConfig = String -> Maybe String -> StackYaml
stackYamlFromMaybe String
wdir Maybe String
syaml
in
forall a. String -> Maybe String -> StackYaml -> Cradle a
stackCradle String
wdir Maybe String
mc StackYaml
stackYamlConfig
StackMulti StackType
ds [(String, StackType)]
ms ->
forall b a. (b -> Cradle a) -> (CradleConfig b, String) -> Cradle a
getCradle b -> Cradle a
buildCustomCradle
(forall a. [String] -> CradleType a -> CradleConfig a
CradleConfig [String]
cradleDeps
(forall a. [(String, CradleConfig a)] -> CradleType a
Multi [(String
p, forall a. [String] -> CradleType a -> CradleConfig a
CradleConfig [] (forall a. StackType -> CradleType a
Stack forall a b. (a -> b) -> a -> b
$ StackType
ds forall a. Semigroup a => a -> a -> a
<> StackType
c)) | (String
p, StackType
c) <- [(String, StackType)]
ms])
, String
wdir)
Bios Callable
bios Maybe Callable
deps Maybe String
mbGhc -> forall a.
String -> Callable -> Maybe Callable -> Maybe String -> Cradle a
biosCradle String
wdir Callable
bios Maybe Callable
deps Maybe String
mbGhc
Direct [String]
xs -> forall a. String -> [String] -> Cradle a
directCradle String
wdir [String]
xs
CradleType b
None -> forall a. String -> Cradle a
noneCradle String
wdir
Multi [(String, CradleConfig b)]
ms -> forall b a.
(b -> Cradle a) -> String -> [(String, CradleConfig b)] -> Cradle a
multiCradle b -> Cradle a
buildCustomCradle String
wdir [(String, CradleConfig b)]
ms
Other b
a Value
_ -> b -> Cradle a
buildCustomCradle b
a
where
cradleDeps :: [String]
cradleDeps = forall a. CradleConfig a -> [String]
cradleDependencies CradleConfig b
cc
addCradleDeps :: [FilePath] -> Cradle a -> Cradle a
addCradleDeps :: forall a. [String] -> Cradle a -> Cradle a
addCradleDeps [String]
deps Cradle a
c =
Cradle a
c { cradleOptsProg :: CradleAction a
cradleOptsProg = forall a. CradleAction a -> CradleAction a
addActionDeps (forall a. Cradle a -> CradleAction a
cradleOptsProg Cradle a
c) }
where
addActionDeps :: CradleAction a -> CradleAction a
addActionDeps :: forall a. CradleAction a -> CradleAction a
addActionDeps CradleAction a
ca =
CradleAction a
ca { runCradle :: LogAction IO (WithSeverity Log)
-> String -> IO (CradleLoadResult ComponentOptions)
runCradle = \LogAction IO (WithSeverity Log)
l String
fp ->
(forall c r.
c -> (CradleError -> c) -> (r -> c) -> CradleLoadResult r -> c
cradleLoadResult
forall r. CradleLoadResult r
CradleNone
(\CradleError
err -> forall r. CradleError -> CradleLoadResult r
CradleFail (CradleError
err { cradleErrorDependencies :: [String]
cradleErrorDependencies = CradleError -> [String]
cradleErrorDependencies CradleError
err forall a. Eq a => [a] -> [a] -> [a]
`union` [String]
deps }))
(\(ComponentOptions [String]
os' String
dir [String]
ds) -> forall r. r -> CradleLoadResult r
CradleSuccess ([String] -> String -> [String] -> ComponentOptions
ComponentOptions [String]
os' String
dir ([String]
ds forall a. Eq a => [a] -> [a] -> [a]
`union` [String]
deps)))
)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a.
CradleAction a
-> LogAction IO (WithSeverity Log)
-> String
-> IO (CradleLoadResult ComponentOptions)
runCradle CradleAction a
ca LogAction IO (WithSeverity Log)
l String
fp
}
inferCradleType :: FilePath -> MaybeT IO (CradleType a, FilePath)
inferCradleType :: forall a. String -> MaybeT IO (CradleType a, String)
inferCradleType String
fp =
forall {a}. MaybeT IO (CradleType a, String)
maybeItsBios
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> forall {a}. MaybeT IO (CradleType a, String)
maybeItsStack
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> forall {a}. MaybeT IO (CradleType a, String)
maybeItsCabal
where
maybeItsBios :: MaybeT IO (CradleType a, String)
maybeItsBios = (\String
wdir -> (forall a.
Callable -> Maybe Callable -> Maybe String -> CradleType a
Bios (String -> Callable
Program forall a b. (a -> b) -> a -> b
$ String
wdir String -> String -> String
</> String
".hie-bios") forall a. Maybe a
Nothing forall a. Maybe a
Nothing, String
wdir)) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> MaybeT IO String
biosWorkDir String
fp
maybeItsStack :: MaybeT IO (CradleType a, String)
maybeItsStack = MaybeT IO String
stackExecutable forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> (forall a. StackType -> CradleType a
Stack forall a b. (a -> b) -> a -> b
$ Maybe String -> Maybe String -> StackType
StackType forall a. Maybe a
Nothing forall a. Maybe a
Nothing,) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> MaybeT IO String
stackWorkDir String
fp
maybeItsCabal :: MaybeT IO (CradleType a, String)
maybeItsCabal = (forall a. CabalType -> CradleType a
Cabal forall a b. (a -> b) -> a -> b
$ Maybe String -> CabalType
CabalType forall a. Maybe a
Nothing,) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> MaybeT IO String
cabalWorkDir String
fp
implicitConfig :: FilePath -> MaybeT IO (CradleConfig a, FilePath)
implicitConfig :: forall a. String -> MaybeT IO (CradleConfig a, String)
implicitConfig = (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first) (forall a. [String] -> CradleType a -> CradleConfig a
CradleConfig [String]
noDeps) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. String -> MaybeT IO (CradleType a, String)
inferCradleType
where
noDeps :: [FilePath]
noDeps :: [String]
noDeps = []
yamlConfig :: FilePath -> MaybeT IO FilePath
yamlConfig :: String -> MaybeT IO String
yamlConfig String
fp = do
String
configDir <- String -> MaybeT IO String
yamlConfigDirectory String
fp
forall (m :: * -> *) a. Monad m => a -> m a
return (String
configDir String -> String -> String
</> String
configFileName)
yamlConfigDirectory :: FilePath -> MaybeT IO FilePath
yamlConfigDirectory :: String -> MaybeT IO String
yamlConfigDirectory = (String -> Bool) -> String -> MaybeT IO String
findFileUpwards (String
configFileName forall a. Eq a => a -> a -> Bool
==)
readCradleConfig :: Yaml.FromJSON b => FilePath -> IO (CradleConfig b)
readCradleConfig :: forall b. FromJSON b => String -> IO (CradleConfig b)
readCradleConfig String
yamlHie = do
Config b
cfg <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall a. FromJSON a => String -> IO (Config a)
readConfig String
yamlHie
forall (m :: * -> *) a. Monad m => a -> m a
return (forall a. Config a -> CradleConfig a
cradle Config b
cfg)
configFileName :: FilePath
configFileName :: String
configFileName = String
"hie.yaml"
argDynamic :: [String]
argDynamic :: [String]
argDynamic = [String
"-dynamic" | Bool
Gap.hostIsDynamic ]
isCabalCradle :: Cradle a -> Bool
isCabalCradle :: forall a. Cradle a -> Bool
isCabalCradle Cradle a
crdl = case forall a. CradleAction a -> ActionName a
actionName (forall a. Cradle a -> CradleAction a
cradleOptsProg Cradle a
crdl) of
ActionName a
Types.Cabal -> Bool
True
ActionName a
_ -> Bool
False
isStackCradle :: Cradle a -> Bool
isStackCradle :: forall a. Cradle a -> Bool
isStackCradle Cradle a
crdl = case forall a. CradleAction a -> ActionName a
actionName (forall a. Cradle a -> CradleAction a
cradleOptsProg Cradle a
crdl) of
ActionName a
Types.Stack -> Bool
True
ActionName a
_ -> Bool
False
isDirectCradle :: Cradle a -> Bool
isDirectCradle :: forall a. Cradle a -> Bool
isDirectCradle Cradle a
crdl = case forall a. CradleAction a -> ActionName a
actionName (forall a. Cradle a -> CradleAction a
cradleOptsProg Cradle a
crdl) of
ActionName a
Types.Direct -> Bool
True
ActionName a
_ -> Bool
False
isBiosCradle :: Cradle a -> Bool
isBiosCradle :: forall a. Cradle a -> Bool
isBiosCradle Cradle a
crdl = case forall a. CradleAction a -> ActionName a
actionName (forall a. Cradle a -> CradleAction a
cradleOptsProg Cradle a
crdl) of
ActionName a
Types.Bios -> Bool
True
ActionName a
_ -> Bool
False
isMultiCradle :: Cradle a -> Bool
isMultiCradle :: forall a. Cradle a -> Bool
isMultiCradle Cradle a
crdl = case forall a. CradleAction a -> ActionName a
actionName (forall a. Cradle a -> CradleAction a
cradleOptsProg Cradle a
crdl) of
ActionName a
Types.Multi -> Bool
True
ActionName a
_ -> Bool
False
isNoneCradle :: Cradle a -> Bool
isNoneCradle :: forall a. Cradle a -> Bool
isNoneCradle Cradle a
crdl = case forall a. CradleAction a -> ActionName a
actionName (forall a. Cradle a -> CradleAction a
cradleOptsProg Cradle a
crdl) of
ActionName a
Types.None -> Bool
True
ActionName a
_ -> Bool
False
isDefaultCradle :: Cradle a -> Bool
isDefaultCradle :: forall a. Cradle a -> Bool
isDefaultCradle Cradle a
crdl = case forall a. CradleAction a -> ActionName a
actionName (forall a. Cradle a -> CradleAction a
cradleOptsProg Cradle a
crdl) of
ActionName a
Types.Default -> Bool
True
ActionName a
_ -> Bool
False
isOtherCradle :: Cradle a -> Bool
isOtherCradle :: forall a. Cradle a -> Bool
isOtherCradle Cradle a
crdl = case forall a. CradleAction a -> ActionName a
actionName (forall a. Cradle a -> CradleAction a
cradleOptsProg Cradle a
crdl) of
Types.Other a
_ -> Bool
True
ActionName a
_ -> Bool
False
defaultCradle :: FilePath -> Cradle a
defaultCradle :: forall a. String -> Cradle a
defaultCradle String
cur_dir =
Cradle
{ cradleRootDir :: String
cradleRootDir = String
cur_dir
, cradleOptsProg :: CradleAction a
cradleOptsProg = CradleAction
{ actionName :: ActionName a
actionName = forall a. ActionName a
Types.Default
, runCradle :: LogAction IO (WithSeverity Log)
-> String -> IO (CradleLoadResult ComponentOptions)
runCradle = \LogAction IO (WithSeverity Log)
_ String
_ ->
forall (m :: * -> *) a. Monad m => a -> m a
return (forall r. r -> CradleLoadResult r
CradleSuccess ([String] -> String -> [String] -> ComponentOptions
ComponentOptions [String]
argDynamic String
cur_dir []))
, runGhcCmd :: LogAction IO (WithSeverity Log)
-> [String] -> IO (CradleLoadResult String)
runGhcCmd = \LogAction IO (WithSeverity Log)
l -> LogAction IO (WithSeverity Log)
-> String -> [String] -> IO (CradleLoadResult String)
runGhcCmdOnPath LogAction IO (WithSeverity Log)
l String
cur_dir
}
}
noneCradle :: FilePath -> Cradle a
noneCradle :: forall a. String -> Cradle a
noneCradle String
cur_dir =
Cradle
{ cradleRootDir :: String
cradleRootDir = String
cur_dir
, cradleOptsProg :: CradleAction a
cradleOptsProg = CradleAction
{ actionName :: ActionName a
actionName = forall a. ActionName a
Types.None
, runCradle :: LogAction IO (WithSeverity Log)
-> String -> IO (CradleLoadResult ComponentOptions)
runCradle = \LogAction IO (WithSeverity Log)
_ String
_ -> forall (m :: * -> *) a. Monad m => a -> m a
return forall r. CradleLoadResult r
CradleNone
, runGhcCmd :: LogAction IO (WithSeverity Log)
-> [String] -> IO (CradleLoadResult String)
runGhcCmd = \LogAction IO (WithSeverity Log)
_ [String]
_ -> forall (m :: * -> *) a. Monad m => a -> m a
return forall r. CradleLoadResult r
CradleNone
}
}
multiCradle :: (b -> Cradle a) -> FilePath -> [(FilePath, CradleConfig b)] -> Cradle a
multiCradle :: forall b a.
(b -> Cradle a) -> String -> [(String, CradleConfig b)] -> Cradle a
multiCradle b -> Cradle a
buildCustomCradle String
cur_dir [(String, CradleConfig b)]
cs =
Cradle
{ cradleRootDir :: String
cradleRootDir = String
cur_dir
, cradleOptsProg :: CradleAction a
cradleOptsProg = CradleAction
{ actionName :: ActionName a
actionName = forall a. ActionName a
multiActionName
, runCradle :: LogAction IO (WithSeverity Log)
-> String -> IO (CradleLoadResult ComponentOptions)
runCradle = \LogAction IO (WithSeverity Log)
l String
fp -> String -> IO String
makeAbsolute String
fp forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall b a.
(b -> Cradle a)
-> String
-> [(String, CradleConfig b)]
-> LogAction IO (WithSeverity Log)
-> String
-> IO (CradleLoadResult ComponentOptions)
multiAction b -> Cradle a
buildCustomCradle String
cur_dir [(String, CradleConfig b)]
cs LogAction IO (WithSeverity Log)
l
, runGhcCmd :: LogAction IO (WithSeverity Log)
-> [String] -> IO (CradleLoadResult String)
runGhcCmd = \LogAction IO (WithSeverity Log)
l [String]
args ->
case forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {a}. CradleConfig a -> Bool
isNoneCradleConfig) forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a, b) -> b
snd [(String, CradleConfig b)]
cs of
[] -> forall (m :: * -> *) a. Monad m => a -> m a
return forall r. CradleLoadResult r
CradleNone
(CradleConfig b
cfg:[CradleConfig b]
_) ->
forall a.
CradleAction a
-> LogAction IO (WithSeverity Log)
-> [String]
-> IO (CradleLoadResult String)
runGhcCmd
(forall a. Cradle a -> CradleAction a
cradleOptsProg forall a b. (a -> b) -> a -> b
$ forall b a. (b -> Cradle a) -> (CradleConfig b, String) -> Cradle a
getCradle b -> Cradle a
buildCustomCradle (CradleConfig b
cfg, String
cur_dir))
LogAction IO (WithSeverity Log)
l
[String]
args
}
}
where
cfgs :: [CradleConfig b]
cfgs = forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a, b) -> b
snd [(String, CradleConfig b)]
cs
multiActionName :: ActionName a
multiActionName
| forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (\CradleConfig b
c -> forall {a}. CradleConfig a -> Bool
isStackCradleConfig CradleConfig b
c Bool -> Bool -> Bool
|| forall {a}. CradleConfig a -> Bool
isNoneCradleConfig CradleConfig b
c) [CradleConfig b]
cfgs
= forall a. ActionName a
Types.Stack
| forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (\CradleConfig b
c -> forall {a}. CradleConfig a -> Bool
isCabalCradleConfig CradleConfig b
c Bool -> Bool -> Bool
|| forall {a}. CradleConfig a -> Bool
isNoneCradleConfig CradleConfig b
c) [CradleConfig b]
cfgs
= forall a. ActionName a
Types.Cabal
| Bool
otherwise
= forall a. ActionName a
Types.Multi
isStackCradleConfig :: CradleConfig a -> Bool
isStackCradleConfig CradleConfig a
cfg = case forall a. CradleConfig a -> CradleType a
cradleType CradleConfig a
cfg of
Stack{} -> Bool
True
StackMulti{} -> Bool
True
CradleType a
_ -> Bool
False
isCabalCradleConfig :: CradleConfig a -> Bool
isCabalCradleConfig CradleConfig a
cfg = case forall a. CradleConfig a -> CradleType a
cradleType CradleConfig a
cfg of
Cabal{} -> Bool
True
CabalMulti{} -> Bool
True
CradleType a
_ -> Bool
False
isNoneCradleConfig :: CradleConfig a -> Bool
isNoneCradleConfig CradleConfig a
cfg = case forall a. CradleConfig a -> CradleType a
cradleType CradleConfig a
cfg of
CradleType a
None -> Bool
True
CradleType a
_ -> Bool
False
multiAction
:: forall b a
. (b -> Cradle a)
-> FilePath
-> [(FilePath, CradleConfig b)]
-> LogAction IO (WithSeverity Log)
-> FilePath
-> IO (CradleLoadResult ComponentOptions)
multiAction :: forall b a.
(b -> Cradle a)
-> String
-> [(String, CradleConfig b)]
-> LogAction IO (WithSeverity Log)
-> String
-> IO (CradleLoadResult ComponentOptions)
multiAction b -> Cradle a
buildCustomCradle String
cur_dir [(String, CradleConfig b)]
cs LogAction IO (WithSeverity Log)
l String
cur_fp =
[(String, CradleConfig b)]
-> IO (CradleLoadResult ComponentOptions)
selectCradle forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< IO [(String, CradleConfig b)]
canonicalizeCradles
where
err_msg :: [String]
err_msg = [String
"Multi Cradle: No prefixes matched"
, String
"pwd: " forall a. [a] -> [a] -> [a]
++ String
cur_dir
, String
"filepath: " forall a. [a] -> [a] -> [a]
++ String
cur_fp
, String
"prefixes:"
] forall a. [a] -> [a] -> [a]
++ [forall a. Show a => a -> String
show (String
pf, forall a. CradleConfig a -> CradleType a
cradleType CradleConfig b
cc) | (String
pf, CradleConfig b
cc) <- [(String, CradleConfig b)]
cs]
canonicalizeCradles :: IO [(FilePath, CradleConfig b)]
canonicalizeCradles :: IO [(String, CradleConfig b)]
canonicalizeCradles =
forall b a. Ord b => (a -> b) -> [a] -> [a]
sortOn (forall a. a -> Down a
Down forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (\(String
p, CradleConfig b
c) -> (,CradleConfig b
c) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> IO String
makeAbsolute (String
cur_dir String -> String -> String
</> String
p)) [(String, CradleConfig b)]
cs
selectCradle :: [(String, CradleConfig b)]
-> IO (CradleLoadResult ComponentOptions)
selectCradle [] =
forall (m :: * -> *) a. Monad m => a -> m a
return (forall r. CradleError -> CradleLoadResult r
CradleFail ([String] -> ExitCode -> [String] -> CradleError
CradleError [] ExitCode
ExitSuccess [String]
err_msg))
selectCradle ((String
p, CradleConfig b
c): [(String, CradleConfig b)]
css) =
if String
p forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` String
cur_fp
then forall a.
CradleAction a
-> LogAction IO (WithSeverity Log)
-> String
-> IO (CradleLoadResult ComponentOptions)
runCradle
(forall a. Cradle a -> CradleAction a
cradleOptsProg (forall b a. (b -> Cradle a) -> (CradleConfig b, String) -> Cradle a
getCradle b -> Cradle a
buildCustomCradle (CradleConfig b
c, String
cur_dir)))
LogAction IO (WithSeverity Log)
l
String
cur_fp
else [(String, CradleConfig b)]
-> IO (CradleLoadResult ComponentOptions)
selectCradle [(String, CradleConfig b)]
css
directCradle :: FilePath -> [String] -> Cradle a
directCradle :: forall a. String -> [String] -> Cradle a
directCradle String
wdir [String]
args =
Cradle
{ cradleRootDir :: String
cradleRootDir = String
wdir
, cradleOptsProg :: CradleAction a
cradleOptsProg = CradleAction
{ actionName :: ActionName a
actionName = forall a. ActionName a
Types.Direct
, runCradle :: LogAction IO (WithSeverity Log)
-> String -> IO (CradleLoadResult ComponentOptions)
runCradle = \LogAction IO (WithSeverity Log)
_ String
_ ->
forall (m :: * -> *) a. Monad m => a -> m a
return (forall r. r -> CradleLoadResult r
CradleSuccess ([String] -> String -> [String] -> ComponentOptions
ComponentOptions ([String]
args forall a. [a] -> [a] -> [a]
++ [String]
argDynamic) String
wdir []))
, runGhcCmd :: LogAction IO (WithSeverity Log)
-> [String] -> IO (CradleLoadResult String)
runGhcCmd = \LogAction IO (WithSeverity Log)
l -> LogAction IO (WithSeverity Log)
-> String -> [String] -> IO (CradleLoadResult String)
runGhcCmdOnPath LogAction IO (WithSeverity Log)
l String
wdir
}
}
biosCradle :: FilePath -> Callable -> Maybe Callable -> Maybe FilePath -> Cradle a
biosCradle :: forall a.
String -> Callable -> Maybe Callable -> Maybe String -> Cradle a
biosCradle String
wdir Callable
biosCall Maybe Callable
biosDepsCall Maybe String
mbGhc =
Cradle
{ cradleRootDir :: String
cradleRootDir = String
wdir
, cradleOptsProg :: CradleAction a
cradleOptsProg = CradleAction
{ actionName :: ActionName a
actionName = forall a. ActionName a
Types.Bios
, runCradle :: LogAction IO (WithSeverity Log)
-> String -> IO (CradleLoadResult ComponentOptions)
runCradle = String
-> Callable
-> Maybe Callable
-> LogAction IO (WithSeverity Log)
-> String
-> IO (CradleLoadResult ComponentOptions)
biosAction String
wdir Callable
biosCall Maybe Callable
biosDepsCall
, runGhcCmd :: LogAction IO (WithSeverity Log)
-> [String] -> IO (CradleLoadResult String)
runGhcCmd = \LogAction IO (WithSeverity Log)
l [String]
args -> LogAction IO (WithSeverity Log)
-> String
-> String
-> [String]
-> String
-> IO (CradleLoadResult String)
readProcessWithCwd LogAction IO (WithSeverity Log)
l String
wdir (forall a. a -> Maybe a -> a
fromMaybe String
"ghc" Maybe String
mbGhc) [String]
args String
""
}
}
biosWorkDir :: FilePath -> MaybeT IO FilePath
biosWorkDir :: String -> MaybeT IO String
biosWorkDir = (String -> Bool) -> String -> MaybeT IO String
findFileUpwards (String
".hie-bios" forall a. Eq a => a -> a -> Bool
==)
biosDepsAction :: LogAction IO (WithSeverity Log) -> FilePath -> Maybe Callable -> FilePath -> IO [FilePath]
biosDepsAction :: LogAction IO (WithSeverity Log)
-> String -> Maybe Callable -> String -> IO [String]
biosDepsAction LogAction IO (WithSeverity Log)
l String
wdir (Just Callable
biosDepsCall) String
fp = do
CreateProcess
biosDeps' <- Callable -> Maybe String -> IO CreateProcess
callableToProcess Callable
biosDepsCall (forall a. a -> Maybe a
Just String
fp)
(ExitCode
ex, [String]
sout, [String]
serr, [(String
_, Maybe [String]
args)]) <- [String]
-> LogAction IO (WithSeverity Log)
-> String
-> CreateProcess
-> IO (ExitCode, [String], [String], [(String, Maybe [String])])
readProcessWithOutputs [String
hie_bios_output] LogAction IO (WithSeverity Log)
l String
wdir CreateProcess
biosDeps'
case ExitCode
ex of
ExitFailure Int
_ -> forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> String
show (ExitCode
ex, [String]
sout, [String]
serr)
ExitCode
ExitSuccess -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a -> a
fromMaybe [] Maybe [String]
args
biosDepsAction LogAction IO (WithSeverity Log)
_ String
_ Maybe Callable
Nothing String
_ = forall (m :: * -> *) a. Monad m => a -> m a
return []
biosAction
:: FilePath
-> Callable
-> Maybe Callable
-> LogAction IO (WithSeverity Log)
-> FilePath
-> IO (CradleLoadResult ComponentOptions)
biosAction :: String
-> Callable
-> Maybe Callable
-> LogAction IO (WithSeverity Log)
-> String
-> IO (CradleLoadResult ComponentOptions)
biosAction String
wdir Callable
bios Maybe Callable
bios_deps LogAction IO (WithSeverity Log)
l String
fp = do
CreateProcess
bios' <- Callable -> Maybe String -> IO CreateProcess
callableToProcess Callable
bios (forall a. a -> Maybe a
Just String
fp)
(ExitCode
ex, [String]
_stdo, [String]
std, [(String
_, Maybe [String]
res),(String
_, Maybe [String]
mb_deps)]) <-
[String]
-> LogAction IO (WithSeverity Log)
-> String
-> CreateProcess
-> IO (ExitCode, [String], [String], [(String, Maybe [String])])
readProcessWithOutputs [String
hie_bios_output, String
hie_bios_deps] LogAction IO (WithSeverity Log)
l String
wdir CreateProcess
bios'
[String]
deps <- case Maybe [String]
mb_deps of
Just [String]
x -> forall (m :: * -> *) a. Monad m => a -> m a
return [String]
x
Maybe [String]
Nothing -> LogAction IO (WithSeverity Log)
-> String -> Maybe Callable -> String -> IO [String]
biosDepsAction LogAction IO (WithSeverity Log)
l String
wdir Maybe Callable
bios_deps String
fp
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ (ExitCode, [String], String, [String])
-> [String] -> CradleLoadResult ComponentOptions
makeCradleResult (ExitCode
ex, [String]
std, String
wdir, forall a. a -> Maybe a -> a
fromMaybe [] Maybe [String]
res) [String]
deps
callableToProcess :: Callable -> Maybe String -> IO CreateProcess
callableToProcess :: Callable -> Maybe String -> IO CreateProcess
callableToProcess (Command String
shellCommand) Maybe String
file = do
[(String, String)]
old_env <- IO [(String, String)]
getEnvironment
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ (String -> CreateProcess
shell String
shellCommand) { env :: Maybe [(String, String)]
env = (forall a. a -> [a] -> [a]
: [(String, String)]
old_env) forall b c a. (b -> c) -> (a -> b) -> a -> c
. (,) String
hie_bios_arg forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe String
file }
callableToProcess (Program String
path) Maybe String
file = do
String
canon_path <- String -> IO String
canonicalizePath String
path
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ String -> [String] -> CreateProcess
proc String
canon_path (forall a. Maybe a -> [a]
maybeToList Maybe String
file)
cabalCradle :: FilePath -> Maybe String -> Cradle a
cabalCradle :: forall a. String -> Maybe String -> Cradle a
cabalCradle String
wdir Maybe String
mc =
Cradle
{ cradleRootDir :: String
cradleRootDir = String
wdir
, cradleOptsProg :: CradleAction a
cradleOptsProg = CradleAction
{ actionName :: ActionName a
actionName = forall a. ActionName a
Types.Cabal
, runCradle :: LogAction IO (WithSeverity Log)
-> String -> IO (CradleLoadResult ComponentOptions)
runCradle = \LogAction IO (WithSeverity Log)
l String
f -> forall (m :: * -> *) a.
CradleLoadResultT m a -> m (CradleLoadResult a)
runCradleResultT forall b c a. (b -> c) -> (a -> b) -> a -> c
. String
-> Maybe String
-> LogAction IO (WithSeverity Log)
-> String
-> CradleLoadResultT IO ComponentOptions
cabalAction String
wdir Maybe String
mc LogAction IO (WithSeverity Log)
l forall a b. (a -> b) -> a -> b
$ String
f
, runGhcCmd :: LogAction IO (WithSeverity Log)
-> [String] -> IO (CradleLoadResult String)
runGhcCmd = \LogAction IO (WithSeverity Log)
l [String]
args -> forall (m :: * -> *) a.
CradleLoadResultT m a -> m (CradleLoadResult a)
runCradleResultT forall a b. (a -> b) -> a -> b
$ do
String
buildDir <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ String -> IO String
cabalBuildDir String
wdir
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ Bool -> String -> IO ()
createDirectoryIfMissing Bool
True (String
buildDir String -> String -> String
</> String
"tmp")
CreateProcess
cabalProc <- LogAction IO (WithSeverity Log)
-> String
-> String
-> [String]
-> CradleLoadResultT IO CreateProcess
cabalProcess LogAction IO (WithSeverity Log)
l String
wdir String
"v2-exec" forall a b. (a -> b) -> a -> b
$ [String
"ghc", String
"-v0", String
"--"] forall a. [a] -> [a] -> [a]
++ [String]
args
CreateProcess -> String -> CradleLoadResultT IO String
readProcessWithCwd' CreateProcess
cabalProc String
""
}
}
cabalProcess :: LogAction IO (WithSeverity Log) -> FilePath -> String -> [String] -> CradleLoadResultT IO CreateProcess
cabalProcess :: LogAction IO (WithSeverity Log)
-> String
-> String
-> [String]
-> CradleLoadResultT IO CreateProcess
cabalProcess LogAction IO (WithSeverity Log)
l String
workDir String
command [String]
args = do
(String, String)
ghcDirs <- LogAction IO (WithSeverity Log)
-> String -> CradleLoadResultT IO (String, String)
cabalGhcDirs LogAction IO (WithSeverity Log)
l String
workDir
[(String, String)]
newEnvironment <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ (String, String) -> IO [(String, String)]
setupEnvironment (String, String)
ghcDirs
CreateProcess
cabalProc <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ (String, String) -> IO CreateProcess
setupCabalCommand (String, String)
ghcDirs
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ (CreateProcess
cabalProc
{ env :: Maybe [(String, String)]
env = forall a. a -> Maybe a
Just [(String, String)]
newEnvironment
, cwd :: Maybe String
cwd = forall a. a -> Maybe a
Just String
workDir
})
where
processEnvironment :: (FilePath, FilePath) -> [(String, String)]
processEnvironment :: (String, String) -> [(String, String)]
processEnvironment (String
ghcBin, String
libdir) =
[(String
hie_bios_ghc, String
ghcBin), (String
hie_bios_ghc_args, String
"-B" forall a. [a] -> [a] -> [a]
++ String
libdir)]
setupEnvironment :: (FilePath, FilePath) -> IO [(String, String)]
setupEnvironment :: (String, String) -> IO [(String, String)]
setupEnvironment (String, String)
ghcDirs = do
[(String, String)]
environment <- IO [(String, String)]
getCleanEnvironment
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ (String, String) -> [(String, String)]
processEnvironment (String, String)
ghcDirs forall a. [a] -> [a] -> [a]
++ [(String, String)]
environment
setupCabalCommand :: (FilePath, FilePath) -> IO CreateProcess
setupCabalCommand :: (String, String) -> IO CreateProcess
setupCabalCommand (String
ghcBin, String
libdir) = do
String
wrapper_fp <- LogAction IO (WithSeverity Log) -> GhcProc -> String -> IO String
withGhcWrapperTool LogAction IO (WithSeverity Log)
l (String
"ghc", []) String
workDir
String
buildDir <- String -> IO String
cabalBuildDir String
workDir
String
ghcPkgPath <- String -> String -> IO String
withGhcPkgTool String
ghcBin String
libdir
let extraCabalArgs :: [String]
extraCabalArgs =
[ String
"--builddir=" forall a. Semigroup a => a -> a -> a
<> String
buildDir
, String
command
, String
"--with-compiler", String
wrapper_fp
, String
"--with-hc-pkg", String
ghcPkgPath
]
LogAction IO (WithSeverity Log)
-> String -> [String] -> IO CreateProcess
loggedProc LogAction IO (WithSeverity Log)
l String
"cabal" ([String]
extraCabalArgs forall a. [a] -> [a] -> [a]
++ [String]
args)
withGhcPkgTool :: FilePath -> FilePath -> IO FilePath
withGhcPkgTool :: String -> String -> IO String
withGhcPkgTool String
ghcPathAbs String
libdir = do
let ghcName :: String
ghcName = String -> String
takeFileName String
ghcPathAbs
ghcPkgPath :: String
ghcPkgPath = String -> String
guessGhcPkgFromGhc String
ghcName
if Bool
isWindows
then forall (f :: * -> *) a. Applicative f => a -> f a
pure String
ghcPkgPath
else String -> IO String
withWrapperTool String
ghcPkgPath
where
ghcDir :: String
ghcDir = String -> String
takeDirectory String
ghcPathAbs
guessGhcPkgFromGhc :: String -> String
guessGhcPkgFromGhc String
ghcName =
let ghcPkgName :: Text
ghcPkgName = Text -> Text -> Text -> Text
T.replace Text
"ghc" Text
"ghc-pkg" (String -> Text
T.pack String
ghcName)
in String
ghcDir String -> String -> String
</> Text -> String
T.unpack Text
ghcPkgName
withWrapperTool :: String -> IO String
withWrapperTool String
ghcPkg = do
let globalPackageDb :: String
globalPackageDb = String
libdir String -> String -> String
</> String
"package.conf.d"
contents :: String
contents = [String] -> String
unlines
[ String
"#!/bin/sh"
, [String] -> String
unwords [String
"exec", String -> String
escapeFilePath String
ghcPkg
, String
"--global-package-db", String -> String
escapeFilePath String
globalPackageDb
, String
"${1+\"$@\"}"
]
]
srcHash :: String
srcHash = forall a. Show a => a -> String
show (String -> Fingerprint
fingerprintString String
contents)
String -> String -> (String -> IO ()) -> IO String
cacheFile String
"ghc-pkg" String
srcHash forall a b. (a -> b) -> a -> b
$ \String
wrapperFp -> String -> String -> IO ()
writeFile String
wrapperFp String
contents
escapeFilePath :: String -> String
escapeFilePath String
fp = String -> String
trimEnd forall a b. (a -> b) -> a -> b
$ [String] -> String
escapeArgs [String
fp]
cabalCradleDependencies :: FilePath -> FilePath -> IO [FilePath]
cabalCradleDependencies :: String -> String -> IO [String]
cabalCradleDependencies String
rootDir String
componentDir = do
let relFp :: String
relFp = String -> String -> String
makeRelative String
rootDir String
componentDir
[String]
cabalFiles' <- String -> IO [String]
findCabalFiles String
componentDir
let cabalFiles :: [String]
cabalFiles = forall a b. (a -> b) -> [a] -> [b]
map (String
relFp String -> String -> String
</>) [String]
cabalFiles'
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map String -> String
normalise forall a b. (a -> b) -> a -> b
$ [String]
cabalFiles forall a. [a] -> [a] -> [a]
++ [String
"cabal.project", String
"cabal.project.local"]
findCabalFiles :: FilePath -> IO [FilePath]
findCabalFiles :: String -> IO [String]
findCabalFiles String
wdir = do
[String]
dirContent <- String -> IO [String]
listDirectory String
wdir
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. (a -> Bool) -> [a] -> [a]
filter ((forall a. Eq a => a -> a -> Bool
== String
".cabal") forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
takeExtension) [String]
dirContent
processCabalWrapperArgs :: [String] -> Maybe (FilePath, [String])
processCabalWrapperArgs :: [String] -> Maybe GhcProc
processCabalWrapperArgs [String]
args =
case [String]
args of
(String
dir: [String]
ghc_args) ->
let final_args :: [String]
final_args =
[String] -> [String]
removeVerbosityOpts
forall a b. (a -> b) -> a -> b
$ [String] -> [String]
removeRTS
forall a b. (a -> b) -> a -> b
$ [String] -> [String]
removeInteractive [String]
ghc_args
in forall a. a -> Maybe a
Just (String
dir, [String]
final_args)
[String]
_ -> forall a. Maybe a
Nothing
type GhcProc = (FilePath, [String])
withGhcWrapperTool :: LogAction IO (WithSeverity Log) -> GhcProc -> FilePath -> IO FilePath
withGhcWrapperTool :: LogAction IO (WithSeverity Log) -> GhcProc -> String -> IO String
withGhcWrapperTool LogAction IO (WithSeverity Log)
l (String
mbGhc, [String]
ghcArgs) String
wdir = do
let wrapperContents :: String
wrapperContents = if Bool
isWindows then String
cabalWrapperHs else String
cabalWrapper
withExtension :: String -> String
withExtension String
fp = if Bool
isWindows then String
fp String -> String -> String
<.> String
"exe" else String
fp
srcHash :: String
srcHash = forall a. Show a => a -> String
show (String -> Fingerprint
fingerprintString String
wrapperContents)
String -> String -> (String -> IO ()) -> IO String
cacheFile (String -> String
withExtension String
"wrapper") String
srcHash forall a b. (a -> b) -> a -> b
$ \String
wrapper_fp ->
if Bool
isWindows
then
forall (m :: * -> *) a.
(MonadIO m, MonadMask m) =>
String -> (String -> m a) -> m a
withSystemTempDirectory String
"hie-bios" forall a b. (a -> b) -> a -> b
$ \ String
tmpDir -> do
let wrapper_hs :: String
wrapper_hs = String
wrapper_fp String -> String -> String
-<.> String
"hs"
String -> String -> IO ()
writeFile String
wrapper_hs String
wrapperContents
CreateProcess
ghc <- LogAction IO (WithSeverity Log)
-> String -> [String] -> IO CreateProcess
loggedProc LogAction IO (WithSeverity Log)
l String
mbGhc forall a b. (a -> b) -> a -> b
$
[String]
ghcArgs forall a. [a] -> [a] -> [a]
++ [String
"-rtsopts=ignore", String
"-outputdir", String
tmpDir, String
"-o", String
wrapper_fp, String
wrapper_hs]
let ghc' :: CreateProcess
ghc' = CreateProcess
ghc { cwd :: Maybe String
cwd = forall a. a -> Maybe a
Just String
wdir }
CreateProcess -> String -> IO String
readCreateProcess CreateProcess
ghc' String
"" forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= String -> IO ()
putStr
else String -> String -> IO ()
writeFile String
wrapper_fp String
wrapperContents
cacheFile :: FilePath -> String -> (FilePath -> IO ()) -> IO FilePath
cacheFile :: String -> String -> (String -> IO ()) -> IO String
cacheFile String
fpName String
srcHash String -> IO ()
populate = do
String
cacheDir <- String -> IO String
getCacheDir String
""
Bool -> String -> IO ()
createDirectoryIfMissing Bool
True String
cacheDir
let newFpName :: String
newFpName = String
cacheDir String -> String -> String
</> (String -> String
dropExtensions String
fpName forall a. Semigroup a => a -> a -> a
<> String
"-" forall a. Semigroup a => a -> a -> a
<> String
srcHash) String -> String -> String
<.> String -> String
takeExtensions String
fpName
forall (m :: * -> *). Monad m => m Bool -> m () -> m ()
unlessM (String -> IO Bool
doesFileExist String
newFpName) forall a b. (a -> b) -> a -> b
$ do
String -> IO ()
populate String
newFpName
String -> IO ()
setMode String
newFpName
forall (f :: * -> *) a. Applicative f => a -> f a
pure String
newFpName
where
setMode :: String -> IO ()
setMode String
wrapper_fp = String -> FileMode -> IO ()
setFileMode String
wrapper_fp FileMode
accessModes
cabalBuildDir :: FilePath -> IO FilePath
cabalBuildDir :: String -> IO String
cabalBuildDir String
workDir = do
String
abs_work_dir <- String -> IO String
makeAbsolute String
workDir
let dirHash :: String
dirHash = forall a. Show a => a -> String
show (String -> Fingerprint
fingerprintString String
abs_work_dir)
String -> IO String
getCacheDir (String
"dist-" forall a. Semigroup a => a -> a -> a
<> forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Bool
isSpace) (String -> String
takeBaseName String
abs_work_dir)forall a. Semigroup a => a -> a -> a
<>String
"-"forall a. Semigroup a => a -> a -> a
<>String
dirHash)
cabalGhcDirs :: LogAction IO (WithSeverity Log) -> FilePath -> CradleLoadResultT IO (FilePath, FilePath)
cabalGhcDirs :: LogAction IO (WithSeverity Log)
-> String -> CradleLoadResultT IO (String, String)
cabalGhcDirs LogAction IO (WithSeverity Log)
l String
workDir = do
String
libdir <- LogAction IO (WithSeverity Log)
-> String
-> String
-> [String]
-> String
-> CradleLoadResultT IO String
readProcessWithCwd_ LogAction IO (WithSeverity Log)
l String
workDir String
"cabal" [String
"exec", String
"-v0", String
"--", String
"ghc", String
"--print-libdir"] String
""
String
exe <- LogAction IO (WithSeverity Log)
-> String
-> String
-> [String]
-> String
-> CradleLoadResultT IO String
readProcessWithCwd_ LogAction IO (WithSeverity Log)
l String
workDir String
"cabal"
[ String
"exec", String
"-v0", String
"--" , String
"ghc", String
"-package-env=-", String
"-ignore-dot-ghci", String
"-e"
, String
"Control.Monad.join (Control.Monad.fmap System.IO.putStr System.Environment.getExecutablePath)"
]
String
""
forall (f :: * -> *) a. Applicative f => a -> f a
pure (String -> String
trimEnd String
exe, String -> String
trimEnd String
libdir)
cabalAction
:: FilePath
-> Maybe String
-> LogAction IO (WithSeverity Log)
-> FilePath
-> CradleLoadResultT IO ComponentOptions
cabalAction :: String
-> Maybe String
-> LogAction IO (WithSeverity Log)
-> String
-> CradleLoadResultT IO ComponentOptions
cabalAction String
workDir Maybe String
mc LogAction IO (WithSeverity Log)
l String
fp = do
let
cabalCommand :: String
cabalCommand = String
"v2-repl"
cabalArgs :: [String]
cabalArgs = [forall a. a -> Maybe a -> a
fromMaybe (String -> String
fixTargetPath String
fp) Maybe String
mc]
CreateProcess
cabalProc <- LogAction IO (WithSeverity Log)
-> String
-> String
-> [String]
-> CradleLoadResultT IO CreateProcess
cabalProcess LogAction IO (WithSeverity Log)
l String
workDir String
cabalCommand [String]
cabalArgs forall (m :: * -> *) a.
Monad m =>
CradleLoadResultT m a
-> (CradleError -> m CradleError) -> CradleLoadResultT m a
`modCradleError` \CradleError
err -> do
[String]
deps <- String -> String -> IO [String]
cabalCradleDependencies String
workDir String
workDir
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ CradleError
err { cradleErrorDependencies :: [String]
cradleErrorDependencies = CradleError -> [String]
cradleErrorDependencies CradleError
err forall a. [a] -> [a] -> [a]
++ [String]
deps }
(ExitCode
ex, [String]
output, [String]
stde, [(String
_, Maybe [String]
maybeArgs)]) <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ [String]
-> LogAction IO (WithSeverity Log)
-> String
-> CreateProcess
-> IO (ExitCode, [String], [String], [(String, Maybe [String])])
readProcessWithOutputs [String
hie_bios_output] LogAction IO (WithSeverity Log)
l String
workDir CreateProcess
cabalProc
let args :: [String]
args = forall a. a -> Maybe a -> a
fromMaybe [] Maybe [String]
maybeArgs
let errorDetails :: [String]
errorDetails =
[String
"Failed command: " forall a. Semigroup a => a -> a -> a
<> CmdSpec -> String
prettyCmdSpec (CreateProcess -> CmdSpec
cmdspec CreateProcess
cabalProc)
, [String] -> String
unlines [String]
output
, [String] -> String
unlines [String]
stde
, [String] -> String
unlines forall a b. (a -> b) -> a -> b
$ [String]
args
, String
"Process Environment:"]
forall a. Semigroup a => a -> a -> a
<> CreateProcess -> [String]
prettyProcessEnv CreateProcess
cabalProc
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (ExitCode
ex forall a. Eq a => a -> a -> Bool
/= ExitCode
ExitSuccess) forall a b. (a -> b) -> a -> b
$ do
[String]
deps <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ String -> String -> IO [String]
cabalCradleDependencies String
workDir String
workDir
let cmd :: String
cmd = forall a. Show a => a -> String
show ([String
"cabal", String
cabalCommand] forall a. Semigroup a => a -> a -> a
<> [String]
cabalArgs)
let errorMsg :: String
errorMsg = String
"Failed to run " forall a. Semigroup a => a -> a -> a
<> String
cmd forall a. Semigroup a => a -> a -> a
<> String
" in directory \"" forall a. Semigroup a => a -> a -> a
<> String
workDir forall a. Semigroup a => a -> a -> a
<> String
"\". Consult the logs for full command and error."
forall (m :: * -> *) a.
Monad m =>
CradleError -> CradleLoadResultT m a
throwCE ([String] -> ExitCode -> [String] -> CradleError
CradleError [String]
deps ExitCode
ex ([String
errorMsg] forall a. Semigroup a => a -> a -> a
<> [String]
errorDetails))
case [String] -> Maybe GhcProc
processCabalWrapperArgs [String]
args of
Maybe GhcProc
Nothing -> do
[String]
deps <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ String -> String -> IO [String]
cabalCradleDependencies String
workDir String
workDir
forall (m :: * -> *) a.
Monad m =>
CradleError -> CradleLoadResultT m a
throwCE ([String] -> ExitCode -> [String] -> CradleError
CradleError [String]
deps ExitCode
ex forall a b. (a -> b) -> a -> b
$
([String
"Failed to parse result of calling cabal" ] forall a. Semigroup a => a -> a -> a
<> [String]
errorDetails))
Just (String
componentDir, [String]
final_args) -> do
[String]
deps <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ String -> String -> IO [String]
cabalCradleDependencies String
workDir String
componentDir
forall (m :: * -> *) a.
m (CradleLoadResult a) -> CradleLoadResultT m a
CradleLoadResultT forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ (ExitCode, [String], String, [String])
-> [String] -> CradleLoadResult ComponentOptions
makeCradleResult (ExitCode
ex, [String]
stde, String
componentDir, [String]
final_args) [String]
deps
where
fixTargetPath :: String -> String
fixTargetPath String
x
| Bool
isWindows Bool -> Bool -> Bool
&& String -> Bool
hasDrive String
x = String -> String -> String
makeRelative String
workDir String
x
| Bool
otherwise = String
x
removeInteractive :: [String] -> [String]
removeInteractive :: [String] -> [String]
removeInteractive = forall a. (a -> Bool) -> [a] -> [a]
filter (forall a. Eq a => a -> a -> Bool
/= String
"--interactive")
data InRTS = OutsideRTS | InsideRTS
removeRTS :: [String] -> [String]
removeRTS :: [String] -> [String]
removeRTS = InRTS -> [String] -> [String]
go InRTS
OutsideRTS
where
go :: InRTS -> [String] -> [String]
go :: InRTS -> [String] -> [String]
go InRTS
_ [] = []
go InRTS
OutsideRTS (String
y:[String]
ys)
| String
"+RTS" forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` String
y = InRTS -> [String] -> [String]
go (if String
"-RTS" forall a. Eq a => [a] -> [a] -> Bool
`isSuffixOf` String
y then InRTS
OutsideRTS else InRTS
InsideRTS) [String]
ys
| Bool
otherwise = String
y forall a. a -> [a] -> [a]
: InRTS -> [String] -> [String]
go InRTS
OutsideRTS [String]
ys
go InRTS
InsideRTS (String
y:[String]
ys) = InRTS -> [String] -> [String]
go (if String
"-RTS" forall a. Eq a => [a] -> [a] -> Bool
`isSuffixOf` String
y then InRTS
OutsideRTS else InRTS
InsideRTS) [String]
ys
removeVerbosityOpts :: [String] -> [String]
removeVerbosityOpts :: [String] -> [String]
removeVerbosityOpts = forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool -> Bool
(&&) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a. Eq a => a -> a -> Bool
/= String
"-v0") forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a. Eq a => a -> a -> Bool
/= String
"-w"))
cabalWorkDir :: FilePath -> MaybeT IO FilePath
cabalWorkDir :: String -> MaybeT IO String
cabalWorkDir String
wdir =
(String -> Bool) -> String -> MaybeT IO String
findFileUpwards (forall a. Eq a => a -> a -> Bool
== String
"cabal.project") String
wdir
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (String -> Bool) -> String -> MaybeT IO String
findFileUpwards (\String
fp -> String -> String
takeExtension String
fp forall a. Eq a => a -> a -> Bool
== String
".cabal") String
wdir
data StackYaml
= NoExplicitYaml
| ExplicitYaml FilePath
stackYamlFromMaybe :: FilePath -> Maybe FilePath -> StackYaml
stackYamlFromMaybe :: String -> Maybe String -> StackYaml
stackYamlFromMaybe String
_wdir Maybe String
Nothing = StackYaml
NoExplicitYaml
stackYamlFromMaybe String
wdir (Just String
fp) = String -> StackYaml
ExplicitYaml (String
wdir String -> String -> String
</> String
fp)
stackYamlProcessArgs :: StackYaml -> [String]
stackYamlProcessArgs :: StackYaml -> [String]
stackYamlProcessArgs (ExplicitYaml String
yaml) = [String
"--stack-yaml", String
yaml]
stackYamlProcessArgs StackYaml
NoExplicitYaml = []
stackYamlLocationOrDefault :: StackYaml -> FilePath
stackYamlLocationOrDefault :: StackYaml -> String
stackYamlLocationOrDefault StackYaml
NoExplicitYaml = String
"stack.yaml"
stackYamlLocationOrDefault (ExplicitYaml String
yaml) = String
yaml
stackCradle :: FilePath -> Maybe String -> StackYaml -> Cradle a
stackCradle :: forall a. String -> Maybe String -> StackYaml -> Cradle a
stackCradle String
wdir Maybe String
mc StackYaml
syaml =
Cradle
{ cradleRootDir :: String
cradleRootDir = String
wdir
, cradleOptsProg :: CradleAction a
cradleOptsProg = CradleAction
{ actionName :: ActionName a
actionName = forall a. ActionName a
Types.Stack
, runCradle :: LogAction IO (WithSeverity Log)
-> String -> IO (CradleLoadResult ComponentOptions)
runCradle = String
-> Maybe String
-> StackYaml
-> LogAction IO (WithSeverity Log)
-> String
-> IO (CradleLoadResult ComponentOptions)
stackAction String
wdir Maybe String
mc StackYaml
syaml
, runGhcCmd :: LogAction IO (WithSeverity Log)
-> [String] -> IO (CradleLoadResult String)
runGhcCmd = \LogAction IO (WithSeverity Log)
l [String]
args -> forall (m :: * -> *) a.
CradleLoadResultT m a -> m (CradleLoadResult a)
runCradleResultT forall a b. (a -> b) -> a -> b
$ do
String
_ <- LogAction IO (WithSeverity Log)
-> String
-> String
-> [String]
-> String
-> CradleLoadResultT IO String
readProcessWithCwd_ LogAction IO (WithSeverity Log)
l String
wdir String
"stack" (StackYaml -> [String]
stackYamlProcessArgs StackYaml
syaml forall a. Semigroup a => a -> a -> a
<> [String
"setup", String
"--silent"]) String
""
LogAction IO (WithSeverity Log)
-> String
-> String
-> [String]
-> String
-> CradleLoadResultT IO String
readProcessWithCwd_ LogAction IO (WithSeverity Log)
l String
wdir String
"stack"
(StackYaml -> [String]
stackYamlProcessArgs StackYaml
syaml forall a. Semigroup a => a -> a -> a
<> [String
"exec", String
"ghc", String
"--"] forall a. Semigroup a => a -> a -> a
<> [String]
args)
String
""
}
}
stackCradleDependencies :: FilePath -> FilePath -> StackYaml -> IO [FilePath]
stackCradleDependencies :: String -> String -> StackYaml -> IO [String]
stackCradleDependencies String
wdir String
componentDir StackYaml
syaml = do
let relFp :: String
relFp = String -> String -> String
makeRelative String
wdir String
componentDir
[String]
cabalFiles' <- String -> IO [String]
findCabalFiles String
componentDir
let cabalFiles :: [String]
cabalFiles = forall a b. (a -> b) -> [a] -> [b]
map (String
relFp String -> String -> String
</>) [String]
cabalFiles'
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map String -> String
normalise forall a b. (a -> b) -> a -> b
$
[String]
cabalFiles forall a. [a] -> [a] -> [a]
++ [String
relFp String -> String -> String
</> String
"package.yaml", StackYaml -> String
stackYamlLocationOrDefault StackYaml
syaml]
stackAction
:: FilePath
-> Maybe String
-> StackYaml
-> LogAction IO (WithSeverity Log)
-> FilePath
-> IO (CradleLoadResult ComponentOptions)
stackAction :: String
-> Maybe String
-> StackYaml
-> LogAction IO (WithSeverity Log)
-> String
-> IO (CradleLoadResult ComponentOptions)
stackAction String
workDir Maybe String
mc StackYaml
syaml LogAction IO (WithSeverity Log)
l String
_fp = do
let ghcProcArgs :: GhcProc
ghcProcArgs = (String
"stack", StackYaml -> [String]
stackYamlProcessArgs StackYaml
syaml forall a. Semigroup a => a -> a -> a
<> [String
"exec", String
"ghc", String
"--"])
String
wrapper_fp <- LogAction IO (WithSeverity Log) -> GhcProc -> String -> IO String
withGhcWrapperTool LogAction IO (WithSeverity Log)
l GhcProc
ghcProcArgs String
workDir
(ExitCode
ex1, [String]
_stdo, [String]
stde, [(String
_, Maybe [String]
maybeArgs)]) <-
LogAction IO (WithSeverity Log)
-> StackYaml -> [String] -> IO CreateProcess
stackProcess LogAction IO (WithSeverity Log)
l StackYaml
syaml
([String
"repl", String
"--no-nix-pure", String
"--with-ghc", String
wrapper_fp]
forall a. Semigroup a => a -> a -> a
<> [ String
comp | Just String
comp <- [Maybe String
mc] ]) forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
[String]
-> LogAction IO (WithSeverity Log)
-> String
-> CreateProcess
-> IO (ExitCode, [String], [String], [(String, Maybe [String])])
readProcessWithOutputs [String
hie_bios_output] LogAction IO (WithSeverity Log)
l String
workDir
(ExitCode
ex2, [String]
pkg_args, [String]
stdr, [(String, Maybe [String])]
_) <-
LogAction IO (WithSeverity Log)
-> StackYaml -> [String] -> IO CreateProcess
stackProcess LogAction IO (WithSeverity Log)
l StackYaml
syaml [String
"path", String
"--ghc-package-path"] forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
[String]
-> LogAction IO (WithSeverity Log)
-> String
-> CreateProcess
-> IO (ExitCode, [String], [String], [(String, Maybe [String])])
readProcessWithOutputs [String
hie_bios_output] LogAction IO (WithSeverity Log)
l String
workDir
let split_pkgs :: [String]
split_pkgs = forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap String -> [String]
splitSearchPath [String]
pkg_args
pkg_ghc_args :: [String]
pkg_ghc_args = forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (\String
p -> [String
"-package-db", String
p] ) [String]
split_pkgs
args :: [String]
args = forall a. a -> Maybe a -> a
fromMaybe [] Maybe [String]
maybeArgs
case [String] -> Maybe GhcProc
processCabalWrapperArgs [String]
args of
Maybe GhcProc
Nothing -> do
[String]
deps <- String -> String -> StackYaml -> IO [String]
stackCradleDependencies String
workDir String
workDir StackYaml
syaml
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall r. CradleError -> CradleLoadResult r
CradleFail
([String] -> ExitCode -> [String] -> CradleError
CradleError [String]
deps ExitCode
ex1 forall a b. (a -> b) -> a -> b
$
[ String
"Failed to parse result of calling stack" ]
forall a. [a] -> [a] -> [a]
++ [String]
stde
forall a. [a] -> [a] -> [a]
++ [String]
args
)
Just (String
componentDir, [String]
ghc_args) -> do
[String]
deps <- String -> String -> StackYaml -> IO [String]
stackCradleDependencies String
workDir String
componentDir StackYaml
syaml
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ (ExitCode, [String], String, [String])
-> [String] -> CradleLoadResult ComponentOptions
makeCradleResult
( [ExitCode] -> ExitCode
combineExitCodes [ExitCode
ex1, ExitCode
ex2]
, [String]
stde forall a. [a] -> [a] -> [a]
++ [String]
stdr, String
componentDir
, [String]
ghc_args forall a. [a] -> [a] -> [a]
++ [String]
pkg_ghc_args
)
[String]
deps
stackProcess :: LogAction IO (WithSeverity Log) -> StackYaml -> [String] -> IO CreateProcess
stackProcess :: LogAction IO (WithSeverity Log)
-> StackYaml -> [String] -> IO CreateProcess
stackProcess LogAction IO (WithSeverity Log)
l StackYaml
syaml [String]
args = LogAction IO (WithSeverity Log)
-> String -> [String] -> IO CreateProcess
loggedProc LogAction IO (WithSeverity Log)
l String
"stack" forall a b. (a -> b) -> a -> b
$ StackYaml -> [String]
stackYamlProcessArgs StackYaml
syaml forall a. Semigroup a => a -> a -> a
<> [String]
args
combineExitCodes :: [ExitCode] -> ExitCode
combineExitCodes :: [ExitCode] -> ExitCode
combineExitCodes = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr ExitCode -> ExitCode -> ExitCode
go ExitCode
ExitSuccess
where
go :: ExitCode -> ExitCode -> ExitCode
go ExitCode
ExitSuccess ExitCode
b = ExitCode
b
go ExitCode
a ExitCode
_ = ExitCode
a
stackExecutable :: MaybeT IO FilePath
stackExecutable :: MaybeT IO String
stackExecutable = forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT forall a b. (a -> b) -> a -> b
$ String -> IO (Maybe String)
findExecutable String
"stack"
stackWorkDir :: FilePath -> MaybeT IO FilePath
stackWorkDir :: String -> MaybeT IO String
stackWorkDir = (String -> Bool) -> String -> MaybeT IO String
findFileUpwards forall {a}. (Eq a, IsString a) => a -> Bool
isStack
where
isStack :: a -> Bool
isStack a
name = a
name forall a. Eq a => a -> a -> Bool
== a
"stack.yaml"
findFileUpwards :: (FilePath -> Bool) -> FilePath -> MaybeT IO FilePath
findFileUpwards :: (String -> Bool) -> String -> MaybeT IO String
findFileUpwards String -> Bool
p String
dir = do
[String]
cnts <-
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO
forall a b. (a -> b) -> a -> b
$ forall e b a.
Exception e =>
(e -> Maybe b) -> (b -> IO a) -> IO a -> IO a
handleJust
(\(IOError
e :: IOError) -> if IOError -> Bool
isPermissionError IOError
e then forall a. a -> Maybe a
Just [] else forall a. Maybe a
Nothing)
forall (f :: * -> *) a. Applicative f => a -> f a
pure
((String -> Bool) -> String -> IO [String]
findFile String -> Bool
p String
dir)
case [String]
cnts of
[] | String
dir' forall a. Eq a => a -> a -> Bool
== String
dir -> forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"No cabal files"
| Bool
otherwise -> (String -> Bool) -> String -> MaybeT IO String
findFileUpwards String -> Bool
p String
dir'
String
_ : [String]
_ -> forall (m :: * -> *) a. Monad m => a -> m a
return String
dir
where dir' :: String
dir' = String -> String
takeDirectory String
dir
findFile :: (FilePath -> Bool) -> FilePath -> IO [FilePath]
findFile :: (String -> Bool) -> String -> IO [String]
findFile String -> Bool
p String
dir = do
Bool
b <- String -> IO Bool
doesDirectoryExist String
dir
if Bool
b then IO [String]
getFiles forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall (m :: * -> *) a.
Applicative m =>
(a -> m Bool) -> [a] -> m [a]
filterM String -> IO Bool
doesPredFileExist else forall (m :: * -> *) a. Monad m => a -> m a
return []
where
getFiles :: IO [String]
getFiles = forall a. (a -> Bool) -> [a] -> [a]
filter String -> Bool
p forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> IO [String]
getDirectoryContents String
dir
doesPredFileExist :: String -> IO Bool
doesPredFileExist String
file = String -> IO Bool
doesFileExist forall a b. (a -> b) -> a -> b
$ String
dir String -> String -> String
</> String
file
getCleanEnvironment :: IO [(String, String)]
getCleanEnvironment :: IO [(String, String)]
getCleanEnvironment = do
forall k v. HashMap k v -> [(k, v)]
Map.toList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k v. (Eq k, Hashable k) => k -> HashMap k v -> HashMap k v
Map.delete String
"GHC_PACKAGE_PATH" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
Map.fromList forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO [(String, String)]
getEnvironment
type Outputs = [OutputName]
type OutputName = String
readProcessWithOutputs
:: Outputs
-> LogAction IO (WithSeverity Log)
-> FilePath
-> CreateProcess
-> IO (ExitCode, [String], [String], [(OutputName, Maybe [String])])
readProcessWithOutputs :: [String]
-> LogAction IO (WithSeverity Log)
-> String
-> CreateProcess
-> IO (ExitCode, [String], [String], [(String, Maybe [String])])
readProcessWithOutputs [String]
outputNames LogAction IO (WithSeverity Log)
l String
workDir CreateProcess
cp = forall a b c. (a -> b -> c) -> b -> a -> c
flip forall {k} (r :: k) (m :: k -> *) a.
ContT r m a -> (a -> m r) -> m r
runContT forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ do
[(String, String)]
old_env <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO [(String, String)]
getCleanEnvironment
[(String, String)]
output_files <- forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (forall a.
[(String, String)] -> String -> ContT a IO (String, String)
withOutput [(String, String)]
old_env) [String]
outputNames
let process :: CreateProcess
process = CreateProcess
cp { env :: Maybe [(String, String)]
env = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ [(String, String)]
output_files forall a. [a] -> [a] -> [a]
++ forall a. a -> Maybe a -> a
fromMaybe [(String, String)]
old_env (CreateProcess -> Maybe [(String, String)]
env CreateProcess
cp),
cwd :: Maybe String
cwd = forall a. a -> Maybe a
Just String
workDir
}
let loggingConduit :: ConduitT ByteString c IO [String]
loggingConduit = forall (m :: * -> *). MonadThrow m => ConduitT ByteString Text m ()
C.decodeUtf8 forall (m :: * -> *) a b c r.
Monad m =>
ConduitT a b m () -> ConduitT b c m r -> ConduitT a c m r
C..| forall (m :: * -> *). Monad m => ConduitT Text Text m ()
C.lines forall (m :: * -> *) a b c r.
Monad m =>
ConduitT a b m () -> ConduitT b c m r -> ConduitT a c m r
C..| forall seq (m :: * -> *).
(IsSequence seq, Monad m) =>
(Element seq -> Bool) -> ConduitT seq seq m ()
C.filterE (forall a. Eq a => a -> a -> Bool
/= Char
'\r')
forall (m :: * -> *) a b c r.
Monad m =>
ConduitT a b m () -> ConduitT b c m r -> ConduitT a c m r
C..| forall (m :: * -> *) a b. Monad m => (a -> b) -> ConduitT a b m ()
C.map Text -> String
T.unpack forall (m :: * -> *) a b c r.
Monad m =>
ConduitT a b m () -> ConduitT b c m r -> ConduitT a c m r
C..| forall (m :: * -> *) a. Monad m => (a -> m ()) -> ConduitT a a m ()
C.iterM (\String
msg -> LogAction IO (WithSeverity Log)
l forall (m :: * -> *) msg. LogAction m msg -> msg -> m ()
<& String -> Log
LogProcessOutput String
msg forall msg. msg -> Severity -> WithSeverity msg
`WithSeverity` Severity
Debug) forall (m :: * -> *) a b c r.
Monad m =>
ConduitT a b m () -> ConduitT b c m r -> ConduitT a c m r
C..| forall (m :: * -> *) a o. Monad m => ConduitT a o m [a]
C.sinkList
(ExitCode
ex, [String]
stdo, [String]
stde) <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a b.
MonadUnliftIO m =>
CreateProcess
-> ConduitT () ByteString m ()
-> ConduitT ByteString Void m a
-> ConduitT ByteString Void m b
-> m (ExitCode, a, b)
sourceProcessWithStreams CreateProcess
process forall a. Monoid a => a
mempty forall {c}. ConduitT ByteString c IO [String]
loggingConduit forall {c}. ConduitT ByteString c IO [String]
loggingConduit
[(String, Maybe [String])]
res <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM [(String, String)]
output_files forall a b. (a -> b) -> a -> b
$ \(String
name,String
path) ->
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ (String
name,) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> IO (Maybe [String])
readOutput String
path
forall (m :: * -> *) a. Monad m => a -> m a
return (ExitCode
ex, [String]
stdo, [String]
stde, [(String, Maybe [String])]
res)
where
readOutput :: FilePath -> IO (Maybe [String])
readOutput :: String -> IO (Maybe [String])
readOutput String
path = do
Bool
haveFile <- String -> IO Bool
doesFileExist String
path
if Bool
haveFile
then forall r. String -> IOMode -> (Handle -> IO r) -> IO r
withFile String
path IOMode
ReadMode forall a b. (a -> b) -> a -> b
$ \Handle
handle -> do
Handle -> BufferMode -> IO ()
hSetBuffering Handle
handle BufferMode
LineBuffering
!String
res <- forall a. NFData a => a -> a
force forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Handle -> IO String
hGetContents Handle
handle
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ String -> [String]
lines forall a b. (a -> b) -> a -> b
$ forall a. (a -> Bool) -> [a] -> [a]
filter (forall a. Eq a => a -> a -> Bool
/= Char
'\r') String
res
else
forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
withOutput :: [(String,String)] -> OutputName -> ContT a IO (OutputName, String)
withOutput :: forall a.
[(String, String)] -> String -> ContT a IO (String, String)
withOutput [(String, String)]
env' String
name =
case forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup String
name [(String, String)]
env' of
Just file :: String
file@(Char
_:String
_) -> forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ \(String, String) -> IO a
action -> do
String -> IO ()
removeFileIfExists String
file
(String, String) -> IO a
action (String
name, String
file)
Maybe String
_ -> forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ \(String, String) -> IO a
action -> forall (m :: * -> *) a.
(MonadIO m, MonadMask m) =>
String -> (String -> Handle -> m a) -> m a
withSystemTempFile String
name forall a b. (a -> b) -> a -> b
$ \ String
file Handle
h -> do
Handle -> IO ()
hClose Handle
h
String -> IO ()
removeFileIfExists String
file
(String, String) -> IO a
action (String
name, String
file)
removeFileIfExists :: FilePath -> IO ()
removeFileIfExists :: String -> IO ()
removeFileIfExists String
f = do
Bool
yes <- String -> IO Bool
doesFileExist String
f
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
yes (String -> IO ()
removeFile String
f)
makeCradleResult :: (ExitCode, [String], FilePath, [String]) -> [FilePath] -> CradleLoadResult ComponentOptions
makeCradleResult :: (ExitCode, [String], String, [String])
-> [String] -> CradleLoadResult ComponentOptions
makeCradleResult (ExitCode
ex, [String]
err, String
componentDir, [String]
gopts) [String]
deps =
case ExitCode
ex of
ExitFailure Int
_ -> forall r. CradleError -> CradleLoadResult r
CradleFail ([String] -> ExitCode -> [String] -> CradleError
CradleError [String]
deps ExitCode
ex [String]
err)
ExitCode
_ ->
let compOpts :: ComponentOptions
compOpts = [String] -> String -> [String] -> ComponentOptions
ComponentOptions [String]
gopts String
componentDir [String]
deps
in forall r. r -> CradleLoadResult r
CradleSuccess ComponentOptions
compOpts
runGhcCmdOnPath :: LogAction IO (WithSeverity Log) -> FilePath -> [String] -> IO (CradleLoadResult String)
runGhcCmdOnPath :: LogAction IO (WithSeverity Log)
-> String -> [String] -> IO (CradleLoadResult String)
runGhcCmdOnPath LogAction IO (WithSeverity Log)
l String
wdir [String]
args = LogAction IO (WithSeverity Log)
-> String
-> String
-> [String]
-> String
-> IO (CradleLoadResult String)
readProcessWithCwd LogAction IO (WithSeverity Log)
l String
wdir String
"ghc" [String]
args String
""
readProcessWithCwd :: LogAction IO (WithSeverity Log) -> FilePath -> FilePath -> [String] -> String -> IO (CradleLoadResult String)
readProcessWithCwd :: LogAction IO (WithSeverity Log)
-> String
-> String
-> [String]
-> String
-> IO (CradleLoadResult String)
readProcessWithCwd LogAction IO (WithSeverity Log)
l String
dir String
cmd [String]
args String
stdin = forall (m :: * -> *) a.
CradleLoadResultT m a -> m (CradleLoadResult a)
runCradleResultT forall a b. (a -> b) -> a -> b
$ LogAction IO (WithSeverity Log)
-> String
-> String
-> [String]
-> String
-> CradleLoadResultT IO String
readProcessWithCwd_ LogAction IO (WithSeverity Log)
l String
dir String
cmd [String]
args String
stdin
readProcessWithCwd_ :: LogAction IO (WithSeverity Log) -> FilePath -> FilePath -> [String] -> String -> CradleLoadResultT IO String
readProcessWithCwd_ :: LogAction IO (WithSeverity Log)
-> String
-> String
-> [String]
-> String
-> CradleLoadResultT IO String
readProcessWithCwd_ LogAction IO (WithSeverity Log)
l String
dir String
cmd [String]
args String
stdin = do
[(String, String)]
cleanEnv <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO [(String, String)]
getCleanEnvironment
CreateProcess
createdProc <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ LogAction IO (WithSeverity Log)
-> String -> [String] -> IO CreateProcess
loggedProc LogAction IO (WithSeverity Log)
l String
cmd [String]
args
let createdProc' :: CreateProcess
createdProc' = CreateProcess
createdProc { cwd :: Maybe String
cwd = forall a. a -> Maybe a
Just String
dir, env :: Maybe [(String, String)]
env = forall a. a -> Maybe a
Just [(String, String)]
cleanEnv }
CreateProcess -> String -> CradleLoadResultT IO String
readProcessWithCwd' CreateProcess
createdProc' String
stdin
readProcessWithCwd' :: CreateProcess -> String -> CradleLoadResultT IO String
readProcessWithCwd' :: CreateProcess -> String -> CradleLoadResultT IO String
readProcessWithCwd' CreateProcess
createdProcess String
stdin = do
Maybe (ExitCode, String, String)
mResult <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional forall a b. (a -> b) -> a -> b
$ CreateProcess -> String -> IO (ExitCode, String, String)
readCreateProcessWithExitCode CreateProcess
createdProcess String
stdin
let cmdString :: String
cmdString = CmdSpec -> String
prettyCmdSpec forall a b. (a -> b) -> a -> b
$ CreateProcess -> CmdSpec
cmdspec CreateProcess
createdProcess
case Maybe (ExitCode, String, String)
mResult of
Just (ExitCode
ExitSuccess, String
stdo, String
_) -> forall (f :: * -> *) a. Applicative f => a -> f a
pure String
stdo
Just (ExitCode
exitCode, String
stdo, String
stde) -> forall (m :: * -> *) a.
Monad m =>
CradleError -> CradleLoadResultT m a
throwCE forall a b. (a -> b) -> a -> b
$
[String] -> ExitCode -> [String] -> CradleError
CradleError [] ExitCode
exitCode forall a b. (a -> b) -> a -> b
$
[String
"Error when calling " forall a. Semigroup a => a -> a -> a
<> String
cmdString, String
stdo, String
stde] forall a. Semigroup a => a -> a -> a
<> CreateProcess -> [String]
prettyProcessEnv CreateProcess
createdProcess
Maybe (ExitCode, String, String)
Nothing -> forall (m :: * -> *) a.
Monad m =>
CradleError -> CradleLoadResultT m a
throwCE forall a b. (a -> b) -> a -> b
$
[String] -> ExitCode -> [String] -> CradleError
CradleError [] ExitCode
ExitSuccess forall a b. (a -> b) -> a -> b
$
[String
"Couldn't execute " forall a. Semigroup a => a -> a -> a
<> String
cmdString] forall a. Semigroup a => a -> a -> a
<> CreateProcess -> [String]
prettyProcessEnv CreateProcess
createdProcess
prettyCmdSpec :: CmdSpec -> String
prettyCmdSpec :: CmdSpec -> String
prettyCmdSpec (ShellCommand String
s) = String
s
prettyCmdSpec (RawCommand String
cmd [String]
args) = String
cmd forall a. [a] -> [a] -> [a]
++ String
" " forall a. [a] -> [a] -> [a]
++ [String] -> String
unwords [String]
args
prettyProcessEnv :: CreateProcess -> [String]
prettyProcessEnv :: CreateProcess -> [String]
prettyProcessEnv CreateProcess
p =
[ String
key forall a. Semigroup a => a -> a -> a
<> String
": " forall a. Semigroup a => a -> a -> a
<> String
value
| (String
key, String
value) <- forall a. a -> Maybe a -> a
fromMaybe [] (CreateProcess -> Maybe [(String, String)]
env CreateProcess
p)
, String
key forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [ String
hie_bios_output
, String
hie_bios_ghc
, String
hie_bios_ghc_args
, String
hie_bios_arg
, String
hie_bios_deps
]
]
loggedProc :: LogAction IO (WithSeverity Log) -> FilePath -> [String] -> IO CreateProcess
loggedProc :: LogAction IO (WithSeverity Log)
-> String -> [String] -> IO CreateProcess
loggedProc LogAction IO (WithSeverity Log)
l String
command [String]
args = do
LogAction IO (WithSeverity Log)
l forall (m :: * -> *) msg. LogAction m msg -> msg -> m ()
<& String -> Log
LogProcessOutput ([String] -> String
unwords forall a b. (a -> b) -> a -> b
$ String
"executing command:"forall a. a -> [a] -> [a]
:String
commandforall a. a -> [a] -> [a]
:[String]
args) forall msg. msg -> Severity -> WithSeverity msg
`WithSeverity` Severity
Debug
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ String -> [String] -> CreateProcess
proc String
command [String]
args