remove 163 lines of code without changing anything except imports
This commit is contained in:
parent
8dd5d180f1
commit
737e45156e
259 changed files with 192 additions and 355 deletions
|
@ -14,7 +14,7 @@ import qualified Data.Map as M
|
||||||
import System.Posix.Signals
|
import System.Posix.Signals
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import qualified Annex
|
import qualified Annex
|
||||||
import Annex.Content
|
import Annex.Content
|
||||||
|
|
||||||
|
|
|
@ -11,7 +11,7 @@ module Annex.AutoMerge
|
||||||
, commitResolvedMerge
|
, commitResolvedMerge
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import qualified Annex.Queue
|
import qualified Annex.Queue
|
||||||
import Annex.Direct
|
import Annex.Direct
|
||||||
import Annex.CatFile
|
import Annex.CatFile
|
||||||
|
|
|
@ -7,7 +7,7 @@
|
||||||
|
|
||||||
module Annex.BloomFilter where
|
module Annex.BloomFilter where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import qualified Annex
|
import qualified Annex
|
||||||
import Utility.Bloom
|
import Utility.Bloom
|
||||||
|
|
||||||
|
|
|
@ -32,7 +32,7 @@ import qualified Data.Map as M
|
||||||
import Data.Bits.Utils
|
import Data.Bits.Utils
|
||||||
import Control.Concurrent (threadDelay)
|
import Control.Concurrent (threadDelay)
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import Annex.BranchState
|
import Annex.BranchState
|
||||||
import Annex.Journal
|
import Annex.Journal
|
||||||
import Annex.Index
|
import Annex.Index
|
||||||
|
|
|
@ -9,7 +9,7 @@
|
||||||
|
|
||||||
module Annex.BranchState where
|
module Annex.BranchState where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import Types.BranchState
|
import Types.BranchState
|
||||||
import qualified Annex
|
import qualified Annex
|
||||||
|
|
||||||
|
|
|
@ -23,7 +23,7 @@ import qualified Data.ByteString.Lazy as L
|
||||||
import qualified Data.Map as M
|
import qualified Data.Map as M
|
||||||
import System.PosixCompat.Types
|
import System.PosixCompat.Types
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import qualified Git
|
import qualified Git
|
||||||
import qualified Git.CatFile
|
import qualified Git.CatFile
|
||||||
import qualified Annex
|
import qualified Annex
|
||||||
|
|
|
@ -11,7 +11,7 @@ module Annex.CheckAttr (
|
||||||
checkAttrStop,
|
checkAttrStop,
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import qualified Git.CheckAttr as Git
|
import qualified Git.CheckAttr as Git
|
||||||
import qualified Annex
|
import qualified Annex
|
||||||
|
|
||||||
|
|
|
@ -12,7 +12,7 @@ module Annex.CheckIgnore (
|
||||||
checkIgnoreStop
|
checkIgnoreStop
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import qualified Git.CheckIgnore as Git
|
import qualified Git.CheckIgnore as Git
|
||||||
import qualified Annex
|
import qualified Annex
|
||||||
|
|
||||||
|
|
|
@ -1,8 +1,9 @@
|
||||||
module Common.Annex (module X) where
|
module Annex.Common (module X) where
|
||||||
|
|
||||||
import Common as X
|
import Common as X
|
||||||
import Types as X
|
import Types as X
|
||||||
import Types.UUID as X (toUUID, fromUUID)
|
import Types.Key as X
|
||||||
|
import Types.UUID as X
|
||||||
import Annex as X (gitRepo, inRepo, fromRepo, calcRepo)
|
import Annex as X (gitRepo, inRepo, fromRepo, calcRepo)
|
||||||
import Locations as X
|
import Annex.Locations as X
|
||||||
import Messages as X
|
import Messages as X
|
|
@ -7,7 +7,7 @@
|
||||||
|
|
||||||
module Annex.Concurrent where
|
module Annex.Concurrent where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import Annex
|
import Annex
|
||||||
import Annex.CatFile
|
import Annex.CatFile
|
||||||
import Annex.CheckAttr
|
import Annex.CheckAttr
|
||||||
|
|
|
@ -52,7 +52,7 @@ module Annex.Content (
|
||||||
import System.IO.Unsafe (unsafeInterleaveIO)
|
import System.IO.Unsafe (unsafeInterleaveIO)
|
||||||
import qualified Data.Set as S
|
import qualified Data.Set as S
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import Logs.Location
|
import Logs.Location
|
||||||
import Logs.Transfer
|
import Logs.Transfer
|
||||||
import qualified Git
|
import qualified Git
|
||||||
|
@ -62,7 +62,6 @@ import qualified Annex.Branch
|
||||||
import Utility.DiskFree
|
import Utility.DiskFree
|
||||||
import Utility.FileMode
|
import Utility.FileMode
|
||||||
import qualified Annex.Url as Url
|
import qualified Annex.Url as Url
|
||||||
import Types.Key
|
|
||||||
import Utility.DataUnits
|
import Utility.DataUnits
|
||||||
import Utility.CopyFile
|
import Utility.CopyFile
|
||||||
import Utility.Metered
|
import Utility.Metered
|
||||||
|
@ -336,12 +335,12 @@ verifyKeyContent v Types.Remote.UnVerified k f = ifM (shouldVerify v)
|
||||||
, return True
|
, return True
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
verifysize = case Types.Key.keySize k of
|
verifysize = case keySize k of
|
||||||
Nothing -> return True
|
Nothing -> return True
|
||||||
Just size -> do
|
Just size -> do
|
||||||
size' <- liftIO $ catchDefaultIO 0 $ getFileSize f
|
size' <- liftIO $ catchDefaultIO 0 $ getFileSize f
|
||||||
return (size' == size)
|
return (size' == size)
|
||||||
verifycontent = case Types.Backend.verifyKeyContent =<< Backend.maybeLookupBackendName (Types.Key.keyBackendName k) of
|
verifycontent = case Types.Backend.verifyKeyContent =<< Backend.maybeLookupBackendName (keyBackendName k) of
|
||||||
Nothing -> return True
|
Nothing -> return True
|
||||||
Just verifier -> verifier k f
|
Just verifier -> verifier k f
|
||||||
|
|
||||||
|
|
|
@ -29,7 +29,7 @@ module Annex.Content.Direct (
|
||||||
addContentWhenNotPresent,
|
addContentWhenNotPresent,
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import Annex.Perms
|
import Annex.Perms
|
||||||
import qualified Git
|
import qualified Git
|
||||||
import Utility.Tmp
|
import Utility.Tmp
|
||||||
|
|
|
@ -10,7 +10,7 @@ module Annex.Difference (
|
||||||
setDifferences,
|
setDifferences,
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import Types.Difference
|
import Types.Difference
|
||||||
import Logs.Difference
|
import Logs.Difference
|
||||||
import Config
|
import Config
|
||||||
|
|
|
@ -10,7 +10,7 @@
|
||||||
|
|
||||||
module Annex.Direct where
|
module Annex.Direct where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import qualified Annex
|
import qualified Annex
|
||||||
import qualified Git
|
import qualified Git
|
||||||
import qualified Git.LsFiles
|
import qualified Git.LsFiles
|
||||||
|
|
|
@ -7,11 +7,10 @@
|
||||||
|
|
||||||
module Annex.Drop where
|
module Annex.Drop where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import Logs.Trust
|
import Logs.Trust
|
||||||
import Annex.NumCopies
|
import Annex.NumCopies
|
||||||
import Types.Remote (uuid)
|
import Types.Remote (uuid)
|
||||||
import Types.Key (key2file)
|
|
||||||
import qualified Remote
|
import qualified Remote
|
||||||
import qualified Command.Drop
|
import qualified Command.Drop
|
||||||
import Command
|
import Command
|
||||||
|
|
|
@ -9,7 +9,7 @@
|
||||||
|
|
||||||
module Annex.Environment where
|
module Annex.Environment where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import Utility.UserInfo
|
import Utility.UserInfo
|
||||||
import qualified Git.Config
|
import qualified Git.Config
|
||||||
import Config
|
import Config
|
||||||
|
|
|
@ -9,7 +9,7 @@ module Annex.FileMatcher where
|
||||||
|
|
||||||
import qualified Data.Map as M
|
import qualified Data.Map as M
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import Limit
|
import Limit
|
||||||
import Utility.Matcher
|
import Utility.Matcher
|
||||||
import Types.Group
|
import Types.Group
|
||||||
|
|
|
@ -11,7 +11,7 @@
|
||||||
|
|
||||||
module Annex.Hook where
|
module Annex.Hook where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import qualified Git.Hook as Git
|
import qualified Git.Hook as Git
|
||||||
import Config
|
import Config
|
||||||
import qualified Annex
|
import qualified Annex
|
||||||
|
|
|
@ -14,7 +14,7 @@ module Annex.Index (
|
||||||
|
|
||||||
import qualified Control.Exception as E
|
import qualified Control.Exception as E
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import Git.Types
|
import Git.Types
|
||||||
import qualified Annex
|
import qualified Annex
|
||||||
import Utility.Env
|
import Utility.Env
|
||||||
|
|
|
@ -21,7 +21,7 @@ module Annex.Ingest (
|
||||||
forceParams,
|
forceParams,
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import Types.KeySource
|
import Types.KeySource
|
||||||
import Backend
|
import Backend
|
||||||
import Annex.Content
|
import Annex.Content
|
||||||
|
|
|
@ -16,7 +16,7 @@ module Annex.Init (
|
||||||
probeCrippledFileSystem,
|
probeCrippledFileSystem,
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import qualified Annex
|
import qualified Annex
|
||||||
import qualified Git
|
import qualified Git
|
||||||
import qualified Git.LsFiles
|
import qualified Git.LsFiles
|
||||||
|
|
|
@ -9,7 +9,7 @@
|
||||||
|
|
||||||
module Annex.InodeSentinal where
|
module Annex.InodeSentinal where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import qualified Annex
|
import qualified Annex
|
||||||
import Utility.InodeCache
|
import Utility.InodeCache
|
||||||
import Annex.Perms
|
import Annex.Perms
|
||||||
|
|
|
@ -13,7 +13,7 @@
|
||||||
|
|
||||||
module Annex.Journal where
|
module Annex.Journal where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import qualified Git
|
import qualified Git
|
||||||
import Annex.Perms
|
import Annex.Perms
|
||||||
import Annex.LockFile
|
import Annex.LockFile
|
||||||
|
|
|
@ -14,14 +14,13 @@
|
||||||
|
|
||||||
module Annex.Link where
|
module Annex.Link where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import qualified Annex
|
import qualified Annex
|
||||||
import qualified Git.HashObject
|
import qualified Git.HashObject
|
||||||
import qualified Git.UpdateIndex
|
import qualified Git.UpdateIndex
|
||||||
import qualified Annex.Queue
|
import qualified Annex.Queue
|
||||||
import Git.Types
|
import Git.Types
|
||||||
import Git.FilePath
|
import Git.FilePath
|
||||||
import Types.Key
|
|
||||||
|
|
||||||
import qualified Data.ByteString.Lazy as L
|
import qualified Data.ByteString.Lazy as L
|
||||||
|
|
||||||
|
|
|
@ -5,7 +5,7 @@
|
||||||
- Licensed under the GNU GPL version 3 or higher.
|
- Licensed under the GNU GPL version 3 or higher.
|
||||||
-}
|
-}
|
||||||
|
|
||||||
module Locations (
|
module Annex.Locations (
|
||||||
keyFile,
|
keyFile,
|
||||||
fileKey,
|
fileKey,
|
||||||
keyPaths,
|
keyPaths,
|
||||||
|
@ -76,9 +76,9 @@ import Data.Char
|
||||||
import Data.Default
|
import Data.Default
|
||||||
|
|
||||||
import Common
|
import Common
|
||||||
import Types.GitConfig
|
|
||||||
import Types.Key
|
import Types.Key
|
||||||
import Types.UUID
|
import Types.UUID
|
||||||
|
import Types.GitConfig
|
||||||
import Types.Difference
|
import Types.Difference
|
||||||
import qualified Git
|
import qualified Git
|
||||||
import Git.FilePath
|
import Git.FilePath
|
|
@ -15,7 +15,7 @@ module Annex.LockFile (
|
||||||
tryExclusiveLock,
|
tryExclusiveLock,
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import Annex
|
import Annex
|
||||||
import Types.LockCache
|
import Types.LockCache
|
||||||
import qualified Git
|
import qualified Git
|
||||||
|
|
|
@ -20,7 +20,9 @@ module Annex.LockPool.PosixOrPid (
|
||||||
checkSaneLock,
|
checkSaneLock,
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Common.Annex
|
import Common
|
||||||
|
import Types
|
||||||
|
import Annex.Locations
|
||||||
import qualified Annex
|
import qualified Annex
|
||||||
import qualified Utility.LockPool.Posix as Posix
|
import qualified Utility.LockPool.Posix as Posix
|
||||||
import qualified Utility.LockPool.PidLock as Pid
|
import qualified Utility.LockPool.PidLock as Pid
|
||||||
|
@ -58,7 +60,7 @@ checkSaneLock f h = H.checkSaneLock f h
|
||||||
|
|
||||||
pidLockFile :: Annex (Maybe FilePath)
|
pidLockFile :: Annex (Maybe FilePath)
|
||||||
pidLockFile = ifM (annexPidLock <$> Annex.getGitConfig)
|
pidLockFile = ifM (annexPidLock <$> Annex.getGitConfig)
|
||||||
( Just <$> fromRepo gitAnnexPidLockFile
|
( Just <$> Annex.fromRepo gitAnnexPidLockFile
|
||||||
, pure Nothing
|
, pure Nothing
|
||||||
)
|
)
|
||||||
|
|
||||||
|
|
|
@ -11,7 +11,7 @@ module Annex.MetaData (
|
||||||
module X
|
module X
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import qualified Annex
|
import qualified Annex
|
||||||
import Types.MetaData as X
|
import Types.MetaData as X
|
||||||
import Annex.MetaData.StandardFields as X
|
import Annex.MetaData.StandardFields as X
|
||||||
|
|
|
@ -9,7 +9,7 @@
|
||||||
|
|
||||||
module Annex.Notification (NotifyWitness, notifyTransfer, notifyDrop) where
|
module Annex.Notification (NotifyWitness, notifyTransfer, notifyDrop) where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import Logs.Transfer
|
import Logs.Transfer
|
||||||
#ifdef WITH_DBUS_NOTIFICATIONS
|
#ifdef WITH_DBUS_NOTIFICATIONS
|
||||||
import qualified Annex
|
import qualified Annex
|
||||||
|
|
|
@ -22,7 +22,7 @@ module Annex.NumCopies (
|
||||||
UnVerifiedCopy(..),
|
UnVerifiedCopy(..),
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import qualified Annex
|
import qualified Annex
|
||||||
import Types.NumCopies
|
import Types.NumCopies
|
||||||
import Logs.NumCopies
|
import Logs.NumCopies
|
||||||
|
|
|
@ -18,7 +18,7 @@ module Annex.Perms (
|
||||||
withShared,
|
withShared,
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import Utility.FileMode
|
import Utility.FileMode
|
||||||
import Git.SharedRepository
|
import Git.SharedRepository
|
||||||
import qualified Annex
|
import qualified Annex
|
||||||
|
|
|
@ -16,7 +16,7 @@ module Annex.Queue (
|
||||||
mergeFrom,
|
mergeFrom,
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import Annex hiding (new)
|
import Annex hiding (new)
|
||||||
import qualified Git.Queue
|
import qualified Git.Queue
|
||||||
import qualified Git.UpdateIndex
|
import qualified Git.UpdateIndex
|
||||||
|
|
|
@ -9,7 +9,7 @@
|
||||||
|
|
||||||
module Annex.Quvi where
|
module Annex.Quvi where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import qualified Annex
|
import qualified Annex
|
||||||
import Utility.Quvi
|
import Utility.Quvi
|
||||||
import Utility.Url
|
import Utility.Url
|
||||||
|
|
|
@ -7,7 +7,7 @@
|
||||||
|
|
||||||
module Annex.ReplaceFile where
|
module Annex.ReplaceFile where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import Annex.Perms
|
import Annex.Perms
|
||||||
import Utility.Tmp
|
import Utility.Tmp
|
||||||
|
|
||||||
|
|
|
@ -7,7 +7,7 @@
|
||||||
|
|
||||||
module Annex.SpecialRemote where
|
module Annex.SpecialRemote where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import Remote (remoteTypes, remoteMap)
|
import Remote (remoteTypes, remoteMap)
|
||||||
import Types.Remote (RemoteConfig, RemoteConfigKey, typename, setup)
|
import Types.Remote (RemoteConfig, RemoteConfigKey, typename, setup)
|
||||||
import Logs.Remote
|
import Logs.Remote
|
||||||
|
|
|
@ -24,7 +24,7 @@ import qualified Data.Map as M
|
||||||
import Data.Hash.MD5
|
import Data.Hash.MD5
|
||||||
import System.Exit
|
import System.Exit
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import Annex.LockFile
|
import Annex.LockFile
|
||||||
import qualified Build.SysConfig as SysConfig
|
import qualified Build.SysConfig as SysConfig
|
||||||
import qualified Annex
|
import qualified Annex
|
||||||
|
|
|
@ -7,7 +7,7 @@
|
||||||
|
|
||||||
module Annex.TaggedPush where
|
module Annex.TaggedPush where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import qualified Remote
|
import qualified Remote
|
||||||
import qualified Annex.Branch
|
import qualified Annex.Branch
|
||||||
import qualified Git
|
import qualified Git
|
||||||
|
|
|
@ -18,7 +18,7 @@ module Annex.Transfer (
|
||||||
forwardRetry,
|
forwardRetry,
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import Logs.Transfer as X
|
import Logs.Transfer as X
|
||||||
import Annex.Notification as X
|
import Annex.Notification as X
|
||||||
import Annex.Perms
|
import Annex.Perms
|
||||||
|
|
|
@ -28,7 +28,7 @@ module Annex.UUID (
|
||||||
bitTorrentUUID,
|
bitTorrentUUID,
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import qualified Git
|
import qualified Git
|
||||||
import qualified Git.Config
|
import qualified Git.Config
|
||||||
import Config
|
import Config
|
||||||
|
|
|
@ -13,7 +13,7 @@ module Annex.Url (
|
||||||
getUserAgent,
|
getUserAgent,
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import qualified Annex
|
import qualified Annex
|
||||||
import Utility.Url as U
|
import Utility.Url as U
|
||||||
import qualified Build.SysConfig as SysConfig
|
import qualified Build.SysConfig as SysConfig
|
||||||
|
|
|
@ -7,8 +7,7 @@
|
||||||
|
|
||||||
module Annex.VariantFile where
|
module Annex.VariantFile where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import Types.Key
|
|
||||||
|
|
||||||
import Data.Hash.MD5
|
import Data.Hash.MD5
|
||||||
|
|
||||||
|
|
|
@ -9,7 +9,7 @@
|
||||||
|
|
||||||
module Annex.Version where
|
module Annex.Version where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import Config
|
import Config
|
||||||
import qualified Annex
|
import qualified Annex
|
||||||
|
|
||||||
|
|
|
@ -7,7 +7,7 @@
|
||||||
|
|
||||||
module Annex.View where
|
module Annex.View where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import Annex.View.ViewedFile
|
import Annex.View.ViewedFile
|
||||||
import Types.View
|
import Types.View
|
||||||
import Types.MetaData
|
import Types.MetaData
|
||||||
|
|
|
@ -16,7 +16,7 @@ module Annex.View.ViewedFile (
|
||||||
prop_viewedFile_roundtrips,
|
prop_viewedFile_roundtrips,
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
|
|
||||||
type FileName = String
|
type FileName = String
|
||||||
type ViewedFile = FileName
|
type ViewedFile = FileName
|
||||||
|
|
|
@ -7,7 +7,7 @@
|
||||||
|
|
||||||
module Annex.Wanted where
|
module Annex.Wanted where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import Logs.PreferredContent
|
import Logs.PreferredContent
|
||||||
import Annex.UUID
|
import Annex.UUID
|
||||||
|
|
||||||
|
|
|
@ -7,7 +7,7 @@
|
||||||
|
|
||||||
module Annex.WorkTree where
|
module Annex.WorkTree where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import Annex.Link
|
import Annex.Link
|
||||||
import Annex.CatFile
|
import Annex.CatFile
|
||||||
import Annex.Version
|
import Annex.Version
|
||||||
|
|
|
@ -9,7 +9,7 @@
|
||||||
|
|
||||||
module Assistant.Alert where
|
module Assistant.Alert where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import Assistant.Types.Alert
|
import Assistant.Types.Alert
|
||||||
import Assistant.Alert.Utility
|
import Assistant.Alert.Utility
|
||||||
import qualified Remote
|
import qualified Remote
|
||||||
|
|
|
@ -7,7 +7,7 @@
|
||||||
|
|
||||||
module Assistant.Alert.Utility where
|
module Assistant.Alert.Utility where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import Assistant.Types.Alert
|
import Assistant.Types.Alert
|
||||||
import Utility.Tense
|
import Utility.Tense
|
||||||
|
|
||||||
|
|
|
@ -7,7 +7,7 @@
|
||||||
|
|
||||||
module Assistant.Common (module X) where
|
module Assistant.Common (module X) where
|
||||||
|
|
||||||
import Common.Annex as X
|
import Annex.Common as X
|
||||||
import Assistant.Monad as X
|
import Assistant.Monad as X
|
||||||
import Assistant.Types.DaemonStatus as X
|
import Assistant.Types.DaemonStatus as X
|
||||||
import Assistant.Types.NamedThread as X
|
import Assistant.Types.NamedThread as X
|
||||||
|
|
|
@ -28,7 +28,7 @@ module Assistant.Monad (
|
||||||
import "mtl" Control.Monad.Reader
|
import "mtl" Control.Monad.Reader
|
||||||
import System.Log.Logger
|
import System.Log.Logger
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import Assistant.Types.ThreadedMonad
|
import Assistant.Types.ThreadedMonad
|
||||||
import Assistant.Types.DaemonStatus
|
import Assistant.Types.DaemonStatus
|
||||||
import Assistant.Types.ScanRemotes
|
import Assistant.Types.ScanRemotes
|
||||||
|
|
|
@ -9,7 +9,7 @@
|
||||||
|
|
||||||
module Assistant.NamedThread where
|
module Assistant.NamedThread where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import Assistant.Types.NamedThread
|
import Assistant.Types.NamedThread
|
||||||
import Assistant.Types.ThreadName
|
import Assistant.Types.ThreadName
|
||||||
import Assistant.Types.DaemonStatus
|
import Assistant.Types.DaemonStatus
|
||||||
|
|
|
@ -9,7 +9,7 @@
|
||||||
|
|
||||||
module Assistant.Pairing where
|
module Assistant.Pairing where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import Utility.Verifiable
|
import Utility.Verifiable
|
||||||
import Assistant.Ssh
|
import Assistant.Ssh
|
||||||
|
|
||||||
|
|
|
@ -7,7 +7,7 @@
|
||||||
|
|
||||||
module Assistant.Ssh where
|
module Assistant.Ssh where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import Utility.Tmp
|
import Utility.Tmp
|
||||||
import Utility.Shell
|
import Utility.Shell
|
||||||
import Utility.Rsync
|
import Utility.Rsync
|
||||||
|
|
|
@ -40,7 +40,6 @@ import Assistant.Unused
|
||||||
import Logs.Unused
|
import Logs.Unused
|
||||||
import Logs.Transfer
|
import Logs.Transfer
|
||||||
import Annex.Path
|
import Annex.Path
|
||||||
import Types.Key (keyBackendName)
|
|
||||||
import qualified Annex
|
import qualified Annex
|
||||||
#ifdef WITH_WEBAPP
|
#ifdef WITH_WEBAPP
|
||||||
import Assistant.WebApp.Types
|
import Assistant.WebApp.Types
|
||||||
|
|
|
@ -9,7 +9,7 @@
|
||||||
|
|
||||||
module Assistant.Types.Buddies where
|
module Assistant.Types.Buddies where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
|
|
||||||
import qualified Data.Map as M
|
import qualified Data.Map as M
|
||||||
import Control.Concurrent.STM
|
import Control.Concurrent.STM
|
||||||
|
|
|
@ -7,7 +7,7 @@
|
||||||
|
|
||||||
module Assistant.Types.DaemonStatus where
|
module Assistant.Types.DaemonStatus where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import Assistant.Pairing
|
import Assistant.Pairing
|
||||||
import Utility.NotificationBroadcaster
|
import Utility.NotificationBroadcaster
|
||||||
import Logs.Transfer
|
import Logs.Transfer
|
||||||
|
|
|
@ -7,7 +7,7 @@
|
||||||
|
|
||||||
module Assistant.Types.NetMessager where
|
module Assistant.Types.NetMessager where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import Assistant.Pairing
|
import Assistant.Pairing
|
||||||
import Git.Types
|
import Git.Types
|
||||||
|
|
||||||
|
|
|
@ -7,7 +7,7 @@
|
||||||
|
|
||||||
module Assistant.Types.Pushes where
|
module Assistant.Types.Pushes where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
|
|
||||||
import Control.Concurrent.STM
|
import Control.Concurrent.STM
|
||||||
import Data.Time.Clock
|
import Data.Time.Clock
|
||||||
|
|
|
@ -7,7 +7,7 @@
|
||||||
|
|
||||||
module Assistant.Types.ScanRemotes where
|
module Assistant.Types.ScanRemotes where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
|
|
||||||
import Control.Concurrent.STM
|
import Control.Concurrent.STM
|
||||||
import qualified Data.Map as M
|
import qualified Data.Map as M
|
||||||
|
|
|
@ -7,7 +7,7 @@
|
||||||
|
|
||||||
module Assistant.Types.ThreadedMonad where
|
module Assistant.Types.ThreadedMonad where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import qualified Annex
|
import qualified Annex
|
||||||
|
|
||||||
import Control.Concurrent
|
import Control.Concurrent
|
||||||
|
|
|
@ -7,7 +7,7 @@
|
||||||
|
|
||||||
module Assistant.Types.TransferQueue where
|
module Assistant.Types.TransferQueue where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import Logs.Transfer
|
import Logs.Transfer
|
||||||
|
|
||||||
import Control.Concurrent.STM
|
import Control.Concurrent.STM
|
||||||
|
|
|
@ -7,7 +7,7 @@
|
||||||
|
|
||||||
module Assistant.Types.TransferrerPool where
|
module Assistant.Types.TransferrerPool where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import Utility.NotificationBroadcaster
|
import Utility.NotificationBroadcaster
|
||||||
import Assistant.Types.DaemonStatus
|
import Assistant.Types.DaemonStatus
|
||||||
|
|
||||||
|
|
|
@ -13,7 +13,6 @@ import qualified Data.Map as M
|
||||||
|
|
||||||
import Assistant.Common
|
import Assistant.Common
|
||||||
import qualified Git
|
import qualified Git
|
||||||
import Types.Key
|
|
||||||
import Logs.Unused
|
import Logs.Unused
|
||||||
import Logs.Location
|
import Logs.Location
|
||||||
import Annex.Content
|
import Annex.Content
|
||||||
|
|
|
@ -19,7 +19,6 @@ import Utility.NotificationBroadcaster
|
||||||
import Logs.Transfer
|
import Logs.Transfer
|
||||||
import Utility.Percentage
|
import Utility.Percentage
|
||||||
import Utility.DataUnits
|
import Utility.DataUnits
|
||||||
import Types.Key
|
|
||||||
import qualified Remote
|
import qualified Remote
|
||||||
import qualified Git
|
import qualified Git
|
||||||
|
|
||||||
|
|
|
@ -7,7 +7,7 @@
|
||||||
|
|
||||||
module Assistant.WebApp.RepoId where
|
module Assistant.WebApp.RepoId where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import Git.Types (RemoteName)
|
import Git.Types (RemoteName)
|
||||||
import qualified Remote
|
import qualified Remote
|
||||||
|
|
||||||
|
|
|
@ -8,7 +8,7 @@
|
||||||
module Assistant.XMPP.Buddies where
|
module Assistant.XMPP.Buddies where
|
||||||
|
|
||||||
import Assistant.XMPP
|
import Assistant.XMPP
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import Assistant.Types.Buddies
|
import Assistant.Types.Buddies
|
||||||
|
|
||||||
import Network.Protocol.XMPP
|
import Network.Protocol.XMPP
|
||||||
|
|
|
@ -16,10 +16,9 @@ module Backend (
|
||||||
isStableKey,
|
isStableKey,
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import qualified Annex
|
import qualified Annex
|
||||||
import Annex.CheckAttr
|
import Annex.CheckAttr
|
||||||
import Types.Key
|
|
||||||
import Types.KeySource
|
import Types.KeySource
|
||||||
import qualified Types.Backend as B
|
import qualified Types.Backend as B
|
||||||
|
|
||||||
|
|
|
@ -12,10 +12,9 @@ module Backend.Hash (
|
||||||
testKeyBackend,
|
testKeyBackend,
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import qualified Annex
|
import qualified Annex
|
||||||
import Types.Backend
|
import Types.Backend
|
||||||
import Types.Key
|
|
||||||
import Types.KeySource
|
import Types.KeySource
|
||||||
import Utility.Hash
|
import Utility.Hash
|
||||||
import Utility.ExternalSHA
|
import Utility.ExternalSHA
|
||||||
|
|
|
@ -10,9 +10,8 @@ module Backend.URL (
|
||||||
fromUrl
|
fromUrl
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import Types.Backend
|
import Types.Backend
|
||||||
import Types.Key
|
|
||||||
import Backend.Utilities
|
import Backend.Utilities
|
||||||
|
|
||||||
backends :: [Backend]
|
backends :: [Backend]
|
||||||
|
|
|
@ -9,7 +9,7 @@ module Backend.Utilities where
|
||||||
|
|
||||||
import Data.Hash.MD5
|
import Data.Hash.MD5
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
|
|
||||||
{- Generates a keyName from an input string. Takes care of sanitizing it.
|
{- Generates a keyName from an input string. Takes care of sanitizing it.
|
||||||
- If it's not too long, the full string is used as the keyName.
|
- If it's not too long, the full string is used as the keyName.
|
||||||
|
|
|
@ -7,9 +7,8 @@
|
||||||
|
|
||||||
module Backend.WORM (backends) where
|
module Backend.WORM (backends) where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import Types.Backend
|
import Types.Backend
|
||||||
import Types.Key
|
|
||||||
import Types.KeySource
|
import Types.KeySource
|
||||||
import Backend.Utilities
|
import Backend.Utilities
|
||||||
import Git.FilePath
|
import Git.FilePath
|
||||||
|
|
|
@ -8,7 +8,7 @@
|
||||||
- Also gpg signs the files.
|
- Also gpg signs the files.
|
||||||
-}
|
-}
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import Types.Distribution
|
import Types.Distribution
|
||||||
import Build.Version (getChangelogVersion, Version)
|
import Build.Version (getChangelogVersion, Version)
|
||||||
import Utility.UserInfo
|
import Utility.UserInfo
|
||||||
|
|
|
@ -10,7 +10,7 @@
|
||||||
|
|
||||||
module Checks where
|
module Checks where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import Types.Command
|
import Types.Command
|
||||||
import Annex.Init
|
import Annex.Init
|
||||||
import Config
|
import Config
|
||||||
|
|
|
@ -15,7 +15,7 @@ import qualified Options.Applicative.Help as H
|
||||||
import qualified Control.Exception as E
|
import qualified Control.Exception as E
|
||||||
import Control.Exception (throw)
|
import Control.Exception (throw)
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import qualified Annex
|
import qualified Annex
|
||||||
import qualified Git
|
import qualified Git
|
||||||
import qualified Git.AutoCorrect
|
import qualified Git.AutoCorrect
|
||||||
|
|
|
@ -9,7 +9,7 @@
|
||||||
|
|
||||||
module CmdLine.Action where
|
module CmdLine.Action where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import qualified Annex
|
import qualified Annex
|
||||||
import Annex.Concurrent
|
import Annex.Concurrent
|
||||||
import Types.Command
|
import Types.Command
|
||||||
|
|
|
@ -7,8 +7,11 @@
|
||||||
|
|
||||||
module CmdLine.Batch where
|
module CmdLine.Batch where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import Command
|
import Types.Command
|
||||||
|
import CmdLine.Action
|
||||||
|
import CmdLine.GitAnnex.Options
|
||||||
|
import Options.Applicative
|
||||||
|
|
||||||
data BatchMode = Batch | NoBatch
|
data BatchMode = Batch | NoBatch
|
||||||
|
|
||||||
|
|
|
@ -11,14 +11,13 @@ import Options.Applicative
|
||||||
import Options.Applicative.Builder.Internal
|
import Options.Applicative.Builder.Internal
|
||||||
import Control.Concurrent
|
import Control.Concurrent
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import qualified Git.Config
|
import qualified Git.Config
|
||||||
import qualified Git.Construct
|
import qualified Git.Construct
|
||||||
import Git.Types
|
import Git.Types
|
||||||
import Types.TrustLevel
|
import Types.TrustLevel
|
||||||
import Types.NumCopies
|
import Types.NumCopies
|
||||||
import Types.Messages
|
import Types.Messages
|
||||||
import Types.Key
|
|
||||||
import Types.Command
|
import Types.Command
|
||||||
import Types.DeferredParse
|
import Types.DeferredParse
|
||||||
import Types.DesktopNotify
|
import Types.DesktopNotify
|
||||||
|
|
|
@ -7,7 +7,7 @@
|
||||||
|
|
||||||
module CmdLine.GitAnnexShell where
|
module CmdLine.GitAnnexShell where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import qualified Git.Construct
|
import qualified Git.Construct
|
||||||
import qualified Git.Config
|
import qualified Git.Config
|
||||||
import CmdLine
|
import CmdLine
|
||||||
|
|
|
@ -7,7 +7,7 @@
|
||||||
|
|
||||||
module CmdLine.GitAnnexShell.Checks where
|
module CmdLine.GitAnnexShell.Checks where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import Command
|
import Command
|
||||||
import qualified Annex
|
import qualified Annex
|
||||||
import Annex.Init
|
import Annex.Init
|
||||||
|
|
|
@ -7,7 +7,7 @@
|
||||||
|
|
||||||
module CmdLine.GitAnnexShell.Fields where
|
module CmdLine.GitAnnexShell.Fields where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import qualified Annex
|
import qualified Annex
|
||||||
import Git.FilePath
|
import Git.FilePath
|
||||||
|
|
||||||
|
|
|
@ -9,7 +9,7 @@ module CmdLine.Option where
|
||||||
|
|
||||||
import Options.Applicative
|
import Options.Applicative
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import CmdLine.Usage
|
import CmdLine.Usage
|
||||||
import CmdLine.GlobalSetter
|
import CmdLine.GlobalSetter
|
||||||
import qualified Annex
|
import qualified Annex
|
||||||
|
|
|
@ -11,9 +11,8 @@
|
||||||
|
|
||||||
module CmdLine.Seek where
|
module CmdLine.Seek where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import Types.Command
|
import Types.Command
|
||||||
import Types.Key
|
|
||||||
import Types.FileMatcher
|
import Types.FileMatcher
|
||||||
import qualified Annex
|
import qualified Annex
|
||||||
import qualified Git
|
import qualified Git
|
||||||
|
|
|
@ -7,7 +7,7 @@
|
||||||
|
|
||||||
module CmdLine.Usage where
|
module CmdLine.Usage where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common
|
||||||
import Types.Command
|
import Types.Command
|
||||||
|
|
||||||
usageMessage :: String -> String
|
usageMessage :: String -> String
|
||||||
|
|
|
@ -23,19 +23,19 @@ module Command (
|
||||||
module ReExported
|
module ReExported
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Common.Annex
|
import Annex.Common as ReExported
|
||||||
import Annex.WorkTree
|
import Annex.WorkTree
|
||||||
import qualified Git
|
import qualified Git
|
||||||
import Types.Command as ReExported
|
import Types.Command as ReExported
|
||||||
import Types.Option as ReExported
|
|
||||||
import Types.DeferredParse as ReExported
|
import Types.DeferredParse as ReExported
|
||||||
import CmdLine.Seek as ReExported
|
|
||||||
import Checks as ReExported
|
import Checks as ReExported
|
||||||
|
import CmdLine.Seek as ReExported
|
||||||
import CmdLine.Usage as ReExported
|
import CmdLine.Usage as ReExported
|
||||||
import CmdLine.Action as ReExported
|
import CmdLine.Action as ReExported
|
||||||
import CmdLine.Option as ReExported
|
import CmdLine.Option as ReExported
|
||||||
import CmdLine.GlobalSetter as ReExported
|
import CmdLine.GlobalSetter as ReExported
|
||||||
import CmdLine.GitAnnex.Options as ReExported
|
import CmdLine.GitAnnex.Options as ReExported
|
||||||
|
import CmdLine.Batch as ReExported
|
||||||
import Options.Applicative as ReExported hiding (command)
|
import Options.Applicative as ReExported hiding (command)
|
||||||
|
|
||||||
import qualified Options.Applicative as O
|
import qualified Options.Applicative as O
|
||||||
|
|
|
@ -7,7 +7,6 @@
|
||||||
|
|
||||||
module Command.Add where
|
module Command.Add where
|
||||||
|
|
||||||
import Common.Annex
|
|
||||||
import Command
|
import Command
|
||||||
import Annex.Ingest
|
import Annex.Ingest
|
||||||
import Logs.Location
|
import Logs.Location
|
||||||
|
@ -16,13 +15,11 @@ import Annex.Content.Direct
|
||||||
import Annex.Link
|
import Annex.Link
|
||||||
import qualified Annex
|
import qualified Annex
|
||||||
import qualified Annex.Queue
|
import qualified Annex.Queue
|
||||||
|
import qualified Database.Keys
|
||||||
import Config
|
import Config
|
||||||
import Utility.InodeCache
|
import Utility.InodeCache
|
||||||
import Annex.FileMatcher
|
import Annex.FileMatcher
|
||||||
import Annex.Version
|
import Annex.Version
|
||||||
import qualified Database.Keys
|
|
||||||
import Types.Key
|
|
||||||
import CmdLine.Batch
|
|
||||||
|
|
||||||
cmd :: Command
|
cmd :: Command
|
||||||
cmd = notBareRepo $ withGlobalOptions (jobsOption : jsonOption : fileMatchingOptions) $
|
cmd = notBareRepo $ withGlobalOptions (jobsOption : jsonOption : fileMatchingOptions) $
|
||||||
|
|
|
@ -7,12 +7,10 @@
|
||||||
|
|
||||||
module Command.AddUnused where
|
module Command.AddUnused where
|
||||||
|
|
||||||
import Common.Annex
|
|
||||||
import Logs.Location
|
import Logs.Location
|
||||||
import Command
|
import Command
|
||||||
import Annex.Ingest
|
import Annex.Ingest
|
||||||
import Command.Unused (withUnusedMaps, UnusedMaps(..), startUnused)
|
import Command.Unused (withUnusedMaps, UnusedMaps(..), startUnused)
|
||||||
import Types.Key
|
|
||||||
|
|
||||||
cmd :: Command
|
cmd :: Command
|
||||||
cmd = notDirect $
|
cmd = notDirect $
|
||||||
|
|
|
@ -11,7 +11,6 @@ module Command.AddUrl where
|
||||||
|
|
||||||
import Network.URI
|
import Network.URI
|
||||||
|
|
||||||
import Common.Annex
|
|
||||||
import Command
|
import Command
|
||||||
import Backend
|
import Backend
|
||||||
import qualified Annex
|
import qualified Annex
|
||||||
|
@ -25,7 +24,6 @@ import Annex.Content
|
||||||
import Annex.Ingest
|
import Annex.Ingest
|
||||||
import Annex.UUID
|
import Annex.UUID
|
||||||
import Logs.Web
|
import Logs.Web
|
||||||
import Types.Key
|
|
||||||
import Types.KeySource
|
import Types.KeySource
|
||||||
import Types.UrlContents
|
import Types.UrlContents
|
||||||
import Config
|
import Config
|
||||||
|
@ -33,7 +31,6 @@ import Annex.Content.Direct
|
||||||
import Annex.FileMatcher
|
import Annex.FileMatcher
|
||||||
import Logs.Location
|
import Logs.Location
|
||||||
import Utility.Metered
|
import Utility.Metered
|
||||||
import CmdLine.Batch
|
|
||||||
import qualified Annex.Transfer as Transfer
|
import qualified Annex.Transfer as Transfer
|
||||||
#ifdef WITH_QUVI
|
#ifdef WITH_QUVI
|
||||||
import Annex.Quvi
|
import Annex.Quvi
|
||||||
|
|
|
@ -7,7 +7,6 @@
|
||||||
|
|
||||||
module Command.Assistant where
|
module Command.Assistant where
|
||||||
|
|
||||||
import Common.Annex
|
|
||||||
import Command
|
import Command
|
||||||
import qualified Command.Watch
|
import qualified Command.Watch
|
||||||
import Annex.Init
|
import Annex.Init
|
||||||
|
|
|
@ -7,9 +7,7 @@
|
||||||
|
|
||||||
module Command.CheckPresentKey where
|
module Command.CheckPresentKey where
|
||||||
|
|
||||||
import Common.Annex
|
|
||||||
import Command
|
import Command
|
||||||
import Types.Key
|
|
||||||
import qualified Remote
|
import qualified Remote
|
||||||
import Annex
|
import Annex
|
||||||
import Types.Messages
|
import Types.Messages
|
||||||
|
|
|
@ -7,7 +7,6 @@
|
||||||
|
|
||||||
module Command.Commit where
|
module Command.Commit where
|
||||||
|
|
||||||
import Common.Annex
|
|
||||||
import Command
|
import Command
|
||||||
import qualified Annex.Branch
|
import qualified Annex.Branch
|
||||||
import qualified Git
|
import qualified Git
|
||||||
|
|
|
@ -7,7 +7,6 @@
|
||||||
|
|
||||||
module Command.ConfigList where
|
module Command.ConfigList where
|
||||||
|
|
||||||
import Common.Annex
|
|
||||||
import Command
|
import Command
|
||||||
import Annex.UUID
|
import Annex.UUID
|
||||||
import Annex.Init
|
import Annex.Init
|
||||||
|
|
|
@ -7,11 +7,8 @@
|
||||||
|
|
||||||
module Command.ContentLocation where
|
module Command.ContentLocation where
|
||||||
|
|
||||||
import Common.Annex
|
|
||||||
import Command
|
import Command
|
||||||
import CmdLine.Batch
|
|
||||||
import Annex.Content
|
import Annex.Content
|
||||||
import Types.Key
|
|
||||||
|
|
||||||
cmd :: Command
|
cmd :: Command
|
||||||
cmd = noCommit $
|
cmd = noCommit $
|
||||||
|
|
|
@ -7,7 +7,6 @@
|
||||||
|
|
||||||
module Command.Copy where
|
module Command.Copy where
|
||||||
|
|
||||||
import Common.Annex
|
|
||||||
import Command
|
import Command
|
||||||
import qualified Command.Move
|
import qualified Command.Move
|
||||||
import qualified Remote
|
import qualified Remote
|
||||||
|
|
|
@ -8,9 +8,7 @@
|
||||||
module Command.Dead where
|
module Command.Dead where
|
||||||
|
|
||||||
import Command
|
import Command
|
||||||
import Common.Annex
|
|
||||||
import Types.TrustLevel
|
import Types.TrustLevel
|
||||||
import Types.Key
|
|
||||||
import Command.Trust (trustCommand)
|
import Command.Trust (trustCommand)
|
||||||
import Logs.Location
|
import Logs.Location
|
||||||
import Remote (keyLocations)
|
import Remote (keyLocations)
|
||||||
|
|
|
@ -7,7 +7,6 @@
|
||||||
|
|
||||||
module Command.Describe where
|
module Command.Describe where
|
||||||
|
|
||||||
import Common.Annex
|
|
||||||
import Command
|
import Command
|
||||||
import qualified Remote
|
import qualified Remote
|
||||||
import Logs.UUID
|
import Logs.UUID
|
||||||
|
|
|
@ -7,7 +7,6 @@
|
||||||
|
|
||||||
module Command.DiffDriver where
|
module Command.DiffDriver where
|
||||||
|
|
||||||
import Common.Annex
|
|
||||||
import Command
|
import Command
|
||||||
import Annex.Content
|
import Annex.Content
|
||||||
import Annex.Link
|
import Annex.Link
|
||||||
|
|
|
@ -7,7 +7,6 @@
|
||||||
|
|
||||||
module Command.Direct where
|
module Command.Direct where
|
||||||
|
|
||||||
import Common.Annex
|
|
||||||
import Command
|
import Command
|
||||||
import qualified Git
|
import qualified Git
|
||||||
import qualified Git.LsFiles
|
import qualified Git.LsFiles
|
||||||
|
|
|
@ -7,7 +7,6 @@
|
||||||
|
|
||||||
module Command.Drop where
|
module Command.Drop where
|
||||||
|
|
||||||
import Common.Annex
|
|
||||||
import Command
|
import Command
|
||||||
import qualified Remote
|
import qualified Remote
|
||||||
import qualified Annex
|
import qualified Annex
|
||||||
|
|
|
@ -7,7 +7,6 @@
|
||||||
|
|
||||||
module Command.DropKey where
|
module Command.DropKey where
|
||||||
|
|
||||||
import Common.Annex
|
|
||||||
import Command
|
import Command
|
||||||
import qualified Annex
|
import qualified Annex
|
||||||
import Logs.Location
|
import Logs.Location
|
||||||
|
|
|
@ -7,7 +7,6 @@
|
||||||
|
|
||||||
module Command.DropUnused where
|
module Command.DropUnused where
|
||||||
|
|
||||||
import Common.Annex
|
|
||||||
import Command
|
import Command
|
||||||
import qualified Command.Drop
|
import qualified Command.Drop
|
||||||
import qualified Remote
|
import qualified Remote
|
||||||
|
|
Some files were not shown because too many files have changed in this diff Show more
Loading…
Add table
Add a link
Reference in a new issue