reorganize some files and imports
This commit is contained in:
parent
3149a62a35
commit
86ffeb73d1
34 changed files with 92 additions and 120 deletions
|
@ -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
|
|
@ -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]
|
|
@ -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
|
|
@ -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
|
|
@ -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]
|
|
@ -5,7 +5,7 @@
|
|||
- Licensed under the GNU GPL version 3 or higher.
|
||||
-}
|
||||
|
||||
module Usage where
|
||||
module CmdLine.Usage where
|
||||
|
||||
import Common.Annex
|
||||
|
|
@ -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
|
||||
|
|
|
@ -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
|
||||
|
|
|
@ -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
|
||||
|
|
|
@ -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
|
||||
|
|
|
@ -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
|
||||
|
|
|
@ -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
|
||||
|
|
|
@ -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] $
|
||||
|
|
|
@ -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
|
||||
|
|
|
@ -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
|
||||
|
|
|
@ -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
|
||||
|
|
|
@ -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]
|
||||
|
|
|
@ -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
|
||||
|
|
|
@ -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
|
||||
|
|
|
@ -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
|
||||
|
|
|
@ -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
|
||||
|
|
|
@ -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
|
||||
)
|
||||
|
|
|
@ -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
|
||||
|
|
|
@ -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
|
||||
|
|
|
@ -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
|
||||
|
|
|
@ -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] $
|
||||
|
|
|
@ -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 ]
|
||||
|
|
|
@ -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
|
||||
|
|
|
@ -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)
|
||||
|
|
|
@ -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
|
||||
|
|
|
@ -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
|
||||
|
|
|
@ -13,7 +13,6 @@ import Common.Annex
|
|||
import Command
|
||||
import Remote
|
||||
import Logs.Trust
|
||||
import GitAnnex.Options
|
||||
|
||||
def :: [Command]
|
||||
def = [noCommit $ withOptions (jsonOption : keyOptions) $
|
||||
|
|
2
Test.hs
2
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
|
||||
|
|
|
@ -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
|
||||
|
|
Loading…
Reference in a new issue