{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE StandaloneDeriving #-}
module Distribution.Utils.Path (
SymbolicPath,
getSymbolicPath,
sameDirectory,
unsafeMakeSymbolicPath,
PackageDir,
SourceDir,
LicenseFile,
IsDir,
) where
import Prelude ()
import Distribution.Compat.Prelude
import Distribution.Parsec
import Distribution.Pretty
import Distribution.Utils.Generic (isAbsoluteOnAnyPlatform)
import qualified Distribution.Compat.CharParsing as P
newtype SymbolicPath from to = SymbolicPath FilePath
deriving (forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall from to x.
Rep (SymbolicPath from to) x -> SymbolicPath from to
forall from to x.
SymbolicPath from to -> Rep (SymbolicPath from to) x
$cto :: forall from to x.
Rep (SymbolicPath from to) x -> SymbolicPath from to
$cfrom :: forall from to x.
SymbolicPath from to -> Rep (SymbolicPath from to) x
Generic, Int -> SymbolicPath from to -> ShowS
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
forall from to. Int -> SymbolicPath from to -> ShowS
forall from to. [SymbolicPath from to] -> ShowS
forall from to. SymbolicPath from to -> FilePath
showList :: [SymbolicPath from to] -> ShowS
$cshowList :: forall from to. [SymbolicPath from to] -> ShowS
show :: SymbolicPath from to -> FilePath
$cshow :: forall from to. SymbolicPath from to -> FilePath
showsPrec :: Int -> SymbolicPath from to -> ShowS
$cshowsPrec :: forall from to. Int -> SymbolicPath from to -> ShowS
Show, ReadPrec [SymbolicPath from to]
ReadPrec (SymbolicPath from to)
ReadS [SymbolicPath from to]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
forall from to. ReadPrec [SymbolicPath from to]
forall from to. ReadPrec (SymbolicPath from to)
forall from to. Int -> ReadS (SymbolicPath from to)
forall from to. ReadS [SymbolicPath from to]
readListPrec :: ReadPrec [SymbolicPath from to]
$creadListPrec :: forall from to. ReadPrec [SymbolicPath from to]
readPrec :: ReadPrec (SymbolicPath from to)
$creadPrec :: forall from to. ReadPrec (SymbolicPath from to)
readList :: ReadS [SymbolicPath from to]
$creadList :: forall from to. ReadS [SymbolicPath from to]
readsPrec :: Int -> ReadS (SymbolicPath from to)
$creadsPrec :: forall from to. Int -> ReadS (SymbolicPath from to)
Read, SymbolicPath from to -> SymbolicPath from to -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall from to.
SymbolicPath from to -> SymbolicPath from to -> Bool
/= :: SymbolicPath from to -> SymbolicPath from to -> Bool
$c/= :: forall from to.
SymbolicPath from to -> SymbolicPath from to -> Bool
== :: SymbolicPath from to -> SymbolicPath from to -> Bool
$c== :: forall from to.
SymbolicPath from to -> SymbolicPath from to -> Bool
Eq, SymbolicPath from to -> SymbolicPath from to -> Bool
SymbolicPath from to -> SymbolicPath from to -> Ordering
SymbolicPath from to
-> SymbolicPath from to -> SymbolicPath from to
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
forall from to. Eq (SymbolicPath from to)
forall from to.
SymbolicPath from to -> SymbolicPath from to -> Bool
forall from to.
SymbolicPath from to -> SymbolicPath from to -> Ordering
forall from to.
SymbolicPath from to
-> SymbolicPath from to -> SymbolicPath from to
min :: SymbolicPath from to
-> SymbolicPath from to -> SymbolicPath from to
$cmin :: forall from to.
SymbolicPath from to
-> SymbolicPath from to -> SymbolicPath from to
max :: SymbolicPath from to
-> SymbolicPath from to -> SymbolicPath from to
$cmax :: forall from to.
SymbolicPath from to
-> SymbolicPath from to -> SymbolicPath from to
>= :: SymbolicPath from to -> SymbolicPath from to -> Bool
$c>= :: forall from to.
SymbolicPath from to -> SymbolicPath from to -> Bool
> :: SymbolicPath from to -> SymbolicPath from to -> Bool
$c> :: forall from to.
SymbolicPath from to -> SymbolicPath from to -> Bool
<= :: SymbolicPath from to -> SymbolicPath from to -> Bool
$c<= :: forall from to.
SymbolicPath from to -> SymbolicPath from to -> Bool
< :: SymbolicPath from to -> SymbolicPath from to -> Bool
$c< :: forall from to.
SymbolicPath from to -> SymbolicPath from to -> Bool
compare :: SymbolicPath from to -> SymbolicPath from to -> Ordering
$ccompare :: forall from to.
SymbolicPath from to -> SymbolicPath from to -> Ordering
Ord, Typeable, SymbolicPath from to -> DataType
SymbolicPath from to -> Constr
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall {from} {to}.
(Data from, Data to) =>
Typeable (SymbolicPath from to)
forall from to.
(Data from, Data to) =>
SymbolicPath from to -> DataType
forall from to.
(Data from, Data to) =>
SymbolicPath from to -> Constr
forall from to.
(Data from, Data to) =>
(forall b. Data b => b -> b)
-> SymbolicPath from to -> SymbolicPath from to
forall from to u.
(Data from, Data to) =>
Int -> (forall d. Data d => d -> u) -> SymbolicPath from to -> u
forall from to u.
(Data from, Data to) =>
(forall d. Data d => d -> u) -> SymbolicPath from to -> [u]
forall from to r r'.
(Data from, Data to) =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SymbolicPath from to -> r
forall from to r r'.
(Data from, Data to) =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SymbolicPath from to -> r
forall from to (m :: * -> *).
(Data from, Data to, Monad m) =>
(forall d. Data d => d -> m d)
-> SymbolicPath from to -> m (SymbolicPath from to)
forall from to (m :: * -> *).
(Data from, Data to, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> SymbolicPath from to -> m (SymbolicPath from to)
forall from to (c :: * -> *).
(Data from, Data to) =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (SymbolicPath from to)
forall from to (c :: * -> *).
(Data from, Data to) =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> SymbolicPath from to
-> c (SymbolicPath from to)
forall from to (t :: * -> *) (c :: * -> *).
(Data from, Data to, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (SymbolicPath from to))
forall from to (t :: * -> * -> *) (c :: * -> *).
(Data from, Data to, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (SymbolicPath from to))
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (SymbolicPath from to)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> SymbolicPath from to
-> c (SymbolicPath from to)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (SymbolicPath from to))
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SymbolicPath from to -> m (SymbolicPath from to)
$cgmapMo :: forall from to (m :: * -> *).
(Data from, Data to, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> SymbolicPath from to -> m (SymbolicPath from to)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SymbolicPath from to -> m (SymbolicPath from to)
$cgmapMp :: forall from to (m :: * -> *).
(Data from, Data to, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> SymbolicPath from to -> m (SymbolicPath from to)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> SymbolicPath from to -> m (SymbolicPath from to)
$cgmapM :: forall from to (m :: * -> *).
(Data from, Data to, Monad m) =>
(forall d. Data d => d -> m d)
-> SymbolicPath from to -> m (SymbolicPath from to)
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> SymbolicPath from to -> u
$cgmapQi :: forall from to u.
(Data from, Data to) =>
Int -> (forall d. Data d => d -> u) -> SymbolicPath from to -> u
gmapQ :: forall u.
(forall d. Data d => d -> u) -> SymbolicPath from to -> [u]
$cgmapQ :: forall from to u.
(Data from, Data to) =>
(forall d. Data d => d -> u) -> SymbolicPath from to -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SymbolicPath from to -> r
$cgmapQr :: forall from to r r'.
(Data from, Data to) =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SymbolicPath from to -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SymbolicPath from to -> r
$cgmapQl :: forall from to r r'.
(Data from, Data to) =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SymbolicPath from to -> r
gmapT :: (forall b. Data b => b -> b)
-> SymbolicPath from to -> SymbolicPath from to
$cgmapT :: forall from to.
(Data from, Data to) =>
(forall b. Data b => b -> b)
-> SymbolicPath from to -> SymbolicPath from to
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (SymbolicPath from to))
$cdataCast2 :: forall from to (t :: * -> * -> *) (c :: * -> *).
(Data from, Data to, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (SymbolicPath from to))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (SymbolicPath from to))
$cdataCast1 :: forall from to (t :: * -> *) (c :: * -> *).
(Data from, Data to, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (SymbolicPath from to))
dataTypeOf :: SymbolicPath from to -> DataType
$cdataTypeOf :: forall from to.
(Data from, Data to) =>
SymbolicPath from to -> DataType
toConstr :: SymbolicPath from to -> Constr
$ctoConstr :: forall from to.
(Data from, Data to) =>
SymbolicPath from to -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (SymbolicPath from to)
$cgunfold :: forall from to (c :: * -> *).
(Data from, Data to) =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (SymbolicPath from to)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> SymbolicPath from to
-> c (SymbolicPath from to)
$cgfoldl :: forall from to (c :: * -> *).
(Data from, Data to) =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> SymbolicPath from to
-> c (SymbolicPath from to)
Data)
instance Binary (SymbolicPath from to)
instance (Typeable from, Typeable to) => Structured (SymbolicPath from to)
instance NFData (SymbolicPath from to) where rnf :: SymbolicPath from to -> ()
rnf = forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf
getSymbolicPath :: SymbolicPath from to -> FilePath
getSymbolicPath :: forall from to. SymbolicPath from to -> FilePath
getSymbolicPath (SymbolicPath FilePath
p) = FilePath
p
sameDirectory :: (IsDir from, IsDir to) => SymbolicPath from to
sameDirectory :: forall from to. (IsDir from, IsDir to) => SymbolicPath from to
sameDirectory = forall from to. FilePath -> SymbolicPath from to
SymbolicPath FilePath
"."
unsafeMakeSymbolicPath :: FilePath -> SymbolicPath from to
unsafeMakeSymbolicPath :: forall from to. FilePath -> SymbolicPath from to
unsafeMakeSymbolicPath = forall from to. FilePath -> SymbolicPath from to
SymbolicPath
instance Parsec (SymbolicPath from to) where
parsec :: forall (m :: * -> *). CabalParsing m => m (SymbolicPath from to)
parsec = do
FilePath
token <- forall (m :: * -> *). CabalParsing m => m FilePath
parsecToken
if forall (t :: * -> *) a. Foldable t => t a -> Bool
null FilePath
token then forall (m :: * -> *) a. Parsing m => FilePath -> m a
P.unexpected FilePath
"empty FilePath"
else if FilePath -> Bool
isAbsoluteOnAnyPlatform FilePath
token then forall (m :: * -> *) a. Parsing m => FilePath -> m a
P.unexpected FilePath
"absolute FilePath"
else forall (m :: * -> *) a. Monad m => a -> m a
return (forall from to. FilePath -> SymbolicPath from to
SymbolicPath FilePath
token)
instance Pretty (SymbolicPath from to) where
pretty :: SymbolicPath from to -> Doc
pretty = FilePath -> Doc
showFilePath forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall from to. SymbolicPath from to -> FilePath
getSymbolicPath
class IsDir dir
data PackageDir deriving (Typeable)
data SourceDir deriving (Typeable)
data LicenseFile deriving (Typeable)
deriving instance Data PackageDir
deriving instance Data SourceDir
deriving instance Data LicenseFile
instance IsDir PackageDir
instance IsDir SourceDir