reorganize some files and imports

This commit is contained in:
Joey Hess 2014-01-26 16:25:55 -04:00
parent 3149a62a35
commit 86ffeb73d1
34 changed files with 92 additions and 120 deletions

View file

@ -7,12 +7,11 @@
{-# LANGUAGE CPP, OverloadedStrings #-} {-# LANGUAGE CPP, OverloadedStrings #-}
module GitAnnex where module CmdLine.GitAnnex where
import qualified Git.CurrentRepo import qualified Git.CurrentRepo
import CmdLine import CmdLine
import Command import Command
import GitAnnex.Options
import qualified Command.Add import qualified Command.Add
import qualified Command.Unannex import qualified Command.Unannex
@ -180,4 +179,4 @@ run args = do
#ifdef WITH_EKG #ifdef WITH_EKG
_ <- forkServer "localhost" 4242 _ <- forkServer "localhost" 4242
#endif #endif
dispatch True args cmds options [] header Git.CurrentRepo.get dispatch True args cmds gitAnnexOptions [] header Git.CurrentRepo.get

View file

@ -5,14 +5,13 @@
- Licensed under the GNU GPL version 3 or higher. - Licensed under the GNU GPL version 3 or higher.
-} -}
module GitAnnex.Options where module CmdLine.GitAnnex.Options where
import System.Console.GetOpt import System.Console.GetOpt
import Common.Annex import Common.Annex
import qualified Git.Config import qualified Git.Config
import Git.Types import Git.Types
import Command
import Types.TrustLevel import Types.TrustLevel
import Types.NumCopies import Types.NumCopies
import Types.Messages import Types.Messages
@ -20,10 +19,11 @@ import qualified Annex
import qualified Remote import qualified Remote
import qualified Limit import qualified Limit
import qualified Limit.Wanted import qualified Limit.Wanted
import qualified Option import CmdLine.Option
import CmdLine.Usage
options :: [Option] gitAnnexOptions :: [Option]
options = Option.common ++ gitAnnexOptions = commonOptions ++
[ Option ['N'] ["numcopies"] (ReqArg setnumcopies paramNumber) [ Option ['N'] ["numcopies"] (ReqArg setnumcopies paramNumber)
"override default number of copies" "override default number of copies"
, Option [] ["trust"] (trustArg Trusted) , Option [] ["trust"] (trustArg Trusted)
@ -64,7 +64,7 @@ options = Option.common ++
"override default User-Agent" "override default User-Agent"
, Option [] ["trust-glacier"] (NoArg (Annex.setFlag "trustglacier")) , Option [] ["trust-glacier"] (NoArg (Annex.setFlag "trustglacier"))
"Trust Amazon Glacier inventory" "Trust Amazon Glacier inventory"
] ++ Option.matcher ] ++ matcherOptions
where where
trustArg t = ReqArg (Remote.forceTrust t) paramRemote trustArg t = ReqArg (Remote.forceTrust t) paramRemote
setnumcopies v = maybe noop setnumcopies v = maybe noop
@ -86,10 +86,10 @@ keyOptions =
] ]
fromOption :: Option fromOption :: Option
fromOption = Option.field ['f'] "from" paramRemote "source remote" fromOption = fieldOption ['f'] "from" paramRemote "source remote"
toOption :: Option toOption :: Option
toOption = Option.field ['t'] "to" paramRemote "destination remote" toOption = fieldOption ['t'] "to" paramRemote "destination remote"
fromToOptions :: [Option] fromToOptions :: [Option]
fromToOptions = [fromOption, toOption] fromToOptions = [fromOption, toOption]

View file

@ -5,7 +5,7 @@
- Licensed under the GNU GPL version 3 or higher. - Licensed under the GNU GPL version 3 or higher.
-} -}
module GitAnnexShell where module CmdLine.GitAnnexShell where
import System.Environment import System.Environment
import System.Console.GetOpt import System.Console.GetOpt
@ -16,7 +16,6 @@ import CmdLine
import Command import Command
import Annex.UUID import Annex.UUID
import Annex (setField) import Annex (setField)
import qualified Option
import Fields import Fields
import Utility.UserInfo import Utility.UserInfo
import Remote.GCrypt (getGCryptUUID) import Remote.GCrypt (getGCryptUUID)
@ -54,7 +53,7 @@ cmds = map adddirparam $ cmds_readonly ++ cmds_notreadonly
adddirparam c = c { cmdparamdesc = "DIRECTORY " ++ cmdparamdesc c } adddirparam c = c { cmdparamdesc = "DIRECTORY " ++ cmdparamdesc c }
options :: [OptDescr (Annex ())] options :: [OptDescr (Annex ())]
options = Option.common ++ options = commonOptions ++
[ Option [] ["uuid"] (ReqArg checkUUID paramUUID) "local repository uuid" [ Option [] ["uuid"] (ReqArg checkUUID paramUUID) "local repository uuid"
] ]
where where

