generalize quiet flag to output type
This will allow adding other styles of output.
This commit is contained in:
parent
55783d886d
commit
57dd34c6be
5 changed files with 13 additions and 12 deletions
7
Annex.hs
7
Annex.hs
|
@ -10,6 +10,7 @@
|
|||
module Annex (
|
||||
Annex,
|
||||
AnnexState(..),
|
||||
OutputType(..),
|
||||
new,
|
||||
run,
|
||||
eval,
|
||||
|
@ -48,7 +49,7 @@ data AnnexState = AnnexState
|
|||
, backends :: [Backend Annex]
|
||||
, remotes :: [Remote Annex]
|
||||
, repoqueue :: Queue
|
||||
, quiet :: Bool
|
||||
, output :: OutputType
|
||||
, force :: Bool
|
||||
, fast :: Bool
|
||||
, branchstate :: BranchState
|
||||
|
@ -63,13 +64,15 @@ data AnnexState = AnnexState
|
|||
, cipher :: Maybe Cipher
|
||||
}
|
||||
|
||||
data OutputType = NormalOutput | QuietOutput
|
||||
|
||||
newState :: Git.Repo -> AnnexState
|
||||
newState gitrepo = AnnexState
|
||||
{ repo = gitrepo
|
||||
, backends = []
|
||||
, remotes = []
|
||||
, repoqueue = empty
|
||||
, quiet = False
|
||||
, output = NormalOutput
|
||||
, force = False
|
||||
, fast = False
|
||||
, branchstate = startBranchState
|
||||
|
|
|
@ -7,8 +7,6 @@
|
|||
|
||||
module Command.Init where
|
||||
|
||||
import Control.Monad
|
||||
|
||||
import Command
|
||||
import qualified Annex
|
||||
import UUID
|
||||
|
|
|
@ -23,11 +23,10 @@ module Content (
|
|||
saveState
|
||||
) where
|
||||
|
||||
import System.IO.Error (try)
|
||||
import System.Directory
|
||||
import Control.Monad.State (liftIO)
|
||||
import System.Path
|
||||
import Control.Monad (when, filterM)
|
||||
import Control.Monad
|
||||
import System.Posix.Files
|
||||
import System.FilePath
|
||||
import Data.Maybe
|
||||
|
|
|
@ -9,7 +9,6 @@ module Messages where
|
|||
|
||||
import Control.Monad.State (liftIO)
|
||||
import System.IO
|
||||
import Control.Monad (unless)
|
||||
import Data.String.Utils
|
||||
|
||||
import Types
|
||||
|
@ -17,8 +16,10 @@ import qualified Annex
|
|||
|
||||
verbose :: Annex () -> Annex ()
|
||||
verbose a = do
|
||||
q <- Annex.getState Annex.quiet
|
||||
unless q a
|
||||
output <- Annex.getState Annex.output
|
||||
case output of
|
||||
Annex.NormalOutput -> a
|
||||
_ -> return ()
|
||||
|
||||
showStart :: String -> String -> Annex ()
|
||||
showStart command file = verbose $ liftIO $ do
|
||||
|
|
|
@ -26,9 +26,9 @@ commonOptions =
|
|||
"allow actions that may lose annexed data"
|
||||
, Option ['F'] ["fast"] (NoArg (setfast True))
|
||||
"avoid slow operations"
|
||||
, Option ['q'] ["quiet"] (NoArg (setquiet True))
|
||||
, Option ['q'] ["quiet"] (NoArg (setoutput Annex.QuietOutput))
|
||||
"avoid verbose output"
|
||||
, Option ['v'] ["verbose"] (NoArg (setquiet False))
|
||||
, Option ['v'] ["verbose"] (NoArg (setoutput Annex.NormalOutput))
|
||||
"allow verbose output (default)"
|
||||
, Option ['d'] ["debug"] (NoArg (setdebug))
|
||||
"show debug messages"
|
||||
|
@ -38,7 +38,7 @@ commonOptions =
|
|||
where
|
||||
setforce v = Annex.changeState $ \s -> s { Annex.force = v }
|
||||
setfast v = Annex.changeState $ \s -> s { Annex.fast = v }
|
||||
setquiet v = Annex.changeState $ \s -> s { Annex.quiet = v }
|
||||
setoutput v = Annex.changeState $ \s -> s { Annex.output = v }
|
||||
setforcebackend v = Annex.changeState $ \s -> s { Annex.forcebackend = Just v }
|
||||
setdebug = liftIO $ updateGlobalLogger rootLoggerName $
|
||||
setLevel DEBUG
|
||||
|
|
Loading…
Reference in a new issue