add directory to views for files that lack specified metadata

* view: New field?=glob and ?tag syntax that includes a directory "_"
  in the view for files that do not have the specified metadata set.
* Added annex.viewunsetdirectory git config to change the name of the
  "_" directory in a view.

When in a view using the new syntax, old git-annex will fail to parse the
view log. It errors with "Not in a view.", which is not ideal. But that
only affects view commands.

annex.viewunsetdirectory is included in the View for a couple of reasons.
One is to avoid needing to warn the user that it should not be changed when
in a view, since that would confuse git-annex. Another reason is that it
helped with plumbing the value through to some pure functions.

annex.viewunsetdirectory is actually mangled the same as any other view
directory. So if it's configured to something like "N/A", there won't be
multiple levels of directories, which would also confuse git-annex.

Sponsored-By: Jack Hill on Patreon
This commit is contained in:
Joey Hess 2023-02-07 16:28:46 -04:00
parent fb30ad7846
commit aa0350ff49
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38
14 changed files with 179 additions and 50 deletions

View file

@ -1,6 +1,6 @@
{- metadata based branch views {- metadata based branch views
- -
- Copyright 2014 Joey Hess <id@joeyh.name> - Copyright 2014-2023 Joey Hess <id@joeyh.name>
- -
- Licensed under the GNU AGPL version 3 or higher. - Licensed under the GNU AGPL version 3 or higher.
-} -}
@ -56,19 +56,23 @@ viewTooLarge view = visibleViewSize view > 5
visibleViewSize :: View -> Int visibleViewSize :: View -> Int
visibleViewSize = length . filter viewVisible . viewComponents visibleViewSize = length . filter viewVisible . viewComponents
{- Parses field=value, field!=value, tag, and !tag {- Parses field=value, field!=value, field?=value, tag, !tag, and ?tag
- -
- Note that the field may not be a legal metadata field name, - Note that the field may not be a legal metadata field name,
- but it's let through anyway. - but it's let through anyway.
- This is useful when matching on directory names with spaces, - This is useful when matching on directory names with spaces,
- which are not legal MetaFields. - which are not legal MetaFields.
-} -}
parseViewParam :: String -> (MetaField, ViewFilter) parseViewParam :: ViewUnset -> String -> (MetaField, ViewFilter)
parseViewParam s = case separate (== '=') s of parseViewParam vu s = case separate (== '=') s of
('!':tag, []) | not (null tag) -> ('!':tag, []) | not (null tag) ->
( tagMetaField ( tagMetaField
, mkExcludeValues tag , mkExcludeValues tag
) )
('?':tag, []) | not (null tag) ->
( tagMetaField
, mkFilterOrUnsetValues tag
)
(tag, []) -> (tag, []) ->
( tagMetaField ( tagMetaField
, mkFilterValues tag , mkFilterValues tag
@ -78,15 +82,22 @@ parseViewParam s = case separate (== '=') s of
( mkMetaFieldUnchecked (T.pack (beginning field)) ( mkMetaFieldUnchecked (T.pack (beginning field))
, mkExcludeValues wanted , mkExcludeValues wanted
) )
| end field == "?" ->
( mkMetaFieldUnchecked (T.pack (beginning field))
, mkFilterOrUnsetValues wanted
)
| otherwise -> | otherwise ->
( mkMetaFieldUnchecked (T.pack field) ( mkMetaFieldUnchecked (T.pack field)
, mkFilterValues wanted , mkFilterValues wanted
) )
where where
mkExcludeValues = ExcludeValues . S.singleton . toMetaValue . encodeBS
mkFilterValues v mkFilterValues v
| any (`elem` v) ['*', '?'] = FilterGlob v | any (`elem` v) ['*', '?'] = FilterGlob v
| otherwise = FilterValues $ S.singleton $ toMetaValue $ encodeBS v | otherwise = FilterValues $ S.singleton $ toMetaValue $ encodeBS v
mkExcludeValues = ExcludeValues . S.singleton . toMetaValue . encodeBS mkFilterOrUnsetValues v
| any (`elem` v) ['*', '?'] = FilterGlobOrUnset v vu
| otherwise = FilterValuesOrUnset (S.singleton $ toMetaValue $ encodeBS v) vu
data ViewChange = Unchanged | Narrowing | Widening data ViewChange = Unchanged | Narrowing | Widening
deriving (Ord, Eq, Show) deriving (Ord, Eq, Show)
@ -136,18 +147,8 @@ filterView v vs = v { viewComponents = viewComponents f' ++ viewComponents v}
toinvisible c = c { viewVisible = False } toinvisible c = c { viewVisible = False }
{- Combine old and new ViewFilters, yielding a result that matches {- Combine old and new ViewFilters, yielding a result that matches
- either old+new, or only new. - either old+new, or only new. Which depends on the types of things
- - being combined.
- If we have FilterValues and change to a FilterGlob,
- it's always a widening change, because the glob could match other
- values. OTOH, going the other way, it's a Narrowing change if the old
- glob matches all the new FilterValues.
-
- With two globs, the old one is discarded, and the new one is used.
- We can tell if that's a narrowing change by checking if the old
- glob matches the new glob. For example, "*" matches "foo*",
- so that's narrowing. While "f?o" does not match "f??", so that's
- widening.
-} -}
combineViewFilter :: ViewFilter -> ViewFilter -> (ViewFilter, ViewChange) combineViewFilter :: ViewFilter -> ViewFilter -> (ViewFilter, ViewChange)
combineViewFilter old@(FilterValues olds) (FilterValues news) combineViewFilter old@(FilterValues olds) (FilterValues news)
@ -160,19 +161,74 @@ combineViewFilter old@(ExcludeValues olds) (ExcludeValues news)
| otherwise = (combined, Narrowing) | otherwise = (combined, Narrowing)
where where
combined = ExcludeValues (S.union olds news) combined = ExcludeValues (S.union olds news)
{- If we have FilterValues and change to a FilterGlob,
- it's always a widening change, because the glob could match other
- values. OTOH, going the other way, it's a Narrowing change if the old
- glob matches all the new FilterValues. -}
combineViewFilter (FilterValues _) newglob@(FilterGlob _) = combineViewFilter (FilterValues _) newglob@(FilterGlob _) =
(newglob, Widening) (newglob, Widening)
combineViewFilter (FilterGlob oldglob) new@(FilterValues s) combineViewFilter (FilterGlob oldglob) new@(FilterValues s)
| all (matchGlob (compileGlob oldglob CaseInsensative (GlobFilePath False)) . decodeBS . fromMetaValue) (S.toList s) = (new, Narrowing) | all (matchGlob (compileGlob oldglob CaseInsensative (GlobFilePath False)) . decodeBS . fromMetaValue) (S.toList s) = (new, Narrowing)
| otherwise = (new, Widening) | otherwise = (new, Widening)
{- With two globs, the old one is discarded, and the new one is used.
- We can tell if that's a narrowing change by checking if the old
- glob matches the new glob. For example, "*" matches "foo*",
- so that's narrowing. While "f?o" does not match "f??", so that's
- widening. -}
combineViewFilter (FilterGlob old) newglob@(FilterGlob new) combineViewFilter (FilterGlob old) newglob@(FilterGlob new)
| old == new = (newglob, Unchanged) | old == new = (newglob, Unchanged)
| matchGlob (compileGlob old CaseInsensative (GlobFilePath False)) new = (newglob, Narrowing) | matchGlob (compileGlob old CaseInsensative (GlobFilePath False)) new = (newglob, Narrowing)
| otherwise = (newglob, Widening) | otherwise = (newglob, Widening)
{- Combining FilterValuesOrUnset and FilterGlobOrUnset with FilterValues
- and FilterGlob maintains the OrUnset if the second parameter has it,
- and is otherwise the same as combining without OrUnset, except that
- eliminating the OrUnset can be narrowing, and adding it can be widening. -}
combineViewFilter old@(FilterValuesOrUnset olds _) (FilterValuesOrUnset news newvu)
| combined == old = (combined, Unchanged)
| otherwise = (combined, Widening)
where
combined = FilterValuesOrUnset (S.union olds news) newvu
combineViewFilter (FilterValues olds) (FilterValuesOrUnset news vu) =
(combined, Widening)
where
combined = FilterValuesOrUnset (S.union olds news) vu
combineViewFilter old@(FilterValuesOrUnset olds _) (FilterValues news)
| combined == old = (combined, Narrowing)
| otherwise = (combined, Widening)
where
combined = FilterValues (S.union olds news)
combineViewFilter (FilterValuesOrUnset _ _) newglob@(FilterGlob _) =
(newglob, Widening)
combineViewFilter (FilterGlob _) new@(FilterValuesOrUnset _ _) =
(new, Widening)
combineViewFilter (FilterValues _) newglob@(FilterGlobOrUnset _ _) =
(newglob, Widening)
combineViewFilter (FilterValuesOrUnset _ _) newglob@(FilterGlobOrUnset _ _) =
(newglob, Widening)
combineViewFilter (FilterGlobOrUnset oldglob _) new@(FilterValues _) =
combineViewFilter (FilterGlob oldglob) new
combineViewFilter (FilterGlobOrUnset oldglob _) new@(FilterValuesOrUnset _ _) =
let (_, viewchange) = combineViewFilter (FilterGlob oldglob) new
in (new, viewchange)
combineViewFilter (FilterGlobOrUnset old _) newglob@(FilterGlobOrUnset new _)
| old == new = (newglob, Unchanged)
| matchGlob (compileGlob old CaseInsensative (GlobFilePath False)) new = (newglob, Narrowing)
| otherwise = (newglob, Widening)
combineViewFilter (FilterGlob _) newglob@(FilterGlobOrUnset _ _) =
(newglob, Widening)
combineViewFilter (FilterGlobOrUnset _ _) newglob@(FilterGlob _) =
(newglob, Narrowing)
{- There is not a way to filter a value and also apply an exclude. So:
- When adding an exclude to a filter, use only the exclude.
- When adding a filter to an exclude, use only the filter. -}
combineViewFilter (FilterGlob _) new@(ExcludeValues _) = (new, Narrowing) combineViewFilter (FilterGlob _) new@(ExcludeValues _) = (new, Narrowing)
combineViewFilter (ExcludeValues _) new@(FilterGlob _) = (new, Widening) combineViewFilter (ExcludeValues _) new@(FilterGlob _) = (new, Widening)
combineViewFilter (FilterValues _) new@(ExcludeValues _) = (new, Narrowing) combineViewFilter (FilterValues _) new@(ExcludeValues _) = (new, Narrowing)
combineViewFilter (ExcludeValues _) new@(FilterValues _) = (new, Widening) combineViewFilter (ExcludeValues _) new@(FilterValues _) = (new, Widening)
combineViewFilter (FilterValuesOrUnset _ _) new@(ExcludeValues _) = (new, Narrowing)
combineViewFilter (ExcludeValues _) new@(FilterValuesOrUnset _ _) = (new, Widening)
combineViewFilter (FilterGlobOrUnset _ _) new@(ExcludeValues _) = (new, Narrowing)
combineViewFilter (ExcludeValues _) new@(FilterGlobOrUnset _ _) = (new, Widening)
{- Generates views for a file from a branch, based on its metadata {- Generates views for a file from a branch, based on its metadata
- and the filename used in the branch. - and the filename used in the branch.
@ -196,7 +252,7 @@ viewedFiles view =
then [] then []
else else
let paths = pathProduct $ let paths = pathProduct $
map (map toViewPath) (visible matches) map (map toviewpath) (visible matches)
in if null paths in if null paths
then [mkviewedfile file] then [mkviewedfile file]
else map (</> mkviewedfile file) paths else map (</> mkviewedfile file) paths
@ -204,28 +260,40 @@ viewedFiles view =
visible = map (fromJust . snd) . visible = map (fromJust . snd) .
filter (viewVisible . fst) . filter (viewVisible . fst) .
zip (viewComponents view) zip (viewComponents view)
toviewpath (MatchingMetaValue v) = toViewPath v
toviewpath (MatchingUnset v) = toViewPath (toMetaValue (encodeBS v))
data MatchingValue = MatchingMetaValue MetaValue | MatchingUnset String
{- Checks if metadata matches a ViewComponent filter, and if so {- Checks if metadata matches a ViewComponent filter, and if so
- returns the value, or values that match. Self-memoizing on ViewComponent. -} - returns the value, or values that match. Self-memoizing on ViewComponent. -}
viewComponentMatcher :: ViewComponent -> (MetaData -> Maybe [MetaValue]) viewComponentMatcher :: ViewComponent -> (MetaData -> Maybe [MatchingValue])
viewComponentMatcher viewcomponent = \metadata -> viewComponentMatcher viewcomponent = \metadata ->
matcher (currentMetaDataValues metafield metadata) matcher Nothing (viewFilter viewcomponent)
(currentMetaDataValues metafield metadata)
where where
metafield = viewField viewcomponent metafield = viewField viewcomponent
matcher = case viewFilter viewcomponent of matcher matchunset (FilterValues s) =
FilterValues s -> \values -> setmatches $ \values -> setmatches matchunset $ S.intersection s values
S.intersection s values matcher matchunset (FilterGlob glob) =
FilterGlob glob -> let cglob = compileGlob glob CaseInsensative (GlobFilePath False)
let cglob = compileGlob glob CaseInsensative (GlobFilePath False) in \values -> setmatches matchunset $
in \values -> setmatches $ S.filter (matchGlob cglob . decodeBS . fromMetaValue) values
S.filter (matchGlob cglob . decodeBS . fromMetaValue) values matcher _ (ExcludeValues excludes) =
ExcludeValues excludes -> \values -> \values ->
if S.null (S.intersection values excludes) if S.null (S.intersection values excludes)
then Just [] then Just []
else Nothing else Nothing
setmatches s matcher _ (FilterValuesOrUnset s (ViewUnset u)) =
| S.null s = Nothing matcher (Just [MatchingUnset u]) (FilterValues s)
| otherwise = Just (S.toList s) matcher _ (FilterGlobOrUnset glob (ViewUnset u)) =
matcher (Just [MatchingUnset u]) (FilterGlob glob)
setmatches matchunset s
| S.null s = matchunset
| otherwise = Just $
map MatchingMetaValue (S.toList s)
-- This is '', a unicode character that displays the same as '/' but is -- This is '', a unicode character that displays the same as '/' but is
-- not it. It is encoded using the filesystem encoding, which allows it -- not it. It is encoded using the filesystem encoding, which allows it
@ -282,14 +350,25 @@ pathProduct (l:ls) = foldl combinel l ls
- Derived metadata is excluded. - Derived metadata is excluded.
-} -}
fromView :: View -> ViewedFile -> MetaData fromView :: View -> ViewedFile -> MetaData
fromView view f = MetaData $ fromView view f = MetaData $ m `M.difference` derived
M.fromList (zip fields values) `M.difference` derived
where where
m = M.fromList $ map convfield $
filter (not . isviewunset) (zip visible values)
visible = filter viewVisible (viewComponents view) visible = filter viewVisible (viewComponents view)
fields = map viewField visible
paths = splitDirectories (dropFileName f) paths = splitDirectories (dropFileName f)
values = map (S.singleton . fromViewPath) paths values = map (S.singleton . fromViewPath) paths
MetaData derived = getViewedFileMetaData f MetaData derived = getViewedFileMetaData f
convfield (vc, v) = (viewField vc, v)
-- When a directory is the one used to hold files that don't
-- have the metadata set, don't include it in the MetaData.
isviewunset (vc, v) = case viewFilter vc of
FilterValues {} -> False
FilterGlob {} -> False
ExcludeValues {} -> False
FilterValuesOrUnset _ (ViewUnset vu) -> isviewunset' vu v
FilterGlobOrUnset _ (ViewUnset vu) -> isviewunset' vu v
isviewunset' vu v = S.member (fromViewPath vu) v
{- Constructing a view that will match arbitrary metadata, and applying {- Constructing a view that will match arbitrary metadata, and applying
- it to a file yields a set of ViewedFile which all contain the same - it to a file yields a set of ViewedFile which all contain the same

View file

@ -2,6 +2,10 @@ git-annex (10.20230127) UNRELEASED; urgency=medium
* S3: Support a region= configuration useful for some non-Amazon S3 * S3: Support a region= configuration useful for some non-Amazon S3
implementations. This feature needs git-annex to be built with aws-0.24. implementations. This feature needs git-annex to be built with aws-0.24.
* view: New field?=glob and ?tag syntax that includes a directory "_"
in the view for files that do not have the specified metadata set.
* Added annex.viewunsetdirectory git config to change the name of the
"_" directory in a view.
-- Joey Hess <id@joeyh.name> Mon, 06 Feb 2023 13:39:18 -0400 -- Joey Hess <id@joeyh.name> Mon, 06 Feb 2023 13:39:18 -0400

View file

@ -8,6 +8,7 @@
module Command.VAdd where module Command.VAdd where
import Command import Command
import qualified Annex
import Annex.View import Annex.View
import Command.View (checkoutViewBranch) import Command.View (checkoutViewBranch)
@ -24,8 +25,9 @@ seek = withWords (commandAction . start)
start :: [String] -> CommandStart start :: [String] -> CommandStart
start params = starting "vadd" (ActionItemOther Nothing) (SeekInput params) $ start params = starting "vadd" (ActionItemOther Nothing) (SeekInput params) $
withCurrentView $ \view -> do withCurrentView $ \view -> do
vu <- annexViewUnsetDirectory <$> Annex.getGitConfig
let (view', change) = refineView view $ let (view', change) = refineView view $
map parseViewParam $ reverse params map (parseViewParam vu) (reverse params)
case change of case change of
Unchanged -> do Unchanged -> do
showNote "unchanged" showNote "unchanged"

View file

@ -8,6 +8,7 @@
module Command.VFilter where module Command.VFilter where
import Command import Command
import qualified Annex
import Annex.View import Annex.View
import Command.View (paramView, checkoutViewBranch) import Command.View (paramView, checkoutViewBranch)
@ -22,8 +23,9 @@ seek = withWords (commandAction . start)
start :: [String] -> CommandStart start :: [String] -> CommandStart
start params = starting "vfilter" (ActionItemOther Nothing) (SeekInput params) $ start params = starting "vfilter" (ActionItemOther Nothing) (SeekInput params) $
withCurrentView $ \view -> do withCurrentView $ \view -> do
vu <- annexViewUnsetDirectory <$> Annex.getGitConfig
let view' = filterView view $ let view' = filterView view $
map parseViewParam $ reverse params map (parseViewParam vu) (reverse params)
next $ if visibleViewSize view' > visibleViewSize view next $ if visibleViewSize view' > visibleViewSize view
then giveup "That would add an additional level of directory structure to the view, rather than filtering it. If you want to do that, use vadd instead of vfilter." then giveup "That would add an additional level of directory structure to the view, rather than filtering it. If you want to do that, use vadd instead of vfilter."
else checkoutViewBranch view' narrowView else checkoutViewBranch view' narrowView

View file

@ -8,6 +8,7 @@
module Command.View where module Command.View where
import Command import Command
import qualified Annex
import qualified Git import qualified Git
import qualified Git.Command import qualified Git.Command
import qualified Git.Ref import qualified Git.Ref
@ -83,8 +84,10 @@ mkView :: [String] -> Annex View
mkView ps = go =<< inRepo Git.Branch.current mkView ps = go =<< inRepo Git.Branch.current
where where
go Nothing = giveup "not on any branch!" go Nothing = giveup "not on any branch!"
go (Just b) = return $ fst $ refineView (View b []) $ go (Just b) = do
map parseViewParam $ reverse ps vu <- annexViewUnsetDirectory <$> Annex.getGitConfig
return $ fst $ refineView (View b []) $
map (parseViewParam vu) (reverse ps)
checkoutViewBranch :: View -> (View -> Annex Git.Branch) -> CommandCleanup checkoutViewBranch :: View -> (View -> Annex Git.Branch) -> CommandCleanup
checkoutViewBranch view mkbranch = do checkoutViewBranch view mkbranch = do

View file

@ -86,6 +86,8 @@ branchView view
branchvals (FilterValues set) = '=' : branchset set branchvals (FilterValues set) = '=' : branchset set
branchvals (FilterGlob glob) = '=' : forcelegal glob branchvals (FilterGlob glob) = '=' : forcelegal glob
branchvals (ExcludeValues set) = "!=" ++ branchset set branchvals (ExcludeValues set) = "!=" ++ branchset set
branchvals (FilterValuesOrUnset set _) = '=' : branchset set
branchvals (FilterGlobOrUnset glob _) = '=' : forcelegal glob
branchset = intercalate "," branchset = intercalate ","
. map (forcelegal . decodeBS . fromMetaValue) . map (forcelegal . decodeBS . fromMetaValue)
. S.toList . S.toList

View file

@ -43,6 +43,7 @@ import Types.Difference
import Types.RefSpec import Types.RefSpec
import Types.RepoVersion import Types.RepoVersion
import Types.StallDetection import Types.StallDetection
import Types.View
import Config.DynamicConfig import Config.DynamicConfig
import Utility.HumanTime import Utility.HumanTime
import Utility.Gpg (GpgCmd, mkGpgCmd) import Utility.Gpg (GpgCmd, mkGpgCmd)
@ -145,6 +146,7 @@ data GitConfig = GitConfig
, mergeDirectoryRenames :: Maybe String , mergeDirectoryRenames :: Maybe String
, annexPrivateRepos :: S.Set UUID , annexPrivateRepos :: S.Set UUID
, annexAdviceNoSshCaching :: Bool , annexAdviceNoSshCaching :: Bool
, annexViewUnsetDirectory :: ViewUnset
} }
extractGitConfig :: ConfigSource -> Git.Repo -> GitConfig extractGitConfig :: ConfigSource -> Git.Repo -> GitConfig
@ -266,6 +268,8 @@ extractGitConfig configsource r = GitConfig
in mapMaybe get (M.toList (Git.config r)) in mapMaybe get (M.toList (Git.config r))
] ]
, annexAdviceNoSshCaching = getbool (annexConfig "advicenosshcaching") True , annexAdviceNoSshCaching = getbool (annexConfig "advicenosshcaching") True
, annexViewUnsetDirectory = ViewUnset $ fromMaybe "_" $
getmaybe (annexConfig "viewunsetdirectory")
} }
where where
getbool k d = fromMaybe d $ getmaybebool k getbool k d = fromMaybe d $ getmaybebool k