View file

@ -5,12 +5,12 @@
- Licensed under the GNU GPL version 3 or higher. - Licensed under the GNU GPL version 3 or higher.
-} -}
module Option ( module CmdLine.Option (
common, commonOptions,
matcher, matcherOptions,
flag, flagOption,
field, fieldOption,
name, optionName,
ArgDescr(..), ArgDescr(..),
OptDescr(..), OptDescr(..),
) where ) where
@ -21,10 +21,10 @@ import Common.Annex
import qualified Annex import qualified Annex
import Types.Messages import Types.Messages
import Limit import Limit
import Usage import CmdLine.Usage
common :: [Option] commonOptions :: [Option]
common = commonOptions =
[ Option [] ["force"] (NoArg (setforce True)) [ Option [] ["force"] (NoArg (setforce True))
"allow actions that may lose annexed data" "allow actions that may lose annexed data"
, Option ['F'] ["fast"] (NoArg (setfast True)) , Option ['F'] ["fast"] (NoArg (setfast True))
@ -50,8 +50,8 @@ common =
setdebug = Annex.changeGitConfig $ \c -> c { annexDebug = True } setdebug = Annex.changeGitConfig $ \c -> c { annexDebug = True }
unsetdebug = Annex.changeGitConfig $ \c -> c { annexDebug = False } unsetdebug = Annex.changeGitConfig $ \c -> c { annexDebug = False }
matcher :: [Option] matcherOptions :: [Option]
matcher = matcherOptions =
[ longopt "not" "negate next option" [ longopt "not" "negate next option"
, longopt "and" "both previous and next option must match" , longopt "and" "both previous and next option must match"
, longopt "or" "either previous or 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 shortopt o = Option o [] $ NoArg $ addToken o
{- An option that sets a flag. -} {- An option that sets a flag. -}
flag :: String -> String -> String -> Option flagOption :: String -> String -> String -> Option
flag short opt description = flagOption short opt description =
Option short [opt] (NoArg (Annex.setFlag opt)) description Option short [opt] (NoArg (Annex.setFlag opt)) description
{- An option that sets a field. -} {- An option that sets a field. -}
field :: String -> String -> String -> String -> Option fieldOption :: String -> String -> String -> String -> Option
field short opt paramdesc description = fieldOption short opt paramdesc description =
Option short [opt] (ReqArg (Annex.setField opt) paramdesc) description Option short [opt] (ReqArg (Annex.setField opt) paramdesc) description
{- The flag or field name used for an option. -} {- The flag or field name used for an option. -}
name :: Option -> String optionName :: Option -> String
name (Option _ o _ _) = Prelude.head o optionName (Option _ o _ _) = Prelude.head o

View file

@ -9,7 +9,7 @@
- Licensed under the GNU GPL version 3 or higher. - Licensed under the GNU GPL version 3 or higher.
-} -}
module Seek where module CmdLine.Seek where
import System.PosixCompat.Files import System.PosixCompat.Files
@ -22,7 +22,7 @@ import qualified Git
import qualified Git.Command import qualified Git.Command
import qualified Git.LsFiles as LsFiles import qualified Git.LsFiles as LsFiles
import qualified Limit import qualified Limit
import qualified Option import CmdLine.Option
import Logs.Location import Logs.Location
import Logs.Unused import Logs.Unused
import Annex.CatFile import Annex.CatFile
@ -108,10 +108,10 @@ withKeys a params = seekActions $ return $ map (a . parse) params
- a conversion function. - a conversion function.
-} -}
getOptionField :: Option -> (Maybe String -> Annex a) -> Annex a 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 Bool
getOptionFlag option = Annex.getFlag (Option.name option) getOptionFlag option = Annex.getFlag (optionName option)
withNothing :: CommandStart -> CommandSeek withNothing :: CommandStart -> CommandSeek
withNothing a [] = seekActions $ return [a] withNothing a [] = seekActions $ return [a]

View file

@ -5,7 +5,7 @@
- Licensed under the GNU GPL version 3 or higher. - Licensed under the GNU GPL version 3 or higher.
-} -}
module Usage where module CmdLine.Usage where
import Common.Annex import Common.Annex

