{-# OPTIONS_GHC -Wno-missing-signatures #-}
module Darcs.Repository.Paths where
import Darcs.Prelude
import Darcs.Util.Cache ( HashedDir(..), hashedDir )
import Darcs.Util.Global ( darcsdir )
import System.FilePath.Posix( (</>) )
makeDarcsdirPath :: String -> String
makeDarcsdirPath :: String -> String
makeDarcsdirPath String
name = String
darcsdir String -> String -> String
</> String
name
lockPath :: String
lockPath = String -> String
makeDarcsdirPath String
"lock"
prefsDir :: String
prefsDir = String
"prefs"
prefsDirPath :: String
prefsDirPath = String -> String
makeDarcsdirPath String
prefsDir
hashedInventory :: String
hashedInventory = String
"hashed_inventory"
hashedInventoryPath :: String
hashedInventoryPath = String -> String
makeDarcsdirPath String
hashedInventory
tentativeHashedInventory :: String
tentativeHashedInventory = String
"tentative_hashed_inventory"
tentativeHashedInventoryPath :: String
tentativeHashedInventoryPath = String -> String
makeDarcsdirPath String
tentativeHashedInventory
inventoriesDir :: String
inventoriesDir = HashedDir -> String
hashedDir HashedDir
HashedInventoriesDir
inventoriesDirPath :: String
inventoriesDirPath = String -> String
makeDarcsdirPath String
inventoriesDir
tentativePristinePath :: String
tentativePristinePath = String -> String
makeDarcsdirPath String
"tentative_pristine"
pristineDir :: String
pristineDir = HashedDir -> String
hashedDir HashedDir
HashedPristineDir
pristineDirPath :: String
pristineDirPath = String -> String
makeDarcsdirPath String
pristineDir
patchesDir :: String
patchesDir = HashedDir -> String
hashedDir HashedDir
HashedPatchesDir
patchesDirPath :: String
patchesDirPath = String -> String
makeDarcsdirPath String
patchesDir
indexPath :: String
indexPath = String
darcsdir String -> String -> String
</> String
"index"
indexInvalidPath :: String
indexInvalidPath = String
darcsdir String -> String -> String
</> String
"index_invalid"
rebasePath :: String
rebasePath = String -> String
makeDarcsdirPath String
"rebase"
tentativeRebasePath :: String
tentativeRebasePath = String -> String
makeDarcsdirPath String
"rebase.tentative"
formatPath :: String
formatPath = String -> String
makeDarcsdirPath String
"format"
pendingPath :: String
pendingPath = String
patchesDirPath String -> String -> String
</> String
"pending"
tentativePendingPath :: String
tentativePendingPath = String
patchesDirPath String -> String -> String
</> String
"pending.tentative"
newPendingPath :: String
newPendingPath = String
patchesDirPath String -> String -> String
</> String
"pending.new"
unrevertPath :: String
unrevertPath = String
patchesDirPath String -> String -> String
</> String
"unrevert"
tentativeUnrevertPath :: String
tentativeUnrevertPath = String
patchesDirPath String -> String -> String
</> String
"unrevert.tentative"
oldPristineDirPath :: String
oldPristineDirPath = String -> String
makeDarcsdirPath String
"pristine"
oldCurrentDirPath :: String
oldCurrentDirPath = String -> String
makeDarcsdirPath String
"current"
oldCheckpointDirPath :: String
oldCheckpointDirPath = String -> String
makeDarcsdirPath String
"checkpoints"
oldInventoryPath :: String
oldInventoryPath = String -> String
makeDarcsdirPath String
"inventory"
oldTentativeInventoryPath :: String
oldTentativeInventoryPath = String -> String
makeDarcsdirPath String
"tentative_inventory"