summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorGravatar Joey Hess <joey@kitenet.net>2014-01-26 16:25:55 -0400
committerGravatar Joey Hess <joey@kitenet.net>2014-01-26 16:25:55 -0400
commit4f050ca9b80d0565e408137f2422e808b82cfd11 (patch)
tree5aca9688e49dee8915a962de4baf4c305ccbfa9e
parent541178b499d084e4041ae4b9d62bf86f5a97c3ff (diff)
reorganize some files and imports
-rw-r--r--CmdLine/GitAnnex.hs (renamed from GitAnnex.hs)5
-rw-r--r--CmdLine/GitAnnex/Options.hs (renamed from GitAnnex/Options.hs)16
-rw-r--r--CmdLine/GitAnnexShell.hs (renamed from GitAnnexShell.hs)5
-rw-r--r--CmdLine/Option.hs (renamed from Option.hs)34
-rw-r--r--CmdLine/Seek.hs (renamed from Seek.hs)8
-rw-r--r--CmdLine/Usage.hs (renamed from Usage.hs)2
-rw-r--r--Command.hs6
-rw-r--r--Command/AddUrl.hs7
-rw-r--r--Command/Assistant.hs5
-rw-r--r--Command/Copy.hs1
-rw-r--r--Command/Drop.hs9
-rw-r--r--Command/DropUnused.hs5
-rw-r--r--Command/ExamineKey.hs1
-rw-r--r--Command/Find.hs8
-rw-r--r--Command/Forget.hs3
-rw-r--r--Command/Fsck.hs22
-rw-r--r--Command/Get.hs1
-rw-r--r--Command/Help.hs3
-rw-r--r--Command/Import.hs11
-rw-r--r--Command/ImportFeed.hs3
-rw-r--r--Command/Info.hs1
-rw-r--r--Command/List.hs5
-rw-r--r--Command/Log.hs11
-rw-r--r--Command/Mirror.hs1
-rw-r--r--Command/Move.hs1
-rw-r--r--Command/Status.hs1
-rw-r--r--Command/Sync.hs5
-rw-r--r--Command/TransferKey.hs4
-rw-r--r--Command/Unused.hs9
-rw-r--r--Command/Watch.hs5
-rw-r--r--Command/WebApp.hs3
-rw-r--r--Command/Whereis.hs1
-rw-r--r--Test.hs2
-rw-r--r--git-annex.hs8
34 files changed, 92 insertions, 120 deletions
diff --git a/GitAnnex.hs b/CmdLine/GitAnnex.hs
index 57ee5d520..b25082963 100644
--- a/GitAnnex.hs
+++ b/CmdLine/GitAnnex.hs
@@ -7,12 +7,11 @@
{-# LANGUAGE CPP, OverloadedStrings #-}
-module GitAnnex where
+module CmdLine.GitAnnex where
import qualified Git.CurrentRepo
import CmdLine
import Command
-import GitAnnex.Options
import qualified Command.Add
import qualified Command.Unannex
@@ -180,4 +179,4 @@ run args = do
#ifdef WITH_EKG
_ <- forkServer "localhost" 4242
#endif
- dispatch True args cmds options [] header Git.CurrentRepo.get
+ dispatch True args cmds gitAnnexOptions [] header Git.CurrentRepo.get
diff --git a/GitAnnex/Options.hs b/CmdLine/GitAnnex/Options.hs
index 235ea00e9..fcf5deaf0 100644
--- a/GitAnnex/Options.hs
+++ b/CmdLine/GitAnnex/Options.hs
@@ -5,14 +5,13 @@
- Licensed under the GNU GPL version 3 or higher.
-}
-module GitAnnex.Options where
+module CmdLine.GitAnnex.Options where
import System.Console.GetOpt
import Common.Annex
import qualified Git.Config
import Git.Types
-import Command
import Types.TrustLevel
import Types.NumCopies
import Types.Messages
@@ -20,10 +19,11 @@ import qualified Annex
import qualified Remote
import qualified Limit
import qualified Limit.Wanted
-import qualified Option
+import CmdLine.Option
+import CmdLine.Usage
-options :: [Option]
-options = Option.common ++
+gitAnnexOptions :: [Option]
+gitAnnexOptions = commonOptions ++
[ Option ['N'] ["numcopies"] (ReqArg setnumcopies paramNumber)
"override default number of copies"
, Option [] ["trust"] (trustArg Trusted)
@@ -64,7 +64,7 @@ options = Option.common ++
"override default User-Agent"
, Option [] ["trust-glacier"] (NoArg (Annex.setFlag "trustglacier"))
"Trust Amazon Glacier inventory"
- ] ++ Option.matcher
+ ] ++ matcherOptions
where
trustArg t = ReqArg (Remote.forceTrust t) paramRemote
setnumcopies v = maybe noop
@@ -86,10 +86,10 @@ keyOptions =
]
fromOption :: Option
-fromOption = Option.field ['f'] "from" paramRemote "source remote"
+fromOption = fieldOption ['f'] "from" paramRemote "source remote"
toOption :: Option
-toOption = Option.field ['t'] "to" paramRemote "destination remote"
+toOption = fieldOption ['t'] "to" paramRemote "destination remote"
fromToOptions :: [Option]
fromToOptions = [fromOption, toOption]
diff --git a/GitAnnexShell.hs b/CmdLine/GitAnnexShell.hs
index 7c3893be3..c7b5bd1c9 100644
--- a/GitAnnexShell.hs
+++ b/CmdLine/GitAnnexShell.hs
@@ -5,7 +5,7 @@
- Licensed under the GNU GPL version 3 or higher.
-}
-module GitAnnexShell where
+module CmdLine.GitAnnexShell where
import System.Environment
import System.Console.GetOpt
@@ -16,7 +16,6 @@ import CmdLine
import Command
import Annex.UUID
import Annex (setField)
-import qualified Option
import Fields
import Utility.UserInfo
import Remote.GCrypt (getGCryptUUID)
@@ -54,7 +53,7 @@ cmds = map adddirparam $ cmds_readonly ++ cmds_notreadonly
adddirparam c = c { cmdparamdesc = "DIRECTORY " ++ cmdparamdesc c }
options :: [OptDescr (Annex ())]
-options = Option.common ++
+options = commonOptions ++
[ Option [] ["uuid"] (ReqArg checkUUID paramUUID) "local repository uuid"
]
where
diff --git a/Option.hs b/CmdLine/Option.hs
index fee13a0cc..915b06849 100644
--- a/Option.hs
+++ b/CmdLine/Option.hs
@@ -5,12 +5,12 @@
- Licensed under the GNU GPL version 3 or higher.
-}
-module Option (
- common,
- matcher,
- flag,
- field,
- name,
+module CmdLine.Option (
+ commonOptions,
+ matcherOptions,
+ flagOption,
+ fieldOption,
+ optionName,
ArgDescr(..),
OptDescr(..),
) where
@@ -21,10 +21,10 @@ import Common.Annex
import qualified Annex
import Types.Messages
import Limit
-import Usage
+import CmdLine.Usage
-common :: [Option]
-common =
+commonOptions :: [Option]
+commonOptions =
[ Option [] ["force"] (NoArg (setforce True))
"allow actions that may lose annexed data"
, Option ['F'] ["fast"] (NoArg (setfast True))
@@ -50,8 +50,8 @@ common =
setdebug = Annex.changeGitConfig $ \c -> c { annexDebug = True }
unsetdebug = Annex.changeGitConfig $ \c -> c { annexDebug = False }
-matcher :: [Option]
-matcher =
+matcherOptions :: [Option]
+matcherOptions =
[ longopt "not" "negate next option"
, longopt "and" "both previous and next option must match"
, longopt "or" "either previous or next option must match"
@@ -63,15 +63,15 @@ matcher =
shortopt o = Option o [] $ NoArg $ addToken o
{- An option that sets a flag. -}
-flag :: String -> String -> String -> Option
-flag short opt description =
+flagOption :: String -> String -> String -> Option
+flagOption short opt description =
Option short [opt] (NoArg (Annex.setFlag opt)) description
{- An option that sets a field. -}
-field :: String -> String -> String -> String -> Option
-field short opt paramdesc description =
+fieldOption :: String -> String -> String -> String -> Option
+fieldOption short opt paramdesc description =
Option short [opt] (ReqArg (Annex.setField opt) paramdesc) description
{- The flag or field name used for an option. -}
-name :: Option -> String
-name (Option _ o _ _) = Prelude.head o
+optionName :: Option -> String
+optionName (Option _ o _ _) = Prelude.head o
diff --git a/Seek.hs b/CmdLine/Seek.hs
index feb94627b..d6d7fbc8b 100644
--- a/Seek.hs
+++ b/CmdLine/Seek.hs
@@ -9,7 +9,7 @@
- Licensed under the GNU GPL version 3 or higher.
-}
-module Seek where
+module CmdLine.Seek where
import System.PosixCompat.Files
@@ -22,7 +22,7 @@ import qualified Git
import qualified Git.Command
import qualified Git.LsFiles as LsFiles
import qualified Limit
-import qualified Option
+import CmdLine.Option
import Logs.Location
import Logs.Unused
import Annex.CatFile
@@ -108,10 +108,10 @@ withKeys a params = seekActions $ return $ map (a . parse) params
- a conversion function.
-}
getOptionField :: Option -> (Maybe String -> Annex a) -> Annex a
-getOptionField option converter = converter <=< Annex.getField $ Option.name option
+getOptionField option converter = converter <=< Annex.getField $ optionName option
getOptionFlag :: Option -> Annex Bool
-getOptionFlag option = Annex.getFlag (Option.name option)
+getOptionFlag option = Annex.getFlag (optionName option)
withNothing :: CommandStart -> CommandSeek
withNothing a [] = seekActions $ return [a]
diff --git a/Usage.hs b/CmdLine/Usage.hs
index 9a48a0908..64b512144 100644
--- a/Usage.hs
+++ b/CmdLine/Usage.hs
@@ -5,7 +5,7 @@
- Licensed under the GNU GPL version 3 or higher.
-}
-module Usage where
+module CmdLine.Usage where
import Common.Annex
diff --git a/Command.hs b/Command.hs
index 1943fc06e..7d179aed2 100644
--- a/Command.hs
+++ b/Command.hs
@@ -29,10 +29,12 @@ import qualified Annex
import qualified Git
import Types.Command as ReExported
import Types.Option as ReExported
-import Seek as ReExported
+import CmdLine.Seek as ReExported
import Checks as ReExported
-import Usage as ReExported
+import CmdLine.Usage as ReExported
import RunCommand as ReExported
+import CmdLine.Option as ReExported
+import CmdLine.GitAnnex.Options as ReExported
{- Generates a normal command -}
command :: String -> String -> CommandSeek -> CommandSection -> String -> Command
diff --git a/Command/AddUrl.hs b/Command/AddUrl.hs
index 8027c4b6b..82b04f07b 100644
--- a/Command/AddUrl.hs
+++ b/Command/AddUrl.hs
@@ -21,7 +21,6 @@ import qualified Annex.Url as Url
import qualified Backend.URL
import Annex.Content
import Logs.Web
-import qualified Option
import Types.Key
import Types.KeySource
import Config
@@ -39,13 +38,13 @@ def = [notBareRepo $ withOptions [fileOption, pathdepthOption, relaxedOption] $
SectionCommon "add urls to annex"]
fileOption :: Option
-fileOption = Option.field [] "file" paramFile "specify what file the url is added to"
+fileOption = fieldOption [] "file" paramFile "specify what file the url is added to"
pathdepthOption :: Option
-pathdepthOption = Option.field [] "pathdepth" paramNumber "path components to use in filename"
+pathdepthOption = fieldOption [] "pathdepth" paramNumber "path components to use in filename"
relaxedOption :: Option
-relaxedOption = Option.flag [] "relaxed" "skip size check"
+relaxedOption = flagOption [] "relaxed" "skip size check"
seek :: CommandSeek
seek ps = do
diff --git a/Command/Assistant.hs b/Command/Assistant.hs
index 260d9c69c..1449743a2 100644
--- a/Command/Assistant.hs
+++ b/Command/Assistant.hs
@@ -9,7 +9,6 @@ module Command.Assistant where
import Common.Annex
import Command
-import qualified Option
import qualified Command.Watch
import Init
import Config.Files
@@ -32,10 +31,10 @@ options =
]
autoStartOption :: Option
-autoStartOption = Option.flag [] "autostart" "start in known repositories"
+autoStartOption = flagOption [] "autostart" "start in known repositories"
startDelayOption :: Option
-startDelayOption = Option.field [] "startdelay" paramNumber "delay before running startup scan"
+startDelayOption = fieldOption [] "startdelay" paramNumber "delay before running startup scan"
seek :: CommandSeek
seek ps = do
diff --git a/Command/Copy.hs b/Command/Copy.hs
index e2bd1fce4..29606061d 100644
--- a/Command/Copy.hs
+++ b/Command/Copy.hs
@@ -9,7 +9,6 @@ module Command.Copy where
import Common.Annex
import Command
-import GitAnnex.Options
import qualified Command.Move
import qualified Remote
import Annex.Wanted
diff --git a/Command/Drop.hs b/Command/Drop.hs
index 0a6d61ba0..d29195b05 100644
--- a/Command/Drop.hs
+++ b/Command/Drop.hs
@@ -16,19 +16,18 @@ import Logs.Location
import Logs.Trust
import Config.NumCopies
import Annex.Content
-import qualified Option
import Annex.Wanted
def :: [Command]
-def = [withOptions [fromOption] $ command "drop" paramPaths seek
+def = [withOptions [dropFromOption] $ command "drop" paramPaths seek
SectionCommon "indicate content of files not currently wanted"]
-fromOption :: Option
-fromOption = Option.field ['f'] "from" paramRemote "drop content from a remote"
+dropFromOption :: Option
+dropFromOption = fieldOption ['f'] "from" paramRemote "drop content from a remote"
seek :: CommandSeek
seek ps = do
- from <- getOptionField fromOption Remote.byNameWithUUID
+ from <- getOptionField dropFromOption Remote.byNameWithUUID
withFilesInGit (whenAnnexed $ start from) ps
start :: Maybe Remote -> FilePath -> (Key, Backend) -> CommandStart
diff --git a/Command/DropUnused.hs b/Command/DropUnused.hs
index af90303fb..a3409ab1b 100644
--- a/Command/DropUnused.hs
+++ b/Command/DropUnused.hs
@@ -13,12 +13,11 @@ import qualified Annex
import qualified Command.Drop
import qualified Remote
import qualified Git
-import qualified Option
import Command.Unused (withUnusedMaps, UnusedMaps(..), startUnused)
import Config.NumCopies
def :: [Command]
-def = [withOptions [Command.Drop.fromOption] $
+def = [withOptions [Command.Drop.dropFromOption] $
command "dropunused" (paramRepeating paramNumRange)
seek SectionMaintenance "drop unused file content"]
@@ -37,7 +36,7 @@ perform numcopies key = maybe droplocal dropremote =<< Remote.byNameWithUUID =<<
showAction $ "from " ++ Remote.name r
Command.Drop.performRemote key numcopies r
droplocal = Command.Drop.performLocal key numcopies Nothing
- from = Annex.getField $ Option.name Command.Drop.fromOption
+ from = Annex.getField $ optionName Command.Drop.dropFromOption
performOther :: (Key -> Git.Repo -> FilePath) -> Key -> CommandPerform
performOther filespec key = do
diff --git a/Command/ExamineKey.hs b/Command/ExamineKey.hs
index 30963287e..dd2bec507 100644
--- a/Command/ExamineKey.hs
+++ b/Command/ExamineKey.hs
@@ -12,7 +12,6 @@ import Command
import qualified Utility.Format
import Command.Find (formatOption, getFormat, showFormatted, keyVars)
import Types.Key
-import GitAnnex.Options
def :: [Command]
def = [noCommit $ noMessages $ withOptions [formatOption, jsonOption] $
diff --git a/Command/Find.hs b/Command/Find.hs
index e7e5b7986..c6a32a944 100644
--- a/Command/Find.hs
+++ b/Command/Find.hs
@@ -17,24 +17,22 @@ import qualified Annex
import qualified Utility.Format
import Utility.DataUnits
import Types.Key
-import qualified Option
-import GitAnnex.Options
def :: [Command]
def = [noCommit $ noMessages $ withOptions [formatOption, print0Option, jsonOption] $
command "find" paramPaths seek SectionQuery "lists available files"]
formatOption :: Option
-formatOption = Option.field [] "format" paramFormat "control format of output"
+formatOption = fieldOption [] "format" paramFormat "control format of output"
getFormat :: Annex (Maybe Utility.Format.Format)
getFormat = getOptionField formatOption $ return . fmap Utility.Format.gen
print0Option :: Option
-print0Option = Option.Option [] ["print0"] (Option.NoArg set)
+print0Option = Option [] ["print0"] (NoArg set)
"terminate output with null"
where
- set = Annex.setField (Option.name formatOption) "${file}\0"
+ set = Annex.setField (optionName formatOption) "${file}\0"
seek :: CommandSeek
seek ps = do
diff --git a/Command/Forget.hs b/Command/Forget.hs
index 0f247f968..dbcce6cc3 100644
--- a/Command/Forget.hs
+++ b/Command/Forget.hs
@@ -12,7 +12,6 @@ import Command
import qualified Annex.Branch as Branch
import Logs.Transitions
import qualified Annex
-import qualified Option
import Data.Time.Clock.POSIX
@@ -24,7 +23,7 @@ forgetOptions :: [Option]
forgetOptions = [dropDeadOption]
dropDeadOption :: Option
-dropDeadOption = Option.flag [] "drop-dead" "drop references to dead repositories"
+dropDeadOption = flagOption [] "drop-dead" "drop references to dead repositories"
seek :: CommandSeek
seek ps = do
diff --git a/Command/Fsck.hs b/Command/Fsck.hs
index 892823584..b20bfc8ab 100644
--- a/Command/Fsck.hs
+++ b/Command/Fsck.hs
@@ -30,11 +30,9 @@ import Annex.UUID
import Utility.DataUnits
import Utility.FileMode
import Config
-import qualified Option
import Types.Key
import Utility.HumanTime
import Git.FilePath
-import GitAnnex.Options hiding (fromOption)
#ifndef mingw32_HOST_OS
import System.Posix.Process (getProcessID)
@@ -50,22 +48,22 @@ def :: [Command]
def = [withOptions fsckOptions $ command "fsck" paramPaths seek
SectionMaintenance "check for problems"]
-fromOption :: Option
-fromOption = Option.field ['f'] "from" paramRemote "check remote"
+fsckFromOption :: Option
+fsckFromOption = fieldOption ['f'] "from" paramRemote "check remote"
startIncrementalOption :: Option
-startIncrementalOption = Option.flag ['S'] "incremental" "start an incremental fsck"
+startIncrementalOption = flagOption ['S'] "incremental" "start an incremental fsck"
moreIncrementalOption :: Option
-moreIncrementalOption = Option.flag ['m'] "more" "continue an incremental fsck"
+moreIncrementalOption = flagOption ['m'] "more" "continue an incremental fsck"
incrementalScheduleOption :: Option
-incrementalScheduleOption = Option.field [] "incremental-schedule" paramTime
+incrementalScheduleOption = fieldOption [] "incremental-schedule" paramTime
"schedule incremental fscking"
fsckOptions :: [Option]
fsckOptions =
- [ fromOption
+ [ fsckFromOption
, startIncrementalOption
, moreIncrementalOption
, incrementalScheduleOption
@@ -73,7 +71,7 @@ fsckOptions =
seek :: CommandSeek
seek ps = do
- from <- getOptionField fromOption Remote.byNameWithUUID
+ from <- getOptionField fsckFromOption Remote.byNameWithUUID
i <- getIncremental
withKeyOptions
(startKey i)
@@ -83,9 +81,9 @@ seek ps = do
getIncremental :: Annex Incremental
getIncremental = do
i <- maybe (return False) (checkschedule . parseDuration)
- =<< Annex.getField (Option.name incrementalScheduleOption)
- starti <- Annex.getFlag (Option.name startIncrementalOption)
- morei <- Annex.getFlag (Option.name moreIncrementalOption)
+ =<< Annex.getField (optionName incrementalScheduleOption)
+ starti <- Annex.getFlag (optionName startIncrementalOption)
+ morei <- Annex.getFlag (optionName moreIncrementalOption)
case (i, starti, morei) of
(False, False, False) -> return NonIncremental
(False, True, _) -> startIncremental
diff --git a/Command/Get.hs b/Command/Get.hs
index edab72e42..f436b15b5 100644
--- a/Command/Get.hs
+++ b/Command/Get.hs
@@ -14,7 +14,6 @@ import Annex.Content
import Logs.Transfer
import Config.NumCopies
import Annex.Wanted
-import GitAnnex.Options
import qualified Command.Move
def :: [Command]
diff --git a/Command/Help.hs b/Command/Help.hs
index 5292c3ca3..7998ed796 100644
--- a/Command/Help.hs
+++ b/Command/Help.hs
@@ -18,7 +18,6 @@ import qualified Command.Copy
import qualified Command.Sync
import qualified Command.Whereis
import qualified Command.Fsck
-import GitAnnex.Options
import System.Console.GetOpt
@@ -42,7 +41,7 @@ start' ["options"] = showCommonOptions
start' _ = showGeneralHelp
showCommonOptions :: IO ()
-showCommonOptions = putStrLn $ usageInfo "Common options:" options
+showCommonOptions = putStrLn $ usageInfo "Common options:" gitAnnexOptions
showGeneralHelp :: IO ()
showGeneralHelp = putStrLn $ unlines
diff --git a/Command/Import.hs b/Command/Import.hs
index dda2f3bc4..db0f8d3f5 100644
--- a/Command/Import.hs
+++ b/Command/Import.hs
@@ -13,7 +13,6 @@ import Common.Annex
import Command
import qualified Annex
import qualified Command.Add
-import qualified Option
import Utility.CopyFile
import Backend
import Remote
@@ -32,16 +31,16 @@ opts =
]
duplicateOption :: Option
-duplicateOption = Option.flag [] "duplicate" "do not delete source files"
+duplicateOption = flagOption [] "duplicate" "do not delete source files"
deduplicateOption :: Option
-deduplicateOption = Option.flag [] "deduplicate" "delete source files whose content was imported before"
+deduplicateOption = flagOption [] "deduplicate" "delete source files whose content was imported before"
cleanDuplicatesOption :: Option
-cleanDuplicatesOption = Option.flag [] "clean-duplicates" "delete duplicate source files (import nothing)"
+cleanDuplicatesOption = flagOption [] "clean-duplicates" "delete duplicate source files (import nothing)"
skipDuplicatesOption :: Option
-skipDuplicatesOption = Option.flag [] "skip-duplicates" "import only new files"
+skipDuplicatesOption = flagOption [] "skip-duplicates" "import only new files"
data DuplicateMode = Default | Duplicate | DeDuplicate | CleanDuplicates | SkipDuplicates
deriving (Eq)
@@ -53,7 +52,7 @@ getDuplicateMode = gen
<*> getflag cleanDuplicatesOption
<*> getflag skipDuplicatesOption
where
- getflag = Annex.getFlag . Option.name
+ getflag = Annex.getFlag . optionName
gen False False False False = Default
gen True False False False = Duplicate
gen False True False False = DeDuplicate
diff --git a/Command/ImportFeed.hs b/Command/ImportFeed.hs
index 2675b7a54..dfa89b344 100644
--- a/Command/ImportFeed.hs
+++ b/Command/ImportFeed.hs
@@ -21,7 +21,6 @@ import qualified Annex
import Command
import qualified Annex.Url as Url
import Logs.Web
-import qualified Option
import qualified Utility.Format
import Utility.Tmp
import Command.AddUrl (addUrlFile, relaxedOption)
@@ -39,7 +38,7 @@ def = [notBareRepo $ withOptions [templateOption, relaxedOption] $
SectionCommon "import files from podcast feeds"]
templateOption :: Option
-templateOption = Option.field [] "template" paramFormat "template for filenames"
+templateOption = fieldOption [] "template" paramFormat "template for filenames"
seek :: CommandSeek
seek ps = do
diff --git a/Command/Info.hs b/Command/Info.hs
index c36ae8eed..d15fbba57 100644
--- a/Command/Info.hs
+++ b/Command/Info.hs
@@ -21,7 +21,6 @@ import qualified Remote
import qualified Command.Unused
import qualified Git
import qualified Annex
-import GitAnnex.Options
import Command
import Utility.DataUnits
import Utility.DiskFree
diff --git a/Command/List.hs b/Command/List.hs
index 763908116..ba6251333 100644
--- a/Command/List.hs
+++ b/Command/List.hs
@@ -20,7 +20,6 @@ import Remote
import Logs.Trust
import Logs.UUID
import Annex.UUID
-import qualified Option
import qualified Annex
import Git.Types (RemoteName)
@@ -29,7 +28,7 @@ def = [noCommit $ withOptions [allrepos] $ command "list" paramPaths seek
SectionQuery "show which remotes contain files"]
allrepos :: Option
-allrepos = Option.flag [] "allrepos" "show all repositories, not only remotes"
+allrepos = flagOption [] "allrepos" "show all repositories, not only remotes"
seek :: CommandSeek
seek ps = do
@@ -38,7 +37,7 @@ seek ps = do
withFilesInGit (whenAnnexed $ start list) ps
getList :: Annex [(UUID, RemoteName, TrustLevel)]
-getList = ifM (Annex.getFlag $ Option.name allrepos)
+getList = ifM (Annex.getFlag $ optionName allrepos)
( nubBy ((==) `on` fst3) <$> ((++) <$> getRemotes <*> getAll)
, getRemotes
)
diff --git a/Command/Log.hs b/Command/Log.hs
index b7ad664cf..1dd5aa51a 100644
--- a/Command/Log.hs
+++ b/Command/Log.hs
@@ -24,7 +24,6 @@ import qualified Annex.Branch
import qualified Git
import Git.Command
import qualified Remote
-import qualified Option
import qualified Annex
data RefChange = RefChange
@@ -44,14 +43,14 @@ options = passthruOptions ++ [gourceOption]
passthruOptions :: [Option]
passthruOptions = map odate ["since", "after", "until", "before"] ++
- [ Option.field ['n'] "max-count" paramNumber
+ [ fieldOption ['n'] "max-count" paramNumber
"limit number of logs displayed"
]
where
- odate n = Option.field [] n paramDate $ "show log " ++ n ++ " date"
+ odate n = fieldOption [] n paramDate $ "show log " ++ n ++ " date"
gourceOption :: Option
-gourceOption = Option.flag [] "gource" "format output for gource"
+gourceOption = flagOption [] "gource" "format output for gource"
seek :: CommandSeek
seek ps = do
@@ -62,8 +61,8 @@ seek ps = do
withFilesInGit (whenAnnexed $ start m zone os gource) ps
where
getoption o = maybe [] (use o) <$>
- Annex.getField (Option.name o)
- use o v = [Param ("--" ++ Option.name o), Param v]
+ Annex.getField (optionName o)
+ use o v = [Param ("--" ++ optionName o), Param v]
start :: M.Map UUID String -> TimeZone -> [CommandParam] -> Bool ->
FilePath -> (Key, Backend) -> CommandStart
diff --git a/Command/Mirror.hs b/Command/Mirror.hs
index 49208065b..4a7a8dd99 100644
--- a/Command/Mirror.hs
+++ b/Command/Mirror.hs
@@ -9,7 +9,6 @@ module Command.Mirror where
import Common.Annex
import Command
-import GitAnnex.Options
import qualified Command.Move
import qualified Command.Drop
import qualified Command.Get
diff --git a/Command/Move.hs b/Command/Move.hs
index 682fb5296..af3623da0 100644
--- a/Command/Move.hs
+++ b/Command/Move.hs
@@ -16,7 +16,6 @@ import qualified Remote
import Annex.UUID
import Logs.Presence
import Logs.Transfer
-import GitAnnex.Options
def :: [Command]
def = [withOptions moveOptions $ command "move" paramPaths seek
diff --git a/Command/Status.hs b/Command/Status.hs
index 462d68e05..cd6c25983 100644
--- a/Command/Status.hs
+++ b/Command/Status.hs
@@ -15,7 +15,6 @@ import Config
import qualified Git.LsFiles as LsFiles
import qualified Git.Ref
import qualified Git
-import GitAnnex.Options
def :: [Command]
def = [notBareRepo $ noCommit $ noMessages $ withOptions [jsonOption] $
diff --git a/Command/Sync.hs b/Command/Sync.hs
index 5763709ac..6ef111bc4 100644
--- a/Command/Sync.hs
+++ b/Command/Sync.hs
@@ -27,7 +27,6 @@ import qualified Git
import Git.Types (BlobType(..))
import qualified Types.Remote
import qualified Remote.Git
-import qualified Option
import Types.Key
import Config
import Annex.ReplaceFile
@@ -53,7 +52,7 @@ syncOptions :: [Option]
syncOptions = [ contentOption ]
contentOption :: Option
-contentOption = Option.flag [] "content" "also transfer file contents"
+contentOption = flagOption [] "content" "also transfer file contents"
seek :: CommandSeek
seek rs = do
@@ -85,7 +84,7 @@ seek rs = do
, map (withbranch . pullRemote) gitremotes
, [ mergeAnnex ]
]
- whenM (Annex.getFlag $ Option.name contentOption) $
+ whenM (Annex.getFlag $ optionName contentOption) $
seekSyncContent remotes
seekActions $ return $ concat
[ [ withbranch pushLocal ]
diff --git a/Command/TransferKey.hs b/Command/TransferKey.hs
index f3856eb2e..b6b237467 100644
--- a/Command/TransferKey.hs
+++ b/Command/TransferKey.hs
@@ -14,8 +14,6 @@ import Logs.Location
import Logs.Transfer
import qualified Remote
import Types.Remote
-import GitAnnex.Options
-import qualified Option
def :: [Command]
def = [withOptions transferKeyOptions $
@@ -26,7 +24,7 @@ transferKeyOptions :: [Option]
transferKeyOptions = fileOption : fromToOptions
fileOption :: Option
-fileOption = Option.field [] "file" paramFile "the associated file"
+fileOption = fieldOption [] "file" paramFile "the associated file"
seek :: CommandSeek
seek ps = do
diff --git a/Command/Unused.hs b/Command/Unused.hs
index 59c5ec1aa..312c26adf 100644
--- a/Command/Unused.hs
+++ b/Command/Unused.hs
@@ -33,17 +33,16 @@ import qualified Git.DiffTree as DiffTree
import qualified Backend
import qualified Remote
import qualified Annex.Branch
-import qualified Option
import Annex.CatFile
import Types.Key
import Git.FilePath
def :: [Command]
-def = [withOptions [fromOption] $ command "unused" paramNothing seek
+def = [withOptions [unusedFromOption] $ command "unused" paramNothing seek
SectionMaintenance "look for unused file content"]
-fromOption :: Option
-fromOption = Option.field ['f'] "from" paramRemote "remote to check for unused content"
+unusedFromOption :: Option
+unusedFromOption = fieldOption ['f'] "from" paramRemote "remote to check for unused content"
seek :: CommandSeek
seek = withNothing start
@@ -51,7 +50,7 @@ seek = withNothing start
{- Finds unused content in the annex. -}
start :: CommandStart
start = do
- from <- Annex.getField $ Option.name fromOption
+ from <- Annex.getField $ optionName unusedFromOption
let (name, action) = case from of
Nothing -> (".", checkUnused)
Just "." -> (".", checkUnused)
diff --git a/Command/Watch.hs b/Command/Watch.hs
index bcfdf14bf..79079337c 100644
--- a/Command/Watch.hs
+++ b/Command/Watch.hs
@@ -10,7 +10,6 @@ module Command.Watch where
import Common.Annex
import Assistant
import Command
-import Option
import Utility.HumanTime
def :: [Command]
@@ -24,10 +23,10 @@ seek ps = do
withNothing (start False foreground stopdaemon Nothing) ps
foregroundOption :: Option
-foregroundOption = Option.flag [] "foreground" "do not daemonize"
+foregroundOption = flagOption [] "foreground" "do not daemonize"
stopOption :: Option
-stopOption = Option.flag [] "stop" "stop daemon"
+stopOption = flagOption [] "stop" "stop daemon"
start :: Bool -> Bool -> Bool -> Maybe Duration -> CommandStart
start assistant foreground stopdaemon startdelay = do
diff --git a/Command/WebApp.hs b/Command/WebApp.hs
index a05984c4e..e433e50c6 100644
--- a/Command/WebApp.hs
+++ b/Command/WebApp.hs
@@ -29,7 +29,6 @@ import qualified Git.Config
import qualified Git.CurrentRepo
import qualified Annex
import Config.Files
-import qualified Option
import Upgrade
import Annex.Version
@@ -45,7 +44,7 @@ def = [ withOptions [listenOption] $
command "webapp" paramNothing seek SectionCommon "launch webapp"]
listenOption :: Option
-listenOption = Option.field [] "listen" paramAddress
+listenOption = fieldOption [] "listen" paramAddress
"accept connections to this address"
seek :: CommandSeek
diff --git a/Command/Whereis.hs b/Command/Whereis.hs
index 723509fb1..387ffebc9 100644
--- a/Command/Whereis.hs
+++ b/Command/Whereis.hs
@@ -13,7 +13,6 @@ import Common.Annex
import Command
import Remote
import Logs.Trust
-import GitAnnex.Options
def :: [Command]
def = [noCommit $ withOptions (jsonOption : keyOptions) $
diff --git a/Test.hs b/Test.hs
index a6cec1aca..3b196e8dd 100644
--- a/Test.hs
+++ b/Test.hs
@@ -66,7 +66,7 @@ import qualified Utility.Hash
import qualified Utility.Scheduled
import qualified Utility.HumanTime
#ifndef mingw32_HOST_OS
-import qualified GitAnnex
+import qualified CmdLine.GitAnnex as GitAnnex
import qualified Remote.Helper.Encryptable
import qualified Types.Crypto
import qualified Utility.Gpg
diff --git a/git-annex.hs b/git-annex.hs
index d5c7e4c9b..198a1f4e6 100644
--- a/git-annex.hs
+++ b/git-annex.hs
@@ -10,8 +10,8 @@
import System.Environment
import System.FilePath
-import qualified GitAnnex
-import qualified GitAnnexShell
+import qualified CmdLine.GitAnnex
+import qualified CmdLine.GitAnnexShell
#ifdef WITH_TESTSUITE
import qualified Test
#endif
@@ -20,8 +20,8 @@ main :: IO ()
main = run =<< getProgName
where
run n
- | isshell n = go GitAnnexShell.run
- | otherwise = go GitAnnex.run
+ | isshell n = go CmdLine.GitAnnexShell.run
+ | otherwise = go CmdLine.GitAnnex.run
isshell n = takeFileName n == "git-annex-shell"
go a = do
ps <- getArgs