git-annex/Logs/View.hs
Joey Hess 67fd06af76 add git annex view command
(And a vpop command, which is still a bit buggy.)

Still need to do vadd and vrm, though this also adds their documentation.

Currently not very happy with the view log data serialization. I had to
lose the TDFA regexps temporarily, so I can have Read/Show instances of
View. I expect the view log format will change in some incompatable way
later, probably adding last known refs for the parent branch to View
or something like that.

Anyway, it basically works, although it's a bit slow looking up the
metadata. The actual git branch construction is about as fast as it can be
using the current git plumbing.

This commit was sponsored by Peter Hogg.
2014-02-18 18:22:20 -04:00

92 lines
2.5 KiB
Haskell

{- git-annex recent views log
-
- The most recently accessed view comes first.
-
- This file is stored locally in .git/annex/, not in the git-annex branch.
-
- Copyright 2014 Joey Hess <joey@kitenet.net>
-
- Licensed under the GNU GPL version 3 or higher.
-}
module Logs.View (
currentView,
setView,
recentViews,
branchView,
prop_branchView_legal,
) where
import Common.Annex
import Types.View
import Types.MetaData
import qualified Git
import qualified Git.Branch
import qualified Git.Ref
import Utility.Tmp
import qualified Data.Set as S
import Data.Char
showLog :: View -> String
showLog (View branch components) = show branch ++ " " ++ show components
parseLog :: String -> Maybe View
parseLog s =
let (branch, components) = separate (== ' ') s
in View
<$> pure (Git.Ref branch)
<*> readish components
setView :: View -> Annex ()
setView v = do
l <- take 99 . filter (/= v) <$> recentViews
f <- fromRepo gitAnnexViewLog
liftIO $ viaTmp writeFile f $ unlines $ map showLog (v : l)
recentViews :: Annex [View]
recentViews = do
f <- fromRepo gitAnnexViewLog
liftIO $ mapMaybe parseLog . lines <$> catchDefaultIO [] (readFile f)
{- Gets the currently checked out view, if there is one. -}
currentView :: Annex (Maybe View)
currentView = do
vs <- recentViews
maybe Nothing (go vs) <$> inRepo Git.Branch.current
where
go [] _ = Nothing
go (v:vs) b
| branchView v == b = Just v
| otherwise = go vs b
{- Generates a git branch name for a View.
-
- There is no guarantee that each view gets a unique branch name,
- but the branch name is used to express the view as well as possible.
-}
branchView :: View -> Git.Branch
branchView view
| null name = Git.Ref "refs/heads/views"
| otherwise = Git.Ref $ "refs/heads/views/" ++ name
where
name = intercalate ";" $ map branchcomp (viewComponents view)
branchcomp c
| multiValue (viewFilter c) = branchcomp' c
| otherwise = "(" ++ branchcomp' c ++ ")"
branchcomp' (ViewComponent metafield viewfilter)
| metafield == tagMetaField = branchvals viewfilter
| otherwise = concat
[ forcelegal (fromMetaField metafield)
, "="
, branchvals viewfilter
]
branchvals (FilterValues set) = forcelegal $
intercalate "," $ map fromMetaValue $ S.toList set
branchvals (FilterGlob glob) = forcelegal glob
forcelegal s
| Git.Ref.legal True s = s
| otherwise = map (\c -> if isAlphaNum c then c else '_') s
prop_branchView_legal :: View -> Bool
prop_branchView_legal = Git.Ref.legal False . show . branchView