View file

@ -1,6 +1,6 @@
{- types for metadata based branch views {- types for metadata based branch views
- -
- Copyright 2014 Joey Hess <id@joeyh.name> - Copyright 2014-2023 Joey Hess <id@joeyh.name>
- -
- Licensed under the GNU AGPL version 3 or higher. - Licensed under the GNU AGPL version 3 or higher.
-} -}
@ -9,9 +9,9 @@
module Types.View where module Types.View where
import Annex.Common
import Types.MetaData import Types.MetaData
import Utility.QuickCheck import Utility.QuickCheck
import Utility.Monad
import qualified Git import qualified Git
import qualified Data.Set as S import qualified Data.Set as S
@ -42,6 +42,11 @@ data ViewFilter
= FilterValues (S.Set MetaValue) = FilterValues (S.Set MetaValue)
| FilterGlob String | FilterGlob String
| ExcludeValues (S.Set MetaValue) | ExcludeValues (S.Set MetaValue)
| FilterValuesOrUnset (S.Set MetaValue) ViewUnset
| FilterGlobOrUnset String ViewUnset
deriving (Eq, Read, Show)
newtype ViewUnset = ViewUnset String
deriving (Eq, Read, Show) deriving (Eq, Read, Show)
instance Arbitrary ViewFilter where instance Arbitrary ViewFilter where
@ -60,3 +65,5 @@ multiValue :: ViewFilter -> Bool
multiValue (FilterValues s) = S.size s > 1 multiValue (FilterValues s) = S.size s > 1
multiValue (FilterGlob _) = True multiValue (FilterGlob _) = True
multiValue (ExcludeValues _) = False multiValue (ExcludeValues _) = False
multiValue (FilterValuesOrUnset _ _) = True
multiValue (FilterGlobOrUnset _ _) = True

