remove redundant imports
Clean build under ghc 8.8.3, which seems to do better at finding cases where two imports both provide the same symbol, and warns about one of them. This commit was sponsored by Ilya Shlyakhter on Patreon.
This commit is contained in:
parent
6ef62cb3c7
commit
aa1ad0b7ca
13 changed files with 7 additions and 17 deletions
|
@ -14,7 +14,6 @@ module Annex.SpecialRemote (
|
|||
|
||||
import Annex.Common
|
||||
import Annex.SpecialRemote.Config
|
||||
import Remote (remoteTypes)
|
||||
import Types.Remote (RemoteConfig, SetupStage(..), typename, setup)
|
||||
import Types.GitConfig
|
||||
import Types.ProposedAccepted
|
||||
|
|
|
@ -11,7 +11,7 @@
|
|||
module Annex.SpecialRemote.Config where
|
||||
|
||||
import Common
|
||||
import Types.Remote (RemoteConfigField, RemoteConfig, configParser)
|
||||
import Types.Remote (configParser)
|
||||
import Types
|
||||
import Types.UUID
|
||||
import Types.ProposedAccepted
|
||||
|
|
|
@ -13,7 +13,7 @@ import Command
|
|||
import Logs.Config
|
||||
import Config
|
||||
import Types.GitConfig (globalConfigs)
|
||||
import Git.Types (ConfigKey(..), fromConfigValue)
|
||||
import Git.Types (fromConfigValue)
|
||||
|
||||
import qualified Data.ByteString.Char8 as S8
|
||||
|
||||
|
|
|
@ -30,7 +30,6 @@ import Logs.UUID
|
|||
import Logs.Trust
|
||||
import Logs.Location
|
||||
import Annex.NumCopies
|
||||
import Remote
|
||||
import Git.Config (boolConfig)
|
||||
import qualified Git.LsTree as LsTree
|
||||
import Utility.Percentage
|
||||
|
@ -319,11 +318,11 @@ showStat s = maybe noop calc =<< s
|
|||
repo_list :: TrustLevel -> Stat
|
||||
repo_list level = stat n $ nojson $ lift $ do
|
||||
us <- filter (/= NoUUID) . M.keys
|
||||
<$> (M.union <$> (M.map fromUUIDDesc <$> uuidDescMap) <*> remoteMap Remote.name)
|
||||
<$> (M.union <$> (M.map fromUUIDDesc <$> uuidDescMap) <*> Remote.remoteMap Remote.name)
|
||||
rs <- fst <$> trustPartition level us
|
||||
countRepoList (length rs)
|
||||
-- This also handles json display.
|
||||
<$> prettyPrintUUIDs n rs
|
||||
<$> Remote.prettyPrintUUIDs n rs
|
||||
where
|
||||
n = showTrustLevel level ++ " repositories"
|
||||
|
||||
|
@ -497,9 +496,9 @@ reposizes_stats = stat desc $ nojson $ do
|
|||
. M.toList
|
||||
<$> cachedRepoData
|
||||
let maxlen = maximum (map (length . snd) l)
|
||||
descm <- lift uuidDescriptions
|
||||
descm <- lift Remote.uuidDescriptions
|
||||
-- This also handles json display.
|
||||
s <- lift $ prettyPrintUUIDsWith (Just "size") desc descm (Just . show) $
|
||||
s <- lift $ Remote.prettyPrintUUIDsWith (Just "size") desc descm (Just . show) $
|
||||
map (\(u, sz) -> (u, Just $ mkdisp sz maxlen)) l
|
||||
return $ countRepoList (length l) s
|
||||
where
|
||||
|
|
|
@ -14,7 +14,6 @@ import qualified Data.Map as M
|
|||
import Command
|
||||
import Annex.SpecialRemote
|
||||
import qualified Remote
|
||||
import qualified Logs.Remote
|
||||
import qualified Types.Remote as R
|
||||
import Types.RemoteConfig
|
||||
import Annex.UUID
|
||||
|
|
|
@ -13,7 +13,6 @@ import Annex.Action
|
|||
import Annex
|
||||
import Utility.Rsync
|
||||
import Types.Transfer
|
||||
import Types.Remote (RetrievalSecurityPolicy(..))
|
||||
import Command.SendKey (fieldTransfer)
|
||||
import qualified CmdLine.GitAnnexShell.Fields as Fields
|
||||
|
||||
|
|
|
@ -31,7 +31,7 @@ import Types.StandardGroups
|
|||
import Types.ScheduledActivity
|
||||
import Types.NumCopies
|
||||
import Remote
|
||||
import Git.Types (ConfigKey(..), fromConfigKey, fromConfigValue)
|
||||
import Git.Types (fromConfigKey, fromConfigValue)
|
||||
|
||||
cmd :: Command
|
||||
cmd = command "vicfg" SectionSetup "edit configuration in git-annex branch"
|
||||
|
|
1
Creds.hs
1
Creds.hs
|
@ -29,7 +29,6 @@ import Annex.SpecialRemote.Config
|
|||
import Annex.Perms
|
||||
import Utility.FileMode
|
||||
import Crypto
|
||||
import Types.Remote (RemoteConfig, RemoteConfigField)
|
||||
import Types.ProposedAccepted
|
||||
import Remote.Helper.Encryptable (remoteCipher, remoteCipher', embedCreds, EncryptionIsSetup, extractCipher)
|
||||
import Utility.Env (getEnv)
|
||||
|
|
|
@ -12,7 +12,6 @@ import Annex.Perms
|
|||
import Utility.FileMode
|
||||
|
||||
import Database.Persist.Sqlite
|
||||
import Control.Monad.IO.Class (liftIO)
|
||||
import qualified Data.Text as T
|
||||
import Lens.Micro
|
||||
|
||||
|
|
|
@ -22,7 +22,6 @@ import P2P.Protocol
|
|||
import P2P.IO
|
||||
import Logs.Location
|
||||
import Types.NumCopies
|
||||
import Types.Remote (RetrievalSecurityPolicy(..))
|
||||
import Utility.Metered
|
||||
|
||||
import Control.Monad.Free
|
||||
|
|
|
@ -40,7 +40,6 @@ import Annex.ChangedRefs
|
|||
|
||||
import Control.Monad.Free
|
||||
import Control.Monad.IO.Class
|
||||
import System.Exit (ExitCode(..))
|
||||
import System.IO.Error
|
||||
import Network.Socket
|
||||
import Control.Concurrent
|
||||
|
|
|
@ -16,7 +16,6 @@ import Types.Key
|
|||
import Types.Creds
|
||||
import Types.ProposedAccepted
|
||||
import qualified Annex
|
||||
import qualified Annex.SpecialRemote.Config
|
||||
import qualified Git
|
||||
import qualified Git.Types as Git
|
||||
import qualified Git.Url
|
||||
|
|
|
@ -25,7 +25,6 @@ module Utility.SimpleProtocol (
|
|||
|
||||
import Data.Char
|
||||
import GHC.IO.Handle
|
||||
import System.Exit (ExitCode(..))
|
||||
|
||||
import Common
|
||||
|
||||
|
|
Loading…
Reference in a new issue