module Darcs.Repository.Clone
    ( cloneRepository
    ) where

import Darcs.Prelude

import Control.Exception ( catch, SomeException )
import Control.Monad ( forM, unless, void, when )
import qualified Data.ByteString.Char8 as BC
import Data.List( intercalate )
import Data.Maybe( catMaybes )
import Safe ( tailErr )
import System.FilePath.Posix ( (</>) )
import System.Directory
    ( removeFile
    , listDirectory
    )

import Darcs.Repository.Create
    ( EmptyRepository(..)
    , createRepository
    )
import Darcs.Repository.Identify ( identifyRepositoryFor, ReadingOrWriting(..) )
import Darcs.Repository.Pristine
    ( applyToTentativePristine
    , createPristineDirectoryTree
    , writePristine
    )
import Darcs.Repository.Hashed
    ( copyHashedInventory
    , readPatches
    , tentativelyRemovePatches
    , writeTentativeInventory
    )
import Darcs.Repository.Transaction
    ( finalizeRepositoryChanges
    , revertRepositoryChanges
    )
import Darcs.Repository.Working
    ( setAllScriptsExecutable
    , setScriptsExecutablePatches )
import Darcs.Repository.InternalTypes
    ( Repository
    , AccessType(..)
    , repoLocation
    , repoFormat
    , repoCache
    , modifyCache
    )
import Darcs.Repository.Job ( withUMaskFlag )
import Darcs.Util.Cache
    ( filterRemoteCaches
    , fetchFileUsingCache
    , speculateFileUsingCache
    , dropNonRepos
    )

import Darcs.Repository.ApplyPatches ( runDefault )
import Darcs.Repository.Inventory
    ( PatchHash
    , encodeValidHash
    , peekPristineHash
    )
import Darcs.Repository.Format
    ( RepoProperty ( HashedInventory, Darcs2, Darcs3 )
    , RepoFormat
    , formatHas
    )
import Darcs.Repository.Prefs ( addRepoSource, deleteSources )
import Darcs.Repository.Match ( getOnePatchset )
import Darcs.Util.File
    ( copyFileOrUrl
    , Cachable(..)
    , gzFetchFilePS
    )
import Darcs.Repository.PatchIndex
    ( doesPatchIndexExist
    , createPIWithInterrupt
    )
import Darcs.Repository.Packs
    ( fetchAndUnpackBasic
    , fetchAndUnpackPatches
    , packsDir
    )
import Darcs.Repository.Paths ( hashedInventoryPath, pristineDirPath )
import Darcs.Repository.Resolution
    ( StandardResolution(..)
    , patchsetConflictResolutions
    , announceConflicts
    )
import Darcs.Repository.Working ( applyToWorking )
import Darcs.Util.Lock ( writeTextFile, withNewDirectory )
import Darcs.Repository.Flags
    ( UpdatePending(..)
    , UseCache(..)
    , RemoteDarcs (..)
    , remoteDarcs
    , CloneKind (..)
    , Verbosity (..)
    , DryRun (..)
    , UMask (..)
    , SetScriptsExecutable (..)
    , SetDefault (..)
    , InheritDefault (..)
    , WithWorkingDir (..)
    , ForgetParent (..)
    , WithPatchIndex (..)
    , PatchFormat (..)
    , AllowConflicts(..)
    , ResolveConflicts(..)
    , WithPrefsTemplates(..)
    )

import Darcs.Patch ( RepoPatch, description )
import Darcs.Patch.Depends ( findUncommon )
import Darcs.Patch.Invertible ( mkInvertible )
import Darcs.Patch.Set
    ( Origin
    , patchSet2FL
    , patchSet2RL
    , patchSetInventoryHashes
    , progressPatchSet
    )
import Darcs.Patch.Match ( MatchFlag(..), patchSetMatch )
import Darcs.Patch.Progress ( progressRLShowTags, progressFL )
import Darcs.Patch.Apply ( Apply(..) )
import Darcs.Patch.Witnesses.Sealed ( Sealed(..) )
import Darcs.Patch.Witnesses.Ordered
    ( (:\/:)(..)
    , FL(..)
    , RL(..)
    , lengthFL
    , mapRL
    , lengthRL
    , nullFL
    )
import Darcs.Patch.PatchInfoAnd ( PatchInfoAnd, extractHash )

import Darcs.Util.Tree( Tree, emptyTree )

import Darcs.Util.Exception ( catchall )
import Darcs.Util.English ( englishNum, Noun(..) )
import Darcs.Util.Global ( darcsdir )
import Darcs.Util.URL ( isValidLocalPath )
import Darcs.Util.SignalHandler ( catchInterrupt, withSignalsBlocked )
import Darcs.Util.Ssh ( resetSshConnections )
import Darcs.Util.Printer ( Doc, ($$), hsep, putDocLn, text )
import Darcs.Util.Printer.Color ( unsafeRenderStringColored )
import Darcs.Util.Progress
    ( debugMessage
    , tediousSize
    , beginTedious
    , endTedious
    )

joinUrl :: [String] -> String
joinUrl :: [String] -> String
joinUrl = String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
"/"

cloneRepository ::
    String    -- origin repository path
    -> String -- new repository name (for relative path)
    -> Verbosity -> UseCache
    -> CloneKind
    -> UMask -> RemoteDarcs
    -> SetScriptsExecutable
    -> SetDefault
    -> InheritDefault
    -> [MatchFlag]
    -> RepoFormat
    -> WithWorkingDir
    -> WithPatchIndex   -- use patch index
    -> Bool   -- use packs
    -> ForgetParent
    -> WithPrefsTemplates
    -> IO ()
cloneRepository :: String
-> String
-> Verbosity
-> UseCache
-> CloneKind
-> UMask
-> RemoteDarcs
-> SetScriptsExecutable
-> SetDefault
-> InheritDefault
-> [MatchFlag]
-> RepoFormat
-> WithWorkingDir
-> WithPatchIndex
-> Bool
-> ForgetParent
-> WithPrefsTemplates
-> IO ()
cloneRepository String
repourl String
mysimplename Verbosity
v UseCache
useCache CloneKind
cloneKind UMask
um RemoteDarcs
rdarcs SetScriptsExecutable
sse
                SetDefault
setDefault InheritDefault
inheritDefault [MatchFlag]
matchFlags RepoFormat
rfsource WithWorkingDir
withWorkingDir
                WithPatchIndex
usePatchIndex Bool
usePacks ForgetParent
forget WithPrefsTemplates
withPrefsTemplates =
  UMask -> IO () -> IO ()