View file

@ -29,10 +29,12 @@ import qualified Annex
import qualified Git import qualified Git
import Types.Command as ReExported import Types.Command as ReExported
import Types.Option as ReExported import Types.Option as ReExported
import Seek as ReExported import CmdLine.Seek as ReExported
import Checks as ReExported import Checks as ReExported
import Usage as ReExported import CmdLine.Usage as ReExported
import RunCommand as ReExported import RunCommand as ReExported
import CmdLine.Option as ReExported
import CmdLine.GitAnnex.Options as ReExported
{- Generates a normal command -} {- Generates a normal command -}
command :: String -> String -> CommandSeek -> CommandSection -> String -> Command command :: String -> String -> CommandSeek -> CommandSection -> String -> Command

View file

@ -21,7 +21,6 @@ import qualified Annex.Url as Url
import qualified Backend.URL import qualified Backend.URL
import Annex.Content import Annex.Content
import Logs.Web import Logs.Web
import qualified Option
import Types.Key import Types.Key
import Types.KeySource import Types.KeySource
import Config import Config
@ -39,13 +38,13 @@ def = [notBareRepo $ withOptions [fileOption, pathdepthOption, relaxedOption] $
SectionCommon "add urls to annex"] SectionCommon "add urls to annex"]
fileOption :: Option 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
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
relaxedOption = Option.flag [] "relaxed" "skip size check" relaxedOption = flagOption [] "relaxed" "skip size check"
seek :: CommandSeek seek :: CommandSeek
seek ps = do seek ps = do

View file

@ -9,7 +9,6 @@ module Command.Assistant where
import Common.Annex import Common.Annex
import Command import Command
import qualified Option
import qualified Command.Watch import qualified Command.Watch
import Init import Init
import Config.Files import Config.Files
@ -32,10 +31,10 @@ options =
] ]
autoStartOption :: Option autoStartOption :: Option
autoStartOption = Option.flag [] "autostart" "start in known repositories" autoStartOption = flagOption [] "autostart" "start in known repositories"
startDelayOption :: Option startDelayOption :: Option
startDelayOption = Option.field [] "startdelay" paramNumber "delay before running startup scan" startDelayOption = fieldOption [] "startdelay" paramNumber "delay before running startup scan"
seek :: CommandSeek seek :: CommandSeek
seek ps = do seek ps = do

View file

@ -9,7 +9,6 @@ module Command.Copy where
import Common.Annex import Common.Annex
import Command import Command
import GitAnnex.Options
import qualified Command.Move import qualified Command.Move
import qualified Remote import qualified Remote
import Annex.Wanted import Annex.Wanted

View file

@ -16,19 +16,18 @@ import Logs.Location
import Logs.Trust import Logs.Trust
import Config.NumCopies import Config.NumCopies
import Annex.Content import Annex.Content
import qualified Option
import Annex.Wanted import Annex.Wanted
def :: [Command] def :: [Command]
def = [withOptions [fromOption] $ command "drop" paramPaths seek def = [withOptions [dropFromOption] $ command "drop" paramPaths seek
SectionCommon "indicate content of files not currently wanted"] SectionCommon "indicate content of files not currently wanted"]
fromOption :: Option dropFromOption :: Option
fromOption = Option.field ['f'] "from" paramRemote "drop content from a remote" dropFromOption = fieldOption ['f'] "from" paramRemote "drop content from a remote"
seek :: CommandSeek seek :: CommandSeek
seek ps = do seek ps = do
from <- getOptionField fromOption Remote.byNameWithUUID from <- getOptionField dropFromOption Remote.byNameWithUUID
withFilesInGit (whenAnnexed $ start from) ps withFilesInGit (whenAnnexed $ start from) ps
start :: Maybe Remote -> FilePath -> (Key, Backend) -> CommandStart start :: Maybe Remote -> FilePath -> (Key, Backend) -> CommandStart

View file