View file

@ -4,7 +4,7 @@ git-annex vadd - add subdirs to current view
# SYNOPSIS # SYNOPSIS
git annex vadd `[field=glob ...] [field=value ...] [tag ...]` git annex vadd `[field=glob ...] [field=value ...] [tag ...] [?tag ...] [field?=glob]`
# DESCRIPTION # DESCRIPTION

View file

@ -4,7 +4,7 @@ git-annex vfilter - filter current view
# SYNOPSIS # SYNOPSIS
git annex vfilter `[tag ...] [field=value ...] [!tag ...] [field!=value ...]` git annex vfilter `[tag ...] [field=value ...] [?tag ...] [field?=glob] [!tag ...] [field!=value ...]`
# DESCRIPTION # DESCRIPTION

View file

@ -4,7 +4,7 @@ git-annex view - enter a view branch
# SYNOPSIS # SYNOPSIS
git annex view `[tag ...] [field=value ...] [field=glob ...] [!tag ...] [field!=value ...]` git annex view `[tag ...] [field=value ...] [field=glob ...] [?tag ...] [field?=glob] [!tag ...] [field!=value ...]`
# DESCRIPTION # DESCRIPTION
@ -21,12 +21,12 @@ Once within such a view, you can make additional directories, and
copy or move files into them. When you commit, the metadata will copy or move files into them. When you commit, the metadata will
be updated to correspond to your changes. Deleting files and committing be updated to correspond to your changes. Deleting files and committing
also updates the metadata. also updates the metadata.
There are fields corresponding to the path to the file. So a file As well as the usual metadata, there are fields available corresponding
"foo/bar/baz/file" has fields "/=foo", "foo/=bar", and "foo/bar/=baz". to the path to the file. So a file "foo/bar/baz/file" has fields "/=foo",
These location fields can be used the same as other metadata to construct "foo/=bar", and "foo/bar/=baz". These location fields can be used the
the view. same as other metadata to construct the view.
For example, `/=foo` will only include files from the foo For example, `/=foo` will only include files from the foo
directory in the view, while `foo/=*` will preserve the directory in the view, while `foo/=*` will preserve the
subdirectories of the foo directory in the view. subdirectories of the foo directory in the view.
@ -34,6 +34,16 @@ subdirectories of the foo directory in the view.
To enter a view containing only files that lack a given metadata To enter a view containing only files that lack a given metadata
value or tag, specify field!=value or !tag. (Globs cannot be used here.) value or tag, specify field!=value or !tag. (Globs cannot be used here.)
`field?=*` is like `field=*` but adds an additional directory named `_` (by
default) that contains files that do not have the field set to any value.
Similarly, `?tag` adds an additional directory named `_` that contains
files that do not have any tags set. Moving files from the `_` directory to
another directory and committing will set the metadata. And moving files
into the `_` directory and committing will unset the metadata.
The name of the `_` directory can be changed using the annex.viewunsetdirectory
git config.
# OPTIONS # OPTIONS
* The [[git-annex-common-options]](1) can be used. * The [[git-annex-common-options]](1) can be used.

