Each for each metadata field, there's now an automatically maintained "$field-lastchanged" that gives the timestamp of the last change to that field.

Note that this is a nearly entirely free feature. The data was already
stored in the metadata log in an easily accessible way, and already was
parsed to a time when parsing the log. The generation of the metadata
fields may even be done lazily, although probably not entirely (the map
has to be evaulated to when queried).
This commit is contained in:
Joey Hess 2014-03-18 18:55:43 -04:00
parent fa641dad2d
commit caa97d1271
8 changed files with 94 additions and 23 deletions

View file

@ -5,11 +5,15 @@
- Licensed under the GNU GPL version 3 or higher. - Licensed under the GNU GPL version 3 or higher.
-} -}
module Annex.MetaData where module Annex.MetaData (
genMetaData,
module X
) where
import Common.Annex import Common.Annex
import qualified Annex import qualified Annex
import Types.MetaData import Types.MetaData as X
import Annex.MetaData.StandardFields as X
import Logs.MetaData import Logs.MetaData
import Annex.CatFile import Annex.CatFile
@ -19,15 +23,6 @@ import Data.Time.Calendar
import Data.Time.Clock import Data.Time.Clock
import Data.Time.Clock.POSIX import Data.Time.Clock.POSIX
tagMetaField :: MetaField
tagMetaField = mkMetaFieldUnchecked "tag"
yearMetaField :: MetaField
yearMetaField = mkMetaFieldUnchecked "year"
monthMetaField :: MetaField
monthMetaField = mkMetaFieldUnchecked "month"
{- Adds metadata for a file that has just been ingested into the {- Adds metadata for a file that has just been ingested into the
- annex, but has not yet been committed to git. - annex, but has not yet been committed to git.
- -

View file

@ -0,0 +1,38 @@
{- git-annex metadata, standard fields
-
- Copyright 2014 Joey Hess <joey@kitenet.net>
-
- Licensed under the GNU GPL version 3 or higher.
-}
module Annex.MetaData.StandardFields (
tagMetaField,
yearMetaField,
monthMetaField,
lastChangedField,
isLastChangedField
) where
import Types.MetaData
import Data.List
tagMetaField :: MetaField
tagMetaField = mkMetaFieldUnchecked "tag"
yearMetaField :: MetaField
yearMetaField = mkMetaFieldUnchecked "year"
monthMetaField :: MetaField
monthMetaField = mkMetaFieldUnchecked "month"
lastChangedField :: MetaField -> MetaField
lastChangedField f = mkMetaFieldUnchecked (fromMetaField f ++ lastchanged)
isLastChangedField :: MetaField -> Bool
isLastChangedField f = lastchanged `isSuffixOf` s && s /= lastchanged
where
s = fromMetaField f
lastchanged :: String
lastchanged = "-lastchanged"

View file

@ -12,7 +12,6 @@ import qualified Annex
import Command import Command
import Annex.MetaData import Annex.MetaData
import Logs.MetaData import Logs.MetaData
import Types.MetaData
import qualified Data.Set as S import qualified Data.Set as S
import Data.Time.Clock.POSIX import Data.Time.Clock.POSIX
@ -84,7 +83,7 @@ perform :: POSIXTime -> [ModMeta] -> Key -> CommandPerform
perform _ [] k = next $ cleanup k perform _ [] k = next $ cleanup k
perform now ms k = do perform now ms k = do
oldm <- getCurrentMetaData k oldm <- getCurrentMetaData k
let m = foldl' unionMetaData emptyMetaData $ map (modMeta oldm) ms let m = combineMetaData $ map (modMeta oldm) ms
addMetaData' k m now addMetaData' k m now
next $ cleanup k next $ cleanup k

View file

@ -36,26 +36,50 @@ module Logs.MetaData (
import Common.Annex import Common.Annex
import Types.MetaData import Types.MetaData
import Annex.MetaData.StandardFields
import qualified Annex.Branch import qualified Annex.Branch
import Logs import Logs
import Logs.SingleValue import Logs.SingleValue
import qualified Data.Set as S import qualified Data.Set as S
import qualified Data.Map as M
import Data.Time.Clock.POSIX import Data.Time.Clock.POSIX
import Data.Time.Format
import System.Locale
instance SingleValueSerializable MetaData where instance SingleValueSerializable MetaData where
serialize = Types.MetaData.serialize serialize = Types.MetaData.serialize
deserialize = Types.MetaData.deserialize deserialize = Types.MetaData.deserialize
getMetaData :: Key -> Annex (Log MetaData) getMetaDataLog :: Key -> Annex (Log MetaData)
getMetaData = readLog . metaDataLogFile getMetaDataLog = readLog . metaDataLogFile
{- Go through the log from oldest to newest, and combine it all {- Go through the log from oldest to newest, and combine it all
- into a single MetaData representing the current state. -} - into a single MetaData representing the current state.
-
- Automatically generates a lastchanged metadata for each field that's
- currently set, based on timestamps in the log.
-}
getCurrentMetaData :: Key -> Annex MetaData getCurrentMetaData :: Key -> Annex MetaData
getCurrentMetaData = currentMetaData . collect <$$> getMetaData getCurrentMetaData k = do
ls <- S.toAscList <$> getMetaDataLog k
let loggedmeta = currentMetaData $ combineMetaData $ map value ls
return $ currentMetaData $ unionMetaData loggedmeta
(lastchanged ls loggedmeta)
where where
collect = foldl' unionMetaData emptyMetaData . map value . S.toAscList lastchanged ls (MetaData wanted) =
let m = foldl' (flip M.union) M.empty (map genlastchanged ls)
in MetaData $ M.mapKeys lastChangedField $
-- Only include fields that are currently set.
m `M.intersection` wanted
-- Makes each field have the timestamp as its value.
genlastchanged l =
let MetaData m = value l
ts = S.singleton $ toMetaValue $
formatTime defaultTimeLocale "%s" $
posixSecondsToUTCTime $
changed l
in M.map (const ts) m
{- Adds in some metadata, which can override existing values, or unset {- Adds in some metadata, which can override existing values, or unset
- them, but otherwise leaves any existing metadata as-is. -} - them, but otherwise leaves any existing metadata as-is. -}
@ -67,10 +91,12 @@ addMetaData k metadata = addMetaData' k metadata =<< liftIO getPOSIXTime
- will tend to be generated across the different log files, and so - will tend to be generated across the different log files, and so
- git will be able to pack the data more efficiently. -} - git will be able to pack the data more efficiently. -}
addMetaData' :: Key -> MetaData -> POSIXTime -> Annex () addMetaData' :: Key -> MetaData -> POSIXTime -> Annex ()
addMetaData' k metadata now = Annex.Branch.change (metaDataLogFile k) $ addMetaData' k (MetaData m) now = Annex.Branch.change (metaDataLogFile k) $
showLog . simplifyLog showLog . simplifyLog
. S.insert (LogEntry now metadata) . S.insert (LogEntry now metadata)
. parseLog . parseLog
where
metadata = MetaData $ M.filterWithKey (\f _ -> not (isLastChangedField f)) m
{- Simplify a log, removing historical values that are no longer {- Simplify a log, removing historical values that are no longer
- needed. - needed.
@ -148,7 +174,7 @@ copyMetaData :: Key -> Key -> Annex ()
copyMetaData oldkey newkey copyMetaData oldkey newkey
| oldkey == newkey = noop | oldkey == newkey = noop
| otherwise = do | otherwise = do
l <- getMetaData oldkey l <- getMetaDataLog oldkey
unless (S.null l) $ unless (S.null l) $
Annex.Branch.change (metaDataLogFile newkey) $ Annex.Branch.change (metaDataLogFile newkey) $
const $ showLog l const $ showLog l

View file

@ -28,6 +28,7 @@ module Types.MetaData (
emptyMetaData, emptyMetaData,
updateMetaData, updateMetaData,
unionMetaData, unionMetaData,
combineMetaData,
differenceMetaData, differenceMetaData,
isSet, isSet,
currentMetaData, currentMetaData,
@ -188,6 +189,9 @@ unionMetaData :: MetaData -> MetaData -> MetaData
unionMetaData (MetaData old) (MetaData new) = MetaData $ unionMetaData (MetaData old) (MetaData new) = MetaData $
M.unionWith S.union new old M.unionWith S.union new old
combineMetaData :: [MetaData] -> MetaData
combineMetaData = foldl' unionMetaData emptyMetaData
differenceMetaData :: MetaData -> MetaData -> MetaData differenceMetaData :: MetaData -> MetaData -> MetaData
differenceMetaData (MetaData m) (MetaData excludem) = MetaData $ differenceMetaData (MetaData m) (MetaData excludem) = MetaData $
M.differenceWith diff m excludem M.differenceWith diff m excludem

3
debian/changelog vendored
View file

@ -27,6 +27,9 @@ git-annex (5.20140307) UNRELEASED; urgency=medium
* map: Fix crash when one of the remotes of a repo is a local directory * map: Fix crash when one of the remotes of a repo is a local directory
that does not exist, or is not a git repo. that does not exist, or is not a git repo.
* rsync special remote: Fix slashes when used on Windows. * rsync special remote: Fix slashes when used on Windows.
* Each for each metadata field, there's now an automatically maintained
"$field-lastchanged" that gives the timestamp of the last change to that
field.
-- Joey Hess <joeyh@debian.org> Thu, 06 Mar 2014 16:17:01 -0400 -- Joey Hess <joeyh@debian.org> Thu, 06 Mar 2014 16:17:01 -0400

View file

@ -23,11 +23,14 @@ The field names are limited to alphanumerics (and `[_-.]`), and are case
insensitive. The metadata values can contain absolutely anything you insensitive. The metadata values can contain absolutely anything you
like -- but you're recommended to keep it simple and reasonably short. like -- but you're recommended to keep it simple and reasonably short.
Here are some recommended metadata fields to use: Here are some metadata fields that git-annex has special support for:
* `tag` - With each tag being a different value. * `tag` - With each tag being a different value.
* `year`, `month` - When this particular version of the file came into * `year`, `month` - When this particular version of the file came into
being. being.
* `$field-lastchanged` - This is automatically maintained for each
field that's set, and gives the time stamp (since the Unix epoch)
of the most recent change to the field. It cannot be modified directly.
To make git-annex automatically set the year and month when adding files, To make git-annex automatically set the year and month when adding files,
run `git config annex.genmetadata true`. Also, see run `git config annex.genmetadata true`. Also, see

View file

@ -18,3 +18,6 @@ Something along the lines of
This would allow me to review files that haven't had any tag changes applied for a while and thus, may need the tags updating. This would allow me to review files that haven't had any tag changes applied for a while and thus, may need the tags updating.
I've done this in every tagging system I've used by (ab)using mtime, but that requires an additional step (of touching the file). I've done this in every tagging system I've used by (ab)using mtime, but that requires an additional step (of touching the file).
> [[done]]; "$field-lastchanged" is automatically made available for each
> field! --[[Joey]]