@ -13,12 +13,11 @@ import qualified Annex
import qualified Command.Drop import qualified Command.Drop
import qualified Remote import qualified Remote
import qualified Git import qualified Git
import qualified Option
import Command.Unused (withUnusedMaps, UnusedMaps(..), startUnused) import Command.Unused (withUnusedMaps, UnusedMaps(..), startUnused)
import Config.NumCopies import Config.NumCopies
def :: [Command] def :: [Command]
def = [withOptions [Command.Drop.fromOption] $ def = [withOptions [Command.Drop.dropFromOption] $
command "dropunused" (paramRepeating paramNumRange) command "dropunused" (paramRepeating paramNumRange)
seek SectionMaintenance "drop unused file content"] seek SectionMaintenance "drop unused file content"]
@ -37,7 +36,7 @@ perform numcopies key = maybe droplocal dropremote =<< Remote.byNameWithUUID =<<
showAction $ "from " ++ Remote.name r showAction $ "from " ++ Remote.name r
Command.Drop.performRemote key numcopies r Command.Drop.performRemote key numcopies r
droplocal = Command.Drop.performLocal key numcopies Nothing 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 :: (Key -> Git.Repo -> FilePath) -> Key -> CommandPerform
performOther filespec key = do performOther filespec key = do

View file

