add tip about metadata driven views (and more flexible view filtering)

While writing this documentation, I realized that there needed to be a way
to stay in a view like tag=* while adding a filter like tag=work that
applies to the same field.

So, there are really two ways a view can be refined. It can have a new
"field=explicitvalue" filter added to it, which does not change the
"shape" of the view, but narrows the files it shows.
Or, it can have a new view added, which adds another level of
subdirectories.

So, added a vfilter command, which takes explicit values to add to the
filter, and rejects changes that would change the shape of the view.

And, made vadd only accept changes that change the shape of the view.

And, changed the View data type slightly; now components that can match
multiple metadata values can be visible, or not visible.

This commit was sponsored by Stelian Iancu.
This commit is contained in:
Joey Hess 2014-02-19 15:10:18 -04:00
parent d8ce6cac36
commit dd7b99c860
9 changed files with 201 additions and 53 deletions

View file

@ -44,11 +44,7 @@ import Text.Regex.TDFA.String
import Text.Regex import Text.Regex
#endif #endif
{- Each visible ViewFilter in a view results in another level of
data ViewChange = Unchanged | Narrowing | Widening
deriving (Ord, Eq, Show)
{- Each multivalued ViewFilter in a view results in another level of
- subdirectory nesting. When a file matches multiple ways, it will appear - subdirectory nesting. When a file matches multiple ways, it will appear
- in multiple subdirectories. This means there is a bit of an exponential - in multiple subdirectories. This means there is a bit of an exponential
- blowup with a single file appearing in a crazy number of places! - blowup with a single file appearing in a crazy number of places!
@ -60,16 +56,38 @@ viewTooLarge :: View -> Bool
viewTooLarge view = visibleViewSize view > 5 viewTooLarge view = visibleViewSize view > 5
visibleViewSize :: View -> Int visibleViewSize :: View -> Int
visibleViewSize = length . filter (multiValue . viewFilter) . viewComponents visibleViewSize = length . filter viewVisible . viewComponents
{- Updates a view, adding a new field to filter on (Narrowing), data ViewChange = Unchanged | Narrowing | Widening
- or allowing a new value in an existing field (Widening). -} deriving (Ord, Eq, Show)
refineView :: View -> MetaField -> String -> (View, ViewChange)
refineView view field wanted {- Updates a view, adding new fields to filter on (Narrowing),
- or allowing new values in an existing field (Widening). -}
refineView :: View -> [(MetaField, String)] -> (View, ViewChange)
refineView = go Unchanged
where
go c v [] = (v, c)
go c v ((f, s):rest) =
let (v', c') = refineView' v f s
in go (max c c') v' rest
{- Adds an additional filter to a view. This can only result in narrowing
- the view. Multivalued filters are added in non-visible form. -}
filterView :: View -> [(MetaField, String)] -> View
filterView v vs = v { viewComponents = viewComponents f' ++ viewComponents v}
where
f = fst $ refineView (v {viewComponents = []}) vs
f' = f { viewComponents = map toinvisible (viewComponents f) }
toinvisible c = c { viewVisible = False }
refineView' :: View -> MetaField -> String -> (View, ViewChange)
refineView' view field wanted
| field `elem` (map viewField components) = | field `elem` (map viewField components) =
let (components', viewchanges) = runWriter $ mapM updatefield components let (components', viewchanges) = runWriter $ mapM updatefield components
in (view { viewComponents = components' }, maximum viewchanges) in (view { viewComponents = components' }, maximum viewchanges)
| otherwise = let view' = view { viewComponents = ViewComponent field viewfilter : components } | otherwise =
let component = ViewComponent field viewfilter (multiValue viewfilter)
view' = view { viewComponents = component : components }
in if viewTooLarge view' in if viewTooLarge view'
then error $ "View is too large (" ++ show (visibleViewSize view') ++ " levels of subdirectories)" then error $ "View is too large (" ++ show (visibleViewSize view') ++ " levels of subdirectories)"
else (view', Narrowing) else (view', Narrowing)
@ -173,8 +191,8 @@ fileViews view =
else map (</> mkfileview file) paths else map (</> mkfileview file) paths
where where
visible = map (fromJust . snd) . visible = map (fromJust . snd) .
filter (multiValue . fst) . filter (viewVisible . fst) .
zip (map viewFilter (viewComponents view)) zip (viewComponents view)
{- 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. -}
@ -255,7 +273,7 @@ pathProduct (l:ls) = foldl combinel l ls
fromView :: View -> FileView -> MetaData fromView :: View -> FileView -> MetaData
fromView view f = foldr (uncurry updateMetaData) newMetaData (zip fields values) fromView view f = foldr (uncurry updateMetaData) newMetaData (zip fields values)
where where
visible = filter (multiValue . viewFilter) (viewComponents view) visible = filter viewVisible (viewComponents view)
fields = map viewField visible fields = map viewField visible
paths = splitDirectories $ dropFileName f paths = splitDirectories $ dropFileName f
values = map fromViewPath paths values = map fromViewPath paths
@ -263,15 +281,15 @@ fromView view f = foldr (uncurry updateMetaData) newMetaData (zip fields values)
{- 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 FileViews which all contain the same - it to a file yields a set of FileViews which all contain the same
- MetaFields that were present in the input metadata - MetaFields that were present in the input metadata
- (excluding fields that are not multivalued). -} - (excluding fields that are not visible). -}
prop_view_roundtrips :: FilePath -> MetaData -> Bool prop_view_roundtrips :: FilePath -> MetaData -> Bool -> Bool
prop_view_roundtrips f metadata = null f || viewTooLarge view || prop_view_roundtrips f metadata visible = null f || viewTooLarge view ||
all hasfields (fileViews view fileViewFromReference f metadata) all hasfields (fileViews view fileViewFromReference f metadata)
where where
view = View (Git.Ref "master") $ view = View (Git.Ref "master") $
map (\(mf, mv) -> ViewComponent mf (FilterValues $ S.filter (not . null . fromMetaValue) mv)) map (\(mf, mv) -> ViewComponent mf (FilterValues $ S.filter (not . null . fromMetaValue) mv) visible)
(fromMetaData metadata) (fromMetaData metadata)
visiblefields = sort (map viewField $ filter (multiValue . viewFilter) (viewComponents view)) visiblefields = sort (map viewField $ filter viewVisible (viewComponents view))
hasfields fv = sort (map fst (fromMetaData (fromView view fv))) == visiblefields hasfields fv = sort (map fst (fromMetaData (fromView view fv))) == visiblefields
{- Applies a view to the currently checked out branch, generating a new {- Applies a view to the currently checked out branch, generating a new
@ -282,7 +300,8 @@ applyView view = applyView' fileViewFromReference view
{- Generates a new branch for a View, which must be a more narrow {- Generates a new branch for a View, which must be a more narrow
- version of the View originally used to generate the currently - version of the View originally used to generate the currently
- checked out branch. - checked out branch. That is, it must match a subset of the files
- in view, not any others.
-} -}
narrowView :: View -> Annex Git.Branch narrowView :: View -> Annex Git.Branch
narrowView = applyView' fileViewReuse narrowView = applyView' fileViewReuse
@ -405,3 +424,6 @@ withIndex :: Annex a -> Annex a
withIndex a = do withIndex a = do
f <- fromRepo gitAnnexViewIndex f <- fromRepo gitAnnexViewIndex
withIndexFile f a withIndexFile f a
withCurrentView :: (View -> Annex a) -> Annex a
withCurrentView a = maybe (error "Not in a view.") a =<< currentView

View file

@ -29,6 +29,7 @@ import qualified Command.ReKey
import qualified Command.MetaData import qualified Command.MetaData
import qualified Command.View import qualified Command.View
import qualified Command.VAdd import qualified Command.VAdd
import qualified Command.VFilter
import qualified Command.VPop import qualified Command.VPop
import qualified Command.VCycle import qualified Command.VCycle
import qualified Command.Reinject import qualified Command.Reinject
@ -142,6 +143,7 @@ cmds = concat
, Command.MetaData.def , Command.MetaData.def
, Command.View.def , Command.View.def
, Command.VAdd.def , Command.VAdd.def
, Command.VFilter.def
, Command.VPop.def , Command.VPop.def
, Command.VCycle.def , Command.VCycle.def
, Command.Fix.def , Command.Fix.def

View file

@ -10,12 +10,11 @@ module Command.VAdd where
import Common.Annex import Common.Annex
import Command import Command
import Annex.View import Annex.View
import Logs.View
import Command.View (paramView, parseViewParam, checkoutViewBranch) import Command.View (paramView, parseViewParam, checkoutViewBranch)
def :: [Command] def :: [Command]
def = [notBareRepo $ notDirect $ def = [notBareRepo $ notDirect $
command "vadd" paramView seek SectionMetaData "refine current view"] command "vadd" paramView seek SectionMetaData "add subdirs to current view"]
seek :: CommandSeek seek :: CommandSeek
seek = withWords start seek = withWords start
@ -23,20 +22,15 @@ seek = withWords start
start :: [String] -> CommandStart start :: [String] -> CommandStart
start params = do start params = do
showStart "vadd" "" showStart "vadd" ""
go =<< currentView withCurrentView $ \view -> do
where let (view', change) = refineView view $
go Nothing = error "Not in a view." map parseViewParam $ reverse params
go (Just view) = do
let (view', change) = calc view Unchanged (reverse params)
case change of case change of
Unchanged -> do Unchanged -> do
showNote "unchanged" showNote "unchanged"
next $ next $ return True next $ next $ return True
Narrowing -> next $ next $ Narrowing -> next $ next $ do
checkoutViewBranch view' narrowView if visibleViewSize view' == visibleViewSize view
then error "That would not add an additional level of directory structure to the view. To filter the view, use vfilter instead of vadd."
else checkoutViewBranch view' narrowView
Widening -> error "Widening view to match more files is not currently supported." Widening -> error "Widening view to match more files is not currently supported."
calc v c [] = (v, c)
calc v c (p:ps) =
let (v', c') = uncurry (refineView v) (parseViewParam p)
in calc v' (max c c') ps

View file

@ -53,12 +53,9 @@ parseViewParam s = case separate (== '=') s of
mkView :: [String] -> Annex View mkView :: [String] -> Annex View
mkView params = do mkView params = do
v <- View <$> viewbranch <*> pure [] v <- View <$> viewbranch <*> pure []
return $ calc v $ reverse params return $ fst $ refineView v $
map parseViewParam $ reverse params
where where
calc v [] = v
calc v (p:ps) =
let (v', _) = uncurry (refineView v) (parseViewParam p)
in calc v' ps
viewbranch = fromMaybe (error "not on any branch!") viewbranch = fromMaybe (error "not on any branch!")
<$> inRepo Git.Branch.current <$> inRepo Git.Branch.current

View file

@ -71,9 +71,9 @@ branchView view
where where
name = intercalate ";" $ map branchcomp (viewComponents view) name = intercalate ";" $ map branchcomp (viewComponents view)
branchcomp c branchcomp c
| multiValue (viewFilter c) = branchcomp' c | viewVisible c = branchcomp' c
| otherwise = "(" ++ branchcomp' c ++ ")" | otherwise = "(" ++ branchcomp' c ++ ")"
branchcomp' (ViewComponent metafield viewfilter) branchcomp' (ViewComponent metafield viewfilter _)
| metafield == tagMetaField = branchvals viewfilter | metafield == tagMetaField = branchvals viewfilter
| otherwise = concat | otherwise = concat
[ forcelegal (fromMetaField metafield) [ forcelegal (fromMetaField metafield)

View file

@ -28,11 +28,12 @@ instance Arbitrary View where
data ViewComponent = ViewComponent data ViewComponent = ViewComponent
{ viewField :: MetaField { viewField :: MetaField
, viewFilter :: ViewFilter , viewFilter :: ViewFilter
, viewVisible :: Bool
} }
deriving (Eq, Read, Show) deriving (Eq, Read, Show)
instance Arbitrary ViewComponent where instance Arbitrary ViewComponent where
arbitrary = ViewComponent <$> arbitrary <*> arbitrary arbitrary = ViewComponent <$> arbitrary <*> arbitrary <*> arbitrary
{- Only files with metadata matching the view are displayed. -} {- Only files with metadata matching the view are displayed. -}
type FileView = FilePath type FileView = FilePath

6
debian/changelog vendored
View file

@ -7,9 +7,9 @@ git-annex (5.20140211) UNRELEASED; urgency=medium
to limit them to acting on files that have particular metadata. to limit them to acting on files that have particular metadata.
* view: New command that creates and checks out a branch that provides * view: New command that creates and checks out a branch that provides
a structured view of selected metadata. a structured view of selected metadata.
* vadd, vpop, vcycle: New commands for operating within views. * vfilter, vadd, vpop, vcycle: New commands for operating within views.
* pre-commit: Update metadata when committing changes to annexed files * pre-commit: Update metadata when committing changes to locations
within a view. of annexed files within a view.
* Add progress display for transfers to/from external special remotes. * Add progress display for transfers to/from external special remotes.
* Windows webapp: Can set up box.com, Amazon S3, and rsync.net remotes * Windows webapp: Can set up box.com, Amazon S3, and rsync.net remotes
* Windows webapp: Can create repos on removable drives. * Windows webapp: Can create repos on removable drives.

View file

@ -722,10 +722,10 @@ subdirectories).
shown in the view. shown in the view.
Multiple values for a metadata field can be specified, either by using Multiple values for a metadata field can be specified, either by using
a glob (field="\*") or by listing each wanted value. The resulting view a glob (`field="*"`) or by listing each wanted value. The resulting view
will put files in subdirectories according to the value of their fields. will put files in subdirectories according to the value of their fields.
Once within a view, you can make additional subdirectories, and Once within 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. be updated to correspond to your changes.
@ -736,16 +736,28 @@ subdirectories).
The optional number tells how many views to pop. The optional number tells how many views to pop.
* `vadd [field=value ...] [tag ...]` * `vfilter [field=value ...] [tag ...]`
Refines the currently checked out view branch, adding additional fields Filters the current view to only the files that have the
or tags. specified values and tags.
* `vadd [field=glob ...]`
Changes the current view, adding an additional level of directories
to categorize the files.
For example, when the view is by author/tag, `vadd year=*` will
change it to year/author/tag.
So will `vadd year=2014 year=2013`, but limiting the years in view
to only those two.
* `vcycle` * `vcycle`
When a view involves nested subdirectories, this cycles the order. When a view involves nested subdirectories, this cycles the order.
For example, when the view has date/author/tag, vcycle will switch
it to author/tag/date. For example, when the view is by year/author/tag, `vcycle` will switch
it to author/tag/year.
# UTILITY COMMANDS # UTILITY COMMANDS

View file

@ -0,0 +1,120 @@
git-annex now has support for storing arbitrary metadata about annexed
files. For example, this can be used to tag files, to record the author
of a file, etc. The metadata is synced around between repositories with
the other information git-annex keeps track of.
One nice way to use the metadata is through **views**. You can ask
git-annex to create a view of files in the currently checked out branch
that have certian metadata. Once you're in a view, you can move and copy
files to adjust their metadata further. Rather than the traditional
hierarchical directory structure, views are dynamic; you can easily
refine or reorder a view.
Let's get started by setting some tags on files. No views yet, just some
metadata:
# git annex metadata --tag todo work/2014/*
# git annex metadata --untag todo work/2014/done/*
# git annex metadata --tag urgent work/2014/presentation_for_tomorrow.odt
# git annex metadata --tag done work/2013/* work/2014/done/*
# git annex metadata --tag work work
# git annex metadata --tag video videos
# git annex metadata --tag work videos/operating_heavy_machinery.mov
# git annex metadata --tag done videos/old
# git annex metadata --tag new videos/lotsofcats.ogv
# git annex metadata --tag sound podcasts
# git annex metadata --tag done podcasts/old
# git annex metadata --tag new podcasts/recent
So, you had a bunch of different kinds of files sorted into a directory
structure. But that didn't really reflect how you approach the files.
Adding some tags lets you categorize the files in different ways.
Ok, metadata is in place, but how to use it? Time to change views!
# git annex view tag=*
view (searching...)
Switched to branch 'views/_'
ok
This searched for all files with any tag, and created a new git branch
that sorts the files according to their tags.
# tree -d
work
todo
urgent
done
new
video
sound
Notice that a single file may appear in multiple directories
depending on its tags. For example, `lotsofcats.ogv` is in
both `new/` and `video/`.
Ah, but you're at work now, and don't want to be distracted by cat videos.
Time to filter the view:
# git annex vfilter tag=work
vfilter
Switched to branch 'views/(work)/_'
ok
Now only the work files are in the view, and they're otherwise categorized
according to their other tags. So you can check the `urgent/` directory
to see what's next, and look in `todo/` for other work related files.
Now that you're in a tag based view, you can move files around between the
directories, and when you commit your changes to git, their tags will be
updated.
# git mv urgent/presentation_for_tomorrow_{work;2014}.odt ../done
# git commit -m "a good day's work"
metadata tag-=urgent
metadata tag+=done
You can return to a previous view by running `git annex vpop`. If you pop
all the way out of all views, you'll be back on the regular git branch you
originally started from. You can also use `git checkout` to switch between
views and other branches.
Beyond simple tags, you can add whatever kinds of metadata you like, and
use that metadata in more elaborate views. For example, let's add a year
field.
# git checkout master
# git annex metadata --set year=2014 work/2014
# git annex metadata --set year=2013 work/2013
# git annex view year=* tag=*
Now you're in a view with two levels of directories, first by year and then
by tag.
# tree -d
2014
|-- work
|-- todo
|-- urgent
`-- done
2013
|-- work
`-- done
Oh, did you want it the other way around? Easy!
# git annex vcycle
# tree -d
work
|-- 2014
`-- 2013
todo
`-- 2014
urgent
`-- 2014
done
|-- 2014
`-- 2013
This has probably only scratched the surface of what you can do with views.