{-# 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
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PathComponent -> PathComponent -> Bool
$c/= :: PathComponent -> PathComponent -> Bool
== :: PathComponent -> PathComponent -> Bool
$c== :: PathComponent -> PathComponent -> Bool
Eq, Eq 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
Ord, 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     -- ^ The @$prefix@ path variable
     | BindirVar     -- ^ The @$bindir@ path variable
     | LibdirVar     -- ^ The @$libdir@ path variable
     | LibsubdirVar  -- ^ The @$libsubdir@ path variable
     | DynlibdirVar  -- ^ The @$dynlibdir@ path variable
     | DatadirVar    -- ^ The @$datadir@ path variable
     | DatasubdirVar -- ^ The @$datasubdir@ path variable
     | DocdirVar     -- ^ The @$docdir@ path variable
     | HtmldirVar    -- ^ The @$htmldir@ path variable
     | PkgNameVar    -- ^ The @$pkg@ package name path variable
     | PkgVerVar     -- ^ The @$version@ package version path variable
     | PkgIdVar      -- ^ The @$pkgid@ package Id path variable, eg @foo-1.0@
     | LibNameVar    -- ^ The @$libname@ path variable
     | CompilerVar   -- ^ The compiler name and version, eg @ghc-6.6.1@
     | OSVar         -- ^ The operating system name, eg @windows@ or @linux@
     | ArchVar       -- ^ The CPU architecture name, eg @i386@ or @x86_64@
     | AbiVar        -- ^ The compiler's ABI identifier,
                     ---  $arch-$os-$compiler-$abitag
     | AbiTagVar     -- ^ The optional ABI tag for the compiler
     | ExecutableNameVar -- ^ The executable name; used in shell wrappers
     | TestSuiteNameVar   -- ^ The name of the test suite being run
     | TestSuiteResultVar -- ^ The result of the test suite being run, eg
                          -- @pass@, @fail@, or @error@.
     | BenchmarkNameVar   -- ^ The name of the benchmark being run
  deriving (PathTemplateVariable -> PathTemplateVariable -> Bool
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
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
Ord, 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 =
    forall a. Int -> [a] -> [a]
take Int
1
    [ (PathTemplateVariable
var, forall a. Int -> [a] -> [a]
drop (forall (t :: * -> *) a. Foldable t => t a -> Int
length FilePath
varStr) FilePath
s)
    | (FilePath
varStr, PathTemplateVariable
var) <- [(FilePath, PathTemplateVariable)]
vars
    , FilePath
varStr forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` FilePath
s ]
    -- NB: order matters! Longer strings first
    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) -- backwards compatibility
                 ,(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
'$'forall a. a -> [a] -> [a]
:forall a. Show a => a -> FilePath
show PathTemplateVariable
var
  showList :: [PathComponent] -> ShowS
showList = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (\PathComponent
x -> (forall a. Show a => a -> ShowS
shows PathComponent
x forall b c a. (b -> c) -> (a -> b) -> a -> c
.)) forall a. a -> a
id

instance Read PathComponent where
  -- for some reason we collapse multiple $ symbols here
  readsPrec :: Int -> ReadS PathComponent
readsPrec Int
_ = ReadS PathComponent
lex0
    where lex0 :: ReadS PathComponent
lex0 [] = []
          lex0 (Char
'$':Char
'$':FilePath
s') = ReadS PathComponent
lex0 (Char
'$'forall a. a -> [a] -> [a]
:FilePath
s')
          lex0 (Char
'$':FilePath
s') = case [ (PathTemplateVariable -> PathComponent
Variable PathTemplateVariable
var, FilePath
s'')
                               | (PathTemplateVariable
var, FilePath
s'') <- forall a. Read a => ReadS a
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 (forall a. [a] -> [a]
reverse FilePath
acc), FilePath
"")]
          lex1 FilePath
acc (Char
'$':Char
'$':FilePath
s) = FilePath -> ReadS PathComponent
lex1 FilePath
acc (Char
'$'forall a. a -> [a] -> [a]
:FilePath
s)
          lex1 FilePath
acc (Char
'$':FilePath
s) = [(FilePath -> PathComponent
Ordinary (forall a. [a] -> [a]
reverse FilePath
acc), Char
'$'forall a. a -> [a] -> [a]
:FilePath
s)]
          lex1 FilePath
acc (Char
c:FilePath
s)   = FilePath -> ReadS PathComponent
lex1 (Char
cforall a. a -> [a] -> [a]
:FilePath
acc) FilePath
s
  readList :: ReadS [PathComponent]
readList [] = [([],FilePath
"")]
  readList FilePath
s  = [ (PathComponent
componentforall a. a -> [a] -> [a]
:[PathComponent]
components, FilePath
s'')
                | (PathComponent
component, FilePath
s') <- forall a. Read a => ReadS a
reads FilePath
s
                , ([PathComponent]
components, FilePath
s'') <- forall a. Read a => ReadS [a]
readList FilePath
s' ]