@ -12,7 +12,6 @@ import Command
import qualified Utility.Format import qualified Utility.Format
import Command.Find (formatOption, getFormat, showFormatted, keyVars) import Command.Find (formatOption, getFormat, showFormatted, keyVars)
import Types.Key import Types.Key
import GitAnnex.Options
def :: [Command] def :: [Command]
def = [noCommit $ noMessages $ withOptions [formatOption, jsonOption] $ def = [noCommit $ noMessages $ withOptions [formatOption, jsonOption] $

View file

@ -17,24 +17,22 @@ import qualified Annex
import qualified Utility.Format import qualified Utility.Format
import Utility.DataUnits import Utility.DataUnits
import Types.Key import Types.Key
import qualified Option
import GitAnnex.Options
def :: [Command] def :: [Command]
def = [noCommit $ noMessages $ withOptions [formatOption, print0Option, jsonOption] $ def = [noCommit $ noMessages $ withOptions [formatOption, print0Option, jsonOption] $
command "find" paramPaths seek SectionQuery "lists available files"] command "find" paramPaths seek SectionQuery "lists available files"]
formatOption :: Option 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 :: Annex (Maybe Utility.Format.Format)
getFormat = getOptionField formatOption $ return . fmap Utility.Format.gen getFormat = getOptionField formatOption $ return . fmap Utility.Format.gen
print0Option :: Option print0Option :: Option
print0Option = Option.Option [] ["print0"] (Option.NoArg set) print0Option = Option [] ["print0"] (NoArg set)
"terminate output with null" "terminate output with null"
where where
set = Annex.setField (Option.name formatOption) "${file}\0" set = Annex.setField (optionName formatOption) "${file}\0"
seek :: CommandSeek seek :: CommandSeek
seek ps = do seek ps = do

View file

@ -12,7 +12,6 @@ import Command
import qualified Annex.Branch as Branch import qualified Annex.Branch as Branch
import Logs.Transitions import Logs.Transitions
import qualified Annex import qualified Annex
import qualified Option
import Data.Time.Clock.POSIX import Data.Time.Clock.POSIX
@ -24,7 +23,7 @@ forgetOptions :: [Option]
forgetOptions = [dropDeadOption] forgetOptions = [dropDeadOption]
dropDeadOption :: Option dropDeadOption :: Option
dropDeadOption = Option.flag [] "drop-dead" "drop references to dead repositories" dropDeadOption = flagOption [] "drop-dead" "drop references to dead repositories"
seek :: CommandSeek seek :: CommandSeek
seek ps = do seek ps = do

View file

@ -30,11 +30,9 @@ import Annex.UUID
import Utility.DataUnits import Utility.DataUnits
import Utility.FileMode import Utility.FileMode
import Config import Config
import qualified Option
import Types.Key import Types.Key
import Utility.HumanTime import Utility.HumanTime
import Git.FilePath import Git.FilePath
import GitAnnex.Options hiding (fromOption)
#ifndef mingw32_HOST_OS #ifndef mingw32_HOST_OS
import System.Posix.Process (getProcessID) import System.Posix.Process (getProcessID)
@ -50,22 +48,22 @@ def :: [Command]
def = [withOptions fsckOptions $ command "fsck" paramPaths seek def = [withOptions fsckOptions $ command "fsck" paramPaths seek
SectionMaintenance "check for problems"] SectionMaintenance "check for problems"]
fromOption :: Option fsckFromOption :: Option
fromOption = Option.field ['f'] "from" paramRemote "check remote" fsckFromOption = fieldOption ['f'] "from" paramRemote "check remote"
startIncrementalOption :: Option startIncrementalOption :: Option
startIncrementalOption = Option.flag ['S'] "incremental" "start an incremental fsck" startIncrementalOption = flagOption ['S'] "incremental" "start an incremental fsck"
moreIncrementalOption :: Option moreIncrementalOption :: Option
moreIncrementalOption = Option.flag ['m'] "more" "continue an incremental fsck" moreIncrementalOption = flagOption ['m'] "more" "continue an incremental fsck"
incrementalScheduleOption :: Option incrementalScheduleOption :: Option
incrementalScheduleOption = Option.field [] "incremental-schedule" paramTime incrementalScheduleOption = fieldOption [] "incremental-schedule" paramTime
"schedule incremental fscking" "schedule incremental fscking"
fsckOptions :: [Option] fsckOptions :: [Option]
fsckOptions = fsckOptions =
[ fromOption [ fsckFromOption
, startIncrementalOption , startIncrementalOption
, moreIncrementalOption , moreIncrementalOption
, incrementalScheduleOption , incrementalScheduleOption
@ -73,7 +71,7 @@ fsckOptions =
seek :: CommandSeek seek :: CommandSeek
seek ps = do seek ps = do
from <- getOptionField fromOption Remote.byNameWithUUID from <- getOptionField fsckFromOption Remote.byNameWithUUID
i <- getIncremental i <- getIncremental
withKeyOptions withKeyOptions
(startKey i) (startKey i)
@ -83,9 +81,9 @@ seek ps = do
getIncremental :: Annex Incremental getIncremental :: Annex Incremental
getIncremental = do getIncremental = do
i <- maybe (return False) (checkschedule . parseDuration) i <- maybe (return False) (checkschedule . parseDuration)
=<< Annex.getField (Option.name incrementalScheduleOption) =<< Annex.getField (optionName incrementalScheduleOption)
starti <- Annex.getFlag (Option.name startIncrementalOption) starti <- Annex.getFlag (optionName startIncrementalOption)
morei <- Annex.getFlag (Option.name moreIncrementalOption) morei <- Annex.getFlag (optionName moreIncrementalOption)
case (i, starti, morei) of case (i, starti, morei) of
(False, False, False) -> return NonIncremental (False, False, False) -> return NonIncremental
(False, True, _) -> startIncremental (False, True, _) -> startIncremental

View file

@ -14,7 +14,6 @@ import Annex.Content
import Logs.Transfer import Logs.Transfer
import Config.NumCopies import Config.NumCopies
import Annex.Wanted import Annex.Wanted
import GitAnnex.Options
import qualified Command.Move import qualified Command.Move
def :: [Command] def :: [Command]

View file

@ -18,7 +18,6 @@ import qualified Command.Copy
import qualified Command.Sync import qualified Command.Sync
import qualified Command.Whereis import qualified Command.Whereis
import qualified Command.Fsck import qualified Command.Fsck
import GitAnnex.Options
import System.Console.GetOpt import System.Console.GetOpt
@ -42,7 +41,7 @@ start' ["options"] = showCommonOptions
start' _ = showGeneralHelp start' _ = showGeneralHelp
showCommonOptions :: IO () showCommonOptions :: IO ()
showCommonOptions = putStrLn $ usageInfo "Common options:" options showCommonOptions = putStrLn $ usageInfo "Common options:" gitAnnexOptions
showGeneralHelp :: IO () showGeneralHelp :: IO ()
showGeneralHelp = putStrLn $ unlines showGeneralHelp = putStrLn $ unlines

View file

@ -13,7 +13,6 @@ import Common.Annex
import Command import Command
import qualified Annex import qualified Annex
import qualified Command.Add import qualified Command.Add
import qualified Option
import Utility.CopyFile import Utility.CopyFile
import Backend import Backend
import Remote import Remote
@ -32,16 +31,16 @@ opts =
] ]
duplicateOption :: Option duplicateOption :: Option
duplicateOption = Option.flag [] "duplicate" "do not delete source files" duplicateOption = flagOption [] "duplicate" "do not delete source files"
deduplicateOption :: Option 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
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
skipDuplicatesOption = Option.flag [] "skip-duplicates" "import only new files" skipDuplicatesOption = flagOption [] "skip-duplicates" "import only new files"
data DuplicateMode = Default | Duplicate | DeDuplicate | CleanDuplicates | SkipDuplicates data DuplicateMode = Default | Duplicate | DeDuplicate | CleanDuplicates | SkipDuplicates
deriving (Eq) deriving (Eq)
@ -53,7 +52,7 @@ getDuplicateMode = gen
<*> getflag cleanDuplicatesOption <*> getflag cleanDuplicatesOption
<*> getflag skipDuplicatesOption <*> getflag skipDuplicatesOption
where where
getflag = Annex.getFlag . Option.name getflag = Annex.getFlag . optionName
gen False False False False = Default gen False False False False = Default
gen True False False False = Duplicate gen True False False False = Duplicate
gen False True False False = DeDuplicate gen False True False False = DeDuplicate

View file

@ -21,7 +21,6 @@ import qualified Annex
import Command import Command
import qualified Annex.Url as Url import qualified Annex.Url as Url
import Logs.Web import Logs.Web
import qualified Option
import qualified Utility.Format import qualified Utility.Format
import Utility.Tmp import Utility.Tmp
import Command.AddUrl (addUrlFile, relaxedOption) import Command.AddUrl (addUrlFile, relaxedOption)
@ -39,7 +38,7 @@ def = [notBareRepo $ withOptions [templateOption, relaxedOption] $
SectionCommon "import files from podcast feeds"] SectionCommon "import files from podcast feeds"]
templateOption :: Option templateOption :: Option
templateOption = Option.field [] "template" paramFormat "template for filenames" templateOption = fieldOption [] "template" paramFormat "template for filenames"
seek :: CommandSeek seek :: CommandSeek
seek ps = do seek ps = do

View file

@ -21,7 +21,6 @@ import qualified Remote
import qualified Command.Unused import qualified Command.Unused
import qualified Git import qualified Git
import qualified Annex import qualified Annex
import GitAnnex.Options
import Command import Command
import Utility.DataUnits import Utility.DataUnits
import Utility.DiskFree import Utility.DiskFree

View file

@ -20,7 +20,6 @@ import Remote
import Logs.Trust import Logs.Trust
import Logs.UUID import Logs.UUID
import Annex.UUID import Annex.UUID
import qualified Option
import qualified Annex import qualified Annex
import Git.Types (RemoteName) import Git.Types (RemoteName)
@ -29,7 +28,7 @@ def = [noCommit $ withOptions [allrepos] $ command "list" paramPaths seek
SectionQuery "show which remotes contain files"] SectionQuery "show which remotes contain files"]
allrepos :: Option allrepos :: Option
allrepos = Option.flag [] "allrepos" "show all repositories, not only remotes" allrepos = flagOption [] "allrepos" "show all repositories, not only remotes"
seek :: CommandSeek seek :: CommandSeek
seek ps = do seek ps = do
@ -38,7 +37,7 @@ seek ps = do
withFilesInGit (whenAnnexed $ start list) ps withFilesInGit (whenAnnexed $ start list) ps
getList :: Annex [(UUID, RemoteName, TrustLevel)] getList :: Annex [(UUID, RemoteName, TrustLevel)]
getList = ifM (Annex.getFlag $ Option.name allrepos) getList = ifM (Annex.getFlag $ optionName allrepos)
( nubBy ((==) `on` fst3) <$> ((++) <$> getRemotes <*> getAll) ( nubBy ((==) `on` fst3) <$> ((++) <$> getRemotes <*> getAll)
, getRemotes , getRemotes
) )

