{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
module Distribution.Simple.InstallDirs.Internal
( PathComponent(..)
, PathTemplateVariable(..)
) where
import Prelude ()
import Distribution.Compat.Prelude
data PathComponent =
Ordinary FilePath
| Variable PathTemplateVariable
deriving (PathComponent -> PathComponent -> Bool
(PathComponent -> PathComponent -> Bool)
-> (PathComponent -> PathComponent -> Bool) -> Eq PathComponent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PathComponent -> PathComponent -> Bool
$c/= :: PathComponent -> PathComponent -> Bool
== :: PathComponent -> PathComponent -> Bool
$c== :: PathComponent -> PathComponent -> Bool
External instance of the constraint type Eq Char
External instance of the constraint type Eq Char
External instance of the constraint type forall a. Eq a => Eq [a]
Instance of class: Eq of the constraint type Eq PathTemplateVariable
Eq, Eq PathComponent
Eq PathComponent
-> (PathComponent -> PathComponent -> Ordering)
-> (PathComponent -> PathComponent -> Bool)
-> (PathComponent -> PathComponent -> Bool)
-> (PathComponent -> PathComponent -> Bool)
-> (PathComponent -> PathComponent -> Bool)
-> (PathComponent -> PathComponent -> PathComponent)
-> (PathComponent -> PathComponent -> PathComponent)
-> Ord PathComponent
PathComponent -> PathComponent -> Bool
PathComponent -> PathComponent -> Ordering
PathComponent -> PathComponent -> PathComponent
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 :: PathComponent -> PathComponent -> PathComponent
$cmin :: PathComponent -> PathComponent -> PathComponent
max :: PathComponent -> PathComponent -> PathComponent
$cmax :: PathComponent -> PathComponent -> PathComponent
>= :: PathComponent -> PathComponent -> Bool
$c>= :: PathComponent -> PathComponent -> Bool
> :: PathComponent -> PathComponent -> Bool
$c> :: PathComponent -> PathComponent -> Bool
<= :: PathComponent -> PathComponent -> Bool
$c<= :: PathComponent -> PathComponent -> Bool
< :: PathComponent -> PathComponent -> Bool
$c< :: PathComponent -> PathComponent -> Bool
compare :: PathComponent -> PathComponent -> Ordering
$ccompare :: PathComponent -> PathComponent -> Ordering
External instance of the constraint type Ord Char
External instance of the constraint type Ord Char
External instance of the constraint type Ord Char
External instance of the constraint type forall a. Ord a => Ord [a]
Instance of class: Eq of the constraint type Eq PathComponent
Instance of class: Ord of the constraint type Ord PathTemplateVariable
Instance of class: Ord of the constraint type Ord PathComponent
Instance of class: Eq of the constraint type Eq PathComponent
Ord, (forall x. PathComponent -> Rep PathComponent x)
-> (forall x. Rep PathComponent x -> PathComponent)
-> Generic PathComponent
forall x. Rep PathComponent x -> PathComponent
forall x. PathComponent -> Rep PathComponent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PathComponent x -> PathComponent
$cfrom :: forall x. PathComponent -> Rep PathComponent x
Generic, Typeable)
instance Binary PathComponent
instance Structured PathComponent
data PathTemplateVariable =
PrefixVar
| BindirVar
| LibdirVar
| LibsubdirVar
| DynlibdirVar
| DatadirVar
| DatasubdirVar
| DocdirVar
| HtmldirVar
| PkgNameVar
| PkgVerVar
| PkgIdVar
| LibNameVar
| CompilerVar
| OSVar
| ArchVar
| AbiVar
| AbiTagVar
| ExecutableNameVar
| TestSuiteNameVar
| TestSuiteResultVar
| BenchmarkNameVar
deriving (PathTemplateVariable -> PathTemplateVariable -> Bool
(PathTemplateVariable -> PathTemplateVariable -> Bool)
-> (PathTemplateVariable -> PathTemplateVariable -> Bool)
-> Eq PathTemplateVariable
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PathTemplateVariable -> PathTemplateVariable -> Bool
$c/= :: PathTemplateVariable -> PathTemplateVariable -> Bool
== :: PathTemplateVariable -> PathTemplateVariable -> Bool
$c== :: PathTemplateVariable -> PathTemplateVariable -> Bool
Eq, Eq PathTemplateVariable
Eq PathTemplateVariable
-> (PathTemplateVariable -> PathTemplateVariable -> Ordering)
-> (PathTemplateVariable -> PathTemplateVariable -> Bool)
-> (PathTemplateVariable -> PathTemplateVariable -> Bool)
-> (PathTemplateVariable -> PathTemplateVariable -> Bool)
-> (PathTemplateVariable -> PathTemplateVariable -> Bool)
-> (PathTemplateVariable
-> PathTemplateVariable -> PathTemplateVariable)
-> (PathTemplateVariable
-> PathTemplateVariable -> PathTemplateVariable)
-> Ord PathTemplateVariable
PathTemplateVariable -> PathTemplateVariable -> Bool
PathTemplateVariable -> PathTemplateVariable -> Ordering
PathTemplateVariable
-> PathTemplateVariable -> PathTemplateVariable
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 :: PathTemplateVariable
-> PathTemplateVariable -> PathTemplateVariable
$cmin :: PathTemplateVariable
-> PathTemplateVariable -> PathTemplateVariable
max :: PathTemplateVariable
-> PathTemplateVariable -> PathTemplateVariable
$cmax :: PathTemplateVariable
-> PathTemplateVariable -> PathTemplateVariable
>= :: PathTemplateVariable -> PathTemplateVariable -> Bool
$c>= :: PathTemplateVariable -> PathTemplateVariable -> Bool
> :: PathTemplateVariable -> PathTemplateVariable -> Bool
$c> :: PathTemplateVariable -> PathTemplateVariable -> Bool
<= :: PathTemplateVariable -> PathTemplateVariable -> Bool
$c<= :: PathTemplateVariable -> PathTemplateVariable -> Bool
< :: PathTemplateVariable -> PathTemplateVariable -> Bool
$c< :: PathTemplateVariable -> PathTemplateVariable -> Bool
compare :: PathTemplateVariable -> PathTemplateVariable -> Ordering
$ccompare :: PathTemplateVariable -> PathTemplateVariable -> Ordering
Instance of class: Eq of the constraint type Eq PathTemplateVariable
Instance of class: Ord of the constraint type Ord PathTemplateVariable
Instance of class: Eq of the constraint type Eq PathTemplateVariable
Ord, (forall x. PathTemplateVariable -> Rep PathTemplateVariable x)
-> (forall x. Rep PathTemplateVariable x -> PathTemplateVariable)
-> Generic PathTemplateVariable
forall x. Rep PathTemplateVariable x -> PathTemplateVariable
forall x. PathTemplateVariable -> Rep PathTemplateVariable x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PathTemplateVariable x -> PathTemplateVariable
$cfrom :: forall x. PathTemplateVariable -> Rep PathTemplateVariable x
Generic, Typeable)
instance Binary PathTemplateVariable
instance Structured PathTemplateVariable
instance Show PathTemplateVariable where
show :: PathTemplateVariable -> FilePath
show PathTemplateVariable
PrefixVar = FilePath
"prefix"
show PathTemplateVariable
LibNameVar = FilePath
"libname"
show PathTemplateVariable
BindirVar = FilePath
"bindir"
show PathTemplateVariable
LibdirVar = FilePath
"libdir"
show PathTemplateVariable
LibsubdirVar = FilePath
"libsubdir"
show PathTemplateVariable
DynlibdirVar = FilePath
"dynlibdir"
show PathTemplateVariable
DatadirVar = FilePath
"datadir"
show PathTemplateVariable
DatasubdirVar = FilePath
"datasubdir"
show PathTemplateVariable
DocdirVar = FilePath
"docdir"
show PathTemplateVariable
HtmldirVar = FilePath
"htmldir"
show PathTemplateVariable
PkgNameVar = FilePath
"pkg"
show PathTemplateVariable
PkgVerVar = FilePath
"version"
show PathTemplateVariable
PkgIdVar = FilePath
"pkgid"
show PathTemplateVariable
CompilerVar = FilePath
"compiler"
show PathTemplateVariable
OSVar = FilePath
"os"
show PathTemplateVariable
ArchVar = FilePath
"arch"
show PathTemplateVariable
AbiTagVar = FilePath
"abitag"
show PathTemplateVariable
AbiVar = FilePath
"abi"
show PathTemplateVariable
ExecutableNameVar = FilePath
"executablename"
show PathTemplateVariable
TestSuiteNameVar = FilePath
"test-suite"
show PathTemplateVariable
TestSuiteResultVar = FilePath
"result"
show PathTemplateVariable
BenchmarkNameVar = FilePath
"benchmark"
instance Read PathTemplateVariable where
readsPrec :: Int -> ReadS PathTemplateVariable
readsPrec Int
_ FilePath
s =
Int
-> [(PathTemplateVariable, FilePath)]
-> [(PathTemplateVariable, FilePath)]
forall a. Int -> [a] -> [a]
take Int
1
[ (PathTemplateVariable
var, Int -> ShowS
forall a. Int -> [a] -> [a]
drop (FilePath -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
External instance of the constraint type Foldable []
length FilePath
varStr) FilePath
s)
| (FilePath
varStr, PathTemplateVariable
var) <- [(FilePath, PathTemplateVariable)]
vars
, FilePath
varStr FilePath -> FilePath -> Bool
forall a. Eq a => [a] -> [a] -> Bool
External instance of the constraint type Eq Char
`isPrefixOf` FilePath
s ]
where vars :: [(FilePath, PathTemplateVariable)]
vars = [(FilePath
"prefix", PathTemplateVariable
PrefixVar)
,(FilePath
"bindir", PathTemplateVariable
BindirVar)
,(FilePath
"libdir", PathTemplateVariable
LibdirVar)
,(FilePath
"libsubdir", PathTemplateVariable
LibsubdirVar)
,(FilePath
"dynlibdir", PathTemplateVariable
DynlibdirVar)
,(FilePath
"datadir", PathTemplateVariable
DatadirVar)
,(FilePath
"datasubdir", PathTemplateVariable
DatasubdirVar)
,(FilePath
"docdir", PathTemplateVariable
DocdirVar)
,(FilePath
"htmldir", PathTemplateVariable
HtmldirVar)
,(FilePath
"pkgid", PathTemplateVariable
PkgIdVar)
,(FilePath
"libname", PathTemplateVariable
LibNameVar)
,(FilePath
"pkgkey", PathTemplateVariable
LibNameVar)
,(FilePath
"pkg", PathTemplateVariable
PkgNameVar)
,(FilePath
"version", PathTemplateVariable
PkgVerVar)
,(FilePath
"compiler", PathTemplateVariable
CompilerVar)
,(FilePath
"os", PathTemplateVariable
OSVar)
,(FilePath
"arch", PathTemplateVariable
ArchVar)
,(FilePath
"abitag", PathTemplateVariable
AbiTagVar)
,(FilePath
"abi", PathTemplateVariable
AbiVar)
,(FilePath
"executablename", PathTemplateVariable
ExecutableNameVar)
,(FilePath
"test-suite", PathTemplateVariable
TestSuiteNameVar)
,(FilePath
"result", PathTemplateVariable
TestSuiteResultVar)
,(FilePath
"benchmark", PathTemplateVariable
BenchmarkNameVar)]
instance Show PathComponent where
show :: PathComponent -> FilePath
show (Ordinary FilePath
path) = FilePath
path
show (Variable PathTemplateVariable
var) = Char
'$'Char -> ShowS
forall a. a -> [a] -> [a]
:PathTemplateVariable -> FilePath
forall a. Show a => a -> FilePath
Instance of class: Show of the constraint type Show PathTemplateVariable
show PathTemplateVariable
var
showList :: [PathComponent] -> ShowS
showList = (PathComponent -> ShowS -> ShowS)
-> ShowS -> [PathComponent] -> ShowS
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
External instance of the constraint type Foldable []
foldr (\PathComponent
x -> (PathComponent -> ShowS
forall a. Show a => a -> ShowS
Instance of class: Show of the constraint type Show PathComponent
shows PathComponent
x ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.)) ShowS
forall a. a -> a
id
instance Read PathComponent where
readsPrec :: Int -> ReadS PathComponent
readsPrec Int
_ = ReadS PathComponent
lex0
where lex0 :: ReadS PathComponent
lex0 [] = []
lex0 (Char
'$':Char
'$':FilePath
s') = ReadS PathComponent
lex0 (Char
'$'Char -> ShowS
forall a. a -> [a] -> [a]
:FilePath
s')
lex0 (Char
'$':FilePath
s') = case [ (PathTemplateVariable -> PathComponent
Variable PathTemplateVariable
var, FilePath
s'')
| (PathTemplateVariable
var, FilePath
s'') <- ReadS PathTemplateVariable
forall a. Read a => ReadS a
Instance of class: Read of the constraint type Read PathTemplateVariable
reads FilePath
s' ] of
[] -> FilePath -> ReadS PathComponent
lex1 FilePath
"$" FilePath
s'
[(PathComponent, FilePath)]
ok -> [(PathComponent, FilePath)]
ok
lex0 FilePath
s' = FilePath -> ReadS PathComponent
lex1 [] FilePath
s'
lex1 :: FilePath -> ReadS PathComponent
lex1 FilePath
"" FilePath
"" = []
lex1 FilePath
acc FilePath
"" = [(FilePath -> PathComponent
Ordinary (ShowS
forall a. [a] -> [a]
reverse FilePath
acc), FilePath
"")]
lex1 FilePath
acc (Char
'$':Char
'$':FilePath
s) = FilePath -> ReadS PathComponent
lex1 FilePath
acc (Char
'$'Char -> ShowS
forall a. a -> [a] -> [a]
:FilePath
s)
lex1 FilePath
acc (Char
'$':FilePath
s) = [(FilePath -> PathComponent
Ordinary (ShowS
forall a. [a] -> [a]
reverse FilePath
acc), Char
'$'Char -> ShowS
forall a. a -> [a] -> [a]
:FilePath
s)]
lex1 FilePath
acc (Char
c:FilePath
s) = FilePath -> ReadS PathComponent
lex1 (Char
cChar -> ShowS
forall a. a -> [a] -> [a]
:FilePath
acc) FilePath
s
readList :: ReadS [PathComponent]
readList [] = [([],FilePath
"")]
readList FilePath
s = [ (PathComponent
componentPathComponent -> [PathComponent] -> [PathComponent]
forall a. a -> [a] -> [a]
:[PathComponent]
components, FilePath
s'')
| (PathComponent
component, FilePath
s') <- ReadS PathComponent
forall a. Read a => ReadS a
Instance of class: Read of the constraint type Read PathComponent
reads FilePath
s
, ([PathComponent]
components, FilePath
s'') <- ReadS [PathComponent]
forall a. Read a => ReadS [a]
Instance of class: Read of the constraint type Read PathComponent
readList FilePath
s' ]