|
| 1 | +{-# LANGUAGE LambdaCase #-} |
| 2 | +{-# LANGUAGE ScopedTypeVariables #-} |
1 | 3 | {-# LANGUAGE NamedFieldPuns, RecordWildCards, RankNTypes #-}
|
2 | 4 | module Distribution.Client.VCS (
|
3 | 5 | -- * VCS driver type
|
@@ -45,20 +47,29 @@ import Distribution.Simple.Program
|
45 | 47 | ( Program(programFindVersion)
|
46 | 48 | , ConfiguredProgram(programVersion)
|
47 | 49 | , simpleProgram, findProgramVersion
|
48 |
| - , ProgramInvocation(..), programInvocation, runProgramInvocation |
| 50 | + , ProgramInvocation(..), programInvocation, runProgramInvocation, getProgramInvocationOutput |
49 | 51 | , emptyProgramDb, requireProgram )
|
50 | 52 | import Distribution.Version
|
51 | 53 | ( mkVersion )
|
52 | 54 | import qualified Distribution.PackageDescription as PD
|
53 | 55 |
|
| 56 | +import Control.Applicative |
| 57 | + ( liftA2 ) |
| 58 | +import Control.Exception |
| 59 | + ( throw, try ) |
54 | 60 | import Control.Monad.Trans
|
55 | 61 | ( liftIO )
|
56 | 62 | import qualified Data.Char as Char
|
| 63 | +import qualified Data.List as List |
57 | 64 | import qualified Data.Map as Map
|
58 | 65 | import System.FilePath
|
59 | 66 | ( takeDirectory )
|
60 | 67 | import System.Directory
|
61 |
| - ( doesDirectoryExist ) |
| 68 | + ( doesDirectoryExist |
| 69 | + , removeDirectoryRecursive |
| 70 | + ) |
| 71 | +import System.IO.Error |
| 72 | + ( isDoesNotExistError ) |
62 | 73 |
|
63 | 74 |
|
64 | 75 | -- | A driver for a version control system, e.g. git, darcs etc.
|
@@ -306,7 +317,41 @@ vcsDarcs =
|
306 | 317 |
|
307 | 318 | vcsSyncRepos :: Verbosity -> ConfiguredProgram
|
308 | 319 | -> [(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 ] |
310 | 355 |
|
311 | 356 | darcsProgram :: Program
|
312 | 357 | darcsProgram = (simpleProgram "darcs") {
|
|
0 commit comments