Ref ByteString conversion done

Test suite passes.
This commit is contained in:
Joey Hess 2020-04-07 17:41:09 -04:00
parent 6c81e0c8f1
commit c0cd07c36b
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38
22 changed files with 72 additions and 47 deletions

View file

@ -5,12 +5,10 @@
- Licensed under the GNU AGPL version 3 or higher.
-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE BangPatterns, OverloadedStrings #-}
module Command.Unused where
import qualified Data.Map as M
import Command
import Logs.Unused
import Annex.Content
@ -37,6 +35,11 @@ import Annex.BloomFilter
import qualified Database.Keys
import Annex.InodeSentinal
import qualified Data.Map as M
import qualified Data.ByteString as S
import qualified Data.ByteString.Char8 as S8
import Data.Char
cmd :: Command
cmd = command "unused" SectionMaintenance "look for unused file content"
paramNothing (seek <$$> optParser)
@ -221,8 +224,7 @@ withKeysReferenced' mdir initial a = do
withKeysReferencedDiffGitRefs :: RefSpec -> (Key -> Annex ()) -> Annex ()
withKeysReferencedDiffGitRefs refspec a = do
rs <- relevantrefs . decodeBS'
<$> inRepo (Git.Command.pipeReadStrict [Param "show-ref"])
rs <- relevantrefs <$> inRepo (Git.Command.pipeReadStrict [Param "show-ref"])
shaHead <- maybe (return Nothing) (inRepo . Git.Ref.sha)
=<< inRepo Git.Branch.currentUnsafe
let haveHead = any (\(shaRef, _) -> Just shaRef == shaHead) rs
@ -233,12 +235,12 @@ withKeysReferencedDiffGitRefs refspec a = do
where
relevantrefs = map (\(r, h) -> (Git.Ref r, Git.Ref h)) .
filter ourbranches .
map (separate (== ' ')) .
lines
map (separate' (== (fromIntegral (ord ' ')))) .
S8.lines
nubRefs = nubBy (\(x, _) (y, _) -> x == y)
ourbranchend = '/' : Git.fromRef Annex.Branch.name
ourbranches (_, b) = not (ourbranchend `isSuffixOf` b)
&& not ("refs/synced/" `isPrefixOf` b)
ourbranchend = S.cons (fromIntegral (ord '/')) (Git.fromRef' Annex.Branch.name)
ourbranches (_, b) = not (ourbranchend `S.isSuffixOf` b)
&& not ("refs/synced/" `S.isPrefixOf` b)
&& not (is_branchView (Git.Ref b))
getreflog rs = inRepo $ Git.RefLog.getMulti rs