module Issue.Filter ( Filter, filterArg, applyFilters, applyClosed, applyPath, ) where import Control.Applicative (liftA2, (<|>)) import Data.Attoparsec.Text qualified as A import Data.List (isPrefixOf) import Data.Text qualified as T import Issue (Issue (..)) import Issue.Tag (tagKey, tagValue) import Issue.TypedValue (castDef) import Options.Applicative qualified as O import Text.RE.TDFA.Text qualified as R -- TODO Revise filter negation -- -- Currently the following syntax in valid: -- -- ``` -- --filter !@t (*) -- --filter !@t v -- --filter !@t modeParser <*> simpleFilterParser where modeParser :: A.Parser Mode modeParser = (const Exclude <$> A.string "!") <|> (pure Include) simpleFilterParser :: A.Parser SimpleFilter simpleFilterParser = byTagParser byTagParser :: A.Parser SimpleFilter byTagParser = ByTag <$> (A.string "@" *> A.takeWhile1 (/= ' ') <* A.skipSpace) <*> ((Just <$> testParser) <|> pure Nothing) data Test = Eq T.Text | Ge T.Text | Gt T.Text | Le T.Text | Lt T.Text | Match R.RE testParser :: A.Parser Test testParser = A.choice [ A.try ( A.string "/" *> ( Match <$> ( R.compileRegex . T.unpack . T.concat =<< O.many ( A.choice [ A.string "\\" *> A.string "/", A.string "\\" *> A.string "\\", T.pack . (: []) <$> A.notChar '/' ] ) ) ) <* A.string "/" ), A.try (A.string ">=" *> (Ge . T.pack <$> value)), A.try (A.string "<=" *> (Le . T.pack <$> value)), A.try (A.string ">" *> (Gt . T.pack <$> value)), A.try (A.string "<" *> (Lt . T.pack <$> value)), (Eq . T.pack <$> A.many1 A.anyChar) ] where value = A.many1 A.anyChar filterArg :: O.Parser [Filter] filterArg = O.many ( O.option (O.eitherReader (A.parseOnly filterParser . T.pack)) ( O.long "filter" <> O.short 'f' <> O.metavar "FILTER" <> O.help "Filters selected issues. Examples: @assigned, !@assigned joe" ) ) applyFilters :: [Filter] -> ([Issue] -> [Issue]) applyFilters fs = filter (filtersPredicate fs) filtersPredicate :: [Filter] -> (Issue -> Bool) filtersPredicate [] = \_ -> True filtersPredicate fs = foldr1 (liftA2 (&&)) (map filterPredicate fs) filterPredicate :: Filter -> (Issue -> Bool) filterPredicate (Filter m sf) = modePredicate m (simpleFilterPredicate sf) modePredicate :: Mode -> (Issue -> Bool) -> (Issue -> Bool) modePredicate Include p = p modePredicate Exclude p = not . p simpleFilterPredicate :: SimpleFilter -> (Issue -> Bool) simpleFilterPredicate (ByTag k v) i = any ((&&) <$> matchKey <*> matchValue) (i.tags ++ i.internalTags) where matchKey = (==) k . tagKey matchValue t = case (v, tagValue t) of (Just (Eq v'), Just w') -> castDef False (==) w' v' (Just (Ge v'), Just w') -> castDef False (>=) w' v' (Just (Gt v'), Just w') -> castDef False (>) w' v' (Just (Le v'), Just w') -> castDef False (<=) w' v' (Just (Lt v'), Just w') -> castDef False (<) w' v' (Just (Match p), Just w') -> R.matched (w' R.?=~ p) (Just _, Nothing) -> False (Nothing, _) -> True applyClosed :: Bool -> [Issue] -> [Issue] applyClosed closed = filter (\issue -> closed || not issue.closed) applyPath :: [FilePath] -> [Issue] -> [Issue] applyPath files = filter ( \issue -> if null files then True else any (`isPrefixOf` issue.file) files )