View file

@ -24,7 +24,6 @@ import qualified Annex.Branch
import qualified Git import qualified Git
import Git.Command import Git.Command
import qualified Remote import qualified Remote
import qualified Option
import qualified Annex import qualified Annex
data RefChange = RefChange data RefChange = RefChange
@ -44,14 +43,14 @@ options = passthruOptions ++ [gourceOption]
passthruOptions :: [Option] passthruOptions :: [Option]
passthruOptions = map odate ["since", "after", "until", "before"] ++ passthruOptions = map odate ["since", "after", "until", "before"] ++
[ Option.field ['n'] "max-count" paramNumber [ fieldOption ['n'] "max-count" paramNumber
"limit number of logs displayed" "limit number of logs displayed"
] ]
where where
odate n = Option.field [] n paramDate $ "show log " ++ n ++ " date" odate n = fieldOption [] n paramDate $ "show log " ++ n ++ " date"
gourceOption :: Option gourceOption :: Option
gourceOption = Option.flag [] "gource" "format output for gource" gourceOption = flagOption [] "gource" "format output for gource"
seek :: CommandSeek seek :: CommandSeek
seek ps = do seek ps = do
@ -62,8 +61,8 @@ seek ps = do
withFilesInGit (whenAnnexed $ start m zone os gource) ps withFilesInGit (whenAnnexed $ start m zone os gource) ps
where where
getoption o = maybe [] (use o) <$> getoption o = maybe [] (use o) <$>
Annex.getField (Option.name o) Annex.getField (optionName o)
use o v = [Param ("--" ++ Option.name o), Param v] use o v = [Param ("--" ++ optionName o), Param v]
start :: M.Map UUID String -> TimeZone -> [CommandParam] -> Bool -> start :: M.Map UUID String -> TimeZone -> [CommandParam] -> Bool ->
FilePath -> (Key, Backend) -> CommandStart FilePath -> (Key, Backend) -> CommandStart

