don't implicitly include all when exclude options are used

This is less erorr-prone, and easier for the user to reason about; it
preserves the man page's promise that only explicitly included
information will be copied.
This commit is contained in:
Joey Hess 2021-05-14 14:14:46 -04:00
parent a58c90ccf4
commit 80a9944f3b
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38
2 changed files with 68 additions and 53 deletions

View file

@ -9,6 +9,8 @@ module Command.FilterBranch where
import Command
import qualified Data.Set as S
cmd :: Command
cmd = withGlobalOptions [annexedMatchingOptions] $
command "filter-branch" SectionMaintenance
@ -18,61 +20,73 @@ cmd = withGlobalOptions [annexedMatchingOptions] $
data FilterBranchOptions = FilterBranchOptions
{ includeFiles :: CmdParams
, keyOptions :: Maybe KeyOptions
, includeKeyInformationFor :: [DeferredParse UUID]
, excludeKeyInformationFor :: [DeferredParse UUID]
, includeAllKeyInformation :: Bool
, includeRepoConfigFor :: [DeferredParse UUID]
, excludeRepoConfigFor :: [DeferredParse UUID]
, includeAllRemoteConfig :: Bool
, keyInformation :: [IncludeExclude (DeferredParse UUID)]
, repoConfig :: [IncludeExclude (DeferredParse UUID)]
, includeGlobalConfig :: Bool
, excludeGlobalConfig :: Bool
}
optParser :: CmdParamsDesc -> Parser FilterBranchOptions
optParser desc = FilterBranchOptions
<$> cmdParams desc
<*> optional parseKeyOptions
<*> many
( parseRepositoryOption "include-key-information-for"
"include key information for a repository"
)
<*> many
( parseRepositoryOption "exclude-key-information-for"
"exclude key information for a repository"
)
<*> switch
( long "include-all-key-information"
<> help "include key information for all repositories"
)
<*> many
( parseRepositoryOption "include-repo-config-for"
"include configuration specific to a repository"
)
<*> many
( parseRepositoryOption "exclude-repo-config-for"
"exclude configuration specific to a repository"
)
<*> switch
( long "include-all-repo-config"
<> help "include configuration of all repositories"
)
<*> many (parseIncludeExclude "key-information")
<*> many (parseIncludeExclude "repo-config")
<*> switch
( long "include-global-config"
<> help "include global configuration"
)
<*> switch
( long "exclude-global-config"
<> help "exclude global configuration"
data IncludeExclude t
= Include t
| Exclude t
| IncludeAll
deriving (Show, Eq, Ord)
isInclude :: IncludeExclude t -> Bool
isInclude (Include _) = True
isInclude IncludeAll = True
isInclude (Exclude _) = False
parseIncludeExclude :: String -> Parser (IncludeExclude (DeferredParse UUID))
parseIncludeExclude s =
( Include <$> parseRepositoryOption
("include-" ++ s ++ "-for")
"include information about a repository"
) <|>
( Exclude <$> parseRepositoryOption
("exclude-" ++ s ++ "-for")
"exclude information about a repository"
) <|>
( flag' IncludeAll
( long ("include-all-" ++ s)
<> help "include information about all non-excluded repositories"
)
)
parseRepositoryOption :: String -> String -> Parser (DeferredParse UUID)
parseRepositoryOption s h = parseUUIDOption <$> strOption
( long s
<> metavar (paramRemote `paramOr` paramDesc `paramOr` paramUUID)
<> help h
<> metavar (paramRemote `paramOr` paramDesc `paramOr` paramUUID)
<> completeRemotes
)
mkUUIDMatcher :: [IncludeExclude (DeferredParse UUID)] -> Annex (UUID -> Bool)
mkUUIDMatcher l = mkUUIDMatcher' <$> mapM get l
where
get (Include v) = Include <$> getParsed v
get (Exclude v) = Exclude <$> getParsed v
get IncludeAll = pure IncludeAll
mkUUIDMatcher' :: [IncludeExclude UUID] -> (UUID -> Bool)
mkUUIDMatcher' l = \u ->
(S.member (Include u) includes || S.member IncludeAll includes)
&& S.notMember (Exclude u) excludes
where
(includes, excludes) = S.partition isInclude (S.fromList l)
seek :: FilterBranchOptions -> CommandSeek
seek o = do
keyinfomatcher <- mkUUIDMatcher (keyInformation o)
configinfomatcher <- mkUUIDMatcher (repoConfig o)
error "TODO"