diff options
Diffstat (limited to 'src/Hakyll/Core/Identifier/Pattern.hs')
-rw-r--r-- | src/Hakyll/Core/Identifier/Pattern.hs | 61 |
1 files changed, 40 insertions, 21 deletions
diff --git a/src/Hakyll/Core/Identifier/Pattern.hs b/src/Hakyll/Core/Identifier/Pattern.hs index cee4bbc..8263f29 100644 --- a/src/Hakyll/Core/Identifier/Pattern.hs +++ b/src/Hakyll/Core/Identifier/Pattern.hs @@ -31,10 +31,16 @@ -- The 'capture' function allows the user to get access to the elements captured -- by the capture elements in the pattern. -- +-- Like an 'Identifier', a 'Pattern' also has a type parameter. This is simply +-- an extra layer of safety, and can be discarded using the 'castPattern' +-- function. +-- module Hakyll.Core.Identifier.Pattern ( Pattern + , castPattern , parseGlob , predicate + , list , regex , inGroup , matches @@ -64,21 +70,28 @@ data GlobComponent = Capture -- | Type that allows matching on identifiers -- -data Pattern = Glob [GlobComponent] - | Predicate (Identifier -> Bool) +data Pattern a = Glob [GlobComponent] + | Predicate (Identifier a -> Bool) + | List [Identifier a] -instance IsString Pattern where +instance IsString (Pattern a) where fromString = parseGlob -instance Monoid Pattern where +instance Monoid (Pattern a) where mempty = Predicate (const True) - g@(Glob _) `mappend` x = Predicate (matches g) `mappend` x - x `mappend` g@(Glob _) = x `mappend` Predicate (matches g) - Predicate f `mappend` Predicate g = Predicate $ \i -> f i && g i + p1 `mappend` p2 = Predicate $ \i -> matches p1 i && matches p2 i + +-- | Discard the phantom type parameter +-- +castPattern :: Pattern a -> Pattern b +castPattern (Glob g) = Glob g +castPattern (Predicate p) = Predicate $ p . castIdentifier +castPattern (List l) = List $ map castIdentifier l +{-# INLINE castPattern #-} -- | Parse a pattern from a string -- -parseGlob :: String -> Pattern +parseGlob :: String -> Pattern a parseGlob = Glob . parse' where parse' str = @@ -95,33 +108,39 @@ parseGlob = Glob . parse' -- -- > predicate (\i -> matches "foo/*" i && not (matches "foo/bar" i)) -- -predicate :: (Identifier -> Bool) -> Pattern +predicate :: (Identifier a -> Bool) -> Pattern a predicate = Predicate +-- | Create a 'Pattern' from a list of 'Identifier's it should match +-- +list :: [Identifier a] -> Pattern a +list = List + -- | Create a 'Pattern' from a regex -- -- Example: -- -- > regex "^foo/[^x]*$ -- -regex :: String -> Pattern +regex :: String -> Pattern a regex str = predicate $ fromMaybe False . (=~~ str) . toFilePath -- | Create a 'Pattern' which matches if the identifier is in a certain group -- (or in no group) -- -inGroup :: Maybe String -> Pattern +inGroup :: Maybe String -> Pattern a inGroup group = predicate $ (== group) . identifierGroup -- | Check if an identifier matches a pattern -- -matches :: Pattern -> Identifier -> Bool +matches :: Pattern a -> Identifier a -> Bool matches (Glob p) = isJust . capture (Glob p) matches (Predicate p) = (p $) +matches (List l) = (`elem` l) -- | Given a list of identifiers, retain only those who match the given pattern -- -filterMatches :: Pattern -> [Identifier] -> [Identifier] +filterMatches :: Pattern a -> [Identifier a] -> [Identifier a] filterMatches = filter . matches -- | Split a list at every possible point, generate a list of (init, tail) @@ -132,9 +151,9 @@ splits = inits &&& tails >>> uncurry zip >>> reverse -- | Match a glob against a pattern, generating a list of captures -- -capture :: Pattern -> Identifier -> Maybe [String] +capture :: Pattern a -> Identifier a -> Maybe [String] capture (Glob p) (Identifier _ i) = capture' p i -capture (Predicate _) _ = Nothing +capture _ _ = Nothing -- | Internal verion of 'capture' -- @@ -164,17 +183,17 @@ capture' (CaptureMany : ms) str = -- -- > "tags/foo" -- -fromCapture :: Pattern -> String -> Identifier +fromCapture :: Pattern a -> String -> Identifier a fromCapture pattern = fromCaptures pattern . repeat -- | Create an identifier from a pattern by filling in the captures with the -- given list of strings -- -fromCaptures :: Pattern -> [String] -> Identifier -fromCaptures (Glob p) = Identifier Nothing . fromCaptures' p -fromCaptures (Predicate _) = error $ - "Hakyll.Core.Identifier.Pattern.fromCaptures: fromCaptures called on a " ++ - "predicate instead of a glob" +fromCaptures :: Pattern a -> [String] -> Identifier a +fromCaptures (Glob p) = Identifier Nothing . fromCaptures' p +fromCaptures _ = error $ + "Hakyll.Core.Identifier.Pattern.fromCaptures: fromCaptures only works " ++ + "on simple globs!" -- | Internally used version of 'fromCaptures' -- |