Support GHC 9.12
[cabal.git] / Cabal / src / Distribution / Simple / InstallDirs / Internal.hs
blob9c411b7dcc15740cbb458c14d821f4e67a0d9e8c
1 {-# LANGUAGE DeriveDataTypeable #-}
2 {-# LANGUAGE DeriveGeneric #-}
4 module Distribution.Simple.InstallDirs.Internal
5 ( PathComponent (..)
6 , PathTemplateVariable (..)
7 ) where
9 import Distribution.Compat.Prelude
10 import Prelude ()
12 data PathComponent
13 = Ordinary FilePath
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
22 PrefixVar
23 | -- | The @$bindir@ path variable
24 BindirVar
25 | -- | The @$libdir@ path variable
26 LibdirVar
27 | -- | The @$libsubdir@ path variable
28 LibsubdirVar
29 | -- | The @$dynlibdir@ path variable
30 DynlibdirVar
31 | -- | The @$datadir@ path variable
32 DatadirVar
33 | -- | The @$datasubdir@ path variable
34 DatasubdirVar
35 | -- | The @$docdir@ path variable
36 DocdirVar
37 | -- | The @$htmldir@ path variable
38 HtmldirVar
39 | -- | The @$pkg@ package name path variable
40 PkgNameVar
41 | -- | The @$version@ package version path variable
42 PkgVerVar
43 | -- | The @$pkgid@ package Id path variable, eg @foo-1.0@
44 PkgIdVar
45 | -- | The @$libname@ path variable
46 LibNameVar
47 | -- | The compiler name and version, eg @ghc-6.6.1@
48 CompilerVar
49 | -- | The operating system name, eg @windows@ or @linux@
50 OSVar
51 | -- | The CPU architecture name, eg @i386@ or @x86_64@
52 ArchVar
53 | -- | The compiler's ABI identifier,
54 AbiVar
55 | --- $arch-$os-$compiler-$abitag
57 -- | The optional ABI tag for the compiler
58 AbiTagVar
59 | -- | The executable name; used in shell wrappers
60 ExecutableNameVar
61 | -- | The name of the test suite being run
62 TestSuiteNameVar
63 | -- | The result of the test suite being run, eg
64 -- @pass@, @fail@, or @error@.
65 TestSuiteResultVar
66 | -- | The name of the benchmark being run
67 BenchmarkNameVar
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"
88 show OSVar = "os"
89 show ArchVar = "arch"
90 show AbiTagVar = "abitag"
91 show AbiVar = "abi"
92 show ExecutableNameVar = "executablename"
93 show TestSuiteNameVar = "test-suite"
94 show TestSuiteResultVar = "result"
95 show BenchmarkNameVar = "benchmark"
97 instance Read PathTemplateVariable where
98 readsPrec _ s =
99 take
101 [ (var, drop (length varStr) s)
102 | (varStr, var) <- vars
103 , varStr `isPrefixOf` s
105 where
106 -- NB: order matters! Longer strings first
107 vars =
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)
123 , ("os", OSVar)
124 , ("arch", ArchVar)
125 , ("abitag", AbiTagVar)
126 , ("abi", AbiVar)
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
140 readsPrec _ = lex0
141 where
142 lex0 [] = []
143 lex0 ('$' : '$' : s') = lex0 ('$' : s')
144 lex0 ('$' : s') = case [ (Variable var, s'')
145 | (var, s'') <- reads s'
146 ] of
147 [] -> lex1 "$" s'
148 ok -> ok
149 lex0 s' = lex1 [] s'
150 lex1 "" "" = []
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 [] = [([], "")]
156 readList s =
157 [ (component : components, s'')
158 | (component, s') <- reads s
159 , (components, s'') <- readList s'