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
|
@ -9,7 +9,7 @@
|
|||
|
||||
module Remote.BitTorrent (remote) where
|
||||
|
||||
import Common.Annex
|
||||
import Annex.Common
|
||||
import Types.Remote
|
||||
import qualified Annex
|
||||
import qualified Git
|
||||
|
@ -18,7 +18,6 @@ import Config.Cost
|
|||
import Logs.Web
|
||||
import Types.UrlContents
|
||||
import Types.CleanupActions
|
||||
import Types.Key
|
||||
import Messages.Progress
|
||||
import Utility.Metered
|
||||
import Utility.Tmp
|
||||
|
|
|
@ -11,10 +11,9 @@ import qualified Data.Map as M
|
|||
import qualified Data.ByteString.Lazy as L
|
||||
import Data.ByteString.Lazy.UTF8 (fromString)
|
||||
|
||||
import Common.Annex
|
||||
import Annex.Common
|
||||
import qualified Annex
|
||||
import Types.Remote
|
||||
import Types.Key
|
||||
import Types.Creds
|
||||
import qualified Git
|
||||
import qualified Git.Command
|
||||
|
|
|
@ -12,9 +12,8 @@ import qualified Data.Map as M
|
|||
import qualified Data.ByteString.Lazy as L
|
||||
import System.IO.Error
|
||||
|
||||
import Common.Annex
|
||||
import Annex.Common
|
||||
import Types.Remote
|
||||
import Types.Key
|
||||
import Types.Creds
|
||||
import qualified Git
|
||||
import Config
|
||||
|
|
|
@ -17,7 +17,7 @@ import qualified Data.ByteString.Lazy as L
|
|||
import qualified Data.Map as M
|
||||
import Data.Default
|
||||
|
||||
import Common.Annex
|
||||
import Annex.Common
|
||||
import Types.Remote
|
||||
import Types.Creds
|
||||
import qualified Git
|
||||
|
|
|
@ -12,7 +12,7 @@ module Remote.Directory.LegacyChunked where
|
|||
import qualified Data.ByteString.Lazy as L
|
||||
import qualified Data.ByteString as S
|
||||
|
||||
import Common.Annex
|
||||
import Annex.Common
|
||||
import Utility.FileMode
|
||||
import Remote.Helper.Special
|
||||
import qualified Remote.Helper.Chunked.Legacy as Legacy
|
||||
|
|
|
@ -9,11 +9,10 @@ module Remote.External (remote) where
|
|||
|
||||
import Remote.External.Types
|
||||
import qualified Annex
|
||||
import Common.Annex
|
||||
import Annex.Common
|
||||
import Types.Remote
|
||||
import Types.CleanupActions
|
||||
import Types.UrlContents
|
||||
import Types.Key
|
||||
import qualified Git
|
||||
import Config
|
||||
import Git.Config (isTrue, boolConfig)
|
||||
|
|
3
Remote/External/Types.hs
vendored
3
Remote/External/Types.hs
vendored
|
@ -31,8 +31,7 @@ module Remote.External.Types (
|
|||
supportedProtocolVersions,
|
||||
) where
|
||||
|
||||
import Common.Annex
|
||||
import Types.Key (file2key, key2file)
|
||||
import Annex.Common
|
||||
import Types.StandardGroups (PreferredContentExpression)
|
||||
import Utility.Metered (BytesProcessed(..))
|
||||
import Logs.Transfer (Direction(..))
|
||||
|
|
|
@ -19,7 +19,7 @@ import qualified Data.ByteString.Lazy as L
|
|||
import Control.Exception
|
||||
import Data.Default
|
||||
|
||||
import Common.Annex
|
||||
import Annex.Common
|
||||
import qualified Annex
|
||||
import Types.Remote
|
||||
import Types.GitConfig
|
||||
|
|
|
@ -13,7 +13,7 @@ module Remote.Git (
|
|||
repoAvail,
|
||||
) where
|
||||
|
||||
import Common.Annex
|
||||
import Annex.Common
|
||||
import Annex.Ssh
|
||||
import Types.Remote
|
||||
import Types.GitConfig
|
||||
|
@ -36,7 +36,6 @@ import Config
|
|||
import Config.Cost
|
||||
import Annex.Init
|
||||
import Annex.Version
|
||||
import Types.Key
|
||||
import Types.CleanupActions
|
||||
import qualified CmdLine.GitAnnexShell.Fields as Fields
|
||||
import Logs.Location
|
||||
|
|
|
@ -11,9 +11,8 @@ import qualified Data.Map as M
|
|||
import qualified Data.Text as T
|
||||
import qualified Data.ByteString.Lazy as L
|
||||
|
||||
import Common.Annex
|
||||
import Annex.Common
|
||||
import Types.Remote
|
||||
import Types.Key
|
||||
import qualified Git
|
||||
import Config
|
||||
import Config.Cost
|
||||
|
|
|
@ -10,7 +10,7 @@
|
|||
|
||||
module Remote.Helper.AWS where
|
||||
|
||||
import Common.Annex
|
||||
import Annex.Common
|
||||
import Creds
|
||||
|
||||
import qualified Data.Map as M
|
||||
|
|
|
@ -17,11 +17,10 @@ module Remote.Helper.Chunked (
|
|||
checkPresentChunks,
|
||||
) where
|
||||
|
||||
import Common.Annex
|
||||
import Annex.Common
|
||||
import Utility.DataUnits
|
||||
import Types.StoreRetrieve
|
||||
import Types.Remote
|
||||
import Types.Key
|
||||
import Logs.Chunk
|
||||
import Utility.Metered
|
||||
import Crypto (EncKey)
|
||||
|
|
|
@ -7,7 +7,7 @@
|
|||
|
||||
module Remote.Helper.Chunked.Legacy where
|
||||
|
||||
import Common.Annex
|
||||
import Annex.Common
|
||||
import Remote.Helper.Chunked
|
||||
import Utility.Metered
|
||||
|
||||
|
|
|
@ -24,7 +24,7 @@ import qualified "sandi" Codec.Binary.Base64 as B64
|
|||
import qualified Data.ByteString as B
|
||||
import Data.Bits.Utils
|
||||
|
||||
import Common.Annex
|
||||
import Annex.Common
|
||||
import Types.Remote
|
||||
import Crypto
|
||||
import Types.Crypto
|
||||
|
|
|
@ -7,7 +7,7 @@
|
|||
|
||||
module Remote.Helper.Git where
|
||||
|
||||
import Common.Annex
|
||||
import Annex.Common
|
||||
import qualified Git
|
||||
import Types.Availability
|
||||
import qualified Types.Remote as Remote
|
||||
|
|
|
@ -11,7 +11,7 @@ module Remote.Helper.Hooks (addHooks) where
|
|||
|
||||
import qualified Data.Map as M
|
||||
|
||||
import Common.Annex
|
||||
import Annex.Common
|
||||
import Types.Remote
|
||||
import Types.CleanupActions
|
||||
import qualified Annex
|
||||
|
|
|
@ -9,7 +9,7 @@
|
|||
|
||||
module Remote.Helper.Http where
|
||||
|
||||
import Common.Annex
|
||||
import Annex.Common
|
||||
import Types.StoreRetrieve
|
||||
import Utility.Metered
|
||||
import Remote.Helper.Special
|
||||
|
|
|
@ -9,7 +9,7 @@
|
|||
|
||||
module Remote.Helper.Messages where
|
||||
|
||||
import Common.Annex
|
||||
import Annex.Common
|
||||
import qualified Git
|
||||
import qualified Types.Remote as Remote
|
||||
|
||||
|
|
|
@ -12,7 +12,7 @@ module Remote.Helper.ReadOnly
|
|||
, readonlyRemoveKey
|
||||
) where
|
||||
|
||||
import Common.Annex
|
||||
import Annex.Common
|
||||
import Types.Remote
|
||||
import Types.StoreRetrieve
|
||||
import Utility.Metered
|
||||
|
|
|
@ -32,7 +32,7 @@ module Remote.Helper.Special (
|
|||
module X
|
||||
) where
|
||||
|
||||
import Common.Annex
|
||||
import Annex.Common
|
||||
import qualified Annex
|
||||
import Types.StoreRetrieve
|
||||
import Types.Remote
|
||||
|
|
|
@ -7,7 +7,7 @@
|
|||
|
||||
module Remote.Helper.Ssh where
|
||||
|
||||
import Common.Annex
|
||||
import Annex.Common
|
||||
import qualified Annex
|
||||
import qualified Git
|
||||
import qualified Git.Url
|
||||
|
@ -15,7 +15,6 @@ import Annex.UUID
|
|||
import Annex.Ssh
|
||||
import CmdLine.GitAnnexShell.Fields (Field, fieldName)
|
||||
import qualified CmdLine.GitAnnexShell.Fields as Fields
|
||||
import Types.Key
|
||||
import Remote.Helper.Messages
|
||||
import Messages.Progress
|
||||
import Utility.Metered
|
||||
|
|
|
@ -7,9 +7,8 @@
|
|||
|
||||
module Remote.Hook (remote) where
|
||||
|
||||
import Common.Annex
|
||||
import Annex.Common
|
||||
import Types.Remote
|
||||
import Types.Key
|
||||
import Types.Creds
|
||||
import qualified Git
|
||||
import Config
|
||||
|
|
|
@ -11,7 +11,7 @@ module Remote.List where
|
|||
|
||||
import qualified Data.Map as M
|
||||
|
||||
import Common.Annex
|
||||
import Annex.Common
|
||||
import qualified Annex
|
||||
import Logs.Remote
|
||||
import Types.Remote
|
||||
|
|
|
@ -18,7 +18,7 @@ module Remote.Rsync (
|
|||
RsyncOpts
|
||||
) where
|
||||
|
||||
import Common.Annex
|
||||
import Annex.Common
|
||||
import Types.Remote
|
||||
import qualified Git
|
||||
import Config
|
||||
|
@ -36,7 +36,6 @@ import Messages.Progress
|
|||
import Utility.Metered
|
||||
import Logs.Transfer
|
||||
import Types.Creds
|
||||
import Types.Key (isChunkKey)
|
||||
import Annex.DirHashes
|
||||
import Utility.Tmp
|
||||
|
||||
|
|
|
@ -10,7 +10,7 @@
|
|||
module Remote.Rsync.RsyncUrl where
|
||||
|
||||
import Types
|
||||
import Locations
|
||||
import Annex.Locations
|
||||
import Utility.Rsync
|
||||
import Utility.SafeCommand
|
||||
|
||||
|
|
|
@ -31,9 +31,8 @@ import Data.IORef
|
|||
import Data.Bits.Utils
|
||||
import System.Log.Logger
|
||||
|
||||
import Common.Annex
|
||||
import Annex.Common
|
||||
import Types.Remote
|
||||
import Types.Key
|
||||
import qualified Git
|
||||
import Config
|
||||
import Config.Cost
|
||||
|
|
|
@ -27,7 +27,7 @@ import Data.Aeson
|
|||
import Data.ByteString.Lazy.UTF8 (fromString)
|
||||
import Control.Concurrent.STM
|
||||
|
||||
import Common.Annex
|
||||
import Annex.Common
|
||||
import Types.Remote
|
||||
import Types.Creds
|
||||
import qualified Git
|
||||
|
|
|
@ -9,7 +9,7 @@
|
|||
|
||||
module Remote.Web (remote, getWebUrls) where
|
||||
|
||||
import Common.Annex
|
||||
import Annex.Common
|
||||
import Types.Remote
|
||||
import Remote.Helper.Messages
|
||||
import qualified Git
|
||||
|
@ -18,7 +18,6 @@ import Annex.Content
|
|||
import Config.Cost
|
||||
import Logs.Web
|
||||
import Annex.UUID
|
||||
import Types.Key
|
||||
import Utility.Metered
|
||||
import qualified Annex.Url as Url
|
||||
#ifdef WITH_QUVI
|
||||
|
|
|
@ -19,7 +19,7 @@ import Network.HTTP.Types
|
|||
import System.IO.Error
|
||||
import Control.Monad.Catch
|
||||
|
||||
import Common.Annex
|
||||
import Annex.Common
|
||||
import Types.Remote
|
||||
import qualified Git
|
||||
import Config
|
||||
|
|
|
@ -11,7 +11,7 @@
|
|||
module Remote.WebDAV.DavLocation where
|
||||
|
||||
import Types
|
||||
import Locations
|
||||
import Annex.Locations
|
||||
import Utility.Url (URLString)
|
||||
|
||||
import System.FilePath.Posix -- for manipulating url paths
|
||||
|
|
Loading…
Add table
Add a link
Reference in a new issue