View file

@ -506,7 +506,7 @@ content from the key-value store.
See [[git-annex-metadata]](1) for details. See [[git-annex-metadata]](1) for details.
* `view [tag ...] [field=value ...] [field=glob ...] [!tag ...] [field!=value ...]` * `view [tag ...] [field=value ...] [field=glob ...] [?tag ...] [field?=glob] [!tag ...] [field!=value ...]`
Uses metadata to build a view branch of the files in the current branch, Uses metadata to build a view branch of the files in the current branch,
and checks out the view branch. Only files in the current branch whose and checks out the view branch. Only files in the current branch whose
@ -1177,6 +1177,12 @@ repository, using [[git-annex-config]]. See its man page for a list.)
To configure the behavior in all clones of the repository, To configure the behavior in all clones of the repository,
this can be set in [[git-annex-config]](1). this can be set in [[git-annex-config]](1).
* `annex.viewunsetdirectory`
This configures the name of a directory that is used in a view to contain
files that do not have metadata set. The default name for the directory
is `"_"`. See [[git-annex-view]](1) for details.
* `annex.debug` * `annex.debug`
Set to true to enable debug logging by default. Set to true to enable debug logging by default.

View file

@ -11,3 +11,5 @@ What do you think? Is something like `git annex view --show-unmatched '???'` wor
Thanks again for git-annex, I love it, it's so versatile... 💛 Thanks again for git-annex, I love it, it's so versatile... 💛
Yann Yann
> [[fixed|done]] --[[Joey]]

View file

@ -0,0 +1,8 @@
[[!comment format=mdwn
username="joey"
subject="""comment 2"""
date="2023-02-07T20:19:29Z"
content="""
Implemented this! Using the "field?=*" syntax described.
With the directory configurable by annex.viewunsetdirectory
"""]]