fix view changing when in subdir
Failed reading some files with relative paths. This is a quick and dirty fix.
This commit is contained in:
parent
9b51d43318
commit
72c118152f
5 changed files with 18 additions and 23 deletions
|
@ -244,7 +244,8 @@ narrowView = applyView' fileViewReuse
|
||||||
- Look up the metadata of annexed files, and generate any FileViews,
|
- Look up the metadata of annexed files, and generate any FileViews,
|
||||||
- and stage them.
|
- and stage them.
|
||||||
-
|
-
|
||||||
- Currently only works in indirect mode.
|
- Currently only works in indirect mode. Must be run from top of
|
||||||
|
- repository.
|
||||||
-}
|
-}
|
||||||
applyView' :: MkFileView -> View -> Annex Git.Branch
|
applyView' :: MkFileView -> View -> Annex Git.Branch
|
||||||
applyView' mkfileview view = do
|
applyView' mkfileview view = do
|
||||||
|
|
|
@ -9,7 +9,6 @@ module Command.VAdd where
|
||||||
|
|
||||||
import Common.Annex
|
import Common.Annex
|
||||||
import Command
|
import Command
|
||||||
import Types.View
|
|
||||||
import Annex.View
|
import Annex.View
|
||||||
import Logs.View
|
import Logs.View
|
||||||
import Command.View (paramView, parseViewParam, checkoutViewBranch)
|
import Command.View (paramView, parseViewParam, checkoutViewBranch)
|
||||||
|
@ -33,15 +32,11 @@ start params = do
|
||||||
Unchanged -> do
|
Unchanged -> do
|
||||||
showNote "unchanged"
|
showNote "unchanged"
|
||||||
next $ next $ return True
|
next $ next $ return True
|
||||||
|
Narrowing -> next $ next $
|
||||||
|
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."
|
||||||
Narrowing -> next $ perform view'
|
|
||||||
|
|
||||||
calc v c [] = (v, c)
|
calc v c [] = (v, c)
|
||||||
calc v c (p:ps) =
|
calc v c (p:ps) =
|
||||||
let (v', c') = uncurry (refineView v) (parseViewParam p)
|
let (v', c') = uncurry (refineView v) (parseViewParam p)
|
||||||
in calc v' (max c c') ps
|
in calc v' (max c c') ps
|
||||||
|
|
||||||
perform :: View -> CommandPerform
|
|
||||||
perform view = do
|
|
||||||
branch <- narrowView view
|
|
||||||
next $ checkoutViewBranch view branch
|
|
||||||
|
|
|
@ -32,14 +32,9 @@ start = go =<< currentView
|
||||||
then do
|
then do
|
||||||
showNote "unchanged"
|
showNote "unchanged"
|
||||||
next $ next $ return True
|
next $ next $ return True
|
||||||
else next $ perform v'
|
else next $ next $ checkoutViewBranch v' narrowView
|
||||||
|
|
||||||
vcycle rest (c:cs)
|
vcycle rest (c:cs)
|
||||||
| multiValue (viewFilter c) = rest ++ cs ++ [c]
|
| multiValue (viewFilter c) = rest ++ cs ++ [c]
|
||||||
| otherwise = vcycle (c:rest) cs
|
| otherwise = vcycle (c:rest) cs
|
||||||
vcycle rest c = rest ++ c
|
vcycle rest c = rest ++ c
|
||||||
|
|
||||||
perform :: View -> CommandPerform
|
|
||||||
perform view = do
|
|
||||||
branch <- narrowView view
|
|
||||||
next $ checkoutViewBranch view branch
|
|
||||||
|
|
|
@ -32,7 +32,7 @@ start = go =<< currentView
|
||||||
<$> recentViews
|
<$> recentViews
|
||||||
case vs of
|
case vs of
|
||||||
(_v:oldv:_) -> next $ next $
|
(_v:oldv:_) -> next $ next $
|
||||||
checkoutViewBranch oldv (branchView oldv)
|
checkoutViewBranch oldv (return . branchView)
|
||||||
_ -> next $ next $
|
_ -> next $ next $
|
||||||
inRepo $ Git.Command.runBool
|
inRepo $ Git.Command.runBool
|
||||||
[ Param "checkout"
|
[ Param "checkout"
|
||||||
|
|
|
@ -40,8 +40,7 @@ start params = do
|
||||||
perform :: View -> CommandPerform
|
perform :: View -> CommandPerform
|
||||||
perform view = do
|
perform view = do
|
||||||
showSideAction "searching"
|
showSideAction "searching"
|
||||||
branch <- applyView view
|
next $ checkoutViewBranch view applyView
|
||||||
next $ checkoutViewBranch view branch
|
|
||||||
|
|
||||||
paramView :: String
|
paramView :: String
|
||||||
paramView = paramPair (paramRepeating "FIELD=VALUE") (paramRepeating "TAG")
|
paramView = paramPair (paramRepeating "FIELD=VALUE") (paramRepeating "TAG")
|
||||||
|
@ -63,20 +62,25 @@ mkView params = do
|
||||||
viewbranch = fromMaybe (error "not on any branch!")
|
viewbranch = fromMaybe (error "not on any branch!")
|
||||||
<$> inRepo Git.Branch.current
|
<$> inRepo Git.Branch.current
|
||||||
|
|
||||||
checkoutViewBranch :: View -> Git.Branch -> CommandCleanup
|
checkoutViewBranch :: View -> (View -> Annex Git.Branch) -> CommandCleanup
|
||||||
checkoutViewBranch view branch = do
|
checkoutViewBranch view mkbranch = do
|
||||||
|
oldcwd <- liftIO getCurrentDirectory
|
||||||
|
|
||||||
|
{- Change to top of repository before creating view branch. -}
|
||||||
|
liftIO . setCurrentDirectory =<< fromRepo Git.repoPath
|
||||||
|
branch <- mkbranch view
|
||||||
|
|
||||||
ok <- inRepo $ Git.Command.runBool
|
ok <- inRepo $ Git.Command.runBool
|
||||||
[ Param "checkout"
|
[ Param "checkout"
|
||||||
, Param (show $ Git.Ref.base branch)
|
, Param (show $ Git.Ref.base branch)
|
||||||
]
|
]
|
||||||
when ok $ do
|
when ok $ do
|
||||||
setView view
|
setView view
|
||||||
top <- fromRepo Git.repoPath
|
|
||||||
cwd <- liftIO getCurrentDirectory
|
|
||||||
{- A git repo can easily have empty directories in it,
|
{- A git repo can easily have empty directories in it,
|
||||||
- and this pollutes the view, so remove them. -}
|
- and this pollutes the view, so remove them. -}
|
||||||
liftIO $ removeemptydirs top
|
liftIO $ removeemptydirs "."
|
||||||
unlessM (liftIO $ doesDirectoryExist cwd) $
|
unlessM (liftIO $ doesDirectoryExist oldcwd) $ do
|
||||||
|
top <- fromRepo Git.repoPath
|
||||||
showLongNote (cwdmissing top)
|
showLongNote (cwdmissing top)
|
||||||
return ok
|
return ok
|
||||||
where
|
where
|
||||||
|
|
Loading…
Add table
Add a link
Reference in a new issue