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