-- File created: 2009-01-17


-- |A number of primitives from which complete 'Pattern's may be constructed.

--

-- Using this together with the functions provided by the 'Monoid' instance of

-- 'Pattern' allows for direct manipulation of 'Pattern's beyond what can be

-- done with just the 'compile' family of functions. And of course you don't

-- have to go via 'String's if you use these.

module System.FilePath.Glob.Primitive
   ( literal
   , singleWildcard, wildcard, recursiveWildcard
   , charRange, numberRange
   ) where

import System.FilePath (isPathSeparator, isExtSeparator)

import System.FilePath.Glob.Base (Pattern(..), Token(..), optimize)

-- |A 'Pattern' which matches the given 'String' literally.

--

-- Handles any embedded path and extension separators.

literal :: String -> Pattern
literal :: String -> Pattern
literal = Pattern -> Pattern
optimize (Pattern -> Pattern) -> (String -> Pattern) -> String -> Pattern
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Token] -> Pattern
Pattern ([Token] -> Pattern) -> (String -> [Token]) -> String -> Pattern
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Token) -> String -> [Token]
forall a b. (a -> b) -> [a] -> [b]
map Char -> Token
f
 where
   f :: Char -> Token
f Char
c | Char -> Bool
isPathSeparator Char
c = Token
PathSeparator
       | Char -> Bool
isExtSeparator Char
c  = Token
ExtSeparator
       | Bool
otherwise         = Char -> Token
Literal Char
c

-- |Matches any single character except a path separator: corresponds to the

-- @?@ operator.

singleWildcard :: Pattern
singleWildcard :: Pattern
singleWildcard = [Token] -> Pattern
Pattern [Token
NonPathSeparator]

-- |Matches any number of characters up to a path separator: corresponds to the

-- @*@ operator.

wildcard :: Pattern
wildcard :: Pattern
wildcard = [Token] -> Pattern
Pattern [Token
AnyNonPathSeparator]

-- |Matches any number of characters including path separators: corresponds to

-- the @**/@ operator.

recursiveWildcard :: Pattern
recursiveWildcard :: Pattern
recursiveWildcard = [Token] -> Pattern
Pattern [Token
AnyDirectory]

-- |Matches a single character if it is within the (inclusive) range in any

-- 'Right' or if it is equal to the character in any 'Left'. Corresponds to the

-- @[]@, @[^]@ and @[!]@ operators.

--

-- If the given 'Bool' is 'False', the result of the match is inverted: the

-- match succeeds if the character does /not/ match according to the above

-- rules.

charRange :: Bool -> [Either Char (Char,Char)] -> Pattern
charRange :: Bool -> [Either Char (Char, Char)] -> Pattern
charRange Bool
b [Either Char (Char, Char)]
rs = Pattern -> Pattern
optimize (Pattern -> Pattern) -> Pattern -> Pattern
forall a b. (a -> b) -> a -> b
$ [Token] -> Pattern
Pattern [Bool -> [Either Char (Char, Char)] -> Token
CharRange Bool
b [Either Char (Char, Char)]
rs]

-- |Matches a number in the given range, which may be open, half-open, or

-- closed. Corresponds to the @\<\>@ operator.

numberRange :: Maybe Integer -> Maybe Integer -> Pattern
numberRange :: Maybe Integer -> Maybe Integer -> Pattern
numberRange Maybe Integer
a Maybe Integer
b = [Token] -> Pattern
Pattern [Maybe String -> Maybe String -> Token
OpenRange ((Integer -> String) -> Maybe Integer -> Maybe String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Integer -> String
forall a. Show a => a -> String
show Maybe Integer
a) ((Integer -> String) -> Maybe Integer -> Maybe String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Integer -> String
forall a. Show a => a -> String
show Maybe Integer
b)]