remove most remnants of direct mode
A few remain, as needed for upgrades, and for accessing objects from remotes that are direct mode repos that have not been converted yet.
This commit is contained in:
parent
adb89ee71b
commit
689d1fcc92
37 changed files with 193 additions and 799 deletions
|
@ -8,11 +8,7 @@
|
|||
module Command.Status where
|
||||
|
||||
import Command
|
||||
import Annex.CatFile
|
||||
import Annex.Content.Direct
|
||||
import Config
|
||||
import Git.Status
|
||||
import qualified Git.Ref
|
||||
import Git.FilePath
|
||||
|
||||
cmd :: Command
|
||||
|
@ -42,10 +38,7 @@ seek o = withWords (commandAction . start o) (statusFiles o)
|
|||
start :: StatusOptions -> [FilePath] -> CommandStart
|
||||
start o locs = do
|
||||
(l, cleanup) <- inRepo $ getStatus ps locs
|
||||
getstatus <- ifM isDirect
|
||||
( return (maybe (pure Nothing) statusDirect . simplifiedStatus)
|
||||
, return (pure . simplifiedStatus)
|
||||
)
|
||||
let getstatus = pure . simplifiedStatus
|
||||
forM_ l $ \s -> maybe noop displayStatus =<< getstatus s
|
||||
ifM (liftIO cleanup)
|
||||
( stop
|
||||
|
@ -71,38 +64,3 @@ displayStatus s = do
|
|||
f <- liftIO $ relPathCwdToFile absf
|
||||
unlessM (showFullJSON $ JSONChunk [("status", [c]), ("file", f)]) $
|
||||
liftIO $ putStrLn $ [c] ++ " " ++ f
|
||||
|
||||
-- Git thinks that present direct mode files are typechanged.
|
||||
-- (On crippled filesystems, git instead thinks they're modified.)
|
||||
-- Check their content to see if they are modified or not.
|
||||
statusDirect :: Status -> Annex (Maybe Status)
|
||||
statusDirect (TypeChanged t) = statusDirect' t
|
||||
statusDirect s@(Modified t) = ifM crippledFileSystem
|
||||
( statusDirect' t
|
||||
, pure (Just s)
|
||||
)
|
||||
statusDirect s = pure (Just s)
|
||||
|
||||
statusDirect' :: TopFilePath -> Annex (Maybe Status)
|
||||
statusDirect' t = do
|
||||
absf <- fromRepo $ fromTopFilePath t
|
||||
f <- liftIO $ relPathCwdToFile absf
|
||||
v <- liftIO (catchMaybeIO $ getFileStatus f)
|
||||
case v of
|
||||
Nothing -> return $ Just $ Deleted t
|
||||
Just s
|
||||
| not (isSymbolicLink s) ->
|
||||
checkkey f s =<< catKeyFile f
|
||||
| otherwise -> Just <$> checkNew f t
|
||||
where
|
||||
checkkey f s (Just k) = ifM (sameFileStatus k f s)
|
||||
( return Nothing
|
||||
, return $ Just $ Modified t
|
||||
)
|
||||
checkkey f _ Nothing = Just <$> checkNew f t
|
||||
|
||||
checkNew :: FilePath -> TopFilePath -> Annex Status
|
||||
checkNew f t = ifM (isJust <$> catObjectDetails (Git.Ref.fileRef f))
|
||||
( return (Modified t)
|
||||
, return (Untracked t)
|
||||
)
|
||||
|
|
Loading…
Add table
Add a link
Reference in a new issue