{-# OPTIONS_GHC -fno-warn-orphans #-}
module Hakyll.Core.Identifier.Pattern
(
Pattern
, fromGlob
, fromList
, fromRegex
, fromVersion
, hasVersion
, hasNoVersion
, (.&&.)
, (.||.)
, complement
, matches
, filterMatches
, capture
, fromCapture
, fromCaptures
) where
import Control.Arrow ((&&&), (>>>))
import Control.Monad (msum)
import Data.List (inits, isPrefixOf,
tails)
import Data.Maybe (isJust)
import qualified Data.Set as S
import System.FilePath (normalise, pathSeparator)
import GHC.Exts (IsString, fromString)
import Text.Regex.TDFA ((=~))
import Hakyll.Core.Identifier
import Hakyll.Core.Identifier.Pattern.Internal
import Hakyll.Core.Util.String (removeWinPathSeparator)
instance IsString Pattern where
fromString :: String -> Pattern
fromString = String -> Pattern
fromGlob
fromGlob :: String -> Pattern
fromGlob :: String -> Pattern
fromGlob = [GlobComponent] -> Pattern
Glob forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [GlobComponent]
parse' forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
normalise
where
parse' :: String -> [GlobComponent]
parse' String
str =
let (String
chunk, String
rest) = forall a. (a -> Bool) -> [a] -> ([a], [a])
break (forall a. Eq a => a -> a -> Bool
== Char
'*') String
str
in case String
rest of
(Char
'*' : Char
'*' : String
xs) -> String -> GlobComponent
Literal String
chunk forall a. a -> [a] -> [a]
: GlobComponent
CaptureMany forall a. a -> [a] -> [a]
: String -> [GlobComponent]
parse' String
xs
(Char
'*' : String
xs) -> String -> GlobComponent
Literal String
chunk forall a. a -> [a] -> [a]
: GlobComponent
Capture forall a. a -> [a] -> [a]
: String -> [GlobComponent]
parse' String
xs
String
"" -> String -> GlobComponent
Literal String
chunk forall a. a -> [a] -> [a]
: []
String
xs -> String -> GlobComponent
Literal String
chunk forall a. a -> [a] -> [a]
: String -> GlobComponent
Literal String
xs forall a. a -> [a] -> [a]
: []
fromList :: [Identifier] -> Pattern
fromList :: [Identifier] -> Pattern
fromList = Set Identifier -> Pattern
List forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Ord a => [a] -> Set a
S.fromList
fromRegex :: String -> Pattern
fromRegex :: String -> Pattern
fromRegex = String -> Pattern
Regex
fromVersion :: Maybe String -> Pattern
fromVersion :: Maybe String -> Pattern
fromVersion = Maybe String -> Pattern
Version
hasVersion :: String -> Pattern
hasVersion :: String -> Pattern
hasVersion = Maybe String -> Pattern
fromVersion forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Maybe a
Just
hasNoVersion :: Pattern
hasNoVersion :: Pattern
hasNoVersion = Maybe String -> Pattern
fromVersion forall a. Maybe a
Nothing
(.&&.) :: Pattern -> Pattern -> Pattern
Pattern
x .&&. :: Pattern -> Pattern -> Pattern
.&&. Pattern
y = Pattern -> Pattern -> Pattern
And Pattern
x Pattern
y
infixr 3 .&&.
(.||.) :: Pattern -> Pattern -> Pattern
Pattern
x .||. :: Pattern -> Pattern -> Pattern
.||. Pattern
y = Pattern -> Pattern
complement (Pattern -> Pattern
complement Pattern
x Pattern -> Pattern -> Pattern
`And` Pattern -> Pattern
complement Pattern
y)
infixr 2 .||.
complement :: Pattern -> Pattern
complement :: Pattern -> Pattern
complement = Pattern -> Pattern
Complement
matches :: Pattern -> Identifier -> Bool
matches :: Pattern -> Identifier -> Bool
matches Pattern
Everything Identifier
_ = Bool
True
matches (Complement Pattern
p) Identifier
i = Bool -> Bool
not forall a b. (a -> b) -> a -> b
$ Pattern -> Identifier -> Bool
matches Pattern
p Identifier
i
matches (And Pattern
x Pattern
y) Identifier
i = Pattern -> Identifier -> Bool
matches Pattern
x Identifier
i Bool -> Bool -> Bool
&& Pattern -> Identifier -> Bool
matches Pattern
y Identifier
i
matches (Glob [GlobComponent]
p) Identifier
i = forall a. Maybe a -> Bool
isJust forall a b. (a -> b) -> a -> b
$ Pattern -> Identifier -> Maybe [String]
capture ([GlobComponent] -> Pattern
Glob [GlobComponent]
p) Identifier
i
matches (List Set Identifier
l) Identifier
i = Identifier
i forall a. Ord a => a -> Set a -> Bool
`S.member` Set Identifier
l
matches (Regex String
r) Identifier
i = (String -> String
removeWinPathSeparator forall a b. (a -> b) -> a -> b
$ Identifier -> String
toFilePath Identifier
i) forall source source1 target.
(RegexMaker Regex CompOption ExecOption source,
RegexContext Regex source1 target) =>
source1 -> source -> target
=~ String
r
matches (Version Maybe String
v) Identifier
i = Identifier -> Maybe String
identifierVersion Identifier
i forall a. Eq a => a -> a -> Bool
== Maybe String
v
filterMatches :: Pattern -> [Identifier] -> [Identifier]
filterMatches :: Pattern -> [Identifier] -> [Identifier]
filterMatches = forall a. (a -> Bool) -> [a] -> [a]
filter forall b c a. (b -> c) -> (a -> b) -> a -> c
. Pattern -> Identifier -> Bool
matches
splits :: [a] -> [([a], [a])]
splits :: forall a. [a] -> [([a], [a])]
splits = forall a. [a] -> [[a]]
inits forall (a :: * -> * -> *) b c c'.
Arrow a =>
a b c -> a b c' -> a b (c, c')
&&& forall a. [a] -> [[a]]
tails forall {k} (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry forall a b. [a] -> [b] -> [(a, b)]
zip forall {k} (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> forall a. [a] -> [a]
reverse
capture :: Pattern -> Identifier -> Maybe [String]
capture :: Pattern -> Identifier -> Maybe [String]
capture (Glob [GlobComponent]
p) Identifier
i = [GlobComponent] -> String -> Maybe [String]
capture' [GlobComponent]
p (Identifier -> String
toFilePath Identifier
i)
capture (Regex String
pat) Identifier
i = forall a. a -> Maybe a
Just [String]
groups
where (String
_, String
_, String
_, [String]
groups) = ((String -> String
removeWinPathSeparator forall a b. (a -> b) -> a -> b
$ Identifier -> String
toFilePath Identifier
i) forall source source1 target.
(RegexMaker Regex CompOption ExecOption source,
RegexContext Regex source1 target) =>
source1 -> source -> target
=~ String
pat) :: (String, String, String, [String])
capture Pattern
_ Identifier
_ = forall a. Maybe a
Nothing
capture' :: [GlobComponent] -> String -> Maybe [String]
capture' :: [GlobComponent] -> String -> Maybe [String]
capture' [] [] = forall a. a -> Maybe a
Just []
capture' [] String
_ = forall a. Maybe a
Nothing
capture' (Literal String
l : [GlobComponent]
ms) String
str
| String
l forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` String
str = [GlobComponent] -> String -> Maybe [String]
capture' [GlobComponent]
ms forall a b. (a -> b) -> a -> b
$ forall a. Int -> [a] -> [a]
drop (forall (t :: * -> *) a. Foldable t => t a -> Int
length String
l) String
str
| Bool
otherwise = forall a. Maybe a
Nothing
capture' (GlobComponent
Capture : [GlobComponent]
ms) String
str =
let (String
chunk, String
rest) = forall a. (a -> Bool) -> [a] -> ([a], [a])
break (forall a. Eq a => a -> a -> Bool
== Char
pathSeparator) String
str
in forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, MonadPlus m) =>
t (m a) -> m a
msum forall a b. (a -> b) -> a -> b
$ [ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (String
i forall a. a -> [a] -> [a]
:) ([GlobComponent] -> String -> Maybe [String]
capture' [GlobComponent]
ms (String
t forall a. [a] -> [a] -> [a]
++ String
rest)) | (String
i, String
t) <- forall a. [a] -> [([a], [a])]
splits String
chunk ]
capture' (GlobComponent
CaptureMany : [GlobComponent]
ms) String
str =
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, MonadPlus m) =>
t (m a) -> m a
msum forall a b. (a -> b) -> a -> b
$ [ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (String
i forall a. a -> [a] -> [a]
:) ([GlobComponent] -> String -> Maybe [String]
capture' [GlobComponent]
ms String
t) | (String
i, String
t) <- forall a. [a] -> [([a], [a])]
splits String
str ]
fromCapture :: Pattern -> String -> Identifier
fromCapture :: Pattern -> String -> Identifier
fromCapture Pattern
pattern = Pattern -> [String] -> Identifier
fromCaptures Pattern
pattern forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> [a]
repeat
fromCaptures :: Pattern -> [String] -> Identifier
fromCaptures :: Pattern -> [String] -> Identifier
fromCaptures (Glob [GlobComponent]
p) = String -> Identifier
fromFilePath forall b c a. (b -> c) -> (a -> b) -> a -> c
. [GlobComponent] -> [String] -> String
fromCaptures' [GlobComponent]
p
fromCaptures Pattern
_ = forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$
String
"Hakyll.Core.Identifier.Pattern.fromCaptures: fromCaptures only works " forall a. [a] -> [a] -> [a]
++
String
"on simple globs!"
fromCaptures' :: [GlobComponent] -> [String] -> String
fromCaptures' :: [GlobComponent] -> [String] -> String
fromCaptures' [] [String]
_ = forall a. Monoid a => a
mempty
fromCaptures' (GlobComponent
m : [GlobComponent]
ms) [] = case GlobComponent
m of
Literal String
l -> String
l forall a. Monoid a => a -> a -> a
`mappend` [GlobComponent] -> [String] -> String
fromCaptures' [GlobComponent]
ms []
GlobComponent
_ -> forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"Hakyll.Core.Identifier.Pattern.fromCaptures': "
forall a. [a] -> [a] -> [a]
++ String
"identifier list exhausted"
fromCaptures' (GlobComponent
m : [GlobComponent]
ms) ids :: [String]
ids@(String
i : [String]
is) = case GlobComponent
m of
Literal String
l -> String
l forall a. Monoid a => a -> a -> a
`mappend` [GlobComponent] -> [String] -> String
fromCaptures' [GlobComponent]
ms [String]
ids
GlobComponent
_ -> String
i forall a. Monoid a => a -> a -> a
`mappend` [GlobComponent] -> [String] -> String
fromCaptures' [GlobComponent]
ms [String]
is