forall a. UMask -> IO a -> IO a
withUMaskFlag UMask
um (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> IO () -> IO ()
withNewDirectory String
mysimplename (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
      let patchfmt :: PatchFormat
patchfmt
            | RepoProperty -> RepoFormat -> Bool
formatHas RepoProperty
Darcs3 RepoFormat
rfsource = PatchFormat
PatchFormat3
            | RepoProperty -> RepoFormat -> Bool
formatHas RepoProperty
Darcs2 RepoFormat
rfsource = PatchFormat
PatchFormat2
            | Bool
otherwise                 = PatchFormat
PatchFormat1
      EmptyRepository Repository 'RO p Origin Origin
_toRepo <-
        PatchFormat
-> WithWorkingDir
-> WithPatchIndex
-> UseCache
-> WithPrefsTemplates
-> IO EmptyRepository
createRepository PatchFormat
patchfmt WithWorkingDir
withWorkingDir
          (if CloneKind
cloneKind CloneKind -> CloneKind -> Bool
forall a. Eq a => a -> a -> Bool
== CloneKind
LazyClone then WithPatchIndex
NoPatchIndex else WithPatchIndex
usePatchIndex)
          UseCache
useCache WithPrefsTemplates
withPrefsTemplates
      String -> IO ()
debugMessage String
"Finished initializing new repository."
      String -> DryRun -> SetDefault -> InheritDefault -> Bool -> IO ()
addRepoSource String
repourl DryRun
NoDryRun SetDefault
setDefault InheritDefault
inheritDefault Bool
False

      String -> IO ()
debugMessage String
"Identifying remote repository..."
      Repository 'RO p Origin Origin
fromRepo <- ReadingOrWriting
-> Repository 'RO p Origin Origin
-> UseCache
-> String
-> IO (Repository 'RO p Origin Origin)
forall (rt :: AccessType) (p :: * -> * -> *) wU wR vR vU.
ReadingOrWriting
-> Repository rt p wU wR
-> UseCache
-> String
-> IO (Repository 'RO p vR vU)
identifyRepositoryFor ReadingOrWriting
Reading Repository 'RO p Origin Origin
_toRepo UseCache
useCache String
repourl
      let fromLoc :: String
fromLoc = Repository 'RO p Origin Origin -> String
forall (rt :: AccessType) (p :: * -> * -> *) wU wR.
Repository rt p wU wR -> String
repoLocation Repository 'RO p Origin Origin
fromRepo

      String -> IO ()
debugMessage String
"Copying prefs..."
      String -> String -> String -> Cachable -> IO ()
copyFileOrUrl (RemoteDarcs -> String
remoteDarcs RemoteDarcs
rdarcs)
        ([String] -> String
joinUrl [String
fromLoc, String
darcsdir, String
"prefs", String
"prefs"])
        (String
darcsdir String -> String -> String
</> String
"prefs/prefs") (CInt -> Cachable
MaxAge CInt
600) IO () -> IO () -> IO ()
forall a. IO a -> IO a -> IO a
`catchall` () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

      String -> IO ()
debugMessage String
"Filtering remote sources..."
      Cache
cache <- Cache -> IO Cache
filterRemoteCaches (Repository 'RO p Origin Origin -> Cache
forall (rt :: AccessType) (p :: * -> * -> *) wU wR.
Repository rt p wU wR -> Cache
repoCache Repository 'RO p Origin Origin
fromRepo)
      Repository 'RO p Origin Origin
_toRepo <- Repository 'RO p Origin Origin
-> IO (Repository 'RO p Origin Origin)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Repository 'RO p Origin Origin
 -> IO (Repository 'RO p Origin Origin))
-> Repository 'RO p Origin Origin
-> IO (Repository 'RO p Origin Origin)
forall a b. (a -> b) -> a -> b
$ (Cache -> Cache)
-> Repository 'RO p Origin Origin -> Repository 'RO p Origin Origin
forall (rt :: AccessType) (p :: * -> * -> *) wU wR.
(Cache -> Cache) -> Repository rt p wU wR -> Repository rt p wU wR
modifyCache (Cache -> Cache -> Cache
forall a b. a -> b -> a
const Cache
cache) Repository 'RO p Origin Origin
_toRepo
      String -> String -> IO ()
forall p. FilePathLike p => p -> String -> IO ()
writeTextFile
        (String
darcsdir String -> String -> String
</> String
"prefs/sources")
        ([String] -> String
unlines [Cache -> String
forall a. Show a => a -> String
show (Cache -> String) -> Cache -> String
forall a b. (a -> b) -> a -> b
$ Cache -> Cache
dropNonRepos Cache
cache])
      String -> IO ()
debugMessage (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"Considering sources:\n"String -> String -> String
forall a. [a] -> [a] -> [a]
++Cache -> String
forall a. Show a => a -> String
show (Repository 'RO p Origin Origin -> Cache
forall (rt :: AccessType) (p :: * -> * -> *) wU wR.
Repository rt p wU wR -> Cache
repoCache Repository 'RO p Origin Origin
_toRepo)

      if RepoProperty -> RepoFormat -> Bool
formatHas RepoProperty
HashedInventory (Repository 'RO p Origin Origin -> RepoFormat
forall (rt :: AccessType) (p :: * -> * -> *) wU wR.
Repository rt p wU wR -> RepoFormat
repoFormat Repository 'RO p Origin Origin
fromRepo) then do
       String -> IO ()
debugMessage String
"Copying basic repository (hashed_inventory and pristine)"
       if Bool
usePacks Bool -> Bool -> Bool
&& (Bool -> Bool
not (Bool -> Bool) -> (String -> Bool) -> String -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Bool
isValidLocalPath) String
fromLoc
         then Repository 'RO p Origin Origin
-> Repository 'RO p Origin Origin
-> Verbosity
-> RemoteDarcs
-> WithWorkingDir
-> IO ()
forall (p :: * -> * -> *) wU wR.
Repository 'RO p wU wR
-> Repository 'RO p wU wR
-> Verbosity
-> RemoteDarcs
-> WithWorkingDir
-> IO ()
copyBasicRepoPacked    Repository 'RO p Origin Origin
fromRepo Repository 'RO p Origin Origin
_toRepo Verbosity
v RemoteDarcs
rdarcs WithWorkingDir
withWorkingDir
         else Repository 'RO p Origin Origin
-> Repository 'RO p Origin Origin
-> Verbosity
-> RemoteDarcs
-> WithWorkingDir
-> IO ()
forall (p :: * -> * -> *) wU wR.
Repository 'RO p wU wR
-> Repository 'RO p wU wR
-> Verbosity
-> RemoteDarcs
-> WithWorkingDir
-> IO ()
copyBasicRepoNotPacked Repository 'RO p Origin Origin
fromRepo Repository 'RO p Origin Origin
_toRepo Verbosity
v RemoteDarcs
rdarcs WithWorkingDir
withWorkingDir
       Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (CloneKind
cloneKind CloneKind -> CloneKind -> Bool
forall a. Eq a => a -> a -> Bool
/= CloneKind
LazyClone) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
         Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (CloneKind
cloneKind CloneKind -> CloneKind -> Bool
forall a. Eq a => a -> a -> Bool
/= CloneKind
CompleteClone) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
           Verbosity -> Doc -> IO ()
putInfo Verbosity
v (Doc -> IO ()) -> Doc -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> Doc
text String
"Copying patches, to get lazy repository hit ctrl-C..."
         String -> IO ()
debugMessage String
"Copying complete repository (inventories and patches)"
         if Bool
usePacks Bool -> Bool -> Bool
&& (Bool -> Bool
not (Bool -> Bool) -> (String -> Bool) -> String -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Bool
isValidLocalPath) String
fromLoc
           then Repository 'RO p Origin Origin
-> Repository 'RO p Origin Origin
-> Verbosity
-> CloneKind
-> IO ()
forall (rt :: AccessType) (p :: * -> * -> *) wU wR.
(RepoPatch p, ApplyState p ~ Tree) =>
Repository 'RO p wU wR
-> Repository rt p wU wR -> Verbosity -> CloneKind -> IO ()
copyCompleteRepoPacked    Repository 'RO p Origin Origin
fromRepo Repository 'RO p Origin Origin
_toRepo Verbosity
v CloneKind
cloneKind
           else Repository 'RO p Origin Origin
-> Repository 'RO p Origin Origin
-> Verbosity
-> CloneKind
-> IO ()
forall (rt :: AccessType) (p :: * -> * -> *) wU wR.
(RepoPatch p, ApplyState p ~ Tree) =>
Repository 'RO p wU wR
-> Repository rt p wU wR -> Verbosity -> CloneKind -> IO ()
copyCompleteRepoNotPacked Repository 'RO p Origin Origin
fromRepo Repository 'RO p Origin Origin
_toRepo Verbosity
v CloneKind
cloneKind
      else
       -- old-fashioned repositories are cloned differently since
       -- we need to copy all patches first and then build pristine
       Repository 'RO p Origin Origin
-> Repository 'RO p Origin Origin
-> Verbosity
-> WithWorkingDir
-> IO ()
forall (p :: * -> * -> *) wU wR.
(RepoPatch p, ApplyState p ~ Tree) =>
Repository 'RO p wU wR
-> Repository 'RO p Origin Origin
-> Verbosity
-> WithWorkingDir
-> IO ()
copyRepoOldFashioned Repository 'RO p Origin Origin
fromRepo Repository 'RO p Origin Origin
_toRepo Verbosity
v WithWorkingDir
withWorkingDir
      Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (SetScriptsExecutable
sse SetScriptsExecutable -> SetScriptsExecutable -> Bool
forall a. Eq a => a -> a -> Bool
== SetScriptsExecutable
YesSetScriptsExecutable) IO ()
setAllScriptsExecutable
      case [MatchFlag] -> Maybe PatchSetMatch
patchSetMatch [MatchFlag]
matchFlags of
       Maybe PatchSetMatch
Nothing -> () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
       Just PatchSetMatch
psm -> do
        Verbosity -> Doc -> IO ()
putInfo Verbosity
v (Doc -> IO ()) -> Doc -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> Doc
text String
"Going to specified version..."
        -- the following is necessary to be able to read _toRepo's patches
        Repository 'RW p Origin Origin
_toRepo <- Repository 'RO p Origin Origin
-> IO (Repository 'RW p Origin Origin)
forall (p :: * -> * -> *) wU wR.
RepoPatch p =>
Repository 'RO p wU wR -> IO (Repository 'RW p wU wR)
revertRepositoryChanges Repository 'RO p Origin Origin
_toRepo
        PatchSet p Origin Origin
patches <- Repository 'RW p Origin Origin -> IO (PatchSet p Origin Origin)
forall (p :: * -> * -> *) (rt :: AccessType) wU wR.
RepoPatch p =>
Repository rt p wU wR -> IO (PatchSet p Origin wR)
readPatches Repository 'RW p Origin Origin
_toRepo
        Sealed PatchSet p Origin wX
context <- Repository 'RW p Origin Origin
-> PatchSetMatch -> IO (Sealed (PatchSet p Origin))
forall (p :: * -> * -> *) (rt :: AccessType) wU wR.
RepoPatch p =>
Repository rt p wU wR
-> PatchSetMatch -> IO (SealedPatchSet p Origin)
getOnePatchset Repository 'RW p Origin Origin
_toRepo PatchSetMatch
psm
        FL (PatchInfoAnd p) wZ Origin
to_remove :\/: FL (PatchInfoAnd p) wZ wX
only_in_context <- (:\/:) (FL (PatchInfoAnd p)) (FL (PatchInfoAnd p)) Origin wX
-> IO
     ((:\/:) (FL (PatchInfoAnd p)) (FL (PatchInfoAnd p)) Origin wX)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ((:\/:) (FL (PatchInfoAnd p)) (FL (PatchInfoAnd p)) Origin wX
 -> IO
      ((:\/:) (FL (PatchInfoAnd p)) (FL (PatchInfoAnd p)) Origin wX))
-> (:\/:) (FL (PatchInfoAnd p)) (FL (PatchInfoAnd p)) Origin wX
-> IO
     ((:\/:) (FL (PatchInfoAnd p)) (FL (PatchInfoAnd p)) Origin wX)
forall a b. (a -> b) -> a -> b
$ PatchSet p Origin Origin
-> PatchSet p Origin wX
-> (:\/:) (FL (PatchInfoAnd p)) (FL (PatchInfoAnd p)) Origin wX
forall (p :: * -> * -> *) wX wY.
Commute p =>
PatchSet p Origin wX
-> PatchSet p Origin wY
-> (:\/:) (FL (PatchInfoAnd p)) (FL (PatchInfoAnd p)) wX wY
findUncommon PatchSet p Origin Origin
patches PatchSet p Origin wX
context
        case FL (PatchInfoAnd p) wZ wX
only_in_context of
          FL (PatchInfoAnd p) wZ wX
NilFL -> do
            let num_to_remove :: Int
num_to_remove = FL (PatchInfoAnd p) wZ Origin -> Int
forall (a :: * -> * -> *) wX wZ. FL a wX wZ -> Int
lengthFL FL (PatchInfoAnd p) wZ Origin
to_remove
            Verbosity -> Doc -> IO ()
putInfo Verbosity
v (Doc -> IO ()) -> Doc -> IO ()
forall a b. (a -> b) -> a -> b
$ [Doc] -> Doc
hsep ([Doc] -> Doc) -> [Doc] -> Doc
forall a b. (a -> b) -> a -> b
$ (String -> Doc) -> [String] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map String -> Doc
text
              [ String
"Unapplying"
              , Int -> String
forall a. Show a => a -> String
show Int
num_to_remove
              , Int -> Noun -> String -> String
forall n. Countable n => Int -> n -> String -> String
englishNum Int
num_to_remove (String -> Noun
Noun String
"patch") String
""
              ]
            Repository 'RW p Origin wZ
_toRepo <-
              Repository 'RW p Origin Origin
-> UpdatePending
-> FL (PatchInfoAnd p) wZ Origin
-> IO (Repository 'RW p Origin wZ)
forall (p :: * -> * -> *) wU wR wX.
(RepoPatch p, ApplyState p ~ Tree) =>
Repository 'RW p wU wR
-> UpdatePending
-> FL (PatchInfoAnd p) wX wR
-> IO (Repository 'RW p wU wX)
tentativelyRemovePatches Repository 'RW p Origin Origin
_toRepo UpdatePending
NoUpdatePending FL (PatchInfoAnd p) wZ Origin
to_remove
            Repository 'RO p Origin wZ
_toRepo <- Repository 'RW p Origin wZ
-> DryRun -> IO (Repository 'RO p Origin wZ)
forall (p :: * -> * -> *) wU wR.
(RepoPatch p, ApplyState p ~ Tree) =>
Repository 'RW p wU wR -> DryRun -> IO (Repository 'RO p wU wR)
finalizeRepositoryChanges Repository 'RW p Origin wZ
_toRepo DryRun
NoDryRun
            DefaultIO () -> IO ()
forall a. DefaultIO a -> IO a
runDefault (FL (PatchInfoAnd p) wZ Origin -> DefaultIO ()
forall (m :: * -> *) wX wY.
ApplyMonad (ApplyState (FL (PatchInfoAnd p))) m =>
FL (PatchInfoAnd p) wX wY -> m ()
forall (p :: * -> * -> *) (m :: * -> *) wX wY.
(Apply p, ApplyMonad (ApplyState p) m) =>
p wX wY -> m ()
unapply FL (PatchInfoAnd p) wZ Origin
to_remove) IO () -> (SomeException -> IO ()) -> IO ()
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
`catch` \(SomeException
e :: SomeException) ->
                String -> IO ()
forall a. String -> IO a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String
"Couldn't undo patch in working tree.\n" String -> String -> String
forall a. [a] -> [a] -> [a]
++ SomeException -> String
forall a. Show a => a -> String
show SomeException
e)
            Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (SetScriptsExecutable
sse SetScriptsExecutable -> SetScriptsExecutable -> Bool
forall a. Eq a => a -> a -> Bool
== SetScriptsExecutable
YesSetScriptsExecutable) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ FL (PatchInfoAnd p) wZ Origin -> IO ()
forall (p :: * -> * -> *) wX wY. PatchInspect p => p wX wY -> IO ()
setScriptsExecutablePatches FL (PatchInfoAnd p) wZ Origin
to_remove
          FL (PatchInfoAnd p) wZ wX
_ ->
            -- This can only happen if the user supplied a context file that
            -- doesn't specify a subset of the remote repo.
            String -> IO ()
forall a. String -> IO a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ Doc -> String
unsafeRenderStringColored
              (Doc -> String) -> Doc -> String
forall a b. (a -> b) -> a -> b
$ String -> Doc
text String
"Missing patches from context:"
              Doc -> Doc -> Doc
$$ FL (PatchInfoAnd p) wZ wX -> Doc
forall wX wY. FL (PatchInfoAnd p) wX wY -> Doc
forall (p :: * -> * -> *) wX wY. ShowPatch p => p wX wY -> Doc
description FL (PatchInfoAnd p) wZ wX
only_in_context
      Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (ForgetParent
forget ForgetParent -> ForgetParent -> Bool
forall a. Eq a => a -> a -> Bool
== ForgetParent
YesForgetParent) IO ()
deleteSources
      -- check for unresolved conflicts
      PatchSet p Origin Origin
patches <- Repository 'RO p Origin Origin -> IO (PatchSet p Origin Origin)
forall (p :: * -> * -> *) (rt :: AccessType) wU wR.
RepoPatch p =>
Repository rt p wU wR -> IO (PatchSet p Origin wR)
readPatches Repository 'RO p Origin Origin
_toRepo
      let conflicts :: StandardResolution (PrimOf p) Origin
conflicts = PatchSet p Origin Origin -> StandardResolution (PrimOf p) Origin
forall (p :: * -> * -> *) wX.
RepoPatch p =>
PatchSet p Origin wX -> StandardResolution (PrimOf p) wX
patchsetConflictResolutions PatchSet p Origin Origin
patches
      Bool
_ <- String
-> AllowConflicts
-> StandardResolution (PrimOf p) Origin
-> IO Bool
forall (prim :: * -> * -> *) wX.
PrimPatch prim =>
String -> AllowConflicts -> StandardResolution prim wX -> IO Bool
announceConflicts String
"clone" (ResolveConflicts -> AllowConflicts
YesAllowConflicts ResolveConflicts
MarkConflicts) StandardResolution (PrimOf p) Origin
conflicts
      Sealed FL (PrimOf p) Origin wX
mangled_res <- Sealed (FL (PrimOf p) Origin) -> IO (Sealed (FL (PrimOf p) Origin))
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Sealed (FL (PrimOf p) Origin)
 -> IO (Sealed (FL (PrimOf p) Origin)))
-> Sealed (FL (PrimOf p) Origin)
-> IO (Sealed (FL (PrimOf p) Origin))
forall a b. (a -> b) -> a -> b
$ StandardResolution (PrimOf p) Origin
-> Sealed (FL (PrimOf p) Origin)
forall (prim :: * -> * -> *) wX.
StandardResolution prim wX -> Mangled prim wX
mangled StandardResolution (PrimOf p) Origin
conflicts
      Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FL (PrimOf p) Origin wX -> Bool
forall (a :: * -> * -> *) wX wZ. FL a wX wZ -> Bool
nullFL FL (PrimOf p) Origin wX
mangled_res) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
        IO () -> IO ()
forall a. IO a -> IO a
withSignalsBlocked (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ IO (Repository 'RO p wX Origin) -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IO (Repository 'RO p wX Origin) -> IO ())
-> IO (Repository 'RO p wX Origin) -> IO ()
forall a b. (a -> b) -> a -> b
$ Repository 'RO p Origin Origin
-> Verbosity
-> FL (PrimOf p) Origin wX
-> IO (Repository 'RO p wX Origin)
forall (p :: * -> * -> *) (rt :: AccessType) wU wR wY.
(ApplyState p ~ Tree, RepoPatch p) =>
Repository rt p wU wR
-> Verbosity -> FL (PrimOf p) wU wY -> IO (Repository rt p wY wR)
applyToWorking Repository 'RO p Origin Origin
_toRepo Verbosity
v FL (PrimOf p) Origin wX
mangled_res

putInfo :: Verbosity -> Doc -> IO ()
putInfo :: Verbosity -> Doc -> IO ()
putInfo Verbosity
Quiet Doc
_ = () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
putInfo Verbosity
_ Doc
d = Doc -> IO ()
putDocLn Doc
d

putVerbose :: Verbosity -> Doc -> IO ()
putVerbose :: Verbosity -> Doc -> IO ()
putVerbose Verbosity
Verbose Doc
d = Doc -> IO ()
putDocLn Doc
d
putVerbose Verbosity
_ Doc
_ = () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

copyBasicRepoNotPacked  :: forall p wU wR.
                           Repository 'RO p wU wR -- remote
                        -> Repository 'RO p wU wR -- existing empty local
                        -> Verbosity
                        -> RemoteDarcs
                        -> WithWorkingDir
                        -> IO ()
copyBasicRepoNotPacked :: forall (p :: * -> * -> *) wU wR.
Repository 'RO p wU wR
-> Repository 'RO p wU wR
-> Verbosity
-> RemoteDarcs
-> WithWorkingDir
-> IO ()
copyBasicRepoNotPacked Repository 'RO p wU wR
fromRepo Repository 'RO p wU wR
toRepo Verbosity
verb RemoteDarcs
rdarcs WithWorkingDir
withWorkingDir = do
  Verbosity -> Doc -> IO ()
putVerbose Verbosity
verb (Doc -> IO ()) -> Doc -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> Doc
text String
"Copying hashed inventory from remote repo..."
  Repository 'RO p wU wR -> RemoteDarcs -> String -> IO ()
forall (p :: * -> * -> *) wU wR.
Repository 'RO p wU wR -> RemoteDarcs -> String -> IO ()
copyHashedInventory Repository 'RO p wU wR
toRepo RemoteDarcs
rdarcs (Repository 'RO p wU wR -> String
forall (rt :: AccessType) (p :: * -> * -> *) wU wR.
Repository rt p wU wR -> String
repoLocation Repository 'RO p wU wR
fromRepo)
  Verbosity -> Doc -> IO ()
putVerbose Verbosity
verb (Doc -> IO ()) -> Doc -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> Doc
text String
"Writing pristine and working tree contents..."
  Repository 'RO p wU wR -> String -> WithWorkingDir -> IO ()
forall (rt :: AccessType) (p :: * -> * -> *) wU wR.
Repository rt p wU wR -> String -> WithWorkingDir -> IO ()
createPristineDirectoryTree Repository 'RO p wU wR
toRepo String
"." WithWorkingDir
withWorkingDir

copyCompleteRepoNotPacked :: forall rt p wU wR. (RepoPatch p, ApplyState p ~ Tree)
                        => Repository 'RO p wU wR -- remote
                        -> Repository rt p wU wR -- existing basic local
                        -> Verbosity
                        -> CloneKind
                        -> IO ()
copyCompleteRepoNotPacked :: forall (rt :: AccessType) (p :: * -> * -> *) wU wR.
(RepoPatch p, ApplyState p ~ Tree) =>
Repository 'RO p wU wR
-> Repository rt p wU wR -> Verbosity -> CloneKind -> IO ()
copyCompleteRepoNotPacked Repository 'RO p wU wR
_ Repository rt p wU wR
toRepo Verbosity
verb CloneKind
cloneKind = do
       let cleanup :: IO ()
cleanup = Verbosity -> Doc -> IO ()
putInfo Verbosity
verb (Doc -> IO ()) -> Doc -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> Doc
text String
"Using lazy repository."
       CloneKind -> IO () -> IO () -> IO ()
allowCtrlC CloneKind
cloneKind IO ()
cleanup (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
         Repository rt p wU wR -> IO ()
forall (rt :: AccessType) (p :: * -> * -> *) wU wR.
RepoPatch p =>
Repository rt p wU wR -> IO ()
fetchPatchesIfNecessary Repository rt p wU wR
toRepo
         Bool
pi <- String -> IO Bool
doesPatchIndexExist (Repository rt p wU wR -> String
forall (rt :: AccessType) (p :: * -> * -> *) wU wR.
Repository rt p wU wR -> String
repoLocation Repository rt p wU wR
toRepo)
         PatchSet p Origin wR
ps <- Repository rt p wU wR -> IO (PatchSet p Origin wR)
forall (p :: * -> * -> *) (rt :: AccessType) wU wR.
RepoPatch p =>
Repository rt p wU wR -> IO (PatchSet p Origin wR)
readPatches Repository rt p wU wR
toRepo
         Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
pi (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ Repository rt p wU wR -> PatchSet p Origin wR -> IO ()
forall (p :: * -> * -> *) (rt :: AccessType) wU wR.
(RepoPatch p, ApplyState p ~ Tree) =>
Repository rt p wU wR -> PatchSet p Origin wR -> IO ()
createPIWithInterrupt Repository rt p wU wR
toRepo PatchSet p Origin wR
ps

copyBasicRepoPacked ::
  forall p wU wR.
     Repository 'RO p wU wR -- remote
  -> Repository 'RO p wU wR -- existing empty local repository
  -> Verbosity
  -> RemoteDarcs
  -> WithWorkingDir
  -> IO ()
copyBasicRepoPacked :: forall (p :: * -> * -> *) wU wR.
Repository 'RO p wU wR
-> Repository 'RO p wU wR
-> Verbosity
-> RemoteDarcs
-> WithWorkingDir
-> IO ()
copyBasicRepoPacked Repository 'RO p wU wR
fromRepo Repository 'RO p wU wR
toRepo Verbosity
verb RemoteDarcs
rdarcs WithWorkingDir
withWorkingDir =
  do let fromLoc :: String
fromLoc = Repository 'RO p wU wR -> String
forall (rt :: AccessType) (p :: * -> * -> *) wU wR.
Repository rt p wU wR -> String
repoLocation Repository 'RO p wU wR
fromRepo
     let hashURL :: String
hashURL = [String] -> String
joinUrl [String
fromLoc, String
darcsdir, String
packsDir, String
"pristine"]
     Maybe ByteString
mPackHash <- (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (ByteString -> Maybe ByteString)
-> IO ByteString -> IO (Maybe ByteString)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> Cachable -> IO ByteString
gzFetchFilePS String
hashURL Cachable
Uncachable) IO (Maybe ByteString)
-> IO (Maybe ByteString) -> IO (Maybe ByteString)
forall a. IO a -> IO a -> IO a
`catchall` (Maybe ByteString -> IO (Maybe ByteString)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ByteString
forall a. Maybe a
Nothing)
     let hiURL :: String
hiURL = String
fromLoc String -> String -> String
</> String
hashedInventoryPath
     ByteString
i <- String -> Cachable -> IO ByteString
gzFetchFilePS String
hiURL Cachable
Uncachable
     let currentHash :: ByteString
currentHash = String -> ByteString
BC.pack (String -> ByteString) -> String -> ByteString
forall a b. (a -> b) -> a -> b
$ PristineHash -> String
forall h. ValidHash h => h -> String
encodeValidHash (PristineHash -> String) -> PristineHash -> String
forall a b. (a -> b) -> a -> b
$ ByteString -> PristineHash
peekPristineHash ByteString
i
     let copyNormally :: IO ()
copyNormally = Repository 'RO p wU wR
-> Repository 'RO p wU wR
-> Verbosity
-> RemoteDarcs
-> WithWorkingDir
-> IO ()
forall (p :: * -> * -> *) wU wR.
Repository 'RO p wU wR
-> Repository 'RO p wU wR
-> Verbosity
-> RemoteDarcs
-> WithWorkingDir
-> IO ()
copyBasicRepoNotPacked Repository 'RO p wU wR
fromRepo Repository 'RO p wU wR
toRepo Verbosity
verb RemoteDarcs
rdarcs WithWorkingDir
withWorkingDir
     case Maybe ByteString
mPackHash of
      Just ByteString
packHash | ByteString
packHash ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== ByteString
currentHash
              -> ( do Repository 'RO p wU wR
-> Repository 'RO p wU wR -> Verbosity -> WithWorkingDir -> IO ()
forall (rt :: AccessType) (p :: * -> * -> *) wU wR.
Repository 'RO p wU wR
-> Repository rt p wU wR -> Verbosity -> WithWorkingDir -> IO ()
copyBasicRepoPacked2 Repository 'RO p wU wR
fromRepo Repository 'RO p wU wR
toRepo Verbosity
verb WithWorkingDir
withWorkingDir
                      -- need to obtain a fresh copy of hashed_inventory as reference
                      Verbosity -> Doc -> IO ()
putVerbose Verbosity
verb (Doc -> IO ()) -> Doc -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> Doc
text String
"Copying hashed inventory from remote repo..."
                      Repository 'RO p wU wR -> RemoteDarcs -> String -> IO ()
forall (p :: * -> * -> *) wU wR.
Repository 'RO p wU wR -> RemoteDarcs -> String -> IO ()
copyHashedInventory Repository 'RO p wU wR
toRepo RemoteDarcs
rdarcs (Repository 'RO p wU wR -> String
forall (rt :: AccessType) (p :: * -> * -> *) wU wR.
Repository rt p wU wR -> String
repoLocation Repository 'RO p wU wR
fromRepo)
                   IO () -> (SomeException -> IO ()) -> IO ()
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
`catch` \(SomeException
e :: SomeException) ->
                               do String -> IO ()
putStrLn (String
"Exception while getting basic pack:\n" String -> String -> String
forall a. [a] -> [a] -> [a]
++ SomeException -> String
forall a. Show a => a -> String
show SomeException
e)
                                  IO ()
copyNormally)
      Maybe ByteString
_       -> do Verbosity -> Doc -> IO ()
putVerbose Verbosity
verb (Doc -> IO ()) -> Doc -> IO ()
forall a b. (a -> b) -> a -> b
$
                      String -> Doc
text String
"Remote repo has no basic pack or outdated basic pack, copying normally."
                    IO ()
copyNormally

copyBasicRepoPacked2 ::
  forall rt p wU wR.
     Repository 'RO p wU wR -- remote
  -> Repository rt p wU wR -- existing empty local repository
  -> Verbosity
  -> WithWorkingDir
  -> IO ()
copyBasicRepoPacked2 :: forall (rt :: AccessType) (p :: * -> * -> *) wU wR.
Repository 'RO p wU wR
-> Repository rt p wU wR -> Verbosity -> WithWorkingDir -> IO ()
copyBasicRepoPacked2 Repository 'RO p wU wR
fromRepo Repository rt p wU wR
toRepo Verbosity
verb WithWorkingDir
withWorkingDir = do
  Verbosity -> Doc -> IO ()
putVerbose Verbosity
verb (Doc -> IO ()) -> Doc -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> Doc
text String
"Cloning packed basic repository."
  -- unpack inventory & pristine cache
  String -> IO ()
cleanDir String
pristineDirPath
  String -> IO ()
removeFile String
hashedInventoryPath
  Cache -> String -> IO ()
fetchAndUnpackBasic (Repository rt p wU wR -> Cache
forall (rt :: AccessType) (p :: * -> * -> *) wU wR.
Repository rt p wU wR -> Cache
repoCache Repository rt p wU wR
toRepo) (Repository 'RO p wU wR -> String
forall (rt :: AccessType) (p :: * -> * -> *) wU wR.
Repository rt p wU wR -> String
repoLocation Repository 'RO p wU wR
fromRepo)
  Verbosity -> Doc -> IO ()
putInfo Verbosity
verb (Doc -> IO ()) -> Doc -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> Doc
text String
"Done fetching and unpacking basic pack."
  Repository rt p wU wR -> String -> WithWorkingDir -> IO ()
forall (rt :: AccessType) (p :: * -> * -> *) wU wR.
Repository rt p wU wR -> String -> WithWorkingDir -> IO ()
createPristineDirectoryTree Repository rt p wU wR
toRepo String
"." WithWorkingDir
withWorkingDir

copyCompleteRepoPacked ::
  forall rt p wU wR. (RepoPatch p, ApplyState p ~ Tree)
  => Repository 'RO p wU wR -- remote
  -> Repository rt p wU wR -- existing basic local repository
  -> Verbosity
  -> CloneKind
  -> IO ()
copyCompleteRepoPacked :: forall (rt :: AccessType) (p :: * -> * -> *) wU wR.
(RepoPatch p, ApplyState p ~ Tree) =>
Repository 'RO p wU wR
-> Repository rt p wU wR -> Verbosity -> CloneKind -> IO ()
copyCompleteRepoPacked Repository 'RO p wU wR
from Repository rt p wU wR
to Verbosity
verb CloneKind
cloneKind =
    Repository 'RO p wU wR
-> Repository rt p wU wR -> Verbosity -> CloneKind -> IO ()
forall (rt :: AccessType) (p :: * -> * -> *) wU wR.
(RepoPatch p, ApplyState p ~ Tree) =>
Repository 'RO p wU wR
-> Repository rt p wU wR -> Verbosity -> CloneKind -> IO ()
copyCompleteRepoPacked2 Repository 'RO p wU wR
from Repository rt p wU wR
to Verbosity
verb CloneKind
cloneKind
  IO () -> (SomeException -> IO ()) -> IO ()
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
`catch`
    \(SomeException
e :: SomeException) -> do
      String -> IO ()
putStrLn (String
"Exception while getting patches pack:\n" String -> String -> String
forall a. [a] -> [a] -> [a]
++ SomeException -> String
forall a. Show a => a -> String
show SomeException
e)
      Verbosity -> Doc -> IO ()
putVerbose Verbosity
verb (Doc -> IO ()) -> Doc -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> Doc
text String
"Problem while copying patches pack, copying normally."
      Repository 'RO p wU wR
-> Repository rt p wU wR -> Verbosity -> CloneKind -> IO ()
forall (rt :: AccessType) (p :: * -> * -> *) wU wR.
(RepoPatch p, ApplyState p ~ Tree) =>
Repository 'RO p wU wR
-> Repository rt p wU wR -> Verbosity -> CloneKind -> IO ()
copyCompleteRepoNotPacked Repository 'RO p wU wR
from Repository rt p wU wR
to Verbosity
verb CloneKind
cloneKind

copyCompleteRepoPacked2 ::
  forall rt p wU wR. (RepoPatch p, ApplyState p ~ Tree)
  => Repository 'RO p wU wR
  -> Repository rt p wU wR
  -> Verbosity
  -> CloneKind
  -> IO ()
copyCompleteRepoPacked2 :: forall (rt :: AccessType) (p :: * -> * -> *) wU wR.
(RepoPatch p, ApplyState p ~ Tree) =>
Repository 'RO p wU wR
-> Repository rt p wU wR -> Verbosity -> CloneKind -> IO ()
copyCompleteRepoPacked2 Repository 'RO p wU wR
fromRepo Repository rt p wU wR
toRepo Verbosity
verb CloneKind
cloneKind = do
  PatchSet p Origin wR
us <- Repository rt p wU wR -> IO (PatchSet p Origin wR)
forall (p :: * -> * -> *) (rt :: AccessType) wU wR.
RepoPatch p =>
Repository rt p wU wR -> IO (PatchSet p Origin wR)
readPatches Repository rt p wU wR
toRepo
  -- get old patches
  let cleanup :: IO ()
cleanup = Verbosity -> Doc -> IO ()
putInfo Verbosity
verb (Doc -> IO ()) -> Doc -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> Doc
text String
"Using lazy repository."
  CloneKind -> IO () -> IO () -> IO ()
allowCtrlC CloneKind
cloneKind IO ()
cleanup (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
    Verbosity -> Doc -> IO ()
putVerbose Verbosity
verb (Doc -> IO ()) -> Doc -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> Doc
text String
"Using patches pack."
    [InventoryHash]
is <-
      [Maybe InventoryHash]
-> (Maybe InventoryHash -> IO InventoryHash) -> IO [InventoryHash]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM (PatchSet p Origin wR -> [Maybe InventoryHash]
forall (p :: * -> * -> *) wX wY.
PatchSet p wX wY -> [Maybe InventoryHash]
patchSetInventoryHashes PatchSet p Origin wR
us) ((Maybe InventoryHash -> IO InventoryHash) -> IO [InventoryHash])
-> (Maybe InventoryHash -> IO InventoryHash) -> IO [InventoryHash]
forall a b. (a -> b) -> a -> b
$
        IO InventoryHash
-> (InventoryHash -> IO InventoryHash)
-> Maybe InventoryHash
-> IO InventoryHash
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (String -> IO InventoryHash
forall a. String -> IO a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"unexpected unhashed inventory") InventoryHash -> IO InventoryHash
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return
    [PatchHash]
hs <-
      [Maybe PatchHash]
-> (Maybe PatchHash -> IO PatchHash) -> IO [PatchHash]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM ((forall wW wZ. PatchInfoAnd p wW wZ -> Maybe PatchHash)
-> RL (PatchInfoAnd p) Origin wR -> [Maybe PatchHash]
forall (a :: * -> * -> *) b wX wY.
(forall wW wZ. a wW wZ -> b) -> RL a wX wY -> [b]
mapRL PatchInfoAnd p wW wZ -> Maybe PatchHash
forall wW wZ. PatchInfoAnd p wW wZ -> Maybe PatchHash
forall (p :: * -> * -> *) wA wB.
PatchInfoAnd p wA wB -> Maybe PatchHash
hashedPatchHash (RL (PatchInfoAnd p) Origin wR -> [Maybe PatchHash])
-> RL (PatchInfoAnd p) Origin wR -> [Maybe PatchHash]
forall a b. (a -> b) -> a -> b
$ PatchSet p Origin wR -> RL (PatchInfoAnd p) Origin wR
forall (p :: * -> * -> *) wStart wX.
PatchSet p wStart wX -> RL (PatchInfoAnd p) wStart wX
patchSet2RL PatchSet p Origin wR
us) ((Maybe PatchHash -> IO PatchHash) -> IO [PatchHash])
-> (Maybe PatchHash -> IO PatchHash) -> IO [PatchHash]
forall a b. (a -> b) -> a -> b
$
        IO PatchHash
-> (PatchHash -> IO PatchHash) -> Maybe PatchHash -> IO PatchHash
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (String -> IO PatchHash
forall a. String -> IO a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"unexpected unhashed patch") PatchHash -> IO PatchHash
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return
    [InventoryHash] -> [PatchHash] -> Cache -> String -> IO ()
fetchAndUnpackPatches [InventoryHash]
is [PatchHash]
hs (Repository rt p wU wR -> Cache
forall (rt :: AccessType) (p :: * -> * -> *) wU wR.
Repository rt p wU wR -> Cache
repoCache Repository rt p wU wR
toRepo) (Repository 'RO p wU wR -> String
forall (rt :: AccessType) (p :: * -> * -> *) wU wR.
Repository rt p wU wR -> String
repoLocation Repository 'RO p wU wR
fromRepo)
    Bool
pi <- String -> IO Bool
doesPatchIndexExist (Repository rt p wU wR -> String
forall (rt :: AccessType) (p :: * -> * -> *) wU wR.
Repository rt p wU wR -> String
repoLocation Repository rt p wU wR
toRepo)
    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
pi (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ Repository rt p wU wR -> PatchSet p Origin wR -> IO ()
forall (p :: * -> * -> *) (rt :: AccessType) wU wR.
(RepoPatch p, ApplyState p ~ Tree) =>
Repository rt p wU wR -> PatchSet p Origin wR -> IO ()
createPIWithInterrupt Repository rt p wU wR
toRepo PatchSet p Origin wR
us -- TODO or do another readPatches?

cleanDir :: FilePath -> IO ()
cleanDir :: String -> IO ()
cleanDir String
d = (String -> IO ()) -> [String] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (\String
x -> String -> IO ()
removeFile (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
d String -> String -> String
</> String
x) ([String] -> IO ()) -> IO [String] -> IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< String -> IO [String]
listDirectory String
d

copyRepoOldFashioned :: forall p wU wR. (RepoPatch p, ApplyState p ~ Tree)
                        => Repository 'RO p wU wR  -- remote repo
                        -> Repository 'RO p Origin Origin -- local empty repo
                        -> Verbosity
                        -> WithWorkingDir
                        -> IO ()
copyRepoOldFashioned :: forall (p :: * -> * -> *) wU wR.
(RepoPatch p, ApplyState p ~ Tree) =>
Repository 'RO p wU wR
-> Repository 'RO p Origin Origin
-> Verbosity
-> WithWorkingDir
-> IO ()
copyRepoOldFashioned Repository 'RO p wU wR
fromRepo Repository 'RO p Origin Origin
_toRepo Verbosity
verb WithWorkingDir
withWorkingDir = do
  Repository 'RW p Origin Origin
_toRepo <- Repository 'RO p Origin Origin
-> IO (Repository 'RW p Origin Origin)
forall (p :: * -> * -> *) wU wR.
RepoPatch p =>
Repository 'RO p wU wR -> IO (Repository 'RW p wU wR)
revertRepositoryChanges Repository 'RO p Origin Origin
_toRepo
  PristineHash
_ <- Repository 'RW p Origin Origin -> Tree IO -> IO PristineHash
forall (rt :: AccessType) (p :: * -> * -> *) wU wR.
Repository rt p wU wR -> Tree IO -> IO PristineHash
writePristine Repository 'RW p Origin Origin
_toRepo Tree IO
forall (m :: * -> *). Tree m
emptyTree
  PatchSet p Origin wR
patches <- Repository 'RO p wU wR -> IO (PatchSet p Origin wR)
forall (p :: * -> * -> *) (rt :: AccessType) wU wR.
RepoPatch p =>
Repository rt p wU wR -> IO (PatchSet p Origin wR)
readPatches Repository 'RO p wU wR
fromRepo
  let k :: String
k = String
"Copying patch"
  String -> IO ()
beginTedious String
k
  String -> Int -> IO ()
tediousSize String
k (RL (PatchInfoAnd p) Origin wR -> Int
forall (a :: * -> * -> *) wX wZ. RL a wX wZ -> Int
lengthRL (RL (PatchInfoAnd p) Origin wR -> Int)
-> RL (PatchInfoAnd p) Origin wR -> Int
forall a b. (a -> b) -> a -> b
$ PatchSet p Origin wR -> RL (PatchInfoAnd p) Origin wR
forall (p :: * -> * -> *) wStart wX.
PatchSet p wStart wX -> RL (PatchInfoAnd p) wStart wX
patchSet2RL PatchSet p Origin wR
patches)
  let patches' :: PatchSet p Origin wR
patches' = String -> PatchSet p Origin wR -> PatchSet p Origin wR
forall (p :: * -> * -> *) wStart wX.
String -> PatchSet p wStart wX -> PatchSet p wStart wX
progressPatchSet String
k PatchSet p Origin wR
patches
  Repository 'RW p Origin Origin -> PatchSet p Origin wR -> IO ()
forall (p :: * -> * -> *) wU wR wX.
RepoPatch p =>
Repository 'RW p wU wR -> PatchSet p Origin wX -> IO ()
writeTentativeInventory Repository 'RW p Origin Origin
_toRepo PatchSet p Origin wR
patches'
  String -> IO ()
endTedious String
k
  PatchSet p Origin Origin
local_patches <- Repository 'RW p Origin Origin -> IO (PatchSet p Origin Origin)
forall (p :: * -> * -> *) (rt :: AccessType) wU wR.
RepoPatch p =>
Repository rt p wU wR -> IO (PatchSet p Origin wR)
readPatches Repository 'RW p Origin Origin
_toRepo
  let patchesToApply :: FL (PatchInfoAnd p) Origin Origin
patchesToApply = String
-> FL (PatchInfoAnd p) Origin Origin
-> FL (PatchInfoAnd p) Origin Origin
forall (a :: * -> * -> *) wX wY. String -> FL a wX wY -> FL a wX wY
progressFL String
"Applying patch" (FL (PatchInfoAnd p) Origin Origin
 -> FL (PatchInfoAnd p) Origin Origin)
-> FL (PatchInfoAnd p) Origin Origin
-> FL (PatchInfoAnd p) Origin Origin
forall a b. (a -> b) -> a -> b
$ PatchSet p Origin Origin -> FL (PatchInfoAnd p) Origin Origin
forall (p :: * -> * -> *) wStart wX.
PatchSet p wStart wX -> FL (PatchInfoAnd p) wStart wX
patchSet2FL PatchSet p Origin Origin
local_patches
  Repository 'RW p Origin Origin
-> Invertible (FL (PatchInfoAnd p)) Origin Origin -> IO ()
forall (p :: * -> * -> *) wU wR wY.
(ApplyState p ~ Tree, RepoPatch p) =>
Repository 'RW p wU wR
-> Invertible (FL (PatchInfoAnd p)) wR wY -> IO ()
applyToTentativePristine Repository 'RW p Origin Origin
_toRepo (FL (PatchInfoAnd p) Origin Origin
-> Invertible (FL (PatchInfoAnd p)) Origin Origin
forall (p :: * -> * -> *) wX wY. p wX wY -> Invertible p wX wY
mkInvertible FL (PatchInfoAnd p) Origin Origin
patchesToApply)
  Repository 'RO p Origin Origin
_toRepo <- Repository 'RW p Origin Origin
-> DryRun -> IO (Repository 'RO p Origin Origin)
forall (p :: * -> * -> *) wU wR.
(RepoPatch p, ApplyState p ~ Tree) =>
Repository 'RW p wU wR -> DryRun -> IO (Repository 'RO p wU wR)
finalizeRepositoryChanges Repository 'RW p Origin Origin
_toRepo DryRun
NoDryRun
  Verbosity -> Doc -> IO ()
putVerbose Verbosity
verb (Doc -> IO ()) -> Doc -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> Doc
text String
"Writing the working tree..."
  Repository 'RO p Origin Origin -> String -> WithWorkingDir -> IO ()
forall (rt :: AccessType) (p :: * -> * -> *) wU wR.
Repository rt p wU wR -> String -> WithWorkingDir -> IO ()
createPristineDirectoryTree Repository 'RO p Origin Origin
_toRepo String
"." WithWorkingDir
withWorkingDir

-- | This function fetches all patches that the given repository has
--   with fetchFileUsingCache.
fetchPatchesIfNecessary :: forall rt p wU wR. RepoPatch p
                        => Repository rt p wU wR
                        -> IO ()
fetchPatchesIfNecessary :: forall (rt :: AccessType) (p :: * -> * -> *) wU wR.
RepoPatch p =>
Repository rt p wU wR -> IO ()
fetchPatchesIfNecessary Repository rt p wU wR
toRepo =
  do  PatchSet p Origin wR
ps <- Repository rt p wU wR -> IO (PatchSet p Origin wR)
forall (p :: * -> * -> *) (rt :: AccessType) wU wR.
RepoPatch p =>
Repository rt p wU wR -> IO (PatchSet p Origin wR)
readPatches Repository rt p wU wR
toRepo
      let patches :: RL (PatchInfoAnd p) Origin wR
patches = PatchSet p Origin wR -> RL (PatchInfoAnd p) Origin wR
forall (p :: * -> * -> *) wStart wX.
PatchSet p wStart wX -> RL (PatchInfoAnd p) wStart wX
patchSet2RL PatchSet p Origin wR
ps
          ppatches :: RL (PatchInfoAnd p) Origin wR
ppatches = String
-> RL (PatchInfoAnd p) Origin wR -> RL (PatchInfoAnd p) Origin wR
forall (p :: * -> * -> *) wX wY.
String -> RL (PatchInfoAnd p) wX wY -> RL (PatchInfoAnd p) wX wY
progressRLShowTags String
"Copying patches" RL (PatchInfoAnd p) Origin wR
patches
          ([PatchHash]
first, [PatchHash]
other) = Int -> [PatchHash] -> ([PatchHash], [PatchHash])
forall a. Int -> [a] -> ([a], [a])
splitAt (Int
100 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) ([PatchHash] -> ([PatchHash], [PatchHash]))
-> [PatchHash] -> ([PatchHash], [PatchHash])
forall a b. (a -> b) -> a -> b
$ [PatchHash] -> [PatchHash]
forall a. Partial => [a] -> [a]
tailErr ([PatchHash] -> [PatchHash]) -> [PatchHash] -> [PatchHash]
forall a b. (a -> b) -> a -> b
$ RL (PatchInfoAnd p) Origin wR -> [PatchHash]
forall wX wY. RL (PatchInfoAnd p) wX wY -> [PatchHash]
hashes RL (PatchInfoAnd p) Origin wR
patches
          speculate :: [[PatchHash]]
speculate = [] [PatchHash] -> [[PatchHash]] -> [[PatchHash]]
forall a. a -> [a] -> [a]
: [PatchHash]
first [PatchHash] -> [[PatchHash]] -> [[PatchHash]]
forall a. a -> [a] -> [a]
: (PatchHash -> [PatchHash]) -> [PatchHash] -> [[PatchHash]]
forall a b. (a -> b) -> [a] -> [b]
map (PatchHash -> [PatchHash] -> [PatchHash]
forall a. a -> [a] -> [a]
:[]) [PatchHash]
other
      ((PatchHash, [PatchHash]) -> IO ())
-> [(PatchHash, [PatchHash])] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (PatchHash, [PatchHash]) -> IO ()
fetchAndSpeculate ([(PatchHash, [PatchHash])] -> IO ())
-> [(PatchHash, [PatchHash])] -> IO ()
forall a b. (a -> b) -> a -> b
$ [PatchHash] -> [[PatchHash]] -> [(PatchHash, [PatchHash])]
forall a b. [a] -> [b] -> [(a, b)]
zip (RL (PatchInfoAnd p) Origin wR -> [PatchHash]
forall wX wY. RL (PatchInfoAnd p) wX wY -> [PatchHash]
hashes RL (PatchInfoAnd p) Origin wR
ppatches) ([[PatchHash]]
speculate [[PatchHash]] -> [[PatchHash]] -> [[PatchHash]]
forall a. [a] -> [a] -> [a]
++ [PatchHash] -> [[PatchHash]]
forall a. a -> [a]
repeat [])
  where hashes :: forall wX wY . RL (PatchInfoAnd p) wX wY -> [PatchHash]
        hashes :: forall wX wY. RL (PatchInfoAnd p) wX wY -> [PatchHash]
hashes = [Maybe PatchHash] -> [PatchHash]
forall a. [Maybe a] -> [a]
catMaybes ([Maybe PatchHash] -> [PatchHash])
-> (RL (PatchInfoAnd p) wX wY -> [Maybe PatchHash])
-> RL (PatchInfoAnd p) wX wY
-> [PatchHash]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall wW wZ. PatchInfoAnd p wW wZ -> Maybe PatchHash)
-> RL (PatchInfoAnd p) wX wY -> [Maybe PatchHash]
forall (a :: * -> * -> *) b wX wY.
(forall wW wZ. a wW wZ -> b) -> RL a wX wY -> [b]
mapRL PatchInfoAnd p wW wZ -> Maybe PatchHash
forall wW wZ. PatchInfoAnd p wW wZ -> Maybe PatchHash
forall (p :: * -> * -> *) wA wB.
PatchInfoAnd p wA wB -> Maybe PatchHash
hashedPatchHash
        fetchAndSpeculate :: (PatchHash, [PatchHash]) -> IO ()
        fetchAndSpeculate :: (PatchHash, [PatchHash]) -> IO ()
fetchAndSpeculate (PatchHash
f, [PatchHash]
ss) = do
          (String, ByteString)
_ <- Cache -> PatchHash -> IO (String, ByteString)
forall h. ValidHash h => Cache -> h -> IO (String, ByteString)
fetchFileUsingCache Cache
c PatchHash
f
          (PatchHash -> IO ()) -> [PatchHash] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (Cache -> PatchHash -> IO ()
forall h. ValidHash h => Cache -> h -> IO ()
speculateFileUsingCache Cache
c) [PatchHash]
ss
        c :: Cache
c = Repository rt p wU wR -> Cache
forall (rt :: AccessType) (p :: * -> * -> *) wU wR.
Repository rt p wU wR -> Cache
repoCache Repository rt p wU wR
toRepo

allowCtrlC :: CloneKind -> IO () -> IO () -> IO ()
allowCtrlC :: CloneKind -> IO () -> IO () -> IO ()
allowCtrlC CloneKind
CompleteClone IO ()
_ IO ()
action = IO ()
action
allowCtrlC CloneKind
_ IO ()
cleanup IO ()
action =
  IO ()
action IO () -> IO () -> IO ()
forall a. IO a -> IO a -> IO a
`catchInterrupt` do
    String -> IO ()
debugMessage String
"Cleanup after SIGINT in allowCtrlC"
    -- the SIGINT has also killed our running ssh connections,
    -- this will cause them to be restarted
    IO ()
resetSshConnections
    IO ()
cleanup

hashedPatchHash :: PatchInfoAnd p wA wB -> Maybe PatchHash
hashedPatchHash :: forall (p :: * -> * -> *) wA wB.
PatchInfoAnd p wA wB -> Maybe PatchHash
hashedPatchHash = (Named p wA wB -> Maybe PatchHash)
-> (PatchHash -> Maybe PatchHash)
-> Either (Named p wA wB) PatchHash
-> Maybe PatchHash
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Maybe PatchHash -> Named p wA wB -> Maybe PatchHash
forall a b. a -> b -> a
const Maybe PatchHash
forall a. Maybe a
Nothing) PatchHash -> Maybe PatchHash
forall a. a -> Maybe a
Just (Either (Named p wA wB) PatchHash -> Maybe PatchHash)
-> (PatchInfoAnd p wA wB -> Either (Named p wA wB) PatchHash)
-> PatchInfoAnd p wA wB
-> Maybe PatchHash
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PatchInfoAnd p wA wB -> Either (Named p wA wB) PatchHash
forall (p :: * -> * -> *) wA wB.
PatchInfoAndG p wA wB -> Either (p wA wB) PatchHash
extractHash