{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RankNTypes #-}
module Distribution.Simple.InstallDirs
( InstallDirs (..)
, InstallDirTemplates
, defaultInstallDirs
, defaultInstallDirs'
, combineInstallDirs
, absoluteInstallDirs
, CopyDest (..)
, prefixRelativeInstallDirs
, substituteInstallDirTemplates
, PathTemplate
, PathTemplateVariable (..)
, PathTemplateEnv
, toPathTemplate
, fromPathTemplate
, combinePathTemplate
, substPathTemplate
, initialPathTemplateEnv
, platformTemplateEnv
, compilerTemplateEnv
, packageTemplateEnv
, abiTemplateEnv
, installDirsTemplateEnv
) where
import Distribution.Compat.Prelude
import Prelude ()
import Distribution.Compat.Environment (lookupEnv)
import Distribution.Compiler
import Distribution.Package
import Distribution.Pretty
import Distribution.Simple.InstallDirs.Internal
import Distribution.System
import System.Directory (getAppUserDataDirectory)
import System.FilePath
( dropDrive
, isPathSeparator
, pathSeparator
, takeDirectory
, (</>)
)
#ifdef mingw32_HOST_OS
import qualified Prelude
import Foreign
import Foreign.C
#endif
data InstallDirs dir = InstallDirs
{ forall dir. InstallDirs dir -> dir
prefix :: dir
, forall dir. InstallDirs dir -> dir
bindir :: dir
, forall dir. InstallDirs dir -> dir
libdir :: dir
, forall dir. InstallDirs dir -> dir
libsubdir :: dir
, forall dir. InstallDirs dir -> dir
dynlibdir :: dir
, forall dir. InstallDirs dir -> dir
flibdir :: dir
, forall dir. InstallDirs dir -> dir
libexecdir :: dir
, forall dir. InstallDirs dir -> dir
libexecsubdir :: dir
, forall dir. InstallDirs dir -> dir
includedir :: dir
, forall dir. InstallDirs dir -> dir
datadir :: dir
, forall dir. InstallDirs dir -> dir
datasubdir :: dir
, forall dir. InstallDirs dir -> dir
docdir :: dir
, forall dir. InstallDirs dir -> dir
mandir :: dir
, forall dir. InstallDirs dir -> dir
htmldir :: dir
, forall dir. InstallDirs dir -> dir
haddockdir :: dir
, forall dir. InstallDirs dir -> dir
sysconfdir :: dir
}
deriving (InstallDirs dir -> InstallDirs dir -> Bool
(InstallDirs dir -> InstallDirs dir -> Bool)
-> (InstallDirs dir -> InstallDirs dir -> Bool)
-> Eq (InstallDirs dir)
forall dir. Eq dir => InstallDirs dir -> InstallDirs dir -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall dir. Eq dir => InstallDirs dir -> InstallDirs dir -> Bool
== :: InstallDirs dir -> InstallDirs dir -> Bool
$c/= :: forall dir. Eq dir => InstallDirs dir -> InstallDirs dir -> Bool
/= :: InstallDirs dir -> InstallDirs dir -> Bool
Eq, ReadPrec [InstallDirs dir]
ReadPrec (InstallDirs dir)
Int -> ReadS (InstallDirs dir)
ReadS [InstallDirs dir]
(Int -> ReadS (InstallDirs dir))
-> ReadS [InstallDirs dir]
-> ReadPrec (InstallDirs dir)
-> ReadPrec [InstallDirs dir]
-> Read (InstallDirs dir)
forall dir. Read dir => ReadPrec [InstallDirs dir]
forall dir. Read dir => ReadPrec (InstallDirs dir)
forall dir. Read dir => Int -> ReadS (InstallDirs dir)
forall dir. Read dir => ReadS [InstallDirs dir]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: forall dir. Read dir => Int -> ReadS (InstallDirs dir)
readsPrec :: Int -> ReadS (InstallDirs dir)
$creadList :: forall dir. Read dir => ReadS [InstallDirs dir]
readList :: ReadS [InstallDirs dir]
$creadPrec :: forall dir. Read dir => ReadPrec (InstallDirs dir)
readPrec :: ReadPrec (InstallDirs dir)
$creadListPrec :: forall dir. Read dir => ReadPrec [InstallDirs dir]
readListPrec :: ReadPrec [InstallDirs dir]
Read, Int -> InstallDirs dir -> ShowS
[InstallDirs dir] -> ShowS
InstallDirs dir -> [Char]
(Int -> InstallDirs dir -> ShowS)
-> (InstallDirs dir -> [Char])
-> ([InstallDirs dir] -> ShowS)
-> Show (InstallDirs dir)
forall dir. Show dir => Int -> InstallDirs dir -> ShowS
forall dir. Show dir => [InstallDirs dir] -> ShowS
forall dir. Show dir => InstallDirs dir -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall dir. Show dir => Int -> InstallDirs dir -> ShowS
showsPrec :: Int -> InstallDirs dir -> ShowS
$cshow :: forall dir. Show dir => InstallDirs dir -> [Char]
show :: InstallDirs dir -> [Char]
$cshowList :: forall dir. Show dir => [InstallDirs dir] -> ShowS
showList :: [InstallDirs dir] -> ShowS
Show, (forall a b. (a -> b) -> InstallDirs a -> InstallDirs b)
-> (forall a b. a -> InstallDirs b -> InstallDirs a)
-> Functor InstallDirs
forall a b. a -> InstallDirs b -> InstallDirs a
forall a b. (a -> b) -> InstallDirs a -> InstallDirs b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> InstallDirs a -> InstallDirs b
fmap :: forall a b. (a -> b) -> InstallDirs a -> InstallDirs b
$c<$ :: forall a b. a -> InstallDirs b -> InstallDirs a
<$ :: forall a b. a -> InstallDirs b -> InstallDirs a
Functor, (forall x. InstallDirs dir -> Rep (InstallDirs dir) x)
-> (forall x. Rep (InstallDirs dir) x -> InstallDirs dir)
-> Generic (InstallDirs dir)
forall x. Rep (InstallDirs dir) x -> InstallDirs dir
forall x. InstallDirs dir -> Rep (InstallDirs dir) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall dir x. Rep (InstallDirs dir) x -> InstallDirs dir
forall dir x. InstallDirs dir -> Rep (InstallDirs dir) x
$cfrom :: forall dir x. InstallDirs dir -> Rep (InstallDirs dir) x
from :: forall x. InstallDirs dir -> Rep (InstallDirs dir) x
$cto :: forall dir x. Rep (InstallDirs dir) x -> InstallDirs dir
to :: forall x. Rep (InstallDirs dir) x -> InstallDirs dir
Generic)
instance Binary dir => Binary (InstallDirs dir)
instance Structured dir => Structured (InstallDirs dir)
instance (Semigroup dir, Monoid dir) => Monoid (InstallDirs dir) where
mempty :: InstallDirs dir
mempty = InstallDirs dir
forall a. (Generic a, GMonoid (Rep a)) => a
gmempty
mappend :: InstallDirs dir -> InstallDirs dir -> InstallDirs dir
mappend = InstallDirs dir -> InstallDirs dir -> InstallDirs dir
forall a. Semigroup a => a -> a -> a
(<>)
instance Semigroup dir => Semigroup (InstallDirs dir) where
<> :: InstallDirs dir -> InstallDirs dir -> InstallDirs dir
(<>) = InstallDirs dir -> InstallDirs dir -> InstallDirs dir
forall a. (Generic a, GSemigroup (Rep a)) => a -> a -> a
gmappend
combineInstallDirs
:: (a -> b -> c)
-> InstallDirs a
-> InstallDirs b
-> InstallDirs c
combineInstallDirs :: forall a b c.
(a -> b -> c) -> InstallDirs a -> InstallDirs b -> InstallDirs c
combineInstallDirs a -> b -> c
combine InstallDirs a
a InstallDirs b
b =
InstallDirs
{ prefix :: c
prefix = InstallDirs a -> a
forall dir. InstallDirs dir -> dir
prefix InstallDirs a
a a -> b -> c
`combine` InstallDirs b -> b
forall dir. InstallDirs dir -> dir
prefix InstallDirs b
b
, bindir :: c
bindir = InstallDirs a -> a
forall dir. InstallDirs dir -> dir
bindir InstallDirs a
a a -> b -> c
`combine` InstallDirs b -> b
forall dir. InstallDirs dir -> dir
bindir InstallDirs b
b
, libdir :: c
libdir = InstallDirs a -> a
forall dir. InstallDirs dir -> dir
libdir InstallDirs a
a a -> b -> c
`combine` InstallDirs b -> b
forall dir. InstallDirs dir -> dir
libdir InstallDirs b
b
, libsubdir :: c
libsubdir = InstallDirs a -> a
forall dir. InstallDirs dir -> dir
libsubdir InstallDirs a
a a -> b -> c
`combine` InstallDirs b -> b
forall dir. InstallDirs dir -> dir
libsubdir InstallDirs b
b
, dynlibdir :: c
dynlibdir = InstallDirs a -> a
forall dir. InstallDirs dir -> dir
dynlibdir InstallDirs a
a a -> b -> c
`combine` InstallDirs b -> b
forall dir. InstallDirs dir -> dir
dynlibdir InstallDirs b
b
, flibdir :: c
flibdir = InstallDirs a -> a
forall dir. InstallDirs dir -> dir
flibdir InstallDirs a
a a -> b -> c
`combine` InstallDirs b -> b
forall dir. InstallDirs dir -> dir
flibdir InstallDirs b
b
, libexecdir :: c
libexecdir = InstallDirs a -> a
forall dir. InstallDirs dir -> dir
libexecdir InstallDirs a
a a -> b -> c
`combine` InstallDirs b -> b
forall dir. InstallDirs dir -> dir
libexecdir InstallDirs b
b
, libexecsubdir :: c
libexecsubdir = InstallDirs a -> a
forall dir. InstallDirs dir -> dir
libexecsubdir InstallDirs a
a a -> b -> c
`combine` InstallDirs b -> b
forall dir. InstallDirs dir -> dir
libexecsubdir InstallDirs b
b
, includedir :: c
includedir = InstallDirs a -> a
forall dir. InstallDirs dir -> dir
includedir InstallDirs a
a a -> b -> c
`combine` InstallDirs b -> b
forall dir. InstallDirs dir -> dir
includedir InstallDirs b
b
, datadir :: c
datadir = InstallDirs a -> a
forall dir. InstallDirs dir -> dir
datadir InstallDirs a
a a -> b -> c
`combine` InstallDirs b -> b
forall dir. InstallDirs dir -> dir
datadir InstallDirs b
b
, datasubdir :: c
datasubdir = InstallDirs a -> a
forall dir. InstallDirs dir -> dir
datasubdir InstallDirs a
a a -> b -> c
`combine` InstallDirs b -> b
forall dir. InstallDirs dir -> dir
datasubdir InstallDirs b
b
, docdir :: c
docdir = InstallDirs a -> a
forall dir. InstallDirs dir -> dir
docdir InstallDirs a
a a -> b -> c
`combine` InstallDirs b -> b
forall dir. InstallDirs dir -> dir
docdir InstallDirs b
b
, mandir :: c
mandir = InstallDirs a -> a
forall dir. InstallDirs dir -> dir
mandir InstallDirs a
a a -> b -> c
`combine` InstallDirs b -> b
forall dir. InstallDirs dir -> dir
mandir InstallDirs b
b
, htmldir :: c
htmldir = InstallDirs a -> a
forall dir. InstallDirs dir -> dir
htmldir InstallDirs a
a a -> b -> c
`combine` InstallDirs b -> b
forall dir. InstallDirs dir -> dir
htmldir InstallDirs b
b
, haddockdir :: c
haddockdir = InstallDirs a -> a
forall dir. InstallDirs dir -> dir
haddockdir InstallDirs a
a a -> b -> c
`combine` InstallDirs b -> b
forall dir. InstallDirs dir -> dir
haddockdir InstallDirs b
b
, sysconfdir :: c
sysconfdir = InstallDirs a -> a
forall dir. InstallDirs dir -> dir
sysconfdir InstallDirs a
a a -> b -> c
`combine` InstallDirs b -> b
forall dir. InstallDirs dir -> dir
sysconfdir InstallDirs b
b
}
appendSubdirs :: (a -> a -> a) -> InstallDirs a -> InstallDirs a
appendSubdirs :: forall a. (a -> a -> a) -> InstallDirs a -> InstallDirs a
appendSubdirs a -> a -> a
append InstallDirs a
dirs =
InstallDirs a
dirs
{ libdir = libdir dirs `append` libsubdir dirs
, libexecdir = libexecdir dirs `append` libexecsubdir dirs
, datadir = datadir dirs `append` datasubdir dirs
, libsubdir = error "internal error InstallDirs.libsubdir"
, libexecsubdir = error "internal error InstallDirs.libexecsubdir"
, datasubdir = error "internal error InstallDirs.datasubdir"
}
type InstallDirTemplates = InstallDirs PathTemplate
defaultInstallDirs :: CompilerFlavor -> Bool -> Bool -> IO InstallDirTemplates
defaultInstallDirs :: CompilerFlavor -> Bool -> Bool -> IO InstallDirTemplates
defaultInstallDirs = Bool -> CompilerFlavor -> Bool -> Bool -> IO InstallDirTemplates
defaultInstallDirs' Bool
False
defaultInstallDirs'
:: Bool
-> CompilerFlavor
-> Bool
-> Bool
-> IO InstallDirTemplates
defaultInstallDirs' :: Bool -> CompilerFlavor -> Bool -> Bool -> IO InstallDirTemplates
defaultInstallDirs' Bool
True CompilerFlavor
comp Bool
userInstall Bool
hasLibs = do
dflt <- Bool -> CompilerFlavor -> Bool -> Bool -> IO InstallDirTemplates
defaultInstallDirs' Bool
False CompilerFlavor
comp Bool
userInstall Bool
hasLibs
return
dflt
{ datasubdir = toPathTemplate $ "$abi" </> "$libname"
, docdir = toPathTemplate $ "$datadir" </> "doc" </> "$abi" </> "$libname"
}
defaultInstallDirs' Bool
False CompilerFlavor
comp Bool
userInstall Bool
_hasLibs = do
installPrefix <-
if Bool
userInstall
then do
mDir <- [Char] -> IO (Maybe [Char])
lookupEnv [Char]
"CABAL_DIR"
case mDir of
Maybe [Char]
Nothing -> [Char] -> IO [Char]
getAppUserDataDirectory [Char]
"cabal"
Just [Char]
dir -> [Char] -> IO [Char]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [Char]
dir
else case OS
buildOS of
OS
Windows -> do
windowsProgramFilesDir <- IO [Char]
getWindowsProgramFilesDir
return (windowsProgramFilesDir </> "Haskell")
OS
Haiku -> [Char] -> IO [Char]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [Char]
"/boot/system/non-packaged"
OS
_ -> [Char] -> IO [Char]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [Char]
"/usr/local"
installLibDir <-
case buildOS of
OS
Windows -> [Char] -> IO [Char]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [Char]
"$prefix"
OS
_ -> [Char] -> IO [Char]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ([Char]
"$prefix" [Char] -> ShowS
</> [Char]
"lib")
return $
fmap toPathTemplate $
InstallDirs
{ prefix = installPrefix
, bindir = "$prefix" </> "bin"
, libdir = installLibDir
, libsubdir = case comp of
CompilerFlavor
UHC -> [Char]
"$pkgid"
CompilerFlavor
_other -> [Char]
"$abi" [Char] -> ShowS
</> [Char]
"$libname"
, dynlibdir =
"$libdir" </> case comp of
CompilerFlavor
UHC -> [Char]
"$pkgid"
CompilerFlavor
_other -> [Char]
"$abi"
, libexecsubdir = "$abi" </> "$pkgid"
, flibdir = "$libdir"
, libexecdir = case buildOS of
OS
Windows -> [Char]
"$prefix" [Char] -> ShowS
</> [Char]
"$libname"
OS
Haiku -> [Char]
"$libdir"
OS
_other -> [Char]
"$prefix" [Char] -> ShowS
</> [Char]
"libexec"
, includedir = case buildOS of
OS
Haiku -> [Char]
"$prefix" [Char] -> ShowS
</> [Char]
"develop" [Char] -> ShowS
</> [Char]
"headers"
OS
_other -> [Char]
"$libdir" [Char] -> ShowS
</> [Char]
"$libsubdir" [Char] -> ShowS
</> [Char]
"include"
, datadir = case buildOS of
OS
Windows -> [Char]
"$prefix"
OS
Haiku -> [Char]
"$prefix" [Char] -> ShowS
</> [Char]
"data"
OS
_other -> [Char]
"$prefix" [Char] -> ShowS
</> [Char]
"share"
, datasubdir = "$abi" </> "$pkgid"
, docdir = case buildOS of
OS
Haiku -> [Char]
"$prefix" [Char] -> ShowS
</> [Char]
"documentation"
OS
_other -> [Char]
"$datadir" [Char] -> ShowS
</> [Char]
"doc" [Char] -> ShowS
</> [Char]
"$abi" [Char] -> ShowS
</> [Char]
"$pkgid"
, mandir = case buildOS of
OS
Haiku -> [Char]
"$docdir" [Char] -> ShowS
</> [Char]
"man"
OS
_other -> [Char]
"$datadir" [Char] -> ShowS
</> [Char]
"man"
, htmldir = "$docdir" </> "html"
, haddockdir = "$htmldir"
, sysconfdir = case buildOS of
OS
Haiku -> [Char]
"boot" [Char] -> ShowS
</> [Char]
"system" [Char] -> ShowS
</> [Char]
"settings"
OS
_other -> [Char]
"$prefix" [Char] -> ShowS
</> [Char]
"etc"
}
substituteInstallDirTemplates
:: PathTemplateEnv
-> InstallDirTemplates
-> InstallDirTemplates
substituteInstallDirTemplates :: PathTemplateEnv -> InstallDirTemplates -> InstallDirTemplates
substituteInstallDirTemplates PathTemplateEnv
env InstallDirTemplates
dirs = InstallDirTemplates
dirs'
where
dirs' :: InstallDirTemplates
dirs' =
InstallDirs
{
prefix :: PathTemplate
prefix = (InstallDirTemplates -> PathTemplate)
-> PathTemplateEnv -> PathTemplate
subst InstallDirTemplates -> PathTemplate
forall dir. InstallDirs dir -> dir
prefix []
, bindir :: PathTemplate
bindir = (InstallDirTemplates -> PathTemplate)
-> PathTemplateEnv -> PathTemplate
subst InstallDirTemplates -> PathTemplate
forall dir. InstallDirs dir -> dir
bindir [(PathTemplateVariable, PathTemplate)
prefixVar]
, libdir :: PathTemplate
libdir = (InstallDirTemplates -> PathTemplate)
-> PathTemplateEnv -> PathTemplate
subst InstallDirTemplates -> PathTemplate
forall dir. InstallDirs dir -> dir
libdir [(PathTemplateVariable, PathTemplate)
prefixVar, (PathTemplateVariable, PathTemplate)
bindirVar]
, libsubdir :: PathTemplate
libsubdir = (InstallDirTemplates -> PathTemplate)
-> PathTemplateEnv -> PathTemplate
subst InstallDirTemplates -> PathTemplate
forall dir. InstallDirs dir -> dir
libsubdir []
, dynlibdir :: PathTemplate
dynlibdir = (InstallDirTemplates -> PathTemplate)
-> PathTemplateEnv -> PathTemplate
subst InstallDirTemplates -> PathTemplate
forall dir. InstallDirs dir -> dir
dynlibdir [(PathTemplateVariable, PathTemplate)
prefixVar, (PathTemplateVariable, PathTemplate)
bindirVar, (PathTemplateVariable, PathTemplate)
libdirVar]
, flibdir :: PathTemplate
flibdir = (InstallDirTemplates -> PathTemplate)
-> PathTemplateEnv -> PathTemplate
subst InstallDirTemplates -> PathTemplate
forall dir. InstallDirs dir -> dir
flibdir [(PathTemplateVariable, PathTemplate)
prefixVar, (PathTemplateVariable, PathTemplate)
bindirVar, (PathTemplateVariable, PathTemplate)
libdirVar]
, libexecdir :: PathTemplate
libexecdir = (InstallDirTemplates -> PathTemplate)
-> PathTemplateEnv -> PathTemplate
subst InstallDirTemplates -> PathTemplate
forall dir. InstallDirs dir -> dir
libexecdir PathTemplateEnv
prefixBinLibVars
, libexecsubdir :: PathTemplate
libexecsubdir = (InstallDirTemplates -> PathTemplate)
-> PathTemplateEnv -> PathTemplate
subst InstallDirTemplates -> PathTemplate
forall dir. InstallDirs dir -> dir
libexecsubdir []
, includedir :: PathTemplate
includedir = (InstallDirTemplates -> PathTemplate)
-> PathTemplateEnv -> PathTemplate
subst InstallDirTemplates -> PathTemplate
forall dir. InstallDirs dir -> dir
includedir PathTemplateEnv
prefixBinLibVars
, datadir :: PathTemplate
datadir = (InstallDirTemplates -> PathTemplate)
-> PathTemplateEnv -> PathTemplate
subst InstallDirTemplates -> PathTemplate
forall dir. InstallDirs dir -> dir
datadir PathTemplateEnv
prefixBinLibVars
, datasubdir :: PathTemplate
datasubdir = (InstallDirTemplates -> PathTemplate)
-> PathTemplateEnv -> PathTemplate
subst InstallDirTemplates -> PathTemplate
forall dir. InstallDirs dir -> dir
datasubdir []
, docdir :: PathTemplate
docdir = (InstallDirTemplates -> PathTemplate)
-> PathTemplateEnv -> PathTemplate
subst InstallDirTemplates -> PathTemplate
forall dir. InstallDirs dir -> dir
docdir PathTemplateEnv
prefixBinLibDataVars
, mandir :: PathTemplate
mandir = (InstallDirTemplates -> PathTemplate)
-> PathTemplateEnv -> PathTemplate
subst InstallDirTemplates -> PathTemplate
forall dir. InstallDirs dir -> dir
mandir (PathTemplateEnv
prefixBinLibDataVars PathTemplateEnv -> PathTemplateEnv -> PathTemplateEnv
forall a. [a] -> [a] -> [a]
++ [(PathTemplateVariable, PathTemplate)
docdirVar])
, htmldir :: PathTemplate
htmldir = (InstallDirTemplates -> PathTemplate)
-> PathTemplateEnv -> PathTemplate
subst InstallDirTemplates -> PathTemplate
forall dir. InstallDirs dir -> dir
htmldir (PathTemplateEnv
prefixBinLibDataVars PathTemplateEnv -> PathTemplateEnv -> PathTemplateEnv
forall a. [a] -> [a] -> [a]
++ [(PathTemplateVariable, PathTemplate)
docdirVar])
, haddockdir :: PathTemplate
haddockdir =
(InstallDirTemplates -> PathTemplate)
-> PathTemplateEnv -> PathTemplate
subst
InstallDirTemplates -> PathTemplate
forall dir. InstallDirs dir -> dir
haddockdir
( PathTemplateEnv
prefixBinLibDataVars
PathTemplateEnv -> PathTemplateEnv -> PathTemplateEnv
forall a. [a] -> [a] -> [a]
++ [(PathTemplateVariable, PathTemplate)
docdirVar, (PathTemplateVariable, PathTemplate)
htmldirVar]
)
, sysconfdir :: PathTemplate
sysconfdir = (InstallDirTemplates -> PathTemplate)
-> PathTemplateEnv -> PathTemplate
subst InstallDirTemplates -> PathTemplate
forall dir. InstallDirs dir -> dir
sysconfdir PathTemplateEnv
prefixBinLibVars
}
subst :: (InstallDirTemplates -> PathTemplate)
-> PathTemplateEnv -> PathTemplate
subst InstallDirTemplates -> PathTemplate
dir PathTemplateEnv
env' = PathTemplateEnv -> PathTemplate -> PathTemplate
substPathTemplate (PathTemplateEnv
env' PathTemplateEnv -> PathTemplateEnv -> PathTemplateEnv
forall a. [a] -> [a] -> [a]
++ PathTemplateEnv
env) (InstallDirTemplates -> PathTemplate
dir InstallDirTemplates
dirs)
prefixVar :: (PathTemplateVariable, PathTemplate)
prefixVar = (PathTemplateVariable
PrefixVar, InstallDirTemplates -> PathTemplate
forall dir. InstallDirs dir -> dir
prefix InstallDirTemplates
dirs')
bindirVar :: (PathTemplateVariable, PathTemplate)
bindirVar = (PathTemplateVariable
BindirVar, InstallDirTemplates -> PathTemplate
forall dir. InstallDirs dir -> dir
bindir InstallDirTemplates
dirs')
libdirVar :: (PathTemplateVariable, PathTemplate)
libdirVar = (PathTemplateVariable
LibdirVar, InstallDirTemplates -> PathTemplate
forall dir. InstallDirs dir -> dir
libdir InstallDirTemplates
dirs')
libsubdirVar :: (PathTemplateVariable, PathTemplate)
libsubdirVar = (PathTemplateVariable
LibsubdirVar, InstallDirTemplates -> PathTemplate
forall dir. InstallDirs dir -> dir
libsubdir InstallDirTemplates
dirs')
datadirVar :: (PathTemplateVariable, PathTemplate)
datadirVar = (PathTemplateVariable
DatadirVar, InstallDirTemplates -> PathTemplate
forall dir. InstallDirs dir -> dir
datadir InstallDirTemplates
dirs')
datasubdirVar :: (PathTemplateVariable, PathTemplate)
datasubdirVar = (PathTemplateVariable
DatasubdirVar, InstallDirTemplates -> PathTemplate
forall dir. InstallDirs dir -> dir
datasubdir InstallDirTemplates
dirs')
docdirVar :: (PathTemplateVariable, PathTemplate)
docdirVar = (PathTemplateVariable
DocdirVar, InstallDirTemplates -> PathTemplate
forall dir. InstallDirs dir -> dir
docdir InstallDirTemplates
dirs')
htmldirVar :: (PathTemplateVariable, PathTemplate)
htmldirVar = (PathTemplateVariable
HtmldirVar, InstallDirTemplates -> PathTemplate
forall dir. InstallDirs dir -> dir
htmldir InstallDirTemplates
dirs')
prefixBinLibVars :: PathTemplateEnv
prefixBinLibVars = [(PathTemplateVariable, PathTemplate)
prefixVar, (PathTemplateVariable, PathTemplate)
bindirVar, (PathTemplateVariable, PathTemplate)
libdirVar, (PathTemplateVariable, PathTemplate)
libsubdirVar]
prefixBinLibDataVars :: PathTemplateEnv
prefixBinLibDataVars = PathTemplateEnv
prefixBinLibVars PathTemplateEnv -> PathTemplateEnv -> PathTemplateEnv
forall a. [a] -> [a] -> [a]
++ [(PathTemplateVariable, PathTemplate)
datadirVar, (PathTemplateVariable, PathTemplate)
datasubdirVar]
absoluteInstallDirs
:: PackageIdentifier
-> UnitId
-> CompilerInfo
-> CopyDest
-> Platform
-> InstallDirs PathTemplate
-> InstallDirs FilePath
absoluteInstallDirs :: PackageIdentifier
-> UnitId
-> CompilerInfo
-> CopyDest
-> Platform
-> InstallDirTemplates
-> InstallDirs [Char]
absoluteInstallDirs PackageIdentifier
pkgId UnitId
libname CompilerInfo
compilerId CopyDest
copydest Platform
platform InstallDirTemplates
dirs =
( case CopyDest
copydest of
CopyTo [Char]
destdir -> ShowS -> InstallDirs [Char] -> InstallDirs [Char]
forall a b. (a -> b) -> InstallDirs a -> InstallDirs b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (([Char]
destdir [Char] -> ShowS
</>) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShowS
dropDrive)
CopyToDb [Char]
dbdir -> ShowS -> InstallDirs [Char] -> InstallDirs [Char]
forall a b. (a -> b) -> InstallDirs a -> InstallDirs b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([Char] -> [Char] -> ShowS
forall {a}. Eq a => [a] -> [a] -> [a] -> [a]
substPrefix [Char]
"${pkgroot}" (ShowS
takeDirectory [Char]
dbdir))
CopyDest
_ -> InstallDirs [Char] -> InstallDirs [Char]
forall a. a -> a
id
)
(InstallDirs [Char] -> InstallDirs [Char])
-> (InstallDirTemplates -> InstallDirs [Char])
-> InstallDirTemplates
-> InstallDirs [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Char] -> ShowS) -> InstallDirs [Char] -> InstallDirs [Char]
forall a. (a -> a -> a) -> InstallDirs a -> InstallDirs a
appendSubdirs [Char] -> ShowS
(</>)
(InstallDirs [Char] -> InstallDirs [Char])
-> (InstallDirTemplates -> InstallDirs [Char])
-> InstallDirTemplates
-> InstallDirs [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (PathTemplate -> [Char])
-> InstallDirTemplates -> InstallDirs [Char]
forall a b. (a -> b) -> InstallDirs a -> InstallDirs b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap PathTemplate -> [Char]
fromPathTemplate
(InstallDirTemplates -> InstallDirs [Char])
-> InstallDirTemplates -> InstallDirs [Char]
forall a b. (a -> b) -> a -> b
$ PathTemplateEnv -> InstallDirTemplates -> InstallDirTemplates
substituteInstallDirTemplates PathTemplateEnv
env InstallDirTemplates
dirs
where
env :: PathTemplateEnv
env = PackageIdentifier
-> UnitId -> CompilerInfo -> Platform -> PathTemplateEnv
initialPathTemplateEnv PackageIdentifier
pkgId UnitId
libname CompilerInfo
compilerId Platform
platform
substPrefix :: [a] -> [a] -> [a] -> [a]
substPrefix [a]
pre [a]
root [a]
path
| [a]
pre [a] -> [a] -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` [a]
path = [a]
root [a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
++ Int -> [a] -> [a]
forall a. Int -> [a] -> [a]
drop ([a] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
pre) [a]
path
| Bool
otherwise = [a]
path
data CopyDest
= NoCopyDest
| CopyTo FilePath
|
CopyToDb FilePath
deriving (CopyDest -> CopyDest -> Bool
(CopyDest -> CopyDest -> Bool)
-> (CopyDest -> CopyDest -> Bool) -> Eq CopyDest
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CopyDest -> CopyDest -> Bool
== :: CopyDest -> CopyDest -> Bool
$c/= :: CopyDest -> CopyDest -> Bool
/= :: CopyDest -> CopyDest -> Bool
Eq, Int -> CopyDest -> ShowS
[CopyDest] -> ShowS
CopyDest -> [Char]
(Int -> CopyDest -> ShowS)
-> (CopyDest -> [Char]) -> ([CopyDest] -> ShowS) -> Show CopyDest
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CopyDest -> ShowS
showsPrec :: Int -> CopyDest -> ShowS
$cshow :: CopyDest -> [Char]
show :: CopyDest -> [Char]
$cshowList :: [CopyDest] -> ShowS
showList :: [CopyDest] -> ShowS
Show, (forall x. CopyDest -> Rep CopyDest x)
-> (forall x. Rep CopyDest x -> CopyDest) -> Generic CopyDest
forall x. Rep CopyDest x -> CopyDest
forall x. CopyDest -> Rep CopyDest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. CopyDest -> Rep CopyDest x
from :: forall x. CopyDest -> Rep CopyDest x
$cto :: forall x. Rep CopyDest x -> CopyDest
to :: forall x. Rep CopyDest x -> CopyDest
Generic)
instance Binary CopyDest
instance Structured CopyDest
prefixRelativeInstallDirs
:: PackageIdentifier
-> UnitId
-> CompilerInfo
-> Platform
-> InstallDirTemplates
-> InstallDirs (Maybe FilePath)
prefixRelativeInstallDirs :: PackageIdentifier
-> UnitId
-> CompilerInfo
-> Platform
-> InstallDirTemplates
-> InstallDirs (Maybe [Char])
prefixRelativeInstallDirs PackageIdentifier
pkgId UnitId
libname CompilerInfo
compilerId Platform
platform InstallDirTemplates
dirs =
(PathTemplate -> Maybe [Char])
-> InstallDirTemplates -> InstallDirs (Maybe [Char])
forall a b. (a -> b) -> InstallDirs a -> InstallDirs b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap PathTemplate -> Maybe [Char]
relative
(InstallDirTemplates -> InstallDirs (Maybe [Char]))
-> (InstallDirTemplates -> InstallDirTemplates)
-> InstallDirTemplates
-> InstallDirs (Maybe [Char])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (PathTemplate -> PathTemplate -> PathTemplate)
-> InstallDirTemplates -> InstallDirTemplates
forall a. (a -> a -> a) -> InstallDirs a -> InstallDirs a
appendSubdirs PathTemplate -> PathTemplate -> PathTemplate
combinePathTemplate
(InstallDirTemplates -> InstallDirs (Maybe [Char]))
-> InstallDirTemplates -> InstallDirs (Maybe [Char])
forall a b. (a -> b) -> a -> b
$ PathTemplateEnv -> InstallDirTemplates -> InstallDirTemplates
substituteInstallDirTemplates
PathTemplateEnv
env
InstallDirTemplates
dirs
{ prefix = PathTemplate [Variable PrefixVar]
}
where
env :: PathTemplateEnv
env = PackageIdentifier
-> UnitId -> CompilerInfo -> Platform -> PathTemplateEnv
initialPathTemplateEnv PackageIdentifier
pkgId UnitId
libname CompilerInfo
compilerId Platform
platform
relative :: PathTemplate -> Maybe [Char]
relative PathTemplate
dir = case PathTemplate
dir of
PathTemplate [PathComponent]
cs -> ([PathComponent] -> [Char])
-> Maybe [PathComponent] -> Maybe [Char]
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (PathTemplate -> [Char]
fromPathTemplate (PathTemplate -> [Char])
-> ([PathComponent] -> PathTemplate) -> [PathComponent] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [PathComponent] -> PathTemplate
PathTemplate) ([PathComponent] -> Maybe [PathComponent]
relative' [PathComponent]
cs)
relative' :: [PathComponent] -> Maybe [PathComponent]
relative' (Variable PathTemplateVariable
PrefixVar : Ordinary (Char
s : [Char]
rest) : [PathComponent]
rest')
| Char -> Bool
isPathSeparator Char
s = [PathComponent] -> Maybe [PathComponent]
forall a. a -> Maybe a
Just ([Char] -> PathComponent
Ordinary [Char]
rest PathComponent -> [PathComponent] -> [PathComponent]
forall a. a -> [a] -> [a]
: [PathComponent]
rest')
relative' (Variable PathTemplateVariable
PrefixVar : [PathComponent]
rest) = [PathComponent] -> Maybe [PathComponent]
forall a. a -> Maybe a
Just [PathComponent]
rest
relative' [PathComponent]
_ = Maybe [PathComponent]
forall a. Maybe a
Nothing
newtype PathTemplate = PathTemplate [PathComponent]
deriving (PathTemplate -> PathTemplate -> Bool
(PathTemplate -> PathTemplate -> Bool)
-> (PathTemplate -> PathTemplate -> Bool) -> Eq PathTemplate
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PathTemplate -> PathTemplate -> Bool
== :: PathTemplate -> PathTemplate -> Bool
$c/= :: PathTemplate -> PathTemplate -> Bool
/= :: PathTemplate -> PathTemplate -> Bool
Eq, Eq PathTemplate
Eq PathTemplate =>
(PathTemplate -> PathTemplate -> Ordering)
-> (PathTemplate -> PathTemplate -> Bool)
-> (PathTemplate -> PathTemplate -> Bool)
-> (PathTemplate -> PathTemplate -> Bool)
-> (PathTemplate -> PathTemplate -> Bool)
-> (PathTemplate -> PathTemplate -> PathTemplate)
-> (PathTemplate -> PathTemplate -> PathTemplate)
-> Ord PathTemplate
PathTemplate -> PathTemplate -> Bool
PathTemplate -> PathTemplate -> Ordering
PathTemplate -> PathTemplate -> PathTemplate
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: PathTemplate -> PathTemplate -> Ordering
compare :: PathTemplate -> PathTemplate -> Ordering
$c< :: PathTemplate -> PathTemplate -> Bool
< :: PathTemplate -> PathTemplate -> Bool
$c<= :: PathTemplate -> PathTemplate -> Bool
<= :: PathTemplate -> PathTemplate -> Bool
$c> :: PathTemplate -> PathTemplate -> Bool
> :: PathTemplate -> PathTemplate -> Bool
$c>= :: PathTemplate -> PathTemplate -> Bool
>= :: PathTemplate -> PathTemplate -> Bool
$cmax :: PathTemplate -> PathTemplate -> PathTemplate
max :: PathTemplate -> PathTemplate -> PathTemplate
$cmin :: PathTemplate -> PathTemplate -> PathTemplate
min :: PathTemplate -> PathTemplate -> PathTemplate
Ord, (forall x. PathTemplate -> Rep PathTemplate x)
-> (forall x. Rep PathTemplate x -> PathTemplate)
-> Generic PathTemplate
forall x. Rep PathTemplate x -> PathTemplate
forall x. PathTemplate -> Rep PathTemplate x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. PathTemplate -> Rep PathTemplate x
from :: forall x. PathTemplate -> Rep PathTemplate x
$cto :: forall x. Rep PathTemplate x -> PathTemplate
to :: forall x. Rep PathTemplate x -> PathTemplate
Generic)
instance Binary PathTemplate
instance Structured PathTemplate
type PathTemplateEnv = [(PathTemplateVariable, PathTemplate)]
toPathTemplate :: FilePath -> PathTemplate
toPathTemplate :: [Char] -> PathTemplate
toPathTemplate [Char]
fp =
[PathComponent] -> PathTemplate
PathTemplate
([PathComponent] -> PathTemplate)
-> ([Char] -> [PathComponent]) -> [Char] -> PathTemplate
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [PathComponent] -> Maybe [PathComponent] -> [PathComponent]
forall a. a -> Maybe a -> a
fromMaybe ([Char] -> [PathComponent]
forall a. HasCallStack => [Char] -> a
error ([Char] -> [PathComponent]) -> [Char] -> [PathComponent]
forall a b. (a -> b) -> a -> b
$ [Char]
"panic! toPathTemplate " [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ ShowS
forall a. Show a => a -> [Char]
show [Char]
fp)
(Maybe [PathComponent] -> [PathComponent])
-> ([Char] -> Maybe [PathComponent]) -> [Char] -> [PathComponent]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> Maybe [PathComponent]
forall a. Read a => [Char] -> Maybe a
readMaybe
([Char] -> PathTemplate) -> [Char] -> PathTemplate
forall a b. (a -> b) -> a -> b
$ [Char]
fp
fromPathTemplate :: PathTemplate -> FilePath
fromPathTemplate :: PathTemplate -> [Char]
fromPathTemplate (PathTemplate [PathComponent]
template) = [PathComponent] -> [Char]
forall a. Show a => a -> [Char]
show [PathComponent]
template
combinePathTemplate :: PathTemplate -> PathTemplate -> PathTemplate
combinePathTemplate :: PathTemplate -> PathTemplate -> PathTemplate
combinePathTemplate (PathTemplate [PathComponent]
t1) (PathTemplate [PathComponent]
t2) =
[PathComponent] -> PathTemplate
PathTemplate ([PathComponent]
t1 [PathComponent] -> [PathComponent] -> [PathComponent]
forall a. [a] -> [a] -> [a]
++ [[Char] -> PathComponent
Ordinary [Char
pathSeparator]] [PathComponent] -> [PathComponent] -> [PathComponent]
forall a. [a] -> [a] -> [a]
++ [PathComponent]
t2)
substPathTemplate :: PathTemplateEnv -> PathTemplate -> PathTemplate
substPathTemplate :: PathTemplateEnv -> PathTemplate -> PathTemplate
substPathTemplate PathTemplateEnv
environment (PathTemplate [PathComponent]
template) =
[PathComponent] -> PathTemplate
PathTemplate ((PathComponent -> [PathComponent])
-> [PathComponent] -> [PathComponent]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap PathComponent -> [PathComponent]
subst [PathComponent]
template)
where
subst :: PathComponent -> [PathComponent]
subst component :: PathComponent
component@(Ordinary [Char]
_) = [PathComponent
component]
subst component :: PathComponent
component@(Variable PathTemplateVariable
variable) =
case PathTemplateVariable -> PathTemplateEnv -> Maybe PathTemplate
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup PathTemplateVariable
variable PathTemplateEnv
environment of
Just (PathTemplate [PathComponent]
components) -> [PathComponent]
components
Maybe PathTemplate
Nothing -> [PathComponent
component]
initialPathTemplateEnv
:: PackageIdentifier
-> UnitId
-> CompilerInfo
-> Platform
-> PathTemplateEnv
initialPathTemplateEnv :: PackageIdentifier
-> UnitId -> CompilerInfo -> Platform -> PathTemplateEnv
initialPathTemplateEnv PackageIdentifier
pkgId UnitId
libname CompilerInfo
compiler Platform
platform =
PackageIdentifier -> UnitId -> PathTemplateEnv
packageTemplateEnv PackageIdentifier
pkgId UnitId
libname
PathTemplateEnv -> PathTemplateEnv -> PathTemplateEnv
forall a. [a] -> [a] -> [a]
++ CompilerInfo -> PathTemplateEnv
compilerTemplateEnv CompilerInfo
compiler
PathTemplateEnv -> PathTemplateEnv -> PathTemplateEnv
forall a. [a] -> [a] -> [a]
++ Platform -> PathTemplateEnv
platformTemplateEnv Platform
platform
PathTemplateEnv -> PathTemplateEnv -> PathTemplateEnv
forall a. [a] -> [a] -> [a]
++ CompilerInfo -> Platform -> PathTemplateEnv
abiTemplateEnv CompilerInfo
compiler Platform
platform
packageTemplateEnv :: PackageIdentifier -> UnitId -> PathTemplateEnv
packageTemplateEnv :: PackageIdentifier -> UnitId -> PathTemplateEnv
packageTemplateEnv PackageIdentifier
pkgId UnitId
uid =
[ (PathTemplateVariable
PkgNameVar, [PathComponent] -> PathTemplate
PathTemplate [[Char] -> PathComponent
Ordinary ([Char] -> PathComponent) -> [Char] -> PathComponent
forall a b. (a -> b) -> a -> b
$ PackageName -> [Char]
forall a. Pretty a => a -> [Char]
prettyShow (PackageIdentifier -> PackageName
forall pkg. Package pkg => pkg -> PackageName
packageName PackageIdentifier
pkgId)])
, (PathTemplateVariable
PkgVerVar, [PathComponent] -> PathTemplate
PathTemplate [[Char] -> PathComponent
Ordinary ([Char] -> PathComponent) -> [Char] -> PathComponent
forall a b. (a -> b) -> a -> b
$ Version -> [Char]
forall a. Pretty a => a -> [Char]
prettyShow (PackageIdentifier -> Version
forall pkg. Package pkg => pkg -> Version
packageVersion PackageIdentifier
pkgId)])
,
(PathTemplateVariable
LibNameVar, [PathComponent] -> PathTemplate
PathTemplate [[Char] -> PathComponent
Ordinary ([Char] -> PathComponent) -> [Char] -> PathComponent
forall a b. (a -> b) -> a -> b
$ UnitId -> [Char]
forall a. Pretty a => a -> [Char]
prettyShow UnitId
uid])
, (PathTemplateVariable
PkgIdVar, [PathComponent] -> PathTemplate
PathTemplate [[Char] -> PathComponent
Ordinary ([Char] -> PathComponent) -> [Char] -> PathComponent
forall a b. (a -> b) -> a -> b
$ PackageIdentifier -> [Char]
forall a. Pretty a => a -> [Char]
prettyShow PackageIdentifier
pkgId])
]
compilerTemplateEnv :: CompilerInfo -> PathTemplateEnv
compilerTemplateEnv :: CompilerInfo -> PathTemplateEnv
compilerTemplateEnv CompilerInfo
compiler =
[ (PathTemplateVariable
CompilerVar, [PathComponent] -> PathTemplate
PathTemplate [[Char] -> PathComponent
Ordinary ([Char] -> PathComponent) -> [Char] -> PathComponent
forall a b. (a -> b) -> a -> b
$ CompilerId -> [Char]
forall a. Pretty a => a -> [Char]
prettyShow (CompilerInfo -> CompilerId
compilerInfoId CompilerInfo
compiler)])
]
platformTemplateEnv :: Platform -> PathTemplateEnv
platformTemplateEnv :: Platform -> PathTemplateEnv
platformTemplateEnv (Platform Arch
arch OS
os) =
[ (PathTemplateVariable
OSVar, [PathComponent] -> PathTemplate
PathTemplate [[Char] -> PathComponent
Ordinary ([Char] -> PathComponent) -> [Char] -> PathComponent
forall a b. (a -> b) -> a -> b
$ OS -> [Char]
forall a. Pretty a => a -> [Char]
prettyShow OS
os])
, (PathTemplateVariable
ArchVar, [PathComponent] -> PathTemplate
PathTemplate [[Char] -> PathComponent
Ordinary ([Char] -> PathComponent) -> [Char] -> PathComponent
forall a b. (a -> b) -> a -> b
$ Arch -> [Char]
forall a. Pretty a => a -> [Char]
prettyShow Arch
arch])
]
abiTemplateEnv :: CompilerInfo -> Platform -> PathTemplateEnv
abiTemplateEnv :: CompilerInfo -> Platform -> PathTemplateEnv
abiTemplateEnv CompilerInfo
compiler (Platform Arch
arch OS
os) =
[
( PathTemplateVariable
AbiVar
, [PathComponent] -> PathTemplate
PathTemplate
[ [Char] -> PathComponent
Ordinary ([Char] -> PathComponent) -> [Char] -> PathComponent
forall a b. (a -> b) -> a -> b
$
Arch -> [Char]
forall a. Pretty a => a -> [Char]
prettyShow Arch
arch
[Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ Char
'-'
Char -> ShowS
forall a. a -> [a] -> [a]
: OS -> [Char]
forall a. Pretty a => a -> [Char]
prettyShow OS
os
[Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ Char
'-'
Char -> ShowS
forall a. a -> [a] -> [a]
: CompilerId -> [Char]
forall a. Pretty a => a -> [Char]
prettyShow (CompilerInfo -> CompilerId
compilerInfoId CompilerInfo
compiler)
[Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ case CompilerInfo -> AbiTag
compilerInfoAbiTag CompilerInfo
compiler of
AbiTag
NoAbiTag -> [Char]
""
AbiTag [Char]
tag -> Char
'-' Char -> ShowS
forall a. a -> [a] -> [a]
: [Char]
tag
]
)
, (PathTemplateVariable
AbiTagVar, [PathComponent] -> PathTemplate
PathTemplate [[Char] -> PathComponent
Ordinary ([Char] -> PathComponent) -> [Char] -> PathComponent
forall a b. (a -> b) -> a -> b
$ AbiTag -> [Char]
abiTagString (CompilerInfo -> AbiTag
compilerInfoAbiTag CompilerInfo
compiler)])
]
installDirsTemplateEnv :: InstallDirs PathTemplate -> PathTemplateEnv
installDirsTemplateEnv :: InstallDirTemplates -> PathTemplateEnv
installDirsTemplateEnv InstallDirTemplates
dirs =
[ (PathTemplateVariable
PrefixVar, InstallDirTemplates -> PathTemplate
forall dir. InstallDirs dir -> dir
prefix InstallDirTemplates
dirs)
, (PathTemplateVariable
BindirVar, InstallDirTemplates -> PathTemplate
forall dir. InstallDirs dir -> dir
bindir InstallDirTemplates
dirs)
, (PathTemplateVariable
LibdirVar, InstallDirTemplates -> PathTemplate
forall dir. InstallDirs dir -> dir
libdir InstallDirTemplates
dirs)
, (PathTemplateVariable
LibsubdirVar, InstallDirTemplates -> PathTemplate
forall dir. InstallDirs dir -> dir
libsubdir InstallDirTemplates
dirs)
, (PathTemplateVariable
DynlibdirVar, InstallDirTemplates -> PathTemplate
forall dir. InstallDirs dir -> dir
dynlibdir InstallDirTemplates
dirs)
, (PathTemplateVariable
DatadirVar, InstallDirTemplates -> PathTemplate
forall dir. InstallDirs dir -> dir
datadir InstallDirTemplates
dirs)
, (PathTemplateVariable
DatasubdirVar, InstallDirTemplates -> PathTemplate
forall dir. InstallDirs dir -> dir
datasubdir InstallDirTemplates
dirs)
, (PathTemplateVariable
DocdirVar, InstallDirTemplates -> PathTemplate
forall dir. InstallDirs dir -> dir
docdir InstallDirTemplates
dirs)
, (PathTemplateVariable
HtmldirVar, InstallDirTemplates -> PathTemplate
forall dir. InstallDirs dir -> dir
htmldir InstallDirTemplates
dirs)
]
instance Show PathTemplate where
show :: PathTemplate -> [Char]
show (PathTemplate [PathComponent]
template) = ShowS
forall a. Show a => a -> [Char]
show ([PathComponent] -> [Char]
forall a. Show a => a -> [Char]
show [PathComponent]
template)
instance Read PathTemplate where
readsPrec :: Int -> ReadS PathTemplate
readsPrec Int
p [Char]
s =
[ ([PathComponent] -> PathTemplate
PathTemplate [PathComponent]
template, [Char]
s')
| ([Char]
path, [Char]
s') <- Int -> ReadS [Char]
forall a. Read a => Int -> ReadS a
readsPrec Int
p [Char]
s
, ([PathComponent]
template, [Char]
"") <- ReadS [PathComponent]
forall a. Read a => ReadS a
reads [Char]
path
]
getWindowsProgramFilesDir :: IO FilePath
getWindowsProgramFilesDir :: IO [Char]
getWindowsProgramFilesDir = do
#ifdef mingw32_HOST_OS
m <- shGetFolderPath csidl_PROGRAM_FILES
#else
let m :: Maybe a
m = Maybe a
forall a. Maybe a
Nothing
#endif
[Char] -> IO [Char]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ([Char] -> Maybe [Char] -> [Char]
forall a. a -> Maybe a -> a
fromMaybe [Char]
"C:\\Program Files" Maybe [Char]
forall a. Maybe a
m)
#ifdef mingw32_HOST_OS
shGetFolderPath :: CInt -> IO (Maybe FilePath)
shGetFolderPath n =
allocaArray long_path_size $ \pPath -> do
r <- c_SHGetFolderPath nullPtr n nullPtr 0 pPath
if (r /= 0)
then return Nothing
else do s <- peekCWString pPath; return (Just s)
where
long_path_size = 1024
csidl_PROGRAM_FILES :: CInt
csidl_PROGRAM_FILES = 0x0026
#if defined(x86_64_HOST_ARCH) || defined(aarch64_HOST_ARCH)
#define CALLCONV ccall
#else
#define CALLCONV stdcall
#endif
foreign import CALLCONV unsafe "shlobj.h SHGetFolderPathW"
c_SHGetFolderPath :: Ptr ()
-> CInt
-> Ptr ()
-> CInt
-> CWString
-> Prelude.IO CInt
#endif