{-# LANGUAGE DeriveGeneric #-}
module Distribution.Simple.Glob.Internal where
import Distribution.Compat.Prelude
import Prelude ()
import qualified Distribution.Compat.CharParsing as P
import Distribution.Parsec
import Distribution.Pretty
import qualified Text.PrettyPrint as Disp
data Glob
=
GlobDir !GlobPieces !Glob
|
GlobDirRecursive !GlobPieces
|
GlobFile !GlobPieces
|
GlobDirTrailing
deriving (Glob -> Glob -> Bool
(Glob -> Glob -> Bool) -> (Glob -> Glob -> Bool) -> Eq Glob
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Glob -> Glob -> Bool
== :: Glob -> Glob -> Bool
$c/= :: Glob -> Glob -> Bool
/= :: Glob -> Glob -> Bool
Eq, Int -> Glob -> ShowS
[Glob] -> ShowS
Glob -> String
(Int -> Glob -> ShowS)
-> (Glob -> String) -> ([Glob] -> ShowS) -> Show Glob
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Glob -> ShowS
showsPrec :: Int -> Glob -> ShowS
$cshow :: Glob -> String
show :: Glob -> String
$cshowList :: [Glob] -> ShowS
showList :: [Glob] -> ShowS
Show, (forall x. Glob -> Rep Glob x)
-> (forall x. Rep Glob x -> Glob) -> Generic Glob
forall x. Rep Glob x -> Glob
forall x. Glob -> Rep Glob x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Glob -> Rep Glob x
from :: forall x. Glob -> Rep Glob x
$cto :: forall x. Rep Glob x -> Glob
to :: forall x. Rep Glob x -> Glob
Generic)
instance Binary Glob
instance Structured Glob
type GlobPieces = [GlobPiece]
data GlobPiece
=
WildCard
|
Literal String
|
Union [GlobPieces]
deriving (GlobPiece -> GlobPiece -> Bool
(GlobPiece -> GlobPiece -> Bool)
-> (GlobPiece -> GlobPiece -> Bool) -> Eq GlobPiece
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GlobPiece -> GlobPiece -> Bool
== :: GlobPiece -> GlobPiece -> Bool
$c/= :: GlobPiece -> GlobPiece -> Bool
/= :: GlobPiece -> GlobPiece -> Bool
Eq, Int -> GlobPiece -> ShowS
[GlobPiece] -> ShowS
GlobPiece -> String
(Int -> GlobPiece -> ShowS)
-> (GlobPiece -> String)
-> ([GlobPiece] -> ShowS)
-> Show GlobPiece
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GlobPiece -> ShowS
showsPrec :: Int -> GlobPiece -> ShowS
$cshow :: GlobPiece -> String
show :: GlobPiece -> String
$cshowList :: [GlobPiece] -> ShowS
showList :: [GlobPiece] -> ShowS
Show, (forall x. GlobPiece -> Rep GlobPiece x)
-> (forall x. Rep GlobPiece x -> GlobPiece) -> Generic GlobPiece
forall x. Rep GlobPiece x -> GlobPiece
forall x. GlobPiece -> Rep GlobPiece x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. GlobPiece -> Rep GlobPiece x
from :: forall x. GlobPiece -> Rep GlobPiece x
$cto :: forall x. Rep GlobPiece x -> GlobPiece
to :: forall x. Rep GlobPiece x -> GlobPiece
Generic)
instance Binary GlobPiece
instance Structured GlobPiece
instance Pretty Glob where
pretty :: Glob -> Doc
pretty (GlobDir [GlobPiece]
glob Glob
pathglob) =
[GlobPiece] -> Doc
dispGlobPieces [GlobPiece]
glob
Doc -> Doc -> Doc
Disp.<> Char -> Doc
Disp.char Char
'/'
Doc -> Doc -> Doc
Disp.<> Glob -> Doc
forall a. Pretty a => a -> Doc
pretty Glob
pathglob
pretty (GlobDirRecursive [GlobPiece]
glob) =
String -> Doc
Disp.text String
"**/"
Doc -> Doc -> Doc
Disp.<> [GlobPiece] -> Doc
dispGlobPieces [GlobPiece]
glob
pretty (GlobFile [GlobPiece]
glob) = [GlobPiece] -> Doc
dispGlobPieces [GlobPiece]
glob
pretty Glob
GlobDirTrailing = Doc
Disp.empty
instance Parsec Glob where
parsec :: forall (m :: * -> *). CabalParsing m => m Glob
parsec = m Glob
forall (m :: * -> *). CabalParsing m => m Glob
parsecPath
where
parsecPath :: CabalParsing m => m Glob
parsecPath :: forall (m :: * -> *). CabalParsing m => m Glob
parsecPath = do
glob <- m [GlobPiece]
forall (m :: * -> *). CabalParsing m => m [GlobPiece]
parsecGlob
dirSep *> (GlobDir glob <$> parsecPath <|> pure (GlobDir glob GlobDirTrailing)) <|> pure (GlobFile glob)
dirSep :: CabalParsing m => m ()
dirSep :: forall (m :: * -> *). CabalParsing m => m ()
dirSep =
() () -> m Char -> m ()
forall a b. a -> m b -> m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char -> m Char
forall (m :: * -> *). CharParsing m => Char -> m Char
P.char Char
'/'
m () -> m () -> m ()
forall a. m a -> m a -> m a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> m () -> m ()
forall a. m a -> m a
forall (m :: * -> *) a. Parsing m => m a -> m a
P.try
( do
_ <- Char -> m Char
forall (m :: * -> *). CharParsing m => Char -> m Char
P.char Char
'\\'
P.notFollowedBy (P.satisfy isGlobEscapedChar)
)
parsecGlob :: CabalParsing m => m GlobPieces
parsecGlob :: forall (m :: * -> *). CabalParsing m => m [GlobPiece]
parsecGlob = m GlobPiece -> m [GlobPiece]
forall a. m a -> m [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
some m GlobPiece
parsecPiece
where
parsecPiece :: m GlobPiece
parsecPiece = [m GlobPiece] -> m GlobPiece
forall (m :: * -> *) a. Alternative m => [m a] -> m a
P.choice [m GlobPiece
literal, m GlobPiece
wildcard, m GlobPiece
union]
wildcard :: m GlobPiece
wildcard = GlobPiece
WildCard GlobPiece -> m Char -> m GlobPiece
forall a b. a -> m b -> m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char -> m Char
forall (m :: * -> *). CharParsing m => Char -> m Char
P.char Char
'*'
union :: m GlobPiece
union = [[GlobPiece]] -> GlobPiece
Union ([[GlobPiece]] -> GlobPiece)
-> (NonEmpty [GlobPiece] -> [[GlobPiece]])
-> NonEmpty [GlobPiece]
-> GlobPiece
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonEmpty [GlobPiece] -> [[GlobPiece]]
forall a. NonEmpty a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList (NonEmpty [GlobPiece] -> GlobPiece)
-> m (NonEmpty [GlobPiece]) -> m GlobPiece
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m Char
-> m Char -> m (NonEmpty [GlobPiece]) -> m (NonEmpty [GlobPiece])
forall (m :: * -> *) bra ket a.
Applicative m =>
m bra -> m ket -> m a -> m a
P.between (Char -> m Char
forall (m :: * -> *). CharParsing m => Char -> m Char
P.char Char
'{') (Char -> m Char
forall (m :: * -> *). CharParsing m => Char -> m Char
P.char Char
'}') (m [GlobPiece] -> m Char -> m (NonEmpty [GlobPiece])
forall (m :: * -> *) a sep.
Alternative m =>
m a -> m sep -> m (NonEmpty a)
P.sepByNonEmpty m [GlobPiece]
forall (m :: * -> *). CabalParsing m => m [GlobPiece]
parsecGlob (Char -> m Char
forall (m :: * -> *). CharParsing m => Char -> m Char
P.char Char
','))
literal :: m GlobPiece
literal = String -> GlobPiece
Literal (String -> GlobPiece) -> m String -> m GlobPiece
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m Char -> m String
forall a. m a -> m [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
some m Char
litchar
litchar :: m Char
litchar = m Char
normal m Char -> m Char -> m Char
forall a. m a -> m a -> m a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> m Char
escape
normal :: m Char
normal = (Char -> Bool) -> m Char
forall (m :: * -> *). CharParsing m => (Char -> Bool) -> m Char
P.satisfy (\Char
c -> Bool -> Bool
not (Char -> Bool
isGlobEscapedChar Char
c) Bool -> Bool -> Bool
&& Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'/' Bool -> Bool -> Bool
&& Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'\\')
escape :: m Char
escape = m Char -> m Char
forall a. m a -> m a
forall (m :: * -> *) a. Parsing m => m a -> m a
P.try (m Char -> m Char) -> m Char -> m Char
forall a b. (a -> b) -> a -> b
$ Char -> m Char
forall (m :: * -> *). CharParsing m => Char -> m Char
P.char Char
'\\' m Char -> m Char -> m Char
forall a b. m a -> m b -> m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> (Char -> Bool) -> m Char
forall (m :: * -> *). CharParsing m => (Char -> Bool) -> m Char
P.satisfy Char -> Bool
isGlobEscapedChar
dispGlobPieces :: GlobPieces -> Disp.Doc
dispGlobPieces :: [GlobPiece] -> Doc
dispGlobPieces = [Doc] -> Doc
Disp.hcat ([Doc] -> Doc) -> ([GlobPiece] -> [Doc]) -> [GlobPiece] -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (GlobPiece -> Doc) -> [GlobPiece] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map GlobPiece -> Doc
dispPiece
where
dispPiece :: GlobPiece -> Doc
dispPiece GlobPiece
WildCard = Char -> Doc
Disp.char Char
'*'
dispPiece (Literal String
str) = String -> Doc
Disp.text (ShowS
escape String
str)
dispPiece (Union [[GlobPiece]]
globs) =
Doc -> Doc
Disp.braces
( [Doc] -> Doc
Disp.hcat
( Doc -> [Doc] -> [Doc]
Disp.punctuate
(Char -> Doc
Disp.char Char
',')
(([GlobPiece] -> Doc) -> [[GlobPiece]] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map [GlobPiece] -> Doc
dispGlobPieces [[GlobPiece]]
globs)
)
)
escape :: ShowS
escape [] = []
escape (Char
c : String
cs)
| Char -> Bool
isGlobEscapedChar Char
c = Char
'\\' Char -> ShowS
forall a. a -> [a] -> [a]
: Char
c Char -> ShowS
forall a. a -> [a] -> [a]
: ShowS
escape String
cs
| Bool
otherwise = Char
c Char -> ShowS
forall a. a -> [a] -> [a]
: ShowS
escape String
cs
isGlobEscapedChar :: Char -> Bool
isGlobEscapedChar :: Char -> Bool
isGlobEscapedChar Char
'*' = Bool
True
isGlobEscapedChar Char
'{' = Bool
True
isGlobEscapedChar Char
'}' = Bool
True
isGlobEscapedChar Char
',' = Bool
True
isGlobEscapedChar Char
_ = Bool
False