Skip to content

Commit 8f5b2f0

Browse files
authored
Merge pull request #7137 from strake/sync-repo-darcs
Sync repo darcs
2 parents ea830d7 + 47ae4f4 commit 8f5b2f0

File tree

2 files changed

+50
-3
lines changed

2 files changed

+50
-3
lines changed

cabal-install/src/Distribution/Client/VCS.hs

Lines changed: 48 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,5 @@
1+
{-# LANGUAGE LambdaCase #-}
2+
{-# LANGUAGE ScopedTypeVariables #-}
13
{-# LANGUAGE NamedFieldPuns, RecordWildCards, RankNTypes #-}
24
module Distribution.Client.VCS (
35
-- * VCS driver type
@@ -45,20 +47,29 @@ import Distribution.Simple.Program
4547
( Program(programFindVersion)
4648
, ConfiguredProgram(programVersion)
4749
, simpleProgram, findProgramVersion
48-
, ProgramInvocation(..), programInvocation, runProgramInvocation
50+
, ProgramInvocation(..), programInvocation, runProgramInvocation, getProgramInvocationOutput
4951
, emptyProgramDb, requireProgram )
5052
import Distribution.Version
5153
( mkVersion )
5254
import qualified Distribution.PackageDescription as PD
5355

56+
import Control.Applicative
57+
( liftA2 )
58+
import Control.Exception
59+
( throw, try )
5460
import Control.Monad.Trans
5561
( liftIO )
5662
import qualified Data.Char as Char
63+
import qualified Data.List as List
5764
import qualified Data.Map as Map
5865
import System.FilePath
5966
( takeDirectory )
6067
import System.Directory
61-
( doesDirectoryExist )
68+
( doesDirectoryExist
69+
, removeDirectoryRecursive
70+
)
71+
import System.IO.Error
72+
( isDoesNotExistError )
6273

6374

6475
-- | A driver for a version control system, e.g. git, darcs etc.
@@ -306,7 +317,41 @@ vcsDarcs =
306317

307318
vcsSyncRepos :: Verbosity -> ConfiguredProgram
308319
-> [(SourceRepositoryPackage f, FilePath)] -> IO [MonitorFilePath]
309-
vcsSyncRepos _v _p _rs = fail "sync repo not yet supported for darcs"
320+
vcsSyncRepos _ _ [] = return []
321+
vcsSyncRepos verbosity prog ((primaryRepo, primaryLocalDir) : secondaryRepos) =
322+
monitors <$ do
323+
vcsSyncRepo verbosity prog primaryRepo primaryLocalDir Nothing
324+
for_ secondaryRepos $ \ (repo, localDir) ->
325+
vcsSyncRepo verbosity prog repo localDir $ Just primaryLocalDir
326+
where
327+
dirs = primaryLocalDir : (snd <$> secondaryRepos)
328+
monitors = monitorDirectoryExistence <$> dirs
329+
330+
vcsSyncRepo verbosity prog SourceRepositoryPackage{..} localDir _peer =
331+
try (lines <$> darcsWithOutput localDir ["log", "--last", "1"]) >>= \ case
332+
Right (_:_:_:x:_)
333+
| Just tag <- (List.stripPrefix "tagged " . List.dropWhile Char.isSpace) x
334+
, Just tag' <- srpTag
335+
, tag == tag' -> pure ()
336+
Left e | not (isDoesNotExistError e) -> throw e
337+
_ -> do
338+
removeDirectoryRecursive localDir `catch` liftA2 unless isDoesNotExistError throw
339+
darcs (takeDirectory localDir) cloneArgs
340+
where
341+
darcs :: FilePath -> [String] -> IO ()
342+
darcs = darcs' runProgramInvocation
343+
344+
darcsWithOutput :: FilePath -> [String] -> IO String
345+
darcsWithOutput = darcs' getProgramInvocationOutput
346+
347+
darcs' f cwd args = f verbosity (programInvocation prog args)
348+
{ progInvokeCwd = Just cwd }
349+
350+
cloneArgs = ["clone"] ++ tagArgs ++ [srpLocation, localDir] ++ verboseArg
351+
tagArgs = case srpTag of
352+
Nothing -> []
353+
Just tag -> ["-t" ++ tag]
354+
verboseArg = [ "--quiet" | verbosity < Verbosity.normal ]
310355

311356
darcsProgram :: Program
312357
darcsProgram = (simpleProgram "darcs") {

changelog.d/sync-repo-darcs

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,2 @@
1+
synopsis: Sync repo darcs
2+
prs: #7137

0 commit comments

Comments
 (0)