wip
This commit is contained in:
parent
18cf21d3ed
commit
b69d11ec42
2 changed files with 59 additions and 45 deletions
|
@ -105,9 +105,9 @@ buildImportCommit remote importtreeconfig importcommitconfig importable =
|
||||||
go basecommit = do
|
go basecommit = do
|
||||||
imported@(History finaltree _) <-
|
imported@(History finaltree _) <-
|
||||||
buildImportTrees basetree subdir importable
|
buildImportTrees basetree subdir importable
|
||||||
skipOldHistory basecommit imported >>= \case
|
whatToCommit basecommit imported >>= \case
|
||||||
Just toadd -> do
|
Just (toadd, basecommit') -> do
|
||||||
finalcommit <- mkcommits basecommit toadd
|
finalcommit <- mkcommits basecommit' toadd
|
||||||
updatestate finaltree
|
updatestate finaltree
|
||||||
return (Just finalcommit)
|
return (Just finalcommit)
|
||||||
Nothing -> return Nothing
|
Nothing -> return Nothing
|
||||||
|
@ -177,14 +177,14 @@ buildImportCommit remote importtreeconfig importcommitconfig importable =
|
||||||
{- Finds what to commit to update a basecommit with an imported History
|
{- Finds what to commit to update a basecommit with an imported History
|
||||||
- of git trees.
|
- of git trees.
|
||||||
-
|
-
|
||||||
- Returns a generally truncated History, as well as the Sha that it should
|
- Returns the part of the imported history that should be committed,
|
||||||
- be committed on top of. Typically, the latter is the same as the
|
- as well as the commit sha that it should be committed on top of.
|
||||||
- basecommit.
|
- Typically, the latter is the same as the basecommit.
|
||||||
-
|
-
|
||||||
- This uses skipOldHistory to try to match up common trees.
|
- This uses skipOldHistory to try to match up common trees.
|
||||||
- Sometimes, that matching doesn't work. For example, a remote without an
|
- Sometimes, that matching doesn't work. For example, a remote without an
|
||||||
- atomic rename operation might result in a History with two trees for
|
- atomic rename operation might result in an imported History with two trees
|
||||||
- each rename, one with the old file removed an another with the new file
|
- for each rename, one with the old file removed an another with the new file
|
||||||
- added. Since the remote tracking branch is updated on export to the git
|
- added. Since the remote tracking branch is updated on export to the git
|
||||||
- commit that was exported, the basecommit could have a single tree for a
|
- commit that was exported, the basecommit could have a single tree for a
|
||||||
- rename.
|
- rename.
|
||||||
|
@ -192,35 +192,37 @@ buildImportCommit remote importtreeconfig importcommitconfig importable =
|
||||||
- In that situation, the top tree in the History will match the
|
- In that situation, the top tree in the History will match the
|
||||||
- basecommit's tree, but then there will be a run of different trees
|
- basecommit's tree, but then there will be a run of different trees
|
||||||
- before they re-converge. That is detected, and the History returned is
|
- before they re-converge. That is detected, and the History returned is
|
||||||
- truncated to the part above the re-convergence point, and the Sha
|
- truncated to the part above the re-convergence point, to be committed
|
||||||
- returned is the re-convergence point.
|
- on top of the re-convergence point.
|
||||||
-}
|
-}
|
||||||
whatToCommit :: Maybe Sha -> History Sha -> Annex (Maybe (History Sha, Sha))
|
whatToCommit :: Maybe Sha -> History Sha -> Annex (Maybe (History Sha, Maybe Sha))
|
||||||
whatToCommit Nothing importedhistory = return (Just importedhistory)
|
whatToCommit (Just basecommit) importedhistory = getknownhistory >>= return . \case
|
||||||
whatToCommit (Just basecommit) importedhistory =
|
Just knownhistory -> whatToCommit' importedhistory basecommit knownhistory
|
||||||
maybe (Just importedhistory) (whatToCommit' importedhistory)
|
Nothing -> Just (importedhistory, Nothing)
|
||||||
<$> getknownhistory
|
|
||||||
where
|
where
|
||||||
getknownhistory = inRepo (getTreeHistoryToDepth (historyDepth importedhistory) basecommit)
|
getknownhistory = inRepo $
|
||||||
|
getHistoryToDepth (historyDepth importedhistory) basecommit
|
||||||
|
whatToCommit Nothing importedhistory = return $ Just (importedhistory, Nothing)
|
||||||
|
|
||||||
whatToCommit' :: History Sha -> History Sha -> Maybe (History Sha, Sha)
|
whatToCommit' :: History Sha -> Sha -> History HistoryCommit -> Maybe (History Sha, Maybe Sha)
|
||||||
whatToCommit' importedhistory knownhistory@(History ktop _) =
|
whatToCommit' importedhistory basecommit knownhistory@(History ktop _) =
|
||||||
case skipOldHistory knownhistory importedhistory of
|
case skipOldHistory (mapHistory historyCommitTree knownhistory) importedhistory of
|
||||||
Nothing -> Nothing
|
Nothing -> Nothing
|
||||||
Just newhistory@(History ntop _)
|
Just newhistory@(History ntop _)
|
||||||
| ntop /= ktop -> newhistory
|
| ntop /= historyCommitTree ktop ->
|
||||||
| otherwise ->
|
Just (newhistory, Just basecommit)
|
||||||
-- XXX find convergence point
|
-- XXX find convergence point
|
||||||
|
| otherwise -> undefined
|
||||||
|
|
||||||
{- Finds the part of the importedhistory of git trees that is new and
|
{- Finds the part of the importedhistory of git trees that is new and
|
||||||
- should be committed on top of the knownhistory, skipping parts that have
|
- should be committed on top of the knownhistory, skipping parts that have
|
||||||
- already been committed.
|
- already been committed.
|
||||||
-
|
-
|
||||||
- Will be Nothing if the knownhistory already matches the top of the
|
- Will be Nothing if the knownhistory is already present at the top of
|
||||||
- importedhistory.
|
- the importedhistory.
|
||||||
-
|
-
|
||||||
- In the simple case where there is only one level of importedhistory,
|
- In the simple case where there is only one level of importedhistory,
|
||||||
- when the knownhistory is has the same tree at its top, there's nothing
|
- when the knownhistory has the same tree at its top, there's nothing
|
||||||
- to commit. And otherwise it should be committed on top of the knownhistory.
|
- to commit. And otherwise it should be committed on top of the knownhistory.
|
||||||
-
|
-
|
||||||
- In the complex case where there are several levels of importedhistory,
|
- In the complex case where there are several levels of importedhistory,
|
||||||
|
@ -235,7 +237,7 @@ skipOldHistory knownhistory importedhistory@(History top rest)
|
||||||
| sametodepth importedhistory knownhistory = Nothing
|
| sametodepth importedhistory knownhistory = Nothing
|
||||||
| otherwise = Just $
|
| otherwise = Just $
|
||||||
History top $ S.fromList $ catMaybes $
|
History top $ S.fromList $ catMaybes $
|
||||||
map (skipOldHistory' knownhistory) (S.toList rest)
|
map (skipOldHistory knownhistory) (S.toList rest)
|
||||||
where
|
where
|
||||||
sametodepth a b = a == truncateHistoryToDepth (historyDepth a) b
|
sametodepth a b = a == truncateHistoryToDepth (historyDepth a) b
|
||||||
|
|
||||||
|
|
|
@ -37,22 +37,29 @@ truncateHistoryToDepth n (History t ps) = History t (go 1 ps)
|
||||||
in flip S.map s $ \(History t' s') ->
|
in flip S.map s $ \(History t' s') ->
|
||||||
History t' (go depth' s')
|
History t' (go depth' s')
|
||||||
|
|
||||||
{- Gets a History of trees from commits starting with the provided commit,
|
|
||||||
- and down to the requested depth. -}
|
data HistoryCommit = HistoryCommit
|
||||||
getTreeHistoryToDepth :: Integer -> Ref -> Repo -> IO (Maybe (History Sha))
|
{ historyCommit :: Sha
|
||||||
getTreeHistoryToDepth n commit r = do
|
, historyCommitTree :: Sha
|
||||||
|
, historyCommitParents :: [Sha]
|
||||||
|
} deriving (Show, Eq, Ord)
|
||||||
|
|
||||||
|
{- Gets a History starting with the provided commit, and down to the
|
||||||
|
- requested depth. -}
|
||||||
|
getHistoryToDepth :: Integer -> Ref -> Repo -> IO (Maybe (History HistoryCommit))
|
||||||
|
getHistoryToDepth n commit r = do
|
||||||
(_, Just inh, _, pid) <- createProcess (gitCreateProcess params r)
|
(_, Just inh, _, pid) <- createProcess (gitCreateProcess params r)
|
||||||
{ std_out = CreatePipe }
|
{ std_out = CreatePipe }
|
||||||
!h <- fmap (truncateHistoryToDepth n)
|
!h <- fmap (truncateHistoryToDepth n)
|
||||||
. build Nothing
|
. build Nothing
|
||||||
. map treecommitparents
|
. map parsehistorycommit
|
||||||
. lines
|
. lines
|
||||||
<$> hGetContents inh
|
<$> hGetContents inh
|
||||||
hClose inh
|
hClose inh
|
||||||
void $ waitForProcess pid
|
void $ waitForProcess pid
|
||||||
return h
|
return h
|
||||||
where
|
where
|
||||||
build h [] = fmap (mapHistory fst) h
|
build h [] = h
|
||||||
build _ (Nothing:_) = Nothing
|
build _ (Nothing:_) = Nothing
|
||||||
build Nothing (Just v:rest) =
|
build Nothing (Just v:rest) =
|
||||||
build (Just (History v S.empty)) rest
|
build (Just (History v S.empty)) rest
|
||||||
|
@ -63,20 +70,21 @@ getTreeHistoryToDepth n commit r = do
|
||||||
-- have been found, and avoid processing any more,
|
-- have been found, and avoid processing any more,
|
||||||
-- this makes it much faster when there is a lot of
|
-- this makes it much faster when there is a lot of
|
||||||
-- history.
|
-- history.
|
||||||
if parentsfound 1 h' then [] else rest
|
if parentsfound h' then [] else rest
|
||||||
|
|
||||||
traverseadd v@(t, (c, ps)) (History v'@(t', (c', ps')) s)
|
traverseadd hc (History hc' s)
|
||||||
| c `elem` ps' =
|
| historyCommit hc `elem` historyCommitParents hc' =
|
||||||
let ps'' = filter (/= c) ps'
|
let otherps = filter (/= historyCommit hc) (historyCommitParents hc')
|
||||||
v'' = (t', (c', ps''))
|
hc'' = hc' { historyCommitParents = otherps }
|
||||||
in History v'' (S.insert (History v S.empty) s)
|
in History hc'' (S.insert (History hc S.empty) s)
|
||||||
| otherwise = History v' (S.map (traverseadd v) s)
|
| otherwise = History hc' (S.map (traverseadd hc) s)
|
||||||
|
|
||||||
parentsfound depth (History (_t, (_c, ps)) s)
|
parentsfound = parentsfound' 1
|
||||||
| not (null ps) = False
|
parentsfound' depth (History hc s)
|
||||||
| null ps && depth == n = True
|
| not (null (historyCommitParents hc)) = False
|
||||||
|
| null (historyCommitParents hc) && depth == n = True
|
||||||
| depth >= n = True
|
| depth >= n = True
|
||||||
| otherwise = all (parentsfound (succ depth)) (S.toList s)
|
| otherwise = all (parentsfound' (succ depth)) (S.toList s)
|
||||||
|
|
||||||
params =
|
params =
|
||||||
[ Param "log"
|
[ Param "log"
|
||||||
|
@ -86,6 +94,10 @@ getTreeHistoryToDepth n commit r = do
|
||||||
, Param "--format=%T %H %P"
|
, Param "--format=%T %H %P"
|
||||||
]
|
]
|
||||||
|
|
||||||
treecommitparents l = case map extractSha (splitc ' ' l) of
|
parsehistorycommit l = case map extractSha (splitc ' ' l) of
|
||||||
(Just t:Just c:ps) -> Just (t, (c, catMaybes ps))
|
(Just t:Just c:ps) -> Just $ HistoryCommit
|
||||||
|
{ historyCommit = c
|
||||||
|
, historyCommitTree = t
|
||||||
|
, historyCommitParents = catMaybes ps
|
||||||
|
}
|
||||||
_ -> Nothing
|
_ -> Nothing
|
||||||
|
|
Loading…
Add table
Add a link
Reference in a new issue