{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
module Stack.Constants
( buildPlanDir
, buildPlanCacheDir
, haskellFileExts
, haskellDefaultPreprocessorExts
, stackProgName
, stackProgName'
, nixProgName
, stackDotYaml
, stackWorkEnvVar
, stackRootEnvVar
, stackXdgEnvVar
, stackRootOptionName
, stackGlobalConfigOptionName
, pantryRootEnvVar
, inContainerEnvVar
, inNixShellEnvVar
, stackProgNameUpper
, wiredInPackages
, cabalPackageName
, implicitGlobalProjectDirDeprecated
, implicitGlobalProjectDir
, defaultUserConfigPathDeprecated
, defaultUserConfigPath
, defaultGlobalConfigPathDeprecated
, defaultGlobalConfigPath
, platformVariantEnvVar
, compilerOptionsCabalFlag
, ghcColorForceFlag
, minTerminalWidth
, maxTerminalWidth
, defaultTerminalWidth
, osIsMacOS
, osIsWindows
, relFileSetupHs
, relFileSetupLhs
, relFileHpackPackageConfig
, relDirGlobalAutogen
, relDirAutogen
, relDirLogs
, relFileCabalMacrosH
, relDirBuild
, relDirBin
, relDirGhci
, relDirGhciScript
, relDirPantry
, relDirPrograms
, relDirUpperPrograms
, relDirStackProgName
, relDirStackWork
, relFileReadmeTxt
, relDirScript
, relDirScripts
, relFileConfigYaml
, relDirSnapshots
, relDirGlobalHints
, relFileGlobalHintsYaml
, relDirInstall
, relDirCompilerTools
, relDirHoogle
, relFileDatabaseHoo
, relDirPkgdb
, relFileStorage
, relDirLoadedSnapshotCache
, bindirSuffix
, docDirSuffix
, htmlDirSuffix
, relDirHpc
, relDirLib
, relDirShare
, relDirLibexec
, relDirEtc
, setupGhciShimCode
, relDirSetupExeCache
, relDirSetupExeSrc
, relFileConfigure
, relDirDist
, relFileSetupMacrosH
, relDirSetup
, relFileSetupLower
, relDirMingw
, relDirMingw32
, relDirMingw64
, relDirLocal
, relDirUsr
, relDirInclude
, relFileIndexHtml
, relDirAll
, relFilePackageCache
, relFileDockerfile
, relFileGhciScript
, relDirCombined
, relFileHpcIndexHtml
, relDirCustom
, relDirPackageConfInplace
, relDirExtraTixFiles
, relDirInstalledPackages
, backupUrlRelPath
, relDirDotLocal
, relDirDotSsh
, relDirDotStackProgName
, relDirUnderHome
, relDirSrc
, relFileLibcMuslx86_64So1
, relFileLibtinfoSo5
, relFileLibtinfoSo6
, relFileLibncurseswSo6
, relFileLibgmpSo10
, relFileLibgmpSo3
, relDirNewCabal
, relFileSetupExe
, relFileSetupUpper
, relFile7zexe
, relFile7zdll
, relFileMainHs
, relFileStack
, relFileStackDotExe
, relFileStackDotTmpDotExe
, relFileStackDotTmp
, ghcShowOptionsOutput
, ghcBootScript
, ghcConfigureScript
, ghcConfigureWindows
, ghcConfigureMacOS
, ghcConfigurePosix
, relDirHadrian
, relFileHadrianStackDotYaml
, hadrianScriptsWindows
, hadrianScriptsPosix
, libDirs
, usrLibDirs
, testGhcEnvRelFile
, relFileBuildLock
, stackDeveloperModeDefault
, isStackUploadDisabled
, globalFooter
, gitHubBasicAuthType
, gitHubTokenEnvVar
, altGitHubTokenEnvVar
) where
import Data.ByteString.Builder ( byteString )
import Data.Char ( toUpper )
import Data.FileEmbed ( embedFile, makeRelativeToProject )
import qualified Data.Set as Set
import qualified Data.Text as T
import Distribution.Package ( mkPackageName )
import Hpack.Config ( packageConfig )
import qualified Language.Haskell.TH.Syntax as TH ( runIO, lift )
import Path ( (</>), mkRelDir, mkRelFile, parseAbsFile )
import Stack.Constants.StackProgName ( stackProgName )
import Stack.Constants.UsrLibDirs ( libDirs, usrLibDirs )
import Stack.Prelude
import Stack.Types.Compiler ( WhichCompiler (..) )
import System.Permissions ( osIsMacOS, osIsWindows )
import System.Process ( readProcess )
data ConstantsException
= WiredInPackagesNotParsedBug
deriving (Int -> ConstantsException -> ShowS
[ConstantsException] -> ShowS
ConstantsException -> [Char]
(Int -> ConstantsException -> ShowS)
-> (ConstantsException -> [Char])
-> ([ConstantsException] -> ShowS)
-> Show ConstantsException
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ConstantsException -> ShowS
showsPrec :: Int -> ConstantsException -> ShowS
$cshow :: ConstantsException -> [Char]
show :: ConstantsException -> [Char]
$cshowList :: [ConstantsException] -> ShowS
showList :: [ConstantsException] -> ShowS
Show, Typeable)
instance Exception ConstantsException where
displayException :: ConstantsException -> [Char]
displayException ConstantsException
WiredInPackagesNotParsedBug = [Char] -> ShowS
bugReport [Char]
"[S-6057]"
[Char]
"Parse error in wiredInPackages."
stackProgName' :: Text
stackProgName' :: Text
stackProgName' = [Char] -> Text
T.pack [Char]
stackProgName
nixProgName :: String
nixProgName :: [Char]
nixProgName = [Char]
"nix"
haskellFileExts :: [Text]
haskellFileExts :: [Text]
haskellFileExts = [Text
"hs", Text
"hsc", Text
"lhs"]
haskellDefaultPreprocessorExts :: [Text]
haskellDefaultPreprocessorExts :: [Text]
haskellDefaultPreprocessorExts = [Text
"gc", Text
"chs", Text
"hsc", Text
"x", Text
"y", Text
"ly", Text
"cpphs"]
stackProgNameUpper :: String
stackProgNameUpper :: [Char]
stackProgNameUpper = (Char -> Char) -> ShowS
forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toUpper [Char]
stackProgName
stackDotYaml :: Path Rel File
stackDotYaml :: Path Rel File
stackDotYaml = $(mkRelFile "stack.yaml")
stackWorkEnvVar :: String
stackWorkEnvVar :: [Char]
stackWorkEnvVar = [Char]
"STACK_WORK"
stackRootEnvVar :: String
stackRootEnvVar :: [Char]
stackRootEnvVar = [Char]
"STACK_ROOT"
stackXdgEnvVar :: String
stackXdgEnvVar :: [Char]
stackXdgEnvVar = [Char]
"STACK_XDG"
stackRootOptionName :: String
stackRootOptionName :: [Char]
stackRootOptionName = [Char]
"stack-root"
stackGlobalConfigOptionName :: String
stackGlobalConfigOptionName :: [Char]
stackGlobalConfigOptionName = [Char]
"global-config"
pantryRootEnvVar :: String
pantryRootEnvVar :: [Char]
pantryRootEnvVar = [Char]
"PANTRY_ROOT"
inContainerEnvVar :: String
inContainerEnvVar :: [Char]
inContainerEnvVar = [Char]
stackProgNameUpper [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ [Char]
"_IN_CONTAINER"
inNixShellEnvVar :: String
inNixShellEnvVar :: [Char]
inNixShellEnvVar = (Char -> Char) -> ShowS
forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toUpper [Char]
stackProgName [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ [Char]
"_IN_NIX_SHELL"
wiredInPackages :: Set PackageName
wiredInPackages :: Set PackageName
wiredInPackages = case Maybe [PackageName]
mparsed of
Just [PackageName]
parsed -> [PackageName] -> Set PackageName
forall a. Ord a => [a] -> Set a
Set.fromList [PackageName]
parsed
Maybe [PackageName]
Nothing -> ConstantsException -> Set PackageName
forall e a. Exception e => e -> a
impureThrow ConstantsException
WiredInPackagesNotParsedBug
where
mparsed :: Maybe [PackageName]
mparsed = ([Char] -> Maybe PackageName) -> [[Char]] -> Maybe [PackageName]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM [Char] -> Maybe PackageName
parsePackageName
[ [Char]
"ghc-prim"
, [Char]
"integer-gmp"
, [Char]
"integer-simple"
, [Char]
"base"
, [Char]
"rts"
, [Char]
"template-haskell"
, [Char]
"dph-seq"
, [Char]
"dph-par"
, [Char]
"ghc"
, [Char]
"interactive"
, [Char]
"ghc-bignum"
]
cabalPackageName :: PackageName
cabalPackageName :: PackageName
cabalPackageName =
[Char] -> PackageName
mkPackageName [Char]
"Cabal"
implicitGlobalProjectDirDeprecated :: Path Abs Dir
-> Path Abs Dir
implicitGlobalProjectDirDeprecated :: Path Abs Dir -> Path Abs Dir
implicitGlobalProjectDirDeprecated Path Abs Dir
p =
Path Abs Dir
p Path Abs Dir -> Path Rel Dir -> Path Abs Dir
forall b t. Path b Dir -> Path Rel t -> Path b t
</>
$(mkRelDir "global")
implicitGlobalProjectDir :: Path Abs Dir
-> Path Abs Dir
implicitGlobalProjectDir :: Path Abs Dir -> Path Abs Dir
implicitGlobalProjectDir Path Abs Dir
p =
Path Abs Dir
p Path Abs Dir -> Path Rel Dir -> Path Abs Dir
forall b t. Path b Dir -> Path Rel t -> Path b t
</>
$(mkRelDir "global-project")
defaultUserConfigPathDeprecated :: Path Abs Dir -> Path Abs File
defaultUserConfigPathDeprecated :: Path Abs Dir -> Path Abs File
defaultUserConfigPathDeprecated = (Path Abs Dir -> Path Rel File -> Path Abs File
forall b t. Path b Dir -> Path Rel t -> Path b t
</> $(mkRelFile "stack.yaml"))
defaultUserConfigPath :: Path Abs Dir -> Path Abs File
defaultUserConfigPath :: Path Abs Dir -> Path Abs File
defaultUserConfigPath = (Path Abs Dir -> Path Rel File -> Path Abs File
forall b t. Path b Dir -> Path Rel t -> Path b t
</> $(mkRelFile "config.yaml"))
defaultGlobalConfigPathDeprecated :: Maybe (Path Abs File)
defaultGlobalConfigPathDeprecated :: Maybe (Path Abs File)
defaultGlobalConfigPathDeprecated = [Char] -> Maybe (Path Abs File)
forall (m :: * -> *). MonadThrow m => [Char] -> m (Path Abs File)
parseAbsFile [Char]
"/etc/stack/config"
defaultGlobalConfigPath :: Maybe (Path Abs File)
defaultGlobalConfigPath :: Maybe (Path Abs File)
defaultGlobalConfigPath = [Char] -> Maybe (Path Abs File)
forall (m :: * -> *). MonadThrow m => [Char] -> m (Path Abs File)
parseAbsFile [Char]
"/etc/stack/config.yaml"
buildPlanDir :: Path Abs Dir
-> Path Abs Dir
buildPlanDir :: Path Abs Dir -> Path Abs Dir
buildPlanDir = (Path Abs Dir -> Path Rel Dir -> Path Abs Dir
forall b t. Path b Dir -> Path Rel t -> Path b t
</> $(mkRelDir "build-plan"))
buildPlanCacheDir ::
Path Abs Dir
-> Path Abs Dir
buildPlanCacheDir :: Path Abs Dir -> Path Abs Dir
buildPlanCacheDir = (Path Abs Dir -> Path Rel Dir -> Path Abs Dir
forall b t. Path b Dir -> Path Rel t -> Path b t
</> $(mkRelDir "build-plan-cache"))
platformVariantEnvVar :: String
platformVariantEnvVar :: [Char]
platformVariantEnvVar = [Char]
stackProgNameUpper [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ [Char]
"_PLATFORM_VARIANT"
compilerOptionsCabalFlag :: WhichCompiler -> String
compilerOptionsCabalFlag :: WhichCompiler -> [Char]
compilerOptionsCabalFlag WhichCompiler
Ghc = [Char]
"--ghc-options"
ghcColorForceFlag :: String
ghcColorForceFlag :: [Char]
ghcColorForceFlag = [Char]
"-fdiagnostics-color=always"
minTerminalWidth :: Int
minTerminalWidth :: Int
minTerminalWidth = Int
40
maxTerminalWidth :: Int
maxTerminalWidth :: Int
maxTerminalWidth = Int
200
defaultTerminalWidth :: Int
defaultTerminalWidth :: Int
defaultTerminalWidth = Int
100
relFileSetupHs :: Path Rel File
relFileSetupHs :: Path Rel File
relFileSetupHs = $(mkRelFile "Setup.hs")
relFileSetupLhs :: Path Rel File
relFileSetupLhs :: Path Rel File
relFileSetupLhs = $(mkRelFile "Setup.lhs")
relFileHpackPackageConfig :: Path Rel File
relFileHpackPackageConfig :: Path Rel File
relFileHpackPackageConfig = $(mkRelFile packageConfig)
relDirGlobalAutogen :: Path Rel Dir
relDirGlobalAutogen :: Path Rel Dir
relDirGlobalAutogen = $(mkRelDir "global-autogen")
relDirAutogen :: Path Rel Dir
relDirAutogen :: Path Rel Dir
relDirAutogen = $(mkRelDir "autogen")
relDirLogs :: Path Rel Dir
relDirLogs :: Path Rel Dir
relDirLogs = $(mkRelDir "logs")
relFileCabalMacrosH :: Path Rel File
relFileCabalMacrosH :: Path Rel File
relFileCabalMacrosH = $(mkRelFile "cabal_macros.h")
relDirBuild :: Path Rel Dir
relDirBuild :: Path Rel Dir
relDirBuild = $(mkRelDir "build")
relDirBin :: Path Rel Dir
relDirBin :: Path Rel Dir
relDirBin = $(mkRelDir "bin")
relDirGhci :: Path Rel Dir
relDirGhci :: Path Rel Dir
relDirGhci = $(mkRelDir "ghci")
relDirGhciScript :: Path Rel Dir
relDirGhciScript :: Path Rel Dir
relDirGhciScript = $(mkRelDir "ghci-script")
relDirPantry :: Path Rel Dir
relDirPantry :: Path Rel Dir
relDirPantry = $(mkRelDir "pantry")
relDirPrograms :: Path Rel Dir
relDirPrograms :: Path Rel Dir
relDirPrograms = $(mkRelDir "programs")
relDirUpperPrograms :: Path Rel Dir
relDirUpperPrograms :: Path Rel Dir
relDirUpperPrograms = $(mkRelDir "Programs")
relDirStackProgName :: Path Rel Dir
relDirStackProgName :: Path Rel Dir
relDirStackProgName = $(mkRelDir stackProgName)
relDirStackWork :: Path Rel Dir
relDirStackWork :: Path Rel Dir
relDirStackWork = $(mkRelDir ".stack-work")
relFileReadmeTxt :: Path Rel File
relFileReadmeTxt :: Path Rel File
relFileReadmeTxt = $(mkRelFile "README.txt")
relDirScript :: Path Rel Dir
relDirScript :: Path Rel Dir
relDirScript = $(mkRelDir "script")
relDirScripts :: Path Rel Dir
relDirScripts :: Path Rel Dir
relDirScripts = $(mkRelDir "scripts")
relFileConfigYaml :: Path Rel File
relFileConfigYaml :: Path Rel File
relFileConfigYaml = $(mkRelFile "config.yaml")
relDirSnapshots :: Path Rel Dir
relDirSnapshots :: Path Rel Dir
relDirSnapshots = $(mkRelDir "snapshots")
relDirGlobalHints :: Path Rel Dir
relDirGlobalHints :: Path Rel Dir
relDirGlobalHints = $(mkRelDir "global-hints")
relFileGlobalHintsYaml :: Path Rel File
relFileGlobalHintsYaml :: Path Rel File
relFileGlobalHintsYaml = $(mkRelFile "global-hints.yaml")
relDirInstall :: Path Rel Dir
relDirInstall :: Path Rel Dir
relDirInstall = $(mkRelDir "install")
relDirCompilerTools :: Path Rel Dir
relDirCompilerTools :: Path Rel Dir
relDirCompilerTools = $(mkRelDir "compiler-tools")
relDirHoogle :: Path Rel Dir
relDirHoogle :: Path Rel Dir
relDirHoogle = $(mkRelDir "hoogle")
relFileDatabaseHoo :: Path Rel File
relFileDatabaseHoo :: Path Rel File
relFileDatabaseHoo = $(mkRelFile "database.hoo")
relDirPkgdb :: Path Rel Dir
relDirPkgdb :: Path Rel Dir
relDirPkgdb = $(mkRelDir "pkgdb")
relFileStorage :: Path Rel File
relFileStorage :: Path Rel File
relFileStorage = $(mkRelFile "stack.sqlite3")
relDirLoadedSnapshotCache :: Path Rel Dir
relDirLoadedSnapshotCache :: Path Rel Dir
relDirLoadedSnapshotCache = $(mkRelDir "loaded-snapshot-cached")
bindirSuffix :: Path Rel Dir
bindirSuffix :: Path Rel Dir
bindirSuffix = Path Rel Dir
relDirBin
docDirSuffix :: Path Rel Dir
docDirSuffix :: Path Rel Dir
docDirSuffix = $(mkRelDir "doc")
htmlDirSuffix :: Path Rel Dir
htmlDirSuffix :: Path Rel Dir
htmlDirSuffix = $(mkRelDir "html")
relDirHpc :: Path Rel Dir
relDirHpc :: Path Rel Dir
relDirHpc = $(mkRelDir "hpc")
relDirLib :: Path Rel Dir
relDirLib :: Path Rel Dir
relDirLib = $(mkRelDir "lib")
relDirShare :: Path Rel Dir
relDirShare :: Path Rel Dir
relDirShare = $(mkRelDir "share")
relDirLibexec :: Path Rel Dir
relDirLibexec :: Path Rel Dir
relDirLibexec = $(mkRelDir "libexec")
relDirEtc :: Path Rel Dir
relDirEtc :: Path Rel Dir
relDirEtc = $(mkRelDir "etc")
setupGhciShimCode :: Builder
setupGhciShimCode :: Builder
setupGhciShimCode = ByteString -> Builder
byteString $(do
path <- makeRelativeToProject "src/setup-shim/StackSetupShim.hs"
embedFile path)
relDirSetupExeCache :: Path Rel Dir
relDirSetupExeCache :: Path Rel Dir
relDirSetupExeCache = $(mkRelDir "setup-exe-cache")
relDirSetupExeSrc :: Path Rel Dir
relDirSetupExeSrc :: Path Rel Dir
relDirSetupExeSrc = $(mkRelDir "setup-exe-src")
relFileConfigure :: Path Rel File
relFileConfigure :: Path Rel File
relFileConfigure = $(mkRelFile "configure")
relDirDist :: Path Rel Dir
relDirDist :: Path Rel Dir
relDirDist = $(mkRelDir "dist")
relFileSetupMacrosH :: Path Rel File
relFileSetupMacrosH :: Path Rel File
relFileSetupMacrosH = $(mkRelFile "setup_macros.h")
relDirSetup :: Path Rel Dir
relDirSetup :: Path Rel Dir
relDirSetup = $(mkRelDir "setup")
relFileSetupLower :: Path Rel File
relFileSetupLower :: Path Rel File
relFileSetupLower = $(mkRelFile "setup")
relDirMingw :: Path Rel Dir
relDirMingw :: Path Rel Dir
relDirMingw = $(mkRelDir "mingw")
relDirMingw32 :: Path Rel Dir
relDirMingw32 :: Path Rel Dir
relDirMingw32 = $(mkRelDir "mingw32")
relDirMingw64 :: Path Rel Dir
relDirMingw64 :: Path Rel Dir
relDirMingw64 = $(mkRelDir "mingw64")
relDirLocal :: Path Rel Dir
relDirLocal :: Path Rel Dir
relDirLocal = $(mkRelDir "local")
relDirUsr :: Path Rel Dir
relDirUsr :: Path Rel Dir
relDirUsr = $(mkRelDir "usr")
relDirInclude :: Path Rel Dir
relDirInclude :: Path Rel Dir
relDirInclude = $(mkRelDir "include")
relFileIndexHtml :: Path Rel File
relFileIndexHtml :: Path Rel File
relFileIndexHtml = $(mkRelFile "index.html")
relDirAll :: Path Rel Dir
relDirAll :: Path Rel Dir
relDirAll = $(mkRelDir "all")
relFilePackageCache :: Path Rel File
relFilePackageCache :: Path Rel File
relFilePackageCache = $(mkRelFile "package.cache")
relFileDockerfile :: Path Rel File
relFileDockerfile :: Path Rel File
relFileDockerfile = $(mkRelFile "Dockerfile")
relFileGhciScript :: Path Rel File
relFileGhciScript :: Path Rel File
relFileGhciScript = $(mkRelFile "ghci-script")
relDirCombined :: Path Rel Dir
relDirCombined :: Path Rel Dir
relDirCombined = $(mkRelDir "combined")
relFileHpcIndexHtml :: Path Rel File
relFileHpcIndexHtml :: Path Rel File
relFileHpcIndexHtml = $(mkRelFile "hpc_index.html")
relDirCustom :: Path Rel Dir
relDirCustom :: Path Rel Dir
relDirCustom = $(mkRelDir "custom")
relDirPackageConfInplace :: Path Rel Dir
relDirPackageConfInplace :: Path Rel Dir
relDirPackageConfInplace = $(mkRelDir "package.conf.inplace")
relDirExtraTixFiles :: Path Rel Dir
= $(mkRelDir "extra-tix-files")
relDirInstalledPackages :: Path Rel Dir
relDirInstalledPackages :: Path Rel Dir
relDirInstalledPackages = $(mkRelDir "installed-packages")
backupUrlRelPath :: Path Rel File
backupUrlRelPath :: Path Rel File
backupUrlRelPath = $(mkRelFile "downloaded.template.file.hsfiles")
relDirDotLocal :: Path Rel Dir
relDirDotLocal :: Path Rel Dir
relDirDotLocal = $(mkRelDir ".local")
relDirDotSsh :: Path Rel Dir
relDirDotSsh :: Path Rel Dir
relDirDotSsh = $(mkRelDir ".ssh")
relDirDotStackProgName :: Path Rel Dir
relDirDotStackProgName :: Path Rel Dir
relDirDotStackProgName = $(mkRelDir ('.' : stackProgName))
relDirUnderHome :: Path Rel Dir
relDirUnderHome :: Path Rel Dir
relDirUnderHome = $(mkRelDir "_home")
relDirSrc :: Path Rel Dir
relDirSrc :: Path Rel Dir
relDirSrc = $(mkRelDir "src")
relFileLibcMuslx86_64So1 :: Path Rel File
relFileLibcMuslx86_64So1 :: Path Rel File
relFileLibcMuslx86_64So1 = $(mkRelFile "libc.musl-x86_64.so.1")
relFileLibtinfoSo5 :: Path Rel File
relFileLibtinfoSo5 :: Path Rel File
relFileLibtinfoSo5 = $(mkRelFile "libtinfo.so.5")
relFileLibtinfoSo6 :: Path Rel File
relFileLibtinfoSo6 :: Path Rel File
relFileLibtinfoSo6 = $(mkRelFile "libtinfo.so.6")
relFileLibncurseswSo6 :: Path Rel File
relFileLibncurseswSo6 :: Path Rel File
relFileLibncurseswSo6 = $(mkRelFile "libncursesw.so.6")
relFileLibgmpSo10 :: Path Rel File
relFileLibgmpSo10 :: Path Rel File
relFileLibgmpSo10 = $(mkRelFile "libgmp.so.10")
relFileLibgmpSo3 :: Path Rel File
relFileLibgmpSo3 :: Path Rel File
relFileLibgmpSo3 = $(mkRelFile "libgmp.so.3")
relDirNewCabal :: Path Rel Dir
relDirNewCabal :: Path Rel Dir
relDirNewCabal = $(mkRelDir "new-cabal")
relFileSetupExe :: Path Rel File
relFileSetupExe :: Path Rel File
relFileSetupExe = $(mkRelFile "Setup.exe")
relFileSetupUpper :: Path Rel File
relFileSetupUpper :: Path Rel File
relFileSetupUpper = $(mkRelFile "Setup")
relFile7zexe :: Path Rel File
relFile7zexe :: Path Rel File
relFile7zexe = $(mkRelFile "7z.exe")
relFile7zdll :: Path Rel File
relFile7zdll :: Path Rel File
relFile7zdll = $(mkRelFile "7z.dll")
relFileMainHs :: Path Rel File
relFileMainHs :: Path Rel File
relFileMainHs = $(mkRelFile "Main.hs")
relFileStackDotExe :: Path Rel File
relFileStackDotExe :: Path Rel File
relFileStackDotExe = $(mkRelFile "stack.exe")
relFileStackDotTmpDotExe :: Path Rel File
relFileStackDotTmpDotExe :: Path Rel File
relFileStackDotTmpDotExe = $(mkRelFile "stack.tmp.exe")
relFileStackDotTmp :: Path Rel File
relFileStackDotTmp :: Path Rel File
relFileStackDotTmp = $(mkRelFile "stack.tmp")
relFileStack :: Path Rel File
relFileStack :: Path Rel File
relFileStack = $(mkRelFile "stack")
ghcShowOptionsOutput :: [String]
ghcShowOptionsOutput :: [[Char]]
ghcShowOptionsOutput =
$(TH.runIO (readProcess "ghc" ["--show-options"] "") >>= TH.lift . lines)
ghcBootScript :: Path Rel File
ghcBootScript :: Path Rel File
ghcBootScript = $(mkRelFile "boot")
ghcConfigureScript :: Path Rel File
ghcConfigureScript :: Path Rel File
ghcConfigureScript = $(mkRelFile "configure")
ghcConfigureWindows :: [String]
ghcConfigureWindows :: [[Char]]
ghcConfigureWindows = [[Char]
"sh", [Char]
"configure", [Char]
"--enable-tarballs-autodownload"]
ghcConfigureMacOS :: [String]
ghcConfigureMacOS :: [[Char]]
ghcConfigureMacOS = [[Char]
"./configure", [Char]
"--with-intree-gmp"]
ghcConfigurePosix :: [String]
ghcConfigurePosix :: [[Char]]
ghcConfigurePosix = [[Char]
"./configure"]
relDirHadrian :: Path Rel Dir
relDirHadrian :: Path Rel Dir
relDirHadrian = $(mkRelDir "hadrian")
relFileHadrianStackDotYaml :: Path Rel File
relFileHadrianStackDotYaml :: Path Rel File
relFileHadrianStackDotYaml = Path Rel Dir
relDirHadrian Path Rel Dir -> Path Rel File -> Path Rel File
forall b t. Path b Dir -> Path Rel t -> Path b t
</> Path Rel File
stackDotYaml
hadrianScriptsWindows :: [Path Rel File]
hadrianScriptsWindows :: [Path Rel File]
hadrianScriptsWindows =
[ $(mkRelFile "hadrian/build-stack.bat")
, $(mkRelFile "hadrian/build.stack.bat")
]
hadrianScriptsPosix :: [Path Rel File]
hadrianScriptsPosix :: [Path Rel File]
hadrianScriptsPosix =
[$(mkRelFile "hadrian/build-stack"), $(mkRelFile "hadrian/build.stack.sh")]
testGhcEnvRelFile :: Path Rel File
testGhcEnvRelFile :: Path Rel File
testGhcEnvRelFile = $(mkRelFile "test-ghc-env")
relFileBuildLock :: Path Rel File
relFileBuildLock :: Path Rel File
relFileBuildLock = $(mkRelFile "build-lock")
stackDeveloperModeDefault :: Bool
stackDeveloperModeDefault :: Bool
stackDeveloperModeDefault = STACK_DEVELOPER_MODE_DEFAULT
isStackUploadDisabled :: Bool
isStackUploadDisabled :: Bool
isStackUploadDisabled = STACK_DISABLE_STACK_UPLOAD
globalFooter :: String
=
[Char]
"Command 'stack --help' for global options that apply to all subcommands."
gitHubBasicAuthType :: ByteString
gitHubBasicAuthType :: ByteString
gitHubBasicAuthType = ByteString
"Bearer"
gitHubTokenEnvVar :: String
gitHubTokenEnvVar :: [Char]
gitHubTokenEnvVar = [Char]
"GH_TOKEN"
altGitHubTokenEnvVar :: String
altGitHubTokenEnvVar :: [Char]
altGitHubTokenEnvVar = [Char]
"GITHUB_TOKEN"