1 {-# LANGUAGE DeriveDataTypeable #-}
2 {-# LANGUAGE DeriveGeneric #-}
4 module Distribution
.Simple
.InstallDirs
.Internal
6 , PathTemplateVariable
(..)
9 import Distribution
.Compat
.Prelude
14 | Variable PathTemplateVariable
15 deriving (Eq
, Ord
, Generic
, Typeable
)
17 instance Binary PathComponent
18 instance Structured PathComponent
20 data PathTemplateVariable
21 = -- | The @$prefix@ path variable
23 |
-- | The @$bindir@ path variable
25 |
-- | The @$libdir@ path variable
27 |
-- | The @$libsubdir@ path variable
29 |
-- | The @$dynlibdir@ path variable
31 |
-- | The @$datadir@ path variable
33 |
-- | The @$datasubdir@ path variable
35 |
-- | The @$docdir@ path variable
37 |
-- | The @$htmldir@ path variable
39 |
-- | The @$pkg@ package name path variable
41 |
-- | The @$version@ package version path variable
43 |
-- | The @$pkgid@ package Id path variable, eg @foo-1.0@
45 |
-- | The @$libname@ path variable
47 |
-- | The compiler name and version, eg @ghc-6.6.1@
49 |
-- | The operating system name, eg @windows@ or @linux@
51 |
-- | The CPU architecture name, eg @i386@ or @x86_64@
53 |
-- | The compiler's ABI identifier,
55 |
--- $arch-$os-$compiler-$abitag
57 -- | The optional ABI tag for the compiler
59 |
-- | The executable name; used in shell wrappers
61 |
-- | The name of the test suite being run
63 |
-- | The result of the test suite being run, eg
64 -- @pass@, @fail@, or @error@.
66 |
-- | The name of the benchmark being run
68 deriving (Eq
, Ord
, Generic
, Typeable
)
70 instance Binary PathTemplateVariable
71 instance Structured PathTemplateVariable
73 instance Show PathTemplateVariable
where
74 show PrefixVar
= "prefix"
75 show LibNameVar
= "libname"
76 show BindirVar
= "bindir"
77 show LibdirVar
= "libdir"
78 show LibsubdirVar
= "libsubdir"
79 show DynlibdirVar
= "dynlibdir"
80 show DatadirVar
= "datadir"
81 show DatasubdirVar
= "datasubdir"
82 show DocdirVar
= "docdir"
83 show HtmldirVar
= "htmldir"
84 show PkgNameVar
= "pkg"
85 show PkgVerVar
= "version"
86 show PkgIdVar
= "pkgid"
87 show CompilerVar
= "compiler"
90 show AbiTagVar
= "abitag"
92 show ExecutableNameVar
= "executablename"
93 show TestSuiteNameVar
= "test-suite"
94 show TestSuiteResultVar
= "result"
95 show BenchmarkNameVar
= "benchmark"
97 instance Read PathTemplateVariable
where
101 [ (var
, drop (length varStr
) s
)
102 |
(varStr
, var
) <- vars
103 , varStr `
isPrefixOf` s
106 -- NB: order matters! Longer strings first
108 [ ("prefix", PrefixVar
)
109 , ("bindir", BindirVar
)
110 , ("libdir", LibdirVar
)
111 , ("libsubdir", LibsubdirVar
)
112 , ("dynlibdir", DynlibdirVar
)
113 , ("datadir", DatadirVar
)
114 , ("datasubdir", DatasubdirVar
)
115 , ("docdir", DocdirVar
)
116 , ("htmldir", HtmldirVar
)
117 , ("pkgid", PkgIdVar
)
118 , ("libname", LibNameVar
)
119 , ("pkgkey", LibNameVar
) -- backwards compatibility
120 , ("pkg", PkgNameVar
)
121 , ("version", PkgVerVar
)
122 , ("compiler", CompilerVar
)
125 , ("abitag", AbiTagVar
)
127 , ("executablename", ExecutableNameVar
)
128 , ("test-suite", TestSuiteNameVar
)
129 , ("result", TestSuiteResultVar
)
130 , ("benchmark", BenchmarkNameVar
)
133 instance Show PathComponent
where
134 show (Ordinary path
) = path
135 show (Variable var
) = '$' : show var
136 showList = foldr (\x
-> (shows x
.)) id
138 instance Read PathComponent
where
139 -- for some reason we collapse multiple $ symbols here
143 lex0
('$' : '$' : s
') = lex0
('$' : s
')
144 lex0
('$' : s
') = case [ (Variable var
, s
'')
145 |
(var
, s
'') <- reads s
'
151 lex1 acc
"" = [(Ordinary
(reverse acc
), "")]
152 lex1 acc
('$' : '$' : s
) = lex1 acc
('$' : s
)
153 lex1 acc
('$' : s
) = [(Ordinary
(reverse acc
), '$' : s
)]
154 lex1 acc
(c
: s
) = lex1
(c
: acc
) s
155 readList [] = [([], "")]
157 [ (component
: components
, s
'')
158 |
(component
, s
') <- reads s
159 , (components
, s
'') <- readList s
'