module Distribution.Simple.InstallDirs (
InstallDirs(..),
InstallDirTemplates,
defaultInstallDirs,
combineInstallDirs,
absoluteInstallDirs,
CopyDest(..),
prefixRelativeInstallDirs,
substituteInstallDirTemplates,
PathTemplate,
PathTemplateVariable(..),
toPathTemplate,
fromPathTemplate,
substPathTemplate,
initialPathTemplateEnv,
platformTemplateEnv,
compilerTemplateEnv,
packageTemplateEnv,
installDirsTemplateEnv,
) where
import Data.List (isPrefixOf)
import Data.Maybe (fromMaybe)
import Data.Monoid (Monoid(..))
import System.Directory (getAppUserDataDirectory)
import System.FilePath ((</>), isPathSeparator, pathSeparator)
#if __HUGS__ || __GLASGOW_HASKELL__ > 606
import System.FilePath (dropDrive)
#endif
import Distribution.Package
( PackageIdentifier, packageName, packageVersion )
import Distribution.System
( OS(..), buildOS, Platform(..), buildPlatform )
import Distribution.Compiler
( CompilerId, CompilerFlavor(..) )
import Distribution.Text
( display )
#if mingw32_HOST_OS || mingw32_TARGET_OS
import Foreign
import Foreign.C
#endif
data libexecdir :: bInstallDirs dir = InstallDirs {
prefix :: dir,
bindir :: dir,
libdir :: dir,
libsubdir :: dir,
dynlibdir :: dir,
libexecdir :: dir,
progdir :: dir,
includedir :: dir,
datadir :: dir,
datasubdir :: dir,
docdir :: dir,
mandir :: dir,
htmldir :: dir,
haddockdir :: dir
} deriving (D:Read ::
(Int -> ReadS a)
-> ReadS [a]
-> ReadPrec a
-> ReadPrec [a]
-> T:Read aRead, D:Show ::
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> T:Show aShow)
instance D:Functor ::
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a)
-> T:Functor fFunctor InstallDirs where
fmap f dirs = InstallDirs {
prefix = f :: a -> bf (prefix :: InstallDirs dir -> dirprefix dirs :: InstallDirs adirs),
bindir = f :: a -> bf (bindir :: InstallDirs dir -> dirbindir dirs :: InstallDirs adirs),
libdir = f :: a -> bf (libdir :: InstallDirs dir -> dirlibdir dirs :: InstallDirs adirs),
libsubdir = f :: a -> bf (libsubdir :: InstallDirs dir -> dirlibsubdir dirs :: InstallDirs adirs),
dynlibdir = f :: a -> bf (dynlibdir :: InstallDirs dir -> dirdynlibdir dirs :: InstallDirs adirs),
libexecdir = f :: a -> bf (libexecdir :: InstallDirs dir -> dirlibexecdir dirs :: InstallDirs adirs),
progdir = f :: a -> bf (progdir :: InstallDirs dir -> dirprogdir dirs :: InstallDirs adirs),
includedir = f :: a -> bf (includedir :: InstallDirs dir -> dirincludedir dirs :: InstallDirs adirs),
datadir = f :: a -> bf (datadir :: InstallDirs dir -> dirdatadir dirs :: InstallDirs adirs),
datasubdir = f :: a -> bf (datasubdir :: InstallDirs dir -> dirdatasubdir dirs :: InstallDirs adirs),
docdir = f :: a -> bf (docdir :: InstallDirs dir -> dirdocdir dirs :: InstallDirs adirs),
mandir = f :: a -> bf (mandir :: InstallDirs dir -> dirmandir dirs :: InstallDirs adirs),
htmldir = f :: a -> bf (htmldir :: InstallDirs dir -> dirhtmldir dirs :: InstallDirs adirs),
haddockdir = f :: a -> bf (haddockdir :: InstallDirs dir -> dirhaddockdir dirs :: InstallDirs adirs)
}
instance ($cmappend) ::
Monoid dir => InstallDirs dir -> InstallDirs dir -> InstallDirs dirMonoid dir => Monoid (InstallDirs dir) where
mempty = InstallDirs {
prefix = mempty :: Monoid a => amempty,
bindir = mempty :: Monoid a => amempty,
libdir = mempty :: Monoid a => amempty,
libsubdir = mempty :: Monoid a => amempty,
dynlibdir = mempty :: Monoid a => amempty,
libexecdir = mempty :: Monoid a => amempty,
progdir = mempty :: Monoid a => amempty,
includedir = mempty :: Monoid a => amempty,
datadir = mempty :: Monoid a => amempty,
datasubdir = mempty :: Monoid a => amempty,
docdir = mempty :: Monoid a => amempty,
mandir = mempty :: Monoid a => amempty,
htmldir = mempty :: Monoid a => amempty,
haddockdir = mempty :: Monoid a => amempty
}
mappend = combineInstallDirs ::
(a -> b -> c) -> InstallDirs a -> InstallDirs b -> InstallDirs ccombineInstallDirs mappend :: Monoid a => a -> a -> amappend
combineInstallDirs :: (a -> b -> c)
-> InstallDirs a
-> InstallDirs b
-> InstallDirs c
combineInstallDirs combine a b = InstallDirs {
prefix = prefix :: InstallDirs dir -> dirprefix a :: PathComponenta combine :: a -> b -> c`combine` prefix :: InstallDirs dir -> dirprefix b :: PathComponentb,
bindir = bindir :: InstallDirs dir -> dirbindir a :: PathComponenta combine :: a -> b -> c`combine` bindir :: InstallDirs dir -> dirbindir b :: PathComponentb,
libdir = libdir :: InstallDirs dir -> dirlibdir a :: PathComponenta combine :: a -> b -> c`combine` libdir :: InstallDirs dir -> dirlibdir b :: PathComponentb,
libsubdir = libsubdir :: InstallDirs dir -> dirlibsubdir a :: PathComponenta combine :: a -> b -> c`combine` libsubdir :: InstallDirs dir -> dirlibsubdir b :: PathComponentb,
dynlibdir = dynlibdir :: InstallDirs dir -> dirdynlibdir a :: PathComponenta combine :: a -> b -> c`combine` dynlibdir :: InstallDirs dir -> dirdynlibdir b :: PathComponentb,
libexecdir = libexecdir :: InstallDirs dir -> dirlibexecdir a :: PathComponenta combine :: a -> b -> c`combine` libexecdir :: InstallDirs dir -> dirlibexecdir b :: PathComponentb,
progdir = progdir :: InstallDirs dir -> dirprogdir a :: PathComponenta combine :: a -> b -> c`combine` progdir :: InstallDirs dir -> dirprogdir b :: PathComponentb,
includedir = includedir :: InstallDirs dir -> dirincludedir a :: PathComponenta combine :: a -> b -> c`combine` includedir :: InstallDirs dir -> dirincludedir b :: PathComponentb,
datadir = datadir :: InstallDirs dir -> dirdatadir a :: PathComponenta combine :: a -> b -> c`combine` datadir :: InstallDirs dir -> dirdatadir b :: PathComponentb,
datasubdir = datasubdir :: InstallDirs dir -> dirdatasubdir a :: PathComponenta combine :: a -> b -> c`combine` datasubdir :: InstallDirs dir -> dirdatasubdir b :: PathComponentb,
docdir = docdir :: InstallDirs dir -> dirdocdir a :: PathComponenta combine :: a -> b -> c`combine` docdir :: InstallDirs dir -> dirdocdir b :: PathComponentb,
mandir = mandir :: InstallDirs dir -> dirmandir a :: PathComponenta combine :: a -> b -> c`combine` mandir :: InstallDirs dir -> dirmandir b :: PathComponentb,
htmldir = htmldir :: InstallDirs dir -> dirhtmldir a :: PathComponenta combine :: a -> b -> c`combine` htmldir :: InstallDirs dir -> dirhtmldir b :: PathComponentb,
haddockdir = haddockdir :: InstallDirs dir -> dirhaddockdir a :: PathComponenta combine :: a -> b -> c`combine` haddockdir :: InstallDirs dir -> dirhaddockdir b :: PathComponentb
}
appendSubdirs :: (a -> a -> a) -> InstallDirs a -> InstallDirs a
appendSubdirs append dirs = dirs :: InstallDirs adirs {
libdir = libdir :: InstallDirs dir -> dirlibdir dirs :: InstallDirs adirs append :: a -> a -> a`append` libsubdir :: InstallDirs dir -> dirlibsubdir dirs :: InstallDirs adirs,
datadir = datadir :: InstallDirs dir -> dirdatadir dirs :: InstallDirs adirs append :: a -> a -> a`append` datasubdir :: InstallDirs dir -> dirdatasubdir dirs :: InstallDirs adirs,
libsubdir = error :: [Char] -> aerror "internal error InstallDirs.libsubdir",
datasubdir = error :: [Char] -> aerror "internal error InstallDirs.datasubdir"
}
type InstallDirTemplates = InstallDirs PathTemplate
defaultInstallDirs :: CompilerFlavor -> Bool -> Bool -> IO InstallDirTemplates
defaultInstallDirs comp userInstall _hasLibs = do
installPrefix <-
if userInstall :: BooluserInstall
then getAppUserDataDirectory :: String -> IO FilePathgetAppUserDataDirectory "cabal"
else case buildOS :: OSbuildOS of
Windows -> do windowsProgramFilesDir <- getWindowsProgramFilesDir :: IO FilePathgetWindowsProgramFilesDir
return :: Monad m => forall a. a -> m areturn (windowsProgramFilesDir :: FilePathwindowsProgramFilesDir (</>) :: FilePath -> FilePath -> FilePath</> "Haskell")
_ -> return :: Monad m => forall a. a -> m areturn "/usr/local"
installLibDir <-
case buildOS :: OSbuildOS of
Windows -> return :: Monad m => forall a. a -> m areturn "$prefix"
_ -> case comp :: CompilerFlavorcomp of
LHC | userInstall :: BooluserInstall -> getAppUserDataDirectory :: String -> IO FilePathgetAppUserDataDirectory "lhc"
_ -> return :: Monad m => forall a. a -> m areturn ("$prefix" (</>) :: FilePath -> FilePath -> FilePath</> "lib")
return :: Monad m => forall a. a -> m areturn ($) :: (a -> b) -> a -> b$ fmap :: Functor f => forall a b. (a -> b) -> f a -> f bfmap toPathTemplate :: FilePath -> PathTemplatetoPathTemplate ($) :: (a -> b) -> a -> b$ InstallDirs {
prefix = installPrefix :: FilePathinstallPrefix,
bindir = "$prefix" (</>) :: FilePath -> FilePath -> FilePath</> "bin",
libdir = installLibDir :: [Char]installLibDir,
libsubdir = case comp :: CompilerFlavorcomp of
Hugs -> "hugs" (</>) :: FilePath -> FilePath -> FilePath</> "packages" (</>) :: FilePath -> FilePath -> FilePath</> "$pkg"
JHC -> "$compiler"
LHC -> "$compiler"
UHC -> "$pkgid"
_other -> "$pkgid" (</>) :: FilePath -> FilePath -> FilePath</> "$compiler",
dynlibdir = "$libdir",
libexecdir = case buildOS :: OSbuildOS of
Windows -> "$prefix" (</>) :: FilePath -> FilePath -> FilePath</> "$pkgid"
_other -> "$prefix" (</>) :: FilePath -> FilePath -> FilePath</> "libexec",
progdir = "$libdir" (</>) :: FilePath -> FilePath -> FilePath</> "hugs" (</>) :: FilePath -> FilePath -> FilePath</> "programs",
includedir = "$libdir" (</>) :: FilePath -> FilePath -> FilePath</> "$libsubdir" (</>) :: FilePath -> FilePath -> FilePath</> "include",
datadir = case buildOS :: OSbuildOS of
Windows -> "$prefix"
_other -> "$prefix" (</>) :: FilePath -> FilePath -> FilePath</> "share",
datasubdir = "$pkgid",
docdir = "$datadir" (</>) :: FilePath -> FilePath -> FilePath</> "doc" (</>) :: FilePath -> FilePath -> FilePath</> "$pkgid",
mandir = "$datadir" (</>) :: FilePath -> FilePath -> FilePath</> "man",
htmldir = "$docdir" (</>) :: FilePath -> FilePath -> FilePath</> "html",
haddockdir = "$htmldir"
}
substituteInstallDirTemplates :: PathTemplateEnv
-> InstallDirTemplates -> InstallDirTemplates
substituteInstallDirTemplates env dirs = dirs' :: InstallDirs PathTemplatedirs'
where
dirs' = InstallDirs {
prefix = subst ::
(InstallDirTemplates -> PathTemplate)
-> [(PathTemplateVariable, PathTemplate)]
-> PathTemplatesubst prefix :: InstallDirs dir -> dirprefix [] :: [a][],
bindir = subst ::
(InstallDirTemplates -> PathTemplate)
-> [(PathTemplateVariable, PathTemplate)]
-> PathTemplatesubst bindir :: InstallDirs dir -> dirbindir [prefixVar :: (PathTemplateVariable, PathTemplate)prefixVar],
libdir = subst ::
(InstallDirTemplates -> PathTemplate)
-> [(PathTemplateVariable, PathTemplate)]
-> PathTemplatesubst libdir :: InstallDirs dir -> dirlibdir [prefixVar :: (PathTemplateVariable, PathTemplate)prefixVar, bindirVar :: (PathTemplateVariable, PathTemplate)bindirVar],
libsubdir = subst ::
(InstallDirTemplates -> PathTemplate)
-> [(PathTemplateVariable, PathTemplate)]
-> PathTemplatesubst libsubdir :: InstallDirs dir -> dirlibsubdir [] :: [a][],
dynlibdir = subst ::
(InstallDirTemplates -> PathTemplate)
-> [(PathTemplateVariable, PathTemplate)]
-> PathTemplatesubst dynlibdir :: InstallDirs dir -> dirdynlibdir [prefixVar :: (PathTemplateVariable, PathTemplate)prefixVar, bindirVar :: (PathTemplateVariable, PathTemplate)bindirVar, libdirVar :: (PathTemplateVariable, PathTemplate)libdirVar],
libexecdir = subst ::
(InstallDirTemplates -> PathTemplate)
-> [(PathTemplateVariable, PathTemplate)]
-> PathTemplatesubst libexecdir :: InstallDirs dir -> dirlibexecdir prefixBinLibVars :: [(PathTemplateVariable, PathTemplate)]prefixBinLibVars,
progdir = subst ::
(InstallDirTemplates -> PathTemplate)
-> [(PathTemplateVariable, PathTemplate)]
-> PathTemplatesubst progdir :: InstallDirs dir -> dirprogdir prefixBinLibVars :: [(PathTemplateVariable, PathTemplate)]prefixBinLibVars,
includedir = subst ::
(InstallDirTemplates -> PathTemplate)
-> [(PathTemplateVariable, PathTemplate)]
-> PathTemplatesubst includedir :: InstallDirs dir -> dirincludedir prefixBinLibVars :: [(PathTemplateVariable, PathTemplate)]prefixBinLibVars,
datadir = subst ::
(InstallDirTemplates -> PathTemplate)
-> [(PathTemplateVariable, PathTemplate)]
-> PathTemplatesubst datadir :: InstallDirs dir -> dirdatadir prefixBinLibVars :: [(PathTemplateVariable, PathTemplate)]prefixBinLibVars,
datasubdir = subst ::
(InstallDirTemplates -> PathTemplate)
-> [(PathTemplateVariable, PathTemplate)]
-> PathTemplatesubst datasubdir :: InstallDirs dir -> dirdatasubdir [] :: [a][],
docdir = subst ::
(InstallDirTemplates -> PathTemplate)
-> [(PathTemplateVariable, PathTemplate)]
-> PathTemplatesubst docdir :: InstallDirs dir -> dirdocdir prefixBinLibDataVars :: [(PathTemplateVariable, PathTemplate)]prefixBinLibDataVars,
mandir = subst ::
(InstallDirTemplates -> PathTemplate)
-> [(PathTemplateVariable, PathTemplate)]
-> PathTemplatesubst mandir :: InstallDirs dir -> dirmandir (prefixBinLibDataVars :: [(PathTemplateVariable, PathTemplate)]prefixBinLibDataVars (++) :: [a] -> [a] -> [a]++ [docdirVar :: (PathTemplateVariable, PathTemplate)docdirVar]),
htmldir = subst ::
(InstallDirTemplates -> PathTemplate)
-> [(PathTemplateVariable, PathTemplate)]
-> PathTemplatesubst htmldir :: InstallDirs dir -> dirhtmldir (prefixBinLibDataVars :: [(PathTemplateVariable, PathTemplate)]prefixBinLibDataVars (++) :: [a] -> [a] -> [a]++ [docdirVar :: (PathTemplateVariable, PathTemplate)docdirVar]),
haddockdir = subst ::
(InstallDirTemplates -> PathTemplate)
-> [(PathTemplateVariable, PathTemplate)]
-> PathTemplatesubst haddockdir :: InstallDirs dir -> dirhaddockdir (prefixBinLibDataVars :: [(PathTemplateVariable, PathTemplate)]prefixBinLibDataVars (++) :: [a] -> [a] -> [a]++
[docdirVar :: (PathTemplateVariable, PathTemplate)docdirVar, htmldirVar :: (PathTemplateVariable, PathTemplate)htmldirVar])
}
subst dir env' = substPathTemplate ::
PathTemplateEnv -> PathTemplate -> PathTemplatesubstPathTemplate (env' :: [(PathTemplateVariable, PathTemplate)]env'(++) :: [a] -> [a] -> [a]++env :: PathTemplateEnvenv) (dir :: PathTemplatedir dirs :: InstallDirs adirs)
prefixVar = (PrefixVar :: PathTemplateVariablePrefixVar, prefix :: InstallDirs dir -> dirprefix dirs' :: InstallDirs PathTemplatedirs')
bindirVar = (BindirVar :: PathTemplateVariableBindirVar, bindir :: InstallDirs dir -> dirbindir dirs' :: InstallDirs PathTemplatedirs')
libdirVar = (LibdirVar :: PathTemplateVariableLibdirVar, libdir :: InstallDirs dir -> dirlibdir dirs' :: InstallDirs PathTemplatedirs')
libsubdirVar = (LibsubdirVar :: PathTemplateVariableLibsubdirVar, libsubdir :: InstallDirs dir -> dirlibsubdir dirs' :: InstallDirs PathTemplatedirs')
datadirVar = (DatadirVar :: PathTemplateVariableDatadirVar, datadir :: InstallDirs dir -> dirdatadir dirs' :: InstallDirs PathTemplatedirs')
datasubdirVar = (DatasubdirVar :: PathTemplateVariableDatasubdirVar, datasubdir :: InstallDirs dir -> dirdatasubdir dirs' :: InstallDirs PathTemplatedirs')
docdirVar = (DocdirVar :: PathTemplateVariableDocdirVar, docdir :: InstallDirs dir -> dirdocdir dirs' :: InstallDirs PathTemplatedirs')
htmldirVar = (HtmldirVar :: PathTemplateVariableHtmldirVar, htmldir :: InstallDirs dir -> dirhtmldir dirs' :: InstallDirs PathTemplatedirs')
prefixBinLibVars = [prefixVar :: (PathTemplateVariable, PathTemplate)prefixVar, bindirVar :: (PathTemplateVariable, PathTemplate)bindirVar, libdirVar :: (PathTemplateVariable, PathTemplate)libdirVar, libsubdirVar :: (PathTemplateVariable, PathTemplate)libsubdirVar]
prefixBinLibDataVars = prefixBinLibVars :: [(PathTemplateVariable, PathTemplate)]prefixBinLibVars (++) :: [a] -> [a] -> [a]++ [datadirVar :: (PathTemplateVariable, PathTemplate)datadirVar, datasubdirVar :: (PathTemplateVariable, PathTemplate)datasubdirVar]
absoluteInstallDirs :: PackageIdentifier -> CompilerId -> CopyDest
-> InstallDirs PathTemplate
-> InstallDirs FilePath
absoluteInstallDirs pkgId compilerId copydest dirs =
(case copydest :: CopyDestcopydest of
CopyTo destdir -> fmap :: Functor f => forall a b. (a -> b) -> f a -> f bfmap ((destdir :: FilePathdestdir (</>) :: FilePath -> FilePath -> FilePath</>) (.) :: (b -> c) -> (a -> b) -> a -> c. dropDrive :: FilePath -> FilePathdropDrive)
_ -> id :: a -> aid)
(.) :: (b -> c) -> (a -> b) -> a -> c. appendSubdirs :: (a -> a -> a) -> InstallDirs a -> InstallDirs aappendSubdirs (</>) :: FilePath -> FilePath -> FilePath(</>)
(.) :: (b -> c) -> (a -> b) -> a -> c. fmap :: Functor f => forall a b. (a -> b) -> f a -> f bfmap fromPathTemplate :: PathTemplate -> FilePathfromPathTemplate
($) :: (a -> b) -> a -> b$ substituteInstallDirTemplates ::
PathTemplateEnv -> InstallDirTemplates -> InstallDirTemplatessubstituteInstallDirTemplates env :: PathTemplateEnvenv dirs :: InstallDirs adirs
where
env = initialPathTemplateEnv ::
PackageIdentifier -> CompilerId -> PathTemplateEnvinitialPathTemplateEnv pkgId :: PackageIdentifierpkgId compilerId :: CompilerIdcompilerId
data CopyDest
= NoCopyDest
| CopyTo FilePath
deriving (D:Eq :: (a -> a -> Bool) -> (a -> a -> Bool) -> T:Eq aEq, D:Show ::
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> T:Show aShow)
prefixRelativeInstallDirs :: PackageIdentifier -> CompilerId
-> InstallDirTemplates
-> InstallDirs (Maybe FilePath)
prefixRelativeInstallDirs pkgId compilerId dirs =
fmap :: Functor f => forall a b. (a -> b) -> f a -> f bfmap relative :: PathTemplate -> Maybe FilePathrelative
(.) :: (b -> c) -> (a -> b) -> a -> c. appendSubdirs :: (a -> a -> a) -> InstallDirs a -> InstallDirs aappendSubdirs combinePathTemplate :: PathTemplate -> PathTemplate -> PathTemplatecombinePathTemplate
($) :: (a -> b) -> a -> b$
substituteInstallDirTemplates ::
PathTemplateEnv -> InstallDirTemplates -> InstallDirTemplatessubstituteInstallDirTemplates env :: PathTemplateEnvenv dirs :: InstallDirs adirs {
prefix = PathTemplate :: [PathComponent] -> PathTemplatePathTemplate [Variable :: PathTemplateVariable -> PathComponentVariable PrefixVar :: PathTemplateVariablePrefixVar]
}
where
env = initialPathTemplateEnv ::
PackageIdentifier -> CompilerId -> PathTemplateEnvinitialPathTemplateEnv pkgId :: PackageIdentifierpkgId compilerId :: CompilerIdcompilerId
relative dir = case dir :: PathTemplatedir of
PathTemplate cs -> fmap :: Functor f => forall a b. (a -> b) -> f a -> f bfmap (fromPathTemplate :: PathTemplate -> FilePathfromPathTemplate (.) :: (b -> c) -> (a -> b) -> a -> c. PathTemplate :: [PathComponent] -> PathTemplatePathTemplate) (relative' :: [PathComponent] -> Maybe [PathComponent]relative' cs :: [PathComponent]cs)
relative' (Variable PrefixVar : Ordinary (s:rest) : rest')
| isPathSeparator :: Char -> BoolisPathSeparator s :: Strings = Just :: a -> Maybe aJust (Ordinary :: FilePath -> PathComponentOrdinary rest :: [PathComponent]rest (:) :: a -> [a] -> [a]: rest' :: [PathComponent]rest')
relative' (Variable PrefixVar : rest) = Just :: a -> Maybe aJust rest :: [PathComponent]rest
relative' _ = Nothing :: Maybe aNothing
newtype PathTemplate = PathTemplate [PathComponent]
data PathComponent =
Ordinary FilePath
| Variable PathTemplateVariable
deriving D:Eq :: (a -> a -> Bool) -> (a -> a -> Bool) -> T:Eq aEq
data PathTemplateVariable =
PrefixVar
| BindirVar
| LibdirVar
| LibsubdirVar
| DatadirVar
| DatasubdirVar
| DocdirVar
| HtmldirVar
| PkgNameVar
| PkgVerVar
| PkgIdVar
| CompilerVar
| OSVar
| ArchVar
| ExecutableNameVar
| TestSuiteNameVar
| TestSuiteResultVar
deriving D:Eq :: (a -> a -> Bool) -> (a -> a -> Bool) -> T:Eq aEq
type PathTemplateEnv = [(PathTemplateVariable, PathTemplate)]
toPathTemplate :: FilePath -> PathTemplate
toPathTemplate = PathTemplate :: [PathComponent] -> PathTemplatePathTemplate (.) :: (b -> c) -> (a -> b) -> a -> c. read :: Read a => String -> aread
fromPathTemplate :: PathTemplate -> FilePath
fromPathTemplate (PathTemplate template) = show :: Show a => a -> Stringshow template :: [PathComponent]template
combinePathTemplate :: PathTemplate -> PathTemplate -> PathTemplate
combinePathTemplate (PathTemplate t1) (PathTemplate t2) =
PathTemplate :: [PathComponent] -> PathTemplatePathTemplate (t1 :: [PathComponent]t1 (++) :: [a] -> [a] -> [a]++ [Ordinary :: FilePath -> PathComponentOrdinary [pathSeparator :: CharpathSeparator]] (++) :: [a] -> [a] -> [a]++ t2 :: [PathComponent]t2)
substPathTemplate :: PathTemplateEnv -> PathTemplate -> PathTemplate
substPathTemplate environment (PathTemplate template) =
PathTemplate :: [PathComponent] -> PathTemplatePathTemplate (concatMap :: (a -> [b]) -> [a] -> [b]concatMap subst ::
(InstallDirTemplates -> PathTemplate)
-> [(PathTemplateVariable, PathTemplate)]
-> PathTemplatesubst template :: [PathComponent]template)
where subst component@(Ordinary _) = [component :: PathComponentcomponent]
subst component@(Variable variable) =
case lookup :: Eq a => a -> [(a, b)] -> Maybe blookup variable :: PathTemplateVariablevariable environment :: PathTemplateEnvenvironment of
Just (PathTemplate components) -> components :: [PathComponent]components
Nothing -> [component :: PathComponentcomponent]
initialPathTemplateEnv :: PackageIdentifier -> CompilerId -> PathTemplateEnv
initialPathTemplateEnv pkgId compilerId =
packageTemplateEnv :: PackageIdentifier -> PathTemplateEnvpackageTemplateEnv pkgId :: PackageIdentifierpkgId
(++) :: [a] -> [a] -> [a]++ compilerTemplateEnv :: CompilerId -> PathTemplateEnvcompilerTemplateEnv compilerId :: CompilerIdcompilerId
(++) :: [a] -> [a] -> [a]++ platformTemplateEnv :: Platform -> PathTemplateEnvplatformTemplateEnv buildPlatform :: PlatformbuildPlatform
packageTemplateEnv :: PackageIdentifier -> PathTemplateEnv
packageTemplateEnv pkgId =
[(PkgNameVar :: PathTemplateVariablePkgNameVar, PathTemplate :: [PathComponent] -> PathTemplatePathTemplate [Ordinary :: FilePath -> PathComponentOrdinary ($) :: (a -> b) -> a -> b$ display :: Text a => a -> Stringdisplay (packageName :: Package pkg => pkg -> PackageNamepackageName pkgId :: PackageIdentifierpkgId)])
,(PkgVerVar :: PathTemplateVariablePkgVerVar, PathTemplate :: [PathComponent] -> PathTemplatePathTemplate [Ordinary :: FilePath -> PathComponentOrdinary ($) :: (a -> b) -> a -> b$ display :: Text a => a -> Stringdisplay (packageVersion :: Package pkg => pkg -> VersionpackageVersion pkgId :: PackageIdentifierpkgId)])
,(PkgIdVar :: PathTemplateVariablePkgIdVar, PathTemplate :: [PathComponent] -> PathTemplatePathTemplate [Ordinary :: FilePath -> PathComponentOrdinary ($) :: (a -> b) -> a -> b$ display :: Text a => a -> Stringdisplay pkgId :: PackageIdentifierpkgId])
]
compilerTemplateEnv :: CompilerId -> PathTemplateEnv
compilerTemplateEnv compilerId =
[(CompilerVar :: PathTemplateVariableCompilerVar, PathTemplate :: [PathComponent] -> PathTemplatePathTemplate [Ordinary :: FilePath -> PathComponentOrdinary ($) :: (a -> b) -> a -> b$ display :: Text a => a -> Stringdisplay compilerId :: CompilerIdcompilerId])
]
platformTemplateEnv :: Platform -> PathTemplateEnv
platformTemplateEnv (Platform arch os) =
[(OSVar :: PathTemplateVariableOSVar, PathTemplate :: [PathComponent] -> PathTemplatePathTemplate [Ordinary :: FilePath -> PathComponentOrdinary ($) :: (a -> b) -> a -> b$ display :: Text a => a -> Stringdisplay os :: OSos])
,(ArchVar :: PathTemplateVariableArchVar, PathTemplate :: [PathComponent] -> PathTemplatePathTemplate [Ordinary :: FilePath -> PathComponentOrdinary ($) :: (a -> b) -> a -> b$ display :: Text a => a -> Stringdisplay arch :: Archarch])
]
installDirsTemplateEnv :: InstallDirs PathTemplate -> PathTemplateEnv
installDirsTemplateEnv dirs =
[(PrefixVar :: PathTemplateVariablePrefixVar, prefix :: InstallDirs dir -> dirprefix dirs :: InstallDirs adirs)
,(BindirVar :: PathTemplateVariableBindirVar, bindir :: InstallDirs dir -> dirbindir dirs :: InstallDirs adirs)
,(LibdirVar :: PathTemplateVariableLibdirVar, libdir :: InstallDirs dir -> dirlibdir dirs :: InstallDirs adirs)
,(LibsubdirVar :: PathTemplateVariableLibsubdirVar, libsubdir :: InstallDirs dir -> dirlibsubdir dirs :: InstallDirs adirs)
,(DatadirVar :: PathTemplateVariableDatadirVar, datadir :: InstallDirs dir -> dirdatadir dirs :: InstallDirs adirs)
,(DatasubdirVar :: PathTemplateVariableDatasubdirVar, datasubdir :: InstallDirs dir -> dirdatasubdir dirs :: InstallDirs adirs)
,(DocdirVar :: PathTemplateVariableDocdirVar, docdir :: InstallDirs dir -> dirdocdir dirs :: InstallDirs adirs)
,(HtmldirVar :: PathTemplateVariableHtmldirVar, htmldir :: InstallDirs dir -> dirhtmldir dirs :: InstallDirs adirs)
]
instance D:Show ::
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> T:Show aShow PathTemplateVariable where
show PrefixVar = "prefix"
show BindirVar = "bindir"
show LibdirVar = "libdir"
show LibsubdirVar = "libsubdir"
show DatadirVar = "datadir"
show DatasubdirVar = "datasubdir"
show DocdirVar = "docdir"
show HtmldirVar = "htmldir"
show PkgNameVar = "pkg"
show PkgVerVar = "version"
show PkgIdVar = "pkgid"
show CompilerVar = "compiler"
show OSVar = "os"
show ArchVar = "arch"
show ExecutableNameVar = "executablename"
show TestSuiteNameVar = "test-suite"
show TestSuiteResultVar = "result"
instance D:Read ::
(Int -> ReadS a)
-> ReadS [a]
-> ReadPrec a
-> ReadPrec [a]
-> T:Read aRead PathTemplateVariable where
readsPrec _ s =
take :: Int -> [a] -> [a]take 1
[ (var :: PathTemplateVariablevar, drop :: Int -> [a] -> [a]drop (length :: [a] -> Intlength varStr :: [Char]varStr) s :: Strings)
| (varStr, var) <- vars :: [([Char], PathTemplateVariable)]vars
, varStr :: [Char]varStr isPrefixOf :: Eq a => [a] -> [a] -> Bool`isPrefixOf` s :: Strings ]
where vars = [("prefix", PrefixVar :: PathTemplateVariablePrefixVar)
,("bindir", BindirVar :: PathTemplateVariableBindirVar)
,("libdir", LibdirVar :: PathTemplateVariableLibdirVar)
,("libsubdir", LibsubdirVar :: PathTemplateVariableLibsubdirVar)
,("datadir", DatadirVar :: PathTemplateVariableDatadirVar)
,("datasubdir", DatasubdirVar :: PathTemplateVariableDatasubdirVar)
,("docdir", DocdirVar :: PathTemplateVariableDocdirVar)
,("htmldir", HtmldirVar :: PathTemplateVariableHtmldirVar)
,("pkgid", PkgIdVar :: PathTemplateVariablePkgIdVar)
,("pkg", PkgNameVar :: PathTemplateVariablePkgNameVar)
,("version", PkgVerVar :: PathTemplateVariablePkgVerVar)
,("compiler", CompilerVar :: PathTemplateVariableCompilerVar)
,("os", OSVar :: PathTemplateVariableOSVar)
,("arch", ArchVar :: PathTemplateVariableArchVar)
,("executablename", ExecutableNameVar :: PathTemplateVariableExecutableNameVar)
,("test-suite", TestSuiteNameVar :: PathTemplateVariableTestSuiteNameVar)
,("result", TestSuiteResultVar :: PathTemplateVariableTestSuiteResultVar)]
instance D:Show ::
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> T:Show aShow PathComponent where
show (Ordinary path) = path :: FilePathpath
show (Variable var) = '$'(:) :: a -> [a] -> [a]:show :: Show a => a -> Stringshow var :: PathTemplateVariablevar
showList = foldr :: (a -> b -> b) -> b -> [a] -> bfoldr (\x -> (shows :: Show a => a -> ShowSshows x :: PathComponentx (.) :: (b -> c) -> (a -> b) -> a -> c.)) id :: a -> aid
instance D:Read ::
(Int -> ReadS a)
-> ReadS [a]
-> ReadPrec a
-> ReadPrec [a]
-> T:Read aRead PathComponent where
readsPrec _ = lex0 :: [Char] -> [(PathComponent, [Char])]lex0
where lex0 [] = [] :: [a][]
lex0 ('$':'$':s') = lex0 :: [Char] -> [(PathComponent, [Char])]lex0 ('$'(:) :: a -> [a] -> [a]:s' :: Strings')
lex0 ('$':s') = case [ (Variable :: PathTemplateVariable -> PathComponentVariable var :: PathTemplateVariablevar, s'' :: Strings'')
| (var, s'') <- reads :: Read a => ReadS areads s' :: Strings' ] of
[] -> lex1 :: [Char] -> [Char] -> [(PathComponent, [Char])]lex1 "$" s' :: Strings'
ok -> ok :: [(PathComponent, String)]ok
lex0 s' = lex1 :: [Char] -> [Char] -> [(PathComponent, [Char])]lex1 [] :: [a][] s' :: Strings'
lex1 "" "" = [] :: [a][]
lex1 acc "" = [(Ordinary :: FilePath -> PathComponentOrdinary (reverse :: [a] -> [a]reverse acc :: [Char]acc), "")]
lex1 acc ('$':'$':s) = lex1 :: [Char] -> [Char] -> [(PathComponent, [Char])]lex1 acc :: [Char]acc ('$'(:) :: a -> [a] -> [a]:s :: Strings)
lex1 acc ('$':s) = [(Ordinary :: FilePath -> PathComponentOrdinary (reverse :: [a] -> [a]reverse acc :: [Char]acc), '$'(:) :: a -> [a] -> [a]:s :: Strings)]
lex1 acc (c:s) = lex1 :: [Char] -> [Char] -> [(PathComponent, [Char])]lex1 (c :: Charc(:) :: a -> [a] -> [a]:acc :: [Char]acc) s :: Strings
readList [] = [([] :: [a][],"")]
readList s = [ (component :: PathComponentcomponent(:) :: a -> [a] -> [a]:components :: [PathComponent]components, s'' :: Strings'')
| (component, s') <- reads :: Read a => ReadS areads s :: Strings
, (components, s'') <- readList :: Read a => ReadS [a]readList s' :: Strings' ]
instance D:Show ::
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> T:Show aShow PathTemplate where
show (PathTemplate template) = show :: Show a => a -> Stringshow (show :: Show a => a -> Stringshow template :: [PathComponent]template)
instance D:Read ::
(Int -> ReadS a)
-> ReadS [a]
-> ReadPrec a
-> ReadPrec [a]
-> T:Read aRead PathTemplate where
readsPrec p s = [ (PathTemplate :: [PathComponent] -> PathTemplatePathTemplate template :: [PathComponent]template, s' :: Strings')
| (path, s') <- readsPrec :: Read a => Int -> ReadS areadsPrec p :: Intp s :: Strings
, (template, "") <- reads :: Read a => ReadS areads path :: FilePathpath ]
getWindowsProgramFilesDir :: IO FilePath
getWindowsProgramFilesDir = do
#if mingw32_HOST_OS || mingw32_TARGET_OS
m <- shGetFolderPath csidl_PROGRAM_FILES
#else
let m = Nothing :: Maybe aNothing
#endif
return :: Monad m => forall a. a -> m areturn (fromMaybe :: a -> Maybe a -> afromMaybe "C:\\Program Files" m :: Maybe am)
#if mingw32_HOST_OS || mingw32_TARGET_OS
shGetFolderPath :: CInt -> IO (Maybe FilePath)
shGetFolderPath n =
# if __HUGS__
return Nothing
# else
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
# endif
csidl_PROGRAM_FILES :: CInt
csidl_PROGRAM_FILES = 0x0026
foreign import stdcall unsafe "shlobj.h SHGetFolderPathW"
c_SHGetFolderPath :: Ptr ()
-> CInt
-> Ptr ()
-> CInt
-> CWString
-> IO CInt
#endif
#if !(__HUGS__ || __GLASGOW_HASKELL__ > 606)
dropDrive :: FilePath -> FilePath
dropDrive (c:cs) | isPathSeparator c = cs
dropDrive (_:':':c:cs) | isWindows
&& isPathSeparator c = cs
dropDrive (_:':':cs) | isWindows = cs
dropDrive cs = cs
isWindows :: Bool
isWindows = case buildOS of
Windows -> True
_ -> False
#endif