View file

@ -9,7 +9,6 @@ module Command.Mirror where
import Common.Annex import Common.Annex
import Command import Command
import GitAnnex.Options
import qualified Command.Move import qualified Command.Move
import qualified Command.Drop import qualified Command.Drop
import qualified Command.Get import qualified Command.Get

View file

@ -16,7 +16,6 @@ import qualified Remote
import Annex.UUID import Annex.UUID
import Logs.Presence import Logs.Presence
import Logs.Transfer import Logs.Transfer
import GitAnnex.Options
def :: [Command] def :: [Command]
def = [withOptions moveOptions $ command "move" paramPaths seek def = [withOptions moveOptions $ command "move" paramPaths seek

View file

@ -15,7 +15,6 @@ import Config
import qualified Git.LsFiles as LsFiles import qualified Git.LsFiles as LsFiles
import qualified Git.Ref import qualified Git.Ref
import qualified Git import qualified Git
import GitAnnex.Options
def :: [Command] def :: [Command]
def = [notBareRepo $ noCommit $ noMessages $ withOptions [jsonOption] $ def = [notBareRepo $ noCommit $ noMessages $ withOptions [jsonOption] $

View file

@ -27,7 +27,6 @@ import qualified Git
import Git.Types (BlobType(..)) import Git.Types (BlobType(..))
import qualified Types.Remote import qualified Types.Remote
import qualified Remote.Git import qualified Remote.Git
import qualified Option
import Types.Key import Types.Key
import Config import Config
import Annex.ReplaceFile import Annex.ReplaceFile
@ -53,7 +52,7 @@ syncOptions :: [Option]
syncOptions = [ contentOption ] syncOptions = [ contentOption ]
contentOption :: Option contentOption :: Option
contentOption = Option.flag [] "content" "also transfer file contents" contentOption = flagOption [] "content" "also transfer file contents"
seek :: CommandSeek seek :: CommandSeek
seek rs = do seek rs = do
@ -85,7 +84,7 @@ seek rs = do
, map (withbranch . pullRemote) gitremotes , map (withbranch . pullRemote) gitremotes
, [ mergeAnnex ] , [ mergeAnnex ]
] ]
whenM (Annex.getFlag $ Option.name contentOption) $ whenM (Annex.getFlag $ optionName contentOption) $
seekSyncContent remotes seekSyncContent remotes
seekActions $ return $ concat seekActions $ return $ concat
[ [ withbranch pushLocal ] [ [ withbranch pushLocal ]

View file

@ -14,8 +14,6 @@ import Logs.Location
import Logs.Transfer import Logs.Transfer
import qualified Remote import qualified Remote
import Types.Remote import Types.Remote
import GitAnnex.Options
import qualified Option
def :: [Command] def :: [Command]
def = [withOptions transferKeyOptions $ def = [withOptions transferKeyOptions $
@ -26,7 +24,7 @@ transferKeyOptions :: [Option]
transferKeyOptions = fileOption : fromToOptions transferKeyOptions = fileOption : fromToOptions
fileOption :: Option fileOption :: Option
fileOption = Option.field [] "file" paramFile "the associated file" fileOption = fieldOption [] "file" paramFile "the associated file"
seek :: CommandSeek seek :: CommandSeek
seek ps = do seek ps = do

View file

@ -33,17 +33,16 @@ import qualified Git.DiffTree as DiffTree
import qualified Backend import qualified Backend
import qualified Remote import qualified Remote
import qualified Annex.Branch import qualified Annex.Branch
import qualified Option
import Annex.CatFile import Annex.CatFile
import Types.Key import Types.Key
import Git.FilePath import Git.FilePath
def :: [Command] def :: [Command]
def = [withOptions [fromOption] $ command "unused" paramNothing seek def = [withOptions [unusedFromOption] $ command "unused" paramNothing seek
SectionMaintenance "look for unused file content"] SectionMaintenance "look for unused file content"]
fromOption :: Option unusedFromOption :: Option
fromOption = Option.field ['f'] "from" paramRemote "remote to check for unused content" unusedFromOption = fieldOption ['f'] "from" paramRemote "remote to check for unused content"
seek :: CommandSeek seek :: CommandSeek
seek = withNothing start seek = withNothing start
@ -51,7 +50,7 @@ seek = withNothing start
{- Finds unused content in the annex. -} {- Finds unused content in the annex. -}
start :: CommandStart start :: CommandStart
start = do start = do
from <- Annex.getField $ Option.name fromOption from <- Annex.getField $ optionName unusedFromOption
let (name, action) = case from of let (name, action) = case from of
Nothing -> (".", checkUnused) Nothing -> (".", checkUnused)
Just "." -> (".", checkUnused) Just "." -> (".", checkUnused)

View file

@ -10,7 +10,6 @@ module Command.Watch where
import Common.Annex import Common.Annex
import Assistant import Assistant
import Command import Command
import Option
import Utility.HumanTime import Utility.HumanTime
def :: [Command] def :: [Command]
@ -24,10 +23,10 @@ seek ps = do
withNothing (start False foreground stopdaemon Nothing) ps withNothing (start False foreground stopdaemon Nothing) ps
foregroundOption :: Option foregroundOption :: Option
foregroundOption = Option.flag [] "foreground" "do not daemonize" foregroundOption = flagOption [] "foreground" "do not daemonize"
stopOption :: Option stopOption :: Option
stopOption = Option.flag [] "stop" "stop daemon" stopOption = flagOption [] "stop" "stop daemon"
start :: Bool -> Bool -> Bool -> Maybe Duration -> CommandStart start :: Bool -> Bool -> Bool -> Maybe Duration -> CommandStart
start assistant foreground stopdaemon startdelay = do start assistant foreground stopdaemon startdelay = do

View file

@ -29,7 +29,6 @@ import qualified Git.Config
import qualified Git.CurrentRepo import qualified Git.CurrentRepo
import qualified Annex import qualified Annex
import Config.Files import Config.Files
import qualified Option
import Upgrade import Upgrade
import Annex.Version import Annex.Version
@ -45,7 +44,7 @@ def = [ withOptions [listenOption] $
command "webapp" paramNothing seek SectionCommon "launch webapp"] command "webapp" paramNothing seek SectionCommon "launch webapp"]
listenOption :: Option listenOption :: Option
listenOption = Option.field [] "listen" paramAddress listenOption = fieldOption [] "listen" paramAddress
"accept connections to this address" "accept connections to this address"
seek :: CommandSeek seek :: CommandSeek

View file

@ -13,7 +13,6 @@ import Common.Annex
import Command import Command
import Remote import Remote
import Logs.Trust import Logs.Trust
import GitAnnex.Options
def :: [Command] def :: [Command]
def = [noCommit $ withOptions (jsonOption : keyOptions) $ def = [noCommit $ withOptions (jsonOption : keyOptions) $

View file

@ -66,7 +66,7 @@ import qualified Utility.Hash
import qualified Utility.Scheduled import qualified Utility.Scheduled
import qualified Utility.HumanTime import qualified Utility.HumanTime
#ifndef mingw32_HOST_OS #ifndef mingw32_HOST_OS
import qualified GitAnnex import qualified CmdLine.GitAnnex as GitAnnex
import qualified Remote.Helper.Encryptable import qualified Remote.Helper.Encryptable
import qualified Types.Crypto import qualified Types.Crypto
import qualified Utility.Gpg import qualified Utility.Gpg

View file

@ -10,8 +10,8 @@
import System.Environment import System.Environment
import System.FilePath import System.FilePath
import qualified GitAnnex import qualified CmdLine.GitAnnex
import qualified GitAnnexShell import qualified CmdLine.GitAnnexShell
#ifdef WITH_TESTSUITE #ifdef WITH_TESTSUITE
import qualified Test import qualified Test
#endif #endif
@ -20,8 +20,8 @@ main :: IO ()
main = run =<< getProgName main = run =<< getProgName
where where
run n run n
| isshell n = go GitAnnexShell.run | isshell n = go CmdLine.GitAnnexShell.run
| otherwise = go GitAnnex.run | otherwise = go CmdLine.GitAnnex.run
isshell n = takeFileName n == "git-annex-shell" isshell n = takeFileName n == "git-annex-shell"
go a = do go a = do
ps <- getArgs ps <- getArgs