{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# 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 Prelude ()
import Distribution.Compat.Prelude
import Distribution.Compat.Environment (lookupEnv)
import Distribution.Pretty
import Distribution.Package
import Distribution.System
import Distribution.Compiler
import Distribution.Simple.InstallDirs.Internal
import System.Directory (getAppUserDataDirectory)
import System.FilePath
( (</>), isPathSeparator
, pathSeparator, dropDrive
, takeDirectory )
#ifdef mingw32_HOST_OS
import qualified Prelude
import Foreign
import Foreign.C
#endif
data InstallDirs dir = InstallDirs {
InstallDirs dir -> dir
prefix :: dir,
InstallDirs dir -> dir
bindir :: dir,
InstallDirs dir -> dir
libdir :: dir,
InstallDirs dir -> dir
libsubdir :: dir,
InstallDirs dir -> dir
dynlibdir :: dir,
InstallDirs dir -> dir
flibdir :: dir,
InstallDirs dir -> dir
libexecdir :: dir,
InstallDirs dir -> dir
libexecsubdir:: dir,
InstallDirs dir -> dir
includedir :: dir,
InstallDirs dir -> dir
datadir :: dir,
InstallDirs dir -> dir
datasubdir :: dir,
InstallDirs dir -> dir
docdir :: dir,
InstallDirs dir -> dir
mandir :: dir,
InstallDirs dir -> dir
htmldir :: dir,
InstallDirs dir -> dir
haddockdir :: 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
/= :: InstallDirs dir -> InstallDirs dir -> Bool
$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
Evidence bound by a type signature of the constraint type Eq dir
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
readListPrec :: ReadPrec [InstallDirs dir]
$creadListPrec :: forall dir. Read dir => ReadPrec [InstallDirs dir]
readPrec :: ReadPrec (InstallDirs dir)
$creadPrec :: forall dir. Read dir => ReadPrec (InstallDirs dir)
readList :: ReadS [InstallDirs dir]
$creadList :: forall dir. Read dir => ReadS [InstallDirs dir]
readsPrec :: Int -> ReadS (InstallDirs dir)
$creadsPrec :: forall dir. Read dir => Int -> ReadS (InstallDirs dir)
External instance of the constraint type Monad ReadPrec
External instance of the constraint type Monad ReadPrec
Instance of class: Read of the constraint type forall dir. Read dir => Read (InstallDirs dir)
Evidence bound by a type signature of the constraint type Read dir
Read, Int -> InstallDirs dir -> ShowS
[InstallDirs dir] -> ShowS
InstallDirs dir -> FilePath
(Int -> InstallDirs dir -> ShowS)
-> (InstallDirs dir -> FilePath)
-> ([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 -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [InstallDirs dir] -> ShowS
$cshowList :: forall dir. Show dir => [InstallDirs dir] -> ShowS
show :: InstallDirs dir -> FilePath
$cshow :: forall dir. Show dir => InstallDirs dir -> FilePath
showsPrec :: Int -> InstallDirs dir -> ShowS
$cshowsPrec :: forall dir. Show dir => Int -> InstallDirs dir -> ShowS
External instance of the constraint type Ord Int
Evidence bound by a type signature of the constraint type Show dir
Show, a -> InstallDirs b -> InstallDirs a
(a -> b) -> InstallDirs a -> InstallDirs b
(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
<$ :: a -> InstallDirs b -> InstallDirs a
$c<$ :: forall a b. a -> InstallDirs b -> InstallDirs a
fmap :: (a -> b) -> InstallDirs a -> InstallDirs b
$cfmap :: forall a b. (a -> b) -> InstallDirs a -> InstallDirs b
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
$cto :: forall dir x. Rep (InstallDirs dir) x -> InstallDirs dir
$cfrom :: forall dir x. InstallDirs dir -> Rep (InstallDirs dir) x
Generic, Typeable)
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
External instance of the constraint type forall (f :: * -> *) i (c :: Meta). GMonoid f => GMonoid (M1 i c f)
External instance of the constraint type forall (f :: * -> *) i (c :: Meta). GMonoid f => GMonoid (M1 i c f)
External instance of the constraint type forall (f :: * -> *) (g :: * -> *).
(GMonoid f, GMonoid g) =>
GMonoid (f :*: g)
External instance of the constraint type forall (f :: * -> *) (g :: * -> *).
(GMonoid f, GMonoid g) =>
GMonoid (f :*: g)
External instance of the constraint type forall (f :: * -> *) (g :: * -> *).
(GMonoid f, GMonoid g) =>
GMonoid (f :*: g)
External instance of the constraint type forall (f :: * -> *) (g :: * -> *).
(GMonoid f, GMonoid g) =>
GMonoid (f :*: g)
External instance of the constraint type forall (f :: * -> *) i (c :: Meta). GMonoid f => GMonoid (M1 i c f)
External instance of the constraint type forall a i. (Semigroup a, Monoid a) => GMonoid (K1 i a)
Evidence bound by a type signature of the constraint type Semigroup dir
Evidence bound by a type signature of the constraint type Monoid dir
External instance of the constraint type forall (f :: * -> *) i (c :: Meta). GMonoid f => GMonoid (M1 i c f)
External instance of the constraint type forall a i. (Semigroup a, Monoid a) => GMonoid (K1 i a)
Evidence bound by a type signature of the constraint type Semigroup dir
Evidence bound by a type signature of the constraint type Monoid dir
External instance of the constraint type forall (f :: * -> *) (g :: * -> *).
(GMonoid f, GMonoid g) =>
GMonoid (f :*: g)
External instance of the constraint type forall (f :: * -> *) i (c :: Meta). GMonoid f => GMonoid (M1 i c f)
External instance of the constraint type forall a i. (Semigroup a, Monoid a) => GMonoid (K1 i a)
Evidence bound by a type signature of the constraint type Semigroup dir
Evidence bound by a type signature of the constraint type Monoid dir
External instance of the constraint type forall (f :: * -> *) i (c :: Meta). GMonoid f => GMonoid (M1 i c f)
External instance of the constraint type forall a i. (Semigroup a, Monoid a) => GMonoid (K1 i a)
Evidence bound by a type signature of the constraint type Semigroup dir
Evidence bound by a type signature of the constraint type Monoid dir
External instance of the constraint type forall (f :: * -> *) (g :: * -> *).
(GMonoid f, GMonoid g) =>
GMonoid (f :*: g)
External instance of the constraint type forall (f :: * -> *) (g :: * -> *).
(GMonoid f, GMonoid g) =>
GMonoid (f :*: g)
External instance of the constraint type forall (f :: * -> *) i (c :: Meta). GMonoid f => GMonoid (M1 i c f)
External instance of the constraint type forall a i. (Semigroup a, Monoid a) => GMonoid (K1 i a)
Evidence bound by a type signature of the constraint type Semigroup dir
Evidence bound by a type signature of the constraint type Monoid dir
External instance of the constraint type forall (f :: * -> *) i (c :: Meta). GMonoid f => GMonoid (M1 i c f)
External instance of the constraint type forall a i. (Semigroup a, Monoid a) => GMonoid (K1 i a)
Evidence bound by a type signature of the constraint type Semigroup dir
Evidence bound by a type signature of the constraint type Monoid dir
External instance of the constraint type forall (f :: * -> *) (g :: * -> *).
(GMonoid f, GMonoid g) =>
GMonoid (f :*: g)
External instance of the constraint type forall (f :: * -> *) i (c :: Meta). GMonoid f => GMonoid (M1 i c f)
External instance of the constraint type forall a i. (Semigroup a, Monoid a) => GMonoid (K1 i a)
Evidence bound by a type signature of the constraint type Semigroup dir
Evidence bound by a type signature of the constraint type Monoid dir
External instance of the constraint type forall (f :: * -> *) i (c :: Meta). GMonoid f => GMonoid (M1 i c f)
External instance of the constraint type forall a i. (Semigroup a, Monoid a) => GMonoid (K1 i a)
Evidence bound by a type signature of the constraint type Semigroup dir
Evidence bound by a type signature of the constraint type Monoid dir
External instance of the constraint type forall (f :: * -> *) (g :: * -> *).
(GMonoid f, GMonoid g) =>
GMonoid (f :*: g)
External instance of the constraint type forall (f :: * -> *) (g :: * -> *).
(GMonoid f, GMonoid g) =>
GMonoid (f :*: g)
External instance of the constraint type forall (f :: * -> *) (g :: * -> *).
(GMonoid f, GMonoid g) =>
GMonoid (f :*: g)
External instance of the constraint type forall (f :: * -> *) i (c :: Meta). GMonoid f => GMonoid (M1 i c f)
External instance of the constraint type forall a i. (Semigroup a, Monoid a) => GMonoid (K1 i a)
Evidence bound by a type signature of the constraint type Semigroup dir
Evidence bound by a type signature of the constraint type Monoid dir
External instance of the constraint type forall (f :: * -> *) i (c :: Meta). GMonoid f => GMonoid (M1 i c f)
External instance of the constraint type forall a i. (Semigroup a, Monoid a) => GMonoid (K1 i a)
Evidence bound by a type signature of the constraint type Semigroup dir
Evidence bound by a type signature of the constraint type Monoid dir
External instance of the constraint type forall (f :: * -> *) (g :: * -> *).
(GMonoid f, GMonoid g) =>
GMonoid (f :*: g)
External instance of the constraint type forall (f :: * -> *) i (c :: Meta). GMonoid f => GMonoid (M1 i c f)
External instance of the constraint type forall a i. (Semigroup a, Monoid a) => GMonoid (K1 i a)
Evidence bound by a type signature of the constraint type Semigroup dir
Evidence bound by a type signature of the constraint type Monoid dir
External instance of the constraint type forall (f :: * -> *) i (c :: Meta). GMonoid f => GMonoid (M1 i c f)
External instance of the constraint type forall a i. (Semigroup a, Monoid a) => GMonoid (K1 i a)
Evidence bound by a type signature of the constraint type Semigroup dir
Evidence bound by a type signature of the constraint type Monoid dir
External instance of the constraint type forall (f :: * -> *) (g :: * -> *).
(GMonoid f, GMonoid g) =>
GMonoid (f :*: g)
External instance of the constraint type forall (f :: * -> *) (g :: * -> *).
(GMonoid f, GMonoid g) =>
GMonoid (f :*: g)
External instance of the constraint type forall (f :: * -> *) i (c :: Meta). GMonoid f => GMonoid (M1 i c f)
External instance of the constraint type forall a i. (Semigroup a, Monoid a) => GMonoid (K1 i a)
Evidence bound by a type signature of the constraint type Semigroup dir
Evidence bound by a type signature of the constraint type Monoid dir
External instance of the constraint type forall (f :: * -> *) i (c :: Meta). GMonoid f => GMonoid (M1 i c f)
External instance of the constraint type forall a i. (Semigroup a, Monoid a) => GMonoid (K1 i a)
Evidence bound by a type signature of the constraint type Semigroup dir
Evidence bound by a type signature of the constraint type Monoid dir
External instance of the constraint type forall (f :: * -> *) (g :: * -> *).
(GMonoid f, GMonoid g) =>
GMonoid (f :*: g)
External instance of the constraint type forall (f :: * -> *) i (c :: Meta). GMonoid f => GMonoid (M1 i c f)
External instance of the constraint type forall a i. (Semigroup a, Monoid a) => GMonoid (K1 i a)
Evidence bound by a type signature of the constraint type Semigroup dir
Evidence bound by a type signature of the constraint type Monoid dir
External instance of the constraint type forall (f :: * -> *) i (c :: Meta). GMonoid f => GMonoid (M1 i c f)
External instance of the constraint type forall a i. (Semigroup a, Monoid a) => GMonoid (K1 i a)
Evidence bound by a type signature of the constraint type Semigroup dir
Evidence bound by a type signature of the constraint type Monoid dir
Instance of class: Generic of the constraint type forall dir. Generic (InstallDirs dir)
gmempty
mappend :: InstallDirs dir -> InstallDirs dir -> InstallDirs dir
mappend = InstallDirs dir -> InstallDirs dir -> InstallDirs dir
forall a. Semigroup a => a -> a -> a
Instance of class: Semigroup of the constraint type forall dir. Semigroup dir => Semigroup (InstallDirs dir)
Evidence bound by a type signature of the constraint type Semigroup dir
(<>)
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
External instance of the constraint type forall (f :: * -> *) i (c :: Meta).
GSemigroup f =>
GSemigroup (M1 i c f)
External instance of the constraint type forall (f :: * -> *) i (c :: Meta).
GSemigroup f =>
GSemigroup (M1 i c f)
External instance of the constraint type forall (f :: * -> *) (g :: * -> *).
(GSemigroup f, GSemigroup g) =>
GSemigroup (f :*: g)
External instance of the constraint type forall (f :: * -> *) (g :: * -> *).
(GSemigroup f, GSemigroup g) =>
GSemigroup (f :*: g)
External instance of the constraint type forall (f :: * -> *) (g :: * -> *).
(GSemigroup f, GSemigroup g) =>
GSemigroup (f :*: g)
External instance of the constraint type forall (f :: * -> *) (g :: * -> *).
(GSemigroup f, GSemigroup g) =>
GSemigroup (f :*: g)
External instance of the constraint type forall (f :: * -> *) i (c :: Meta).
GSemigroup f =>
GSemigroup (M1 i c f)
External instance of the constraint type forall a i. Semigroup a => GSemigroup (K1 i a)
Evidence bound by a type signature of the constraint type Semigroup dir
External instance of the constraint type forall (f :: * -> *) i (c :: Meta).
GSemigroup f =>
GSemigroup (M1 i c f)
External instance of the constraint type forall a i. Semigroup a => GSemigroup (K1 i a)
Evidence bound by a type signature of the constraint type Semigroup dir
External instance of the constraint type forall (f :: * -> *) (g :: * -> *).
(GSemigroup f, GSemigroup g) =>
GSemigroup (f :*: g)
External instance of the constraint type forall (f :: * -> *) i (c :: Meta).
GSemigroup f =>
GSemigroup (M1 i c f)
External instance of the constraint type forall a i. Semigroup a => GSemigroup (K1 i a)
Evidence bound by a type signature of the constraint type Semigroup dir
External instance of the constraint type forall (f :: * -> *) i (c :: Meta).
GSemigroup f =>
GSemigroup (M1 i c f)
External instance of the constraint type forall a i. Semigroup a => GSemigroup (K1 i a)
Evidence bound by a type signature of the constraint type Semigroup dir
External instance of the constraint type forall (f :: * -> *) (g :: * -> *).
(GSemigroup f, GSemigroup g) =>
GSemigroup (f :*: g)
External instance of the constraint type forall (f :: * -> *) (g :: * -> *).
(GSemigroup f, GSemigroup g) =>
GSemigroup (f :*: g)
External instance of the constraint type forall (f :: * -> *) i (c :: Meta).
GSemigroup f =>
GSemigroup (M1 i c f)
External instance of the constraint type forall a i. Semigroup a => GSemigroup (K1 i a)
Evidence bound by a type signature of the constraint type Semigroup dir
External instance of the constraint type forall (f :: * -> *) i (c :: Meta).
GSemigroup f =>
GSemigroup (M1 i c f)
External instance of the constraint type forall a i. Semigroup a => GSemigroup (K1 i a)
Evidence bound by a type signature of the constraint type Semigroup dir
External instance of the constraint type forall (f :: * -> *) (g :: * -> *).
(GSemigroup f, GSemigroup g) =>
GSemigroup (f :*: g)
External instance of the constraint type forall (f :: * -> *) i (c :: Meta).
GSemigroup f =>
GSemigroup (M1 i c f)
External instance of the constraint type forall a i. Semigroup a => GSemigroup (K1 i a)
Evidence bound by a type signature of the constraint type Semigroup dir
External instance of the constraint type forall (f :: * -> *) i (c :: Meta).
GSemigroup f =>
GSemigroup (M1 i c f)
External instance of the constraint type forall a i. Semigroup a => GSemigroup (K1 i a)
Evidence bound by a type signature of the constraint type Semigroup dir
External instance of the constraint type forall (f :: * -> *) (g :: * -> *).
(GSemigroup f, GSemigroup g) =>
GSemigroup (f :*: g)
External instance of the constraint type forall (f :: * -> *) (g :: * -> *).
(GSemigroup f, GSemigroup g) =>
GSemigroup (f :*: g)
External instance of the constraint type forall (f :: * -> *) (g :: * -> *).
(GSemigroup f, GSemigroup g) =>
GSemigroup (f :*: g)
External instance of the constraint type forall (f :: * -> *) i (c :: Meta).
GSemigroup f =>
GSemigroup (M1 i c f)
External instance of the constraint type forall a i. Semigroup a => GSemigroup (K1 i a)
Evidence bound by a type signature of the constraint type Semigroup dir
External instance of the constraint type forall (f :: * -> *) i (c :: Meta).
GSemigroup f =>
GSemigroup (M1 i c f)
External instance of the constraint type forall a i. Semigroup a => GSemigroup (K1 i a)
Evidence bound by a type signature of the constraint type Semigroup dir
External instance of the constraint type forall (f :: * -> *) (g :: * -> *).
(GSemigroup f, GSemigroup g) =>
GSemigroup (f :*: g)
External instance of the constraint type forall (f :: * -> *) i (c :: Meta).
GSemigroup f =>
GSemigroup (M1 i c f)
External instance of the constraint type forall a i. Semigroup a => GSemigroup (K1 i a)
Evidence bound by a type signature of the constraint type Semigroup dir
External instance of the constraint type forall (f :: * -> *) i (c :: Meta).
GSemigroup f =>
GSemigroup (M1 i c f)
External instance of the constraint type forall a i. Semigroup a => GSemigroup (K1 i a)
Evidence bound by a type signature of the constraint type Semigroup dir
External instance of the constraint type forall (f :: * -> *) (g :: * -> *).
(GSemigroup f, GSemigroup g) =>
GSemigroup (f :*: g)
External instance of the constraint type forall (f :: * -> *) (g :: * -> *).
(GSemigroup f, GSemigroup g) =>
GSemigroup (f :*: g)
External instance of the constraint type forall (f :: * -> *) i (c :: Meta).
GSemigroup f =>
GSemigroup (M1 i c f)
External instance of the constraint type forall a i. Semigroup a => GSemigroup (K1 i a)
Evidence bound by a type signature of the constraint type Semigroup dir
External instance of the constraint type forall (f :: * -> *) i (c :: Meta).
GSemigroup f =>
GSemigroup (M1 i c f)
External instance of the constraint type forall a i. Semigroup a => GSemigroup (K1 i a)
Evidence bound by a type signature of the constraint type Semigroup dir
External instance of the constraint type forall (f :: * -> *) (g :: * -> *).
(GSemigroup f, GSemigroup g) =>
GSemigroup (f :*: g)
External instance of the constraint type forall (f :: * -> *) i (c :: Meta).
GSemigroup f =>
GSemigroup (M1 i c f)
External instance of the constraint type forall a i. Semigroup a => GSemigroup (K1 i a)
Evidence bound by a type signature of the constraint type Semigroup dir
External instance of the constraint type forall (f :: * -> *) i (c :: Meta).
GSemigroup f =>
GSemigroup (M1 i c f)
External instance of the constraint type forall a i. Semigroup a => GSemigroup (K1 i a)
Evidence bound by a type signature of the constraint type Semigroup dir
Instance of class: Generic of the constraint type forall dir. Generic (InstallDirs dir)
gmappend
combineInstallDirs :: (a -> b -> c)
-> InstallDirs a
-> InstallDirs b
-> InstallDirs c
combineInstallDirs :: (a -> b -> c) -> InstallDirs a -> InstallDirs b -> InstallDirs c
combineInstallDirs a -> b -> c
combine InstallDirs a
a InstallDirs b
b = InstallDirs :: forall dir.
dir
-> dir
-> dir
-> dir
-> dir
-> dir
-> dir
-> dir
-> dir
-> dir
-> dir
-> dir
-> dir
-> dir
-> dir
-> dir
-> InstallDirs dir
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 :: (a -> a -> a) -> InstallDirs a -> InstallDirs a
appendSubdirs a -> a -> a
append InstallDirs a
dirs = InstallDirs a
dirs {
libdir :: a
libdir = InstallDirs a -> a
forall dir. InstallDirs dir -> dir
libdir InstallDirs a
dirs a -> a -> a
`append` InstallDirs a -> a
forall dir. InstallDirs dir -> dir
libsubdir InstallDirs a
dirs,
libexecdir :: a
libexecdir = InstallDirs a -> a
forall dir. InstallDirs dir -> dir
libexecdir InstallDirs a
dirs a -> a -> a
`append` InstallDirs a -> a
forall dir. InstallDirs dir -> dir
libexecsubdir InstallDirs a
dirs,
datadir :: a
datadir = InstallDirs a -> a
forall dir. InstallDirs dir -> dir
datadir InstallDirs a
dirs a -> a -> a
`append` InstallDirs a -> a
forall dir. InstallDirs dir -> dir
datasubdir InstallDirs a
dirs,
libsubdir :: a
libsubdir = FilePath -> a
forall a. HasCallStack => FilePath -> a
error FilePath
"internal error InstallDirs.libsubdir",
libexecsubdir :: a
libexecsubdir = FilePath -> a
forall a. HasCallStack => FilePath -> a
error FilePath
"internal error InstallDirs.libexecsubdir",
datasubdir :: a
datasubdir = FilePath -> a
forall a. HasCallStack => FilePath -> a
error FilePath
"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
InstallDirTemplates
dflt <- Bool -> CompilerFlavor -> Bool -> Bool -> IO InstallDirTemplates
defaultInstallDirs' Bool
False CompilerFlavor
comp Bool
userInstall Bool
hasLibs
InstallDirTemplates -> IO InstallDirTemplates
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return InstallDirTemplates
dflt { datasubdir :: PathTemplate
datasubdir = FilePath -> PathTemplate
toPathTemplate (FilePath -> PathTemplate) -> FilePath -> PathTemplate
forall a b. (a -> b) -> a -> b
$ FilePath
"$abi" FilePath -> ShowS
</> FilePath
"$libname",
docdir :: PathTemplate
docdir = FilePath -> PathTemplate
toPathTemplate (FilePath -> PathTemplate) -> FilePath -> PathTemplate
forall a b. (a -> b) -> a -> b
$ FilePath
"$datadir" FilePath -> ShowS
</> FilePath
"doc" FilePath -> ShowS
</> FilePath
"$abi" FilePath -> ShowS
</> FilePath
"$libname"
}
defaultInstallDirs' Bool
False CompilerFlavor
comp Bool
userInstall Bool
_hasLibs = do
FilePath
installPrefix <-
if Bool
userInstall
then do
Maybe FilePath
mDir <- FilePath -> IO (Maybe FilePath)
lookupEnv FilePath
"CABAL_DIR"
case Maybe FilePath
mDir of
Maybe FilePath
Nothing -> FilePath -> IO FilePath
getAppUserDataDirectory FilePath
"cabal"
Just FilePath
dir -> FilePath -> IO FilePath
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return FilePath
dir
else case OS
buildOS of
OS
Windows -> do FilePath
windowsProgramFilesDir <- IO FilePath
getWindowsProgramFilesDir
FilePath -> IO FilePath
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return (FilePath
windowsProgramFilesDir FilePath -> ShowS
</> FilePath
"Haskell")
OS
_ -> FilePath -> IO FilePath
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return FilePath
"/usr/local"
FilePath
installLibDir <-
case OS
buildOS of
OS
Windows -> FilePath -> IO FilePath
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return FilePath
"$prefix"
OS
_ -> FilePath -> IO FilePath
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return (FilePath
"$prefix" FilePath -> ShowS
</> FilePath
"lib")
InstallDirTemplates -> IO InstallDirTemplates
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return (InstallDirTemplates -> IO InstallDirTemplates)
-> InstallDirTemplates -> IO InstallDirTemplates
forall a b. (a -> b) -> a -> b
$ (FilePath -> PathTemplate)
-> InstallDirs FilePath -> InstallDirTemplates
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Instance of class: Functor of the constraint type Functor InstallDirs
fmap FilePath -> PathTemplate
toPathTemplate (InstallDirs FilePath -> InstallDirTemplates)
-> InstallDirs FilePath -> InstallDirTemplates
forall a b. (a -> b) -> a -> b
$ InstallDirs :: forall dir.
dir
-> dir
-> dir
-> dir
-> dir
-> dir
-> dir
-> dir
-> dir
-> dir
-> dir
-> dir
-> dir
-> dir
-> dir
-> dir
-> InstallDirs dir
InstallDirs {
prefix :: FilePath
prefix = FilePath
installPrefix,
bindir :: FilePath
bindir = FilePath
"$prefix" FilePath -> ShowS
</> FilePath
"bin",
libdir :: FilePath
libdir = FilePath
installLibDir,
libsubdir :: FilePath
libsubdir = case CompilerFlavor
comp of
CompilerFlavor
UHC -> FilePath
"$pkgid"
CompilerFlavor
_other -> FilePath
"$abi" FilePath -> ShowS
</> FilePath
"$libname",
dynlibdir :: FilePath
dynlibdir = FilePath
"$libdir" FilePath -> ShowS
</> case CompilerFlavor
comp of
CompilerFlavor
UHC -> FilePath
"$pkgid"
CompilerFlavor
_other -> FilePath
"$abi",
libexecsubdir :: FilePath
libexecsubdir= FilePath
"$abi" FilePath -> ShowS
</> FilePath
"$pkgid",
flibdir :: FilePath
flibdir = FilePath
"$libdir",
libexecdir :: FilePath
libexecdir = case OS
buildOS of
OS
Windows -> FilePath
"$prefix" FilePath -> ShowS
</> FilePath
"$libname"
OS
_other -> FilePath
"$prefix" FilePath -> ShowS
</> FilePath
"libexec",
includedir :: FilePath
includedir = FilePath
"$libdir" FilePath -> ShowS
</> FilePath
"$libsubdir" FilePath -> ShowS
</> FilePath
"include",
datadir :: FilePath
datadir = case OS
buildOS of
OS
Windows -> FilePath
"$prefix"
OS
_other -> FilePath
"$prefix" FilePath -> ShowS
</> FilePath
"share",
datasubdir :: FilePath
datasubdir = FilePath
"$abi" FilePath -> ShowS
</> FilePath
"$pkgid",
docdir :: FilePath
docdir = FilePath
"$datadir" FilePath -> ShowS
</> FilePath
"doc" FilePath -> ShowS
</> FilePath
"$abi" FilePath -> ShowS
</> FilePath
"$pkgid",
mandir :: FilePath
mandir = FilePath
"$datadir" FilePath -> ShowS
</> FilePath
"man",
htmldir :: FilePath
htmldir = FilePath
"$docdir" FilePath -> ShowS
</> FilePath
"html",
haddockdir :: FilePath
haddockdir = FilePath
"$htmldir",
sysconfdir :: FilePath
sysconfdir = FilePath
"$prefix" FilePath -> ShowS
</> FilePath
"etc"
}
substituteInstallDirTemplates :: PathTemplateEnv
-> InstallDirTemplates -> InstallDirTemplates
substituteInstallDirTemplates :: PathTemplateEnv -> InstallDirTemplates -> InstallDirTemplates
substituteInstallDirTemplates PathTemplateEnv
env InstallDirTemplates
dirs = InstallDirTemplates
dirs'
where
dirs' :: InstallDirTemplates
dirs' = InstallDirs :: forall dir.
dir
-> dir
-> dir
-> dir
-> dir
-> dir
-> dir
-> dir
-> dir
-> dir
-> dir
-> dir
-> dir
-> dir
-> dir
-> dir
-> InstallDirs dir
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 FilePath
absoluteInstallDirs PackageIdentifier
pkgId UnitId
libname CompilerInfo
compilerId CopyDest
copydest Platform
platform InstallDirTemplates
dirs =
(case CopyDest
copydest of
CopyTo FilePath
destdir -> ShowS -> InstallDirs FilePath -> InstallDirs FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Instance of class: Functor of the constraint type Functor InstallDirs
fmap ((FilePath
destdir FilePath -> ShowS
</>) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShowS
dropDrive)
CopyToDb FilePath
dbdir -> ShowS -> InstallDirs FilePath -> InstallDirs FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Instance of class: Functor of the constraint type Functor InstallDirs
fmap (FilePath -> FilePath -> ShowS
forall {a}. Eq a => [a] -> [a] -> [a] -> [a]
External instance of the constraint type Eq Char
substPrefix FilePath
"${pkgroot}" (ShowS
takeDirectory FilePath
dbdir))
CopyDest
_ -> InstallDirs FilePath -> InstallDirs FilePath
forall a. a -> a
id)
(InstallDirs FilePath -> InstallDirs FilePath)
-> (InstallDirTemplates -> InstallDirs FilePath)
-> InstallDirTemplates
-> InstallDirs FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FilePath -> ShowS) -> InstallDirs FilePath -> InstallDirs FilePath
forall a. (a -> a -> a) -> InstallDirs a -> InstallDirs a
appendSubdirs FilePath -> ShowS
(</>)
(InstallDirs FilePath -> InstallDirs FilePath)
-> (InstallDirTemplates -> InstallDirs FilePath)
-> InstallDirTemplates
-> InstallDirs FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (PathTemplate -> FilePath)
-> InstallDirTemplates -> InstallDirs FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Instance of class: Functor of the constraint type Functor InstallDirs
fmap PathTemplate -> FilePath
fromPathTemplate
(InstallDirTemplates -> InstallDirs FilePath)
-> InstallDirTemplates -> InstallDirs FilePath
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
Evidence bound by a type signature of the constraint type Eq a
`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 (t :: * -> *) a. Foldable t => t a -> Int
External instance of the constraint type Foldable []
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
/= :: CopyDest -> CopyDest -> Bool
$c/= :: CopyDest -> CopyDest -> Bool
== :: CopyDest -> CopyDest -> Bool
$c== :: CopyDest -> CopyDest -> Bool
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq Char
External instance of the constraint type Eq Char
Eq, Int -> CopyDest -> ShowS
[CopyDest] -> ShowS
CopyDest -> FilePath
(Int -> CopyDest -> ShowS)
-> (CopyDest -> FilePath) -> ([CopyDest] -> ShowS) -> Show CopyDest
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [CopyDest] -> ShowS
$cshowList :: [CopyDest] -> ShowS
show :: CopyDest -> FilePath
$cshow :: CopyDest -> FilePath
showsPrec :: Int -> CopyDest -> ShowS
$cshowsPrec :: Int -> CopyDest -> ShowS
External instance of the constraint type Ord Int
External instance of the constraint type Ord Int
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type Show Char
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
$cto :: forall x. Rep CopyDest x -> CopyDest
$cfrom :: forall x. CopyDest -> Rep CopyDest x
Generic)
instance Binary CopyDest
prefixRelativeInstallDirs :: PackageIdentifier
-> UnitId
-> CompilerInfo
-> Platform
-> InstallDirTemplates
-> InstallDirs (Maybe FilePath)
prefixRelativeInstallDirs :: PackageIdentifier
-> UnitId
-> CompilerInfo
-> Platform
-> InstallDirTemplates
-> InstallDirs (Maybe FilePath)
prefixRelativeInstallDirs PackageIdentifier
pkgId UnitId
libname CompilerInfo
compilerId Platform
platform InstallDirTemplates
dirs =
(PathTemplate -> Maybe FilePath)
-> InstallDirTemplates -> InstallDirs (Maybe FilePath)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Instance of class: Functor of the constraint type Functor InstallDirs
fmap PathTemplate -> Maybe FilePath
relative
(InstallDirTemplates -> InstallDirs (Maybe FilePath))
-> (InstallDirTemplates -> InstallDirTemplates)
-> InstallDirTemplates
-> InstallDirs (Maybe FilePath)
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 FilePath))
-> InstallDirTemplates -> InstallDirs (Maybe FilePath)
forall a b. (a -> b) -> a -> b
$
PathTemplateEnv -> InstallDirTemplates -> InstallDirTemplates
substituteInstallDirTemplates PathTemplateEnv
env InstallDirTemplates
dirs {
prefix :: PathTemplate
prefix = [PathComponent] -> PathTemplate
PathTemplate [PathTemplateVariable -> PathComponent
Variable PathTemplateVariable
PrefixVar]
}
where
env :: PathTemplateEnv
env = PackageIdentifier
-> UnitId -> CompilerInfo -> Platform -> PathTemplateEnv
initialPathTemplateEnv PackageIdentifier
pkgId UnitId
libname CompilerInfo
compilerId Platform
platform
relative :: PathTemplate -> Maybe FilePath
relative PathTemplate
dir = case PathTemplate
dir of
PathTemplate [PathComponent]
cs -> ([PathComponent] -> FilePath)
-> Maybe [PathComponent] -> Maybe FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Maybe
fmap (PathTemplate -> FilePath
fromPathTemplate (PathTemplate -> FilePath)
-> ([PathComponent] -> PathTemplate) -> [PathComponent] -> FilePath
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:FilePath
rest) : [PathComponent]
rest')
| Char -> Bool
isPathSeparator Char
s = [PathComponent] -> Maybe [PathComponent]
forall a. a -> Maybe a
Just (FilePath -> PathComponent
Ordinary FilePath
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
/= :: PathTemplate -> PathTemplate -> Bool
$c/= :: PathTemplate -> PathTemplate -> Bool
== :: PathTemplate -> PathTemplate -> Bool
$c== :: PathTemplate -> PathTemplate -> Bool
External instance of the constraint type Eq PathComponent
External instance of the constraint type Eq PathComponent
External instance of the constraint type Eq PathComponent
External instance of the constraint type forall a. Eq a => Eq [a]
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
min :: PathTemplate -> PathTemplate -> PathTemplate
$cmin :: PathTemplate -> PathTemplate -> PathTemplate
max :: PathTemplate -> PathTemplate -> PathTemplate
$cmax :: PathTemplate -> PathTemplate -> PathTemplate
>= :: PathTemplate -> PathTemplate -> Bool
$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
compare :: PathTemplate -> PathTemplate -> Ordering
$ccompare :: PathTemplate -> PathTemplate -> Ordering
External instance of the constraint type Ord PathComponent
External instance of the constraint type Ord PathComponent
External instance of the constraint type Ord PathComponent
External instance of the constraint type Ord PathComponent
External instance of the constraint type Ord PathComponent
External instance of the constraint type Ord PathComponent
External instance of the constraint type Ord PathComponent
External instance of the constraint type Ord PathComponent
External instance of the constraint type forall a. Ord a => Ord [a]
Instance of class: Eq of the constraint type Eq PathTemplate
Instance of class: Eq of the constraint type Eq 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
$cto :: forall x. Rep PathTemplate x -> PathTemplate
$cfrom :: forall x. PathTemplate -> Rep PathTemplate x
Generic, Typeable)
instance Binary PathTemplate
instance Structured PathTemplate
type PathTemplateEnv = [(PathTemplateVariable, PathTemplate)]
toPathTemplate :: FilePath -> PathTemplate
toPathTemplate :: FilePath -> PathTemplate
toPathTemplate FilePath
fp = [PathComponent] -> PathTemplate
PathTemplate
([PathComponent] -> PathTemplate)
-> (FilePath -> [PathComponent]) -> FilePath -> PathTemplate
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [PathComponent] -> Maybe [PathComponent] -> [PathComponent]
forall a. a -> Maybe a -> a
fromMaybe (FilePath -> [PathComponent]
forall a. HasCallStack => FilePath -> a
error (FilePath -> [PathComponent]) -> FilePath -> [PathComponent]
forall a b. (a -> b) -> a -> b
$ FilePath
"panic! toPathTemplate " FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ ShowS
forall a. Show a => a -> FilePath
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type Show Char
show FilePath
fp)
(Maybe [PathComponent] -> [PathComponent])
-> (FilePath -> Maybe [PathComponent])
-> FilePath
-> [PathComponent]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> Maybe [PathComponent]
forall a. Read a => FilePath -> Maybe a
External instance of the constraint type forall a. Read a => Read [a]
External instance of the constraint type Read PathComponent
readMaybe
(FilePath -> PathTemplate) -> FilePath -> PathTemplate
forall a b. (a -> b) -> a -> b
$ FilePath
fp
fromPathTemplate :: PathTemplate -> FilePath
fromPathTemplate :: PathTemplate -> FilePath
fromPathTemplate (PathTemplate [PathComponent]
template) = [PathComponent] -> FilePath
forall a. Show a => a -> FilePath
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type Show PathComponent
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]
++ [FilePath -> 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]
External instance of the constraint type Foldable []
concatMap PathComponent -> [PathComponent]
subst [PathComponent]
template)
where subst :: PathComponent -> [PathComponent]
subst component :: PathComponent
component@(Ordinary FilePath
_) = [PathComponent
component]
subst component :: PathComponent
component@(Variable PathTemplateVariable
variable) =
case PathTemplateVariable -> PathTemplateEnv -> Maybe PathTemplate
forall a b. Eq a => a -> [(a, b)] -> Maybe b
External instance of the constraint type Eq PathTemplateVariable
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 [FilePath -> PathComponent
Ordinary (FilePath -> PathComponent) -> FilePath -> PathComponent
forall a b. (a -> b) -> a -> b
$ PackageName -> FilePath
forall a. Pretty a => a -> FilePath
External instance of the constraint type Pretty PackageName
prettyShow (PackageIdentifier -> PackageName
forall pkg. Package pkg => pkg -> PackageName
External instance of the constraint type Package PackageIdentifier
packageName PackageIdentifier
pkgId)])
,(PathTemplateVariable
PkgVerVar, [PathComponent] -> PathTemplate
PathTemplate [FilePath -> PathComponent
Ordinary (FilePath -> PathComponent) -> FilePath -> PathComponent
forall a b. (a -> b) -> a -> b
$ Version -> FilePath
forall a. Pretty a => a -> FilePath
External instance of the constraint type Pretty Version
prettyShow (PackageIdentifier -> Version
forall pkg. Package pkg => pkg -> Version
External instance of the constraint type Package PackageIdentifier
packageVersion PackageIdentifier
pkgId)])
,(PathTemplateVariable
LibNameVar, [PathComponent] -> PathTemplate
PathTemplate [FilePath -> PathComponent
Ordinary (FilePath -> PathComponent) -> FilePath -> PathComponent
forall a b. (a -> b) -> a -> b
$ UnitId -> FilePath
forall a. Pretty a => a -> FilePath
External instance of the constraint type Pretty UnitId
prettyShow UnitId
uid])
,(PathTemplateVariable
PkgIdVar, [PathComponent] -> PathTemplate
PathTemplate [FilePath -> PathComponent
Ordinary (FilePath -> PathComponent) -> FilePath -> PathComponent
forall a b. (a -> b) -> a -> b
$ PackageIdentifier -> FilePath
forall a. Pretty a => a -> FilePath
External instance of the constraint type Pretty PackageIdentifier
prettyShow PackageIdentifier
pkgId])
]
compilerTemplateEnv :: CompilerInfo -> PathTemplateEnv
compilerTemplateEnv :: CompilerInfo -> PathTemplateEnv
compilerTemplateEnv CompilerInfo
compiler =
[(PathTemplateVariable
CompilerVar, [PathComponent] -> PathTemplate
PathTemplate [FilePath -> PathComponent
Ordinary (FilePath -> PathComponent) -> FilePath -> PathComponent
forall a b. (a -> b) -> a -> b
$ CompilerId -> FilePath
forall a. Pretty a => a -> FilePath
External instance of the constraint type Pretty CompilerId
prettyShow (CompilerInfo -> CompilerId
compilerInfoId CompilerInfo
compiler)])
]
platformTemplateEnv :: Platform -> PathTemplateEnv
platformTemplateEnv :: Platform -> PathTemplateEnv
platformTemplateEnv (Platform Arch
arch OS
os) =
[(PathTemplateVariable
OSVar, [PathComponent] -> PathTemplate
PathTemplate [FilePath -> PathComponent
Ordinary (FilePath -> PathComponent) -> FilePath -> PathComponent
forall a b. (a -> b) -> a -> b
$ OS -> FilePath
forall a. Pretty a => a -> FilePath
External instance of the constraint type Pretty OS
prettyShow OS
os])
,(PathTemplateVariable
ArchVar, [PathComponent] -> PathTemplate
PathTemplate [FilePath -> PathComponent
Ordinary (FilePath -> PathComponent) -> FilePath -> PathComponent
forall a b. (a -> b) -> a -> b
$ Arch -> FilePath
forall a. Pretty a => a -> FilePath
External instance of the constraint type Pretty Arch
prettyShow Arch
arch])
]
abiTemplateEnv :: CompilerInfo -> Platform -> PathTemplateEnv
abiTemplateEnv :: CompilerInfo -> Platform -> PathTemplateEnv
abiTemplateEnv CompilerInfo
compiler (Platform Arch
arch OS
os) =
[(PathTemplateVariable
AbiVar, [PathComponent] -> PathTemplate
PathTemplate [FilePath -> PathComponent
Ordinary (FilePath -> PathComponent) -> FilePath -> PathComponent
forall a b. (a -> b) -> a -> b
$ Arch -> FilePath
forall a. Pretty a => a -> FilePath
External instance of the constraint type Pretty Arch
prettyShow Arch
arch FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ Char
'-'Char -> ShowS
forall a. a -> [a] -> [a]
:OS -> FilePath
forall a. Pretty a => a -> FilePath
External instance of the constraint type Pretty OS
prettyShow OS
os FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++
Char
'-'Char -> ShowS
forall a. a -> [a] -> [a]
:CompilerId -> FilePath
forall a. Pretty a => a -> FilePath
External instance of the constraint type Pretty CompilerId
prettyShow (CompilerInfo -> CompilerId
compilerInfoId CompilerInfo
compiler) FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++
case CompilerInfo -> AbiTag
compilerInfoAbiTag CompilerInfo
compiler of
AbiTag
NoAbiTag -> FilePath
""
AbiTag FilePath
tag -> Char
'-'Char -> ShowS
forall a. a -> [a] -> [a]
:FilePath
tag])
,(PathTemplateVariable
AbiTagVar, [PathComponent] -> PathTemplate
PathTemplate [FilePath -> PathComponent
Ordinary (FilePath -> PathComponent) -> FilePath -> PathComponent
forall a b. (a -> b) -> a -> b
$ AbiTag -> FilePath
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 -> FilePath
show (PathTemplate [PathComponent]
template) = ShowS
forall a. Show a => a -> FilePath
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type Show Char
show ([PathComponent] -> FilePath
forall a. Show a => a -> FilePath
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type Show PathComponent
show [PathComponent]
template)
instance Read PathTemplate where
readsPrec :: Int -> ReadS PathTemplate
readsPrec Int
p FilePath
s = [ ([PathComponent] -> PathTemplate
PathTemplate [PathComponent]
template, FilePath
s')
| (FilePath
path, FilePath
s') <- Int -> ReadS FilePath
forall a. Read a => Int -> ReadS a
External instance of the constraint type forall a. Read a => Read [a]
External instance of the constraint type Read Char
readsPrec Int
p FilePath
s
, ([PathComponent]
template, FilePath
"") <- ReadS [PathComponent]
forall a. Read a => ReadS a
External instance of the constraint type forall a. Read a => Read [a]
External instance of the constraint type Read PathComponent
reads FilePath
path ]
getWindowsProgramFilesDir :: NoCallStackIO FilePath
getWindowsProgramFilesDir :: IO FilePath
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
FilePath -> IO FilePath
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return (FilePath -> Maybe FilePath -> FilePath
forall a. a -> Maybe a -> a
fromMaybe FilePath
"C:\\Program Files" Maybe FilePath
forall a. Maybe a
m)
#ifdef mingw32_HOST_OS
shGetFolderPath :: CInt -> NoCallStackIO (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
#ifdef x86_64_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