{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE UndecidableInstances #-}
module Charon.Runner.Args
( getArgs,
Args (..),
TomlConfigPath (..),
)
where
import Charon.Backend.Data (Backend, parseBackend)
import Charon.Data.Index (Sort, readSort)
import Charon.Data.PathData.Formatting
( ColFormat (ColFormatFixed, ColFormatMax),
Coloring (ColoringDetect, ColoringOff, ColoringOn),
)
import Charon.Data.PathData.Formatting qualified as PathData
import Charon.Data.Paths (PathI (MkPathI), PathIndex (TrashHome))
import Charon.Data.UniqueSeqNE (UniqueSeqNE)
import Charon.Data.UniqueSeqNE qualified as UniqueSeqNE
import Charon.Prelude
import Charon.Runner.Command
( Command
( Convert,
Delete,
Empty,
List,
Merge,
Metadata,
PermDelete,
Restore
),
CommandP1,
)
import Charon.Runner.Command.List
( ListCmd (MkListCmd),
ListFormatPhase1 (MkListFormatPhase1),
ListFormatStyle,
parseListFormat,
)
import Charon.Runner.FileSizeMode (FileSizeMode, parseFileSizeMode)
import Charon.Utils qualified as Utils
import Control.Applicative qualified as A
import Data.List qualified as L
import Data.Version (Version (versionBranch))
import Effects.Optparse (osPath)
import Options.Applicative
( CommandFields,
InfoMod,
Mod,
OptionFields,
Parser,
ParserInfo
( ParserInfo,
infoFailureCode,
infoFooter,
infoFullDesc,
infoHeader,
infoParser,
infoPolicy,
infoProgDesc
),
(<**>),
)
import Options.Applicative qualified as OA
import Options.Applicative.Help.Chunk (Chunk (Chunk))
import Options.Applicative.Help.Chunk qualified as Chunk
import Options.Applicative.Help.Pretty qualified as Pretty
import Options.Applicative.Types (ArgPolicy (Intersperse))
import Paths_charon qualified as Paths
import Text.Read qualified as TR
data TomlConfigPath
=
TomlNone
|
TomlDefault
|
TomlPath OsPath
deriving stock
( TomlConfigPath -> TomlConfigPath -> Bool
(TomlConfigPath -> TomlConfigPath -> Bool)
-> (TomlConfigPath -> TomlConfigPath -> Bool) -> Eq TomlConfigPath
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TomlConfigPath -> TomlConfigPath -> Bool
== :: TomlConfigPath -> TomlConfigPath -> Bool
$c/= :: TomlConfigPath -> TomlConfigPath -> Bool
/= :: TomlConfigPath -> TomlConfigPath -> Bool
Eq,
Int -> TomlConfigPath -> ShowS
[TomlConfigPath] -> ShowS
TomlConfigPath -> String
(Int -> TomlConfigPath -> ShowS)
-> (TomlConfigPath -> String)
-> ([TomlConfigPath] -> ShowS)
-> Show TomlConfigPath
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TomlConfigPath -> ShowS
showsPrec :: Int -> TomlConfigPath -> ShowS
$cshow :: TomlConfigPath -> String
show :: TomlConfigPath -> String
$cshowList :: [TomlConfigPath] -> ShowS
showList :: [TomlConfigPath] -> ShowS
Show
)
data Args = MkArgs
{
Args -> TomlConfigPath
tomlConfigPath :: TomlConfigPath,
Args -> Maybe Backend
backend :: Maybe Backend,
Args -> Maybe (Maybe LogLevel)
logLevel :: !(Maybe (Maybe LogLevel)),
Args -> Maybe FileSizeMode
logSizeMode :: Maybe FileSizeMode,
Args -> Maybe (PathI 'TrashHome)
trashHome :: !(Maybe (PathI TrashHome)),
Args -> CommandP1
command :: CommandP1
}
deriving stock (Args -> Args -> Bool
(Args -> Args -> Bool) -> (Args -> Args -> Bool) -> Eq Args
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Args -> Args -> Bool
== :: Args -> Args -> Bool
$c/= :: Args -> Args -> Bool
/= :: Args -> Args -> Bool
Eq, (forall x. Args -> Rep Args x)
-> (forall x. Rep Args x -> Args) -> Generic Args
forall x. Rep Args x -> Args
forall x. Args -> Rep Args x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Args -> Rep Args x
from :: forall x. Args -> Rep Args x
$cto :: forall x. Rep Args x -> Args
to :: forall x. Rep Args x -> Args
Generic, Int -> Args -> ShowS
[Args] -> ShowS
Args -> String
(Int -> Args -> ShowS)
-> (Args -> String) -> ([Args] -> ShowS) -> Show Args
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Args -> ShowS
showsPrec :: Int -> Args -> ShowS
$cshow :: Args -> String
show :: Args -> String
$cshowList :: [Args] -> ShowS
showList :: [Args] -> ShowS
Show)
makeFieldLabelsNoPrefix ''Args
getArgs :: (MonadOptparse m) => m Args
getArgs :: forall (m :: * -> *). MonadOptparse m => m Args
getArgs = ParserInfo Args -> m Args
forall a. HasCallStack => ParserInfo a -> m a
forall (m :: * -> *) a.
(MonadOptparse m, HasCallStack) =>
ParserInfo a -> m a
execParser ParserInfo Args
parserInfoArgs
parserInfoArgs :: ParserInfo Args
parserInfoArgs :: ParserInfo Args
parserInfoArgs =
ParserInfo
{ infoParser :: Parser Args
infoParser = Parser Args
argsParser,
infoFullDesc :: Bool
infoFullDesc = Bool
True,
infoProgDesc :: Chunk Doc
infoProgDesc = Chunk Doc
desc,
infoHeader :: Chunk Doc
infoHeader = Maybe Doc -> Chunk Doc
forall a. Maybe a -> Chunk a
Chunk Maybe Doc
headerTxt,
infoFooter :: Chunk Doc
infoFooter = Maybe Doc -> Chunk Doc
forall a. Maybe a -> Chunk a
Chunk Maybe Doc
footerTxt,
infoFailureCode :: Int
infoFailureCode = Int
1,
infoPolicy :: ArgPolicy
infoPolicy = ArgPolicy
Intersperse
}
where
headerTxt :: Maybe Doc
headerTxt = Doc -> Maybe Doc
forall a. a -> Maybe a
Just Doc
"Charon: A tool for deleting files to a trash directory."
footerTxt :: Maybe Doc
footerTxt = Doc -> Maybe Doc
forall a. a -> Maybe a
Just (Doc -> Maybe Doc) -> Doc -> Maybe Doc
forall a b. (a -> b) -> a -> b
$ String -> Doc
forall a. IsString a => String -> a
fromString String
versNum
desc :: Chunk Doc
desc =
String -> Chunk Doc
Chunk.paragraph
(String -> Chunk Doc) -> String -> Chunk Doc
forall a b. (a -> b) -> a -> b
$ [String] -> String
forall a. Monoid a => [a] -> a
mconcat
[ String
"Charon moves files to a trash directory, so they can later be ",
String
"restored or permanently deleted. It is intended as a safer ",
String
"alternative to rm. See github.com/tbidne/charon#readme for ",
String
"full documentation."
]
argsParser :: Parser Args
argsParser :: Parser Args
argsParser =
TomlConfigPath
-> Maybe Backend
-> Maybe (Maybe LogLevel)
-> Maybe FileSizeMode
-> Maybe (PathI 'TrashHome)
-> CommandP1
-> Args
MkArgs
(TomlConfigPath
-> Maybe Backend
-> Maybe (Maybe LogLevel)
-> Maybe FileSizeMode
-> Maybe (PathI 'TrashHome)
-> CommandP1
-> Args)
-> Parser TomlConfigPath
-> Parser
(Maybe Backend
-> Maybe (Maybe LogLevel)
-> Maybe FileSizeMode
-> Maybe (PathI 'TrashHome)
-> CommandP1
-> Args)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser TomlConfigPath
configParser
Parser
(Maybe Backend
-> Maybe (Maybe LogLevel)
-> Maybe FileSizeMode
-> Maybe (PathI 'TrashHome)
-> CommandP1
-> Args)
-> Parser (Maybe Backend)
-> Parser
(Maybe (Maybe LogLevel)
-> Maybe FileSizeMode
-> Maybe (PathI 'TrashHome)
-> CommandP1
-> Args)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser (Maybe Backend)
backendParser
Parser
(Maybe (Maybe LogLevel)
-> Maybe FileSizeMode
-> Maybe (PathI 'TrashHome)
-> CommandP1
-> Args)
-> Parser (Maybe (Maybe LogLevel))
-> Parser
(Maybe FileSizeMode
-> Maybe (PathI 'TrashHome) -> CommandP1 -> Args)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser (Maybe (Maybe LogLevel))
logLevelParser
Parser
(Maybe FileSizeMode
-> Maybe (PathI 'TrashHome) -> CommandP1 -> Args)
-> Parser (Maybe FileSizeMode)
-> Parser (Maybe (PathI 'TrashHome) -> CommandP1 -> Args)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser (Maybe FileSizeMode)
logSizeModeParser
Parser (Maybe (PathI 'TrashHome) -> CommandP1 -> Args)
-> Parser (Maybe (PathI 'TrashHome)) -> Parser (CommandP1 -> Args)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser (Maybe (PathI 'TrashHome))
trashParser
Parser (CommandP1 -> Args)
-> Parser ((CommandP1 -> Args) -> CommandP1 -> Args)
-> Parser (CommandP1 -> Args)
forall (f :: * -> *) a b. Applicative f => f a -> f (a -> b) -> f b
<**> Parser ((CommandP1 -> Args) -> CommandP1 -> Args)
forall a. Parser (a -> a)
version
Parser (CommandP1 -> Args)
-> Parser ((CommandP1 -> Args) -> CommandP1 -> Args)
-> Parser (CommandP1 -> Args)
forall (f :: * -> *) a b. Applicative f => f a -> f (a -> b) -> f b
<**> Parser ((CommandP1 -> Args) -> CommandP1 -> Args)
forall a. Parser (a -> a)
OA.helper
Parser (CommandP1 -> Args) -> Parser CommandP1 -> Parser Args
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser CommandP1
commandParser
version :: Parser (a -> a)
version :: forall a. Parser (a -> a)
version = String -> Mod OptionFields (a -> a) -> Parser (a -> a)
forall a. String -> Mod OptionFields (a -> a) -> Parser (a -> a)
OA.infoOption String
versNum (String -> Mod OptionFields (a -> a)
forall (f :: * -> *) a. HasName f => String -> Mod f a
OA.long String
"version")
versNum :: String
versNum :: String
versNum = String
"Version: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
L.intercalate String
"." (Int -> String
forall a. Show a => a -> String
show (Int -> String) -> [Int] -> [String]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Version -> [Int]
versionBranch Version
Paths.version)
backendParser :: Parser (Maybe Backend)
backendParser :: Parser (Maybe Backend)
backendParser =
Parser Backend -> Parser (Maybe Backend)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
OA.optional
(Parser Backend -> Parser (Maybe Backend))
-> Parser Backend -> Parser (Maybe Backend)
forall a b. (a -> b) -> a -> b
$ ReadM Backend -> Mod OptionFields Backend -> Parser Backend
forall a. ReadM a -> Mod OptionFields a -> Parser a
OA.option (ReadM Text
forall s. IsString s => ReadM s
OA.str ReadM Text -> (Text -> ReadM Backend) -> ReadM Backend
forall a b. ReadM a -> (a -> ReadM b) -> ReadM b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> ReadM Backend
forall (m :: * -> *). MonadFail m => Text -> m Backend
parseBackend)
(Mod OptionFields Backend -> Parser Backend)
-> Mod OptionFields Backend -> Parser Backend
forall a b. (a -> b) -> a -> b
$ [Mod OptionFields Backend] -> Mod OptionFields Backend
forall a. Monoid a => [a] -> a
mconcat
[ String -> Mod OptionFields Backend
forall (f :: * -> *) a. HasName f => String -> Mod f a
OA.long String
"backend",
Char -> Mod OptionFields Backend
forall (f :: * -> *) a. HasName f => Char -> Mod f a
OA.short Char
'b',
String -> Mod OptionFields Backend
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OA.metavar String
"(cbor|fdo|json)",
Maybe Doc -> Mod OptionFields Backend
forall (f :: * -> *) a. Maybe Doc -> Mod f a
OA.helpDoc Maybe Doc
helpTxt
]
where
helpTxt :: Maybe Doc
helpTxt =
[Maybe Doc] -> Maybe Doc
forall a. Monoid a => [a] -> a
mconcat
[ Maybe Doc
intro,
Doc -> Maybe Doc
forall a. a -> Maybe a
Just Doc
Pretty.hardline,
Maybe Doc
cbor,
Maybe Doc
fdo,
Maybe Doc
js,
Doc -> Maybe Doc
forall a. a -> Maybe a
Just Doc
Pretty.hardline
]
intro :: Maybe Doc
intro =
String -> Maybe Doc
toMDoc String
"Backend to use with charon. This option affects how path metadata is stored. Options are: "
cbor :: Maybe Doc
cbor = Doc -> Maybe Doc
forall a. a -> Maybe a
Just Doc
Pretty.hardline Maybe Doc -> Maybe Doc -> Maybe Doc
forall a. Semigroup a => a -> a -> a
<> String -> Maybe Doc
toMDoc String
"- cbor: Space efficient, not inspectable."
fdo :: Maybe Doc
fdo = Doc -> Maybe Doc
forall a. a -> Maybe a
Just Doc
Pretty.hardline Maybe Doc -> Maybe Doc -> Maybe Doc
forall a. Semigroup a => a -> a -> a
<> String -> Maybe Doc
toMDoc String
"- fdo: Compatible with FreeDesktop.org."
js :: Maybe Doc
js = Doc -> Maybe Doc
forall a. a -> Maybe a
Just Doc
Pretty.hardline Maybe Doc -> Maybe Doc -> Maybe Doc
forall a. Semigroup a => a -> a -> a
<> String -> Maybe Doc
toMDoc String
"- json: Inspectable."
toMDoc :: String -> Maybe Doc
toMDoc = Chunk Doc -> Maybe Doc
forall a. Chunk a -> Maybe a
Chunk.unChunk (Chunk Doc -> Maybe Doc)
-> (String -> Chunk Doc) -> String -> Maybe Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Chunk Doc
Chunk.paragraph
backendDestParser :: Parser Backend
backendDestParser :: Parser Backend
backendDestParser =
ReadM Backend -> Mod OptionFields Backend -> Parser Backend
forall a. ReadM a -> Mod OptionFields a -> Parser a
OA.option (ReadM Text
forall s. IsString s => ReadM s
OA.str ReadM Text -> (Text -> ReadM Backend) -> ReadM Backend
forall a b. ReadM a -> (a -> ReadM b) -> ReadM b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> ReadM Backend
forall (m :: * -> *). MonadFail m => Text -> m Backend
parseBackend)
(Mod OptionFields Backend -> Parser Backend)
-> Mod OptionFields Backend -> Parser Backend
forall a b. (a -> b) -> a -> b
$ [Mod OptionFields Backend] -> Mod OptionFields Backend
forall a. Monoid a => [a] -> a
mconcat
[ String -> Mod OptionFields Backend
forall (f :: * -> *) a. HasName f => String -> Mod f a
OA.long String
"dest",
Char -> Mod OptionFields Backend
forall (f :: * -> *) a. HasName f => Char -> Mod f a
OA.short Char
'd',
String -> Mod OptionFields Backend
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OA.metavar String
"(cbor|fdo|json)",
String -> Mod OptionFields Backend
forall (f :: * -> *) a. String -> Mod f a
mkHelp String
helpTxt
]
where
helpTxt :: String
helpTxt =
[String] -> String
forall a. Monoid a => [a] -> a
mconcat
[ String
"Backend to which we convert the current backend. See --backend ",
String
"for more details."
]
configParser :: Parser TomlConfigPath
configParser :: Parser TomlConfigPath
configParser =
ReadM TomlConfigPath
-> Mod OptionFields TomlConfigPath -> Parser TomlConfigPath
forall a. ReadM a -> Mod OptionFields a -> Parser a
OA.option
ReadM TomlConfigPath
readTomlPath
(Mod OptionFields TomlConfigPath -> Parser TomlConfigPath)
-> Mod OptionFields TomlConfigPath -> Parser TomlConfigPath
forall a b. (a -> b) -> a -> b
$ [Mod OptionFields TomlConfigPath]
-> Mod OptionFields TomlConfigPath
forall a. Monoid a => [a] -> a
mconcat
[ TomlConfigPath -> Mod OptionFields TomlConfigPath
forall (f :: * -> *) a. HasValue f => a -> Mod f a
OA.value TomlConfigPath
TomlDefault,
String -> Mod OptionFields TomlConfigPath
forall (f :: * -> *) a. HasName f => String -> Mod f a
OA.long String
"config",
Char -> Mod OptionFields TomlConfigPath
forall (f :: * -> *) a. HasName f => Char -> Mod f a
OA.short Char
'c',
String -> Mod OptionFields TomlConfigPath
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OA.metavar String
"(none|PATH)",
String -> Mod OptionFields TomlConfigPath
forall (f :: * -> *) a. String -> Mod f a
mkHelp String
helpTxt
]
where
helpTxt :: String
helpTxt =
[String] -> String
forall a. Monoid a => [a] -> a
mconcat
[ String
"Path to the toml config file. Can be the string 'none' -- in which ",
String
"case no toml config is used -- or a path to the config file. If ",
String
"not specified then we look in the XDG config directory ",
String
"e.g. ~/.config/charon/config.toml"
]
readTomlPath :: ReadM TomlConfigPath
readTomlPath = do
OsPath
p <- ReadM OsPath
osPath
if OsPath
p OsPath -> OsPath -> Bool
forall a. Eq a => a -> a -> Bool
== [osp|none|]
then TomlConfigPath -> ReadM TomlConfigPath
forall a. a -> ReadM a
forall (f :: * -> *) a. Applicative f => a -> f a
pure TomlConfigPath
TomlNone
else TomlConfigPath -> ReadM TomlConfigPath
forall a. a -> ReadM a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (TomlConfigPath -> ReadM TomlConfigPath)
-> TomlConfigPath -> ReadM TomlConfigPath
forall a b. (a -> b) -> a -> b
$ OsPath -> TomlConfigPath
TomlPath OsPath
p
commandParser :: Parser CommandP1
commandParser :: Parser CommandP1
commandParser =
Mod CommandFields CommandP1 -> Parser CommandP1
forall a. Mod CommandFields a -> Parser a
OA.hsubparser
( [Mod CommandFields CommandP1] -> Mod CommandFields CommandP1
forall a. Monoid a => [a] -> a
mconcat
[ String
-> Parser CommandP1
-> InfoMod CommandP1
-> Mod CommandFields CommandP1
forall a. String -> Parser a -> InfoMod a -> Mod CommandFields a
mkCommand String
"delete" Parser CommandP1
forall {s :: Phase}. Parser (Command s)
delParser InfoMod CommandP1
forall {a}. InfoMod a
delTxt,
String
-> Parser CommandP1
-> InfoMod CommandP1
-> Mod CommandFields CommandP1
forall a. String -> Parser a -> InfoMod a -> Mod CommandFields a
mkCommand String
"d" Parser CommandP1
forall {s :: Phase}. Parser (Command s)
delParser (String -> InfoMod CommandP1
forall a. String -> InfoMod a
mkCmdDesc String
"Alias for delete."),
String
-> Parser CommandP1
-> InfoMod CommandP1
-> Mod CommandFields CommandP1
forall a. String -> Parser a -> InfoMod a -> Mod CommandFields a
mkCommand String
"perm-delete" Parser CommandP1
forall {s :: Phase}. Parser (Command s)
permDelParser InfoMod CommandP1
forall {a}. InfoMod a
permDelTxt,
String
-> Parser CommandP1
-> InfoMod CommandP1
-> Mod CommandFields CommandP1
forall a. String -> Parser a -> InfoMod a -> Mod CommandFields a
mkCommand String
"x" Parser CommandP1
forall {s :: Phase}. Parser (Command s)
permDelParser (String -> InfoMod CommandP1
forall a. String -> InfoMod a
mkCmdDesc String
"Alias for perm-delete."),
String
-> Parser CommandP1
-> InfoMod CommandP1
-> Mod CommandFields CommandP1
forall a. String -> Parser a -> InfoMod a -> Mod CommandFields a
mkCommand String
"empty" Parser CommandP1
forall {s :: Phase}. Parser (Command s)
emptyParser InfoMod CommandP1
forall {a}. InfoMod a
emptyTxt,
String
-> Parser CommandP1
-> InfoMod CommandP1
-> Mod CommandFields CommandP1
forall a. String -> Parser a -> InfoMod a -> Mod CommandFields a
mkCommand String
"e" Parser CommandP1
forall {s :: Phase}. Parser (Command s)
emptyParser (String -> InfoMod CommandP1
forall a. String -> InfoMod a
mkCmdDesc String
"Alias for empty."),
String -> Mod CommandFields CommandP1
forall a. String -> Mod CommandFields a
OA.commandGroup String
"Delete Commands"
]
)
Parser CommandP1 -> Parser CommandP1 -> Parser CommandP1
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Mod CommandFields CommandP1 -> Parser CommandP1
forall a. Mod CommandFields a -> Parser a
OA.hsubparser
( [Mod CommandFields CommandP1] -> Mod CommandFields CommandP1
forall a. Monoid a => [a] -> a
mconcat
[ String
-> Parser CommandP1
-> InfoMod CommandP1
-> Mod CommandFields CommandP1
forall a. String -> Parser a -> InfoMod a -> Mod CommandFields a
mkCommand String
"restore" Parser CommandP1
forall {s :: Phase}. Parser (Command s)
restoreParser InfoMod CommandP1
forall {a}. InfoMod a
restoreTxt,
String
-> Parser CommandP1
-> InfoMod CommandP1
-> Mod CommandFields CommandP1
forall a. String -> Parser a -> InfoMod a -> Mod CommandFields a
mkCommand String
"r" Parser CommandP1
forall {s :: Phase}. Parser (Command s)
restoreParser (String -> InfoMod CommandP1
forall a. String -> InfoMod a
mkCmdDesc String
"Alias for restore."),
String -> Mod CommandFields CommandP1
forall a. String -> Mod CommandFields a
OA.commandGroup String
"Restore Commands",
Mod CommandFields CommandP1
forall (f :: * -> *) a. Mod f a
OA.hidden
]
)
Parser CommandP1 -> Parser CommandP1 -> Parser CommandP1
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Mod CommandFields CommandP1 -> Parser CommandP1
forall a. Mod CommandFields a -> Parser a
OA.hsubparser
( [Mod CommandFields CommandP1] -> Mod CommandFields CommandP1
forall a. Monoid a => [a] -> a
mconcat
[ String
-> Parser CommandP1
-> InfoMod CommandP1
-> Mod CommandFields CommandP1
forall a. String -> Parser a -> InfoMod a -> Mod CommandFields a
mkCommand String
"list" Parser CommandP1
listParser InfoMod CommandP1
forall {a}. InfoMod a
listTxt,
String
-> Parser CommandP1
-> InfoMod CommandP1
-> Mod CommandFields CommandP1
forall a. String -> Parser a -> InfoMod a -> Mod CommandFields a
mkCommand String
"l" Parser CommandP1
listParser (String -> InfoMod CommandP1
forall a. String -> InfoMod a
mkCmdDesc String
"Alias for list."),
String
-> Parser CommandP1
-> InfoMod CommandP1
-> Mod CommandFields CommandP1
forall a. String -> Parser a -> InfoMod a -> Mod CommandFields a
mkCommand String
"metadata" Parser CommandP1
forall {s :: Phase}. Parser (Command s)
metadataParser InfoMod CommandP1
forall {a}. InfoMod a
metadataTxt,
String
-> Parser CommandP1
-> InfoMod CommandP1
-> Mod CommandFields CommandP1
forall a. String -> Parser a -> InfoMod a -> Mod CommandFields a
mkCommand String
"m" Parser CommandP1
forall {s :: Phase}. Parser (Command s)
metadataParser (String -> InfoMod CommandP1
forall a. String -> InfoMod a
mkCmdDesc String
"Alias for metadata."),
String -> Mod CommandFields CommandP1
forall a. String -> Mod CommandFields a
OA.commandGroup String
"Information Commands",
Mod CommandFields CommandP1
forall (f :: * -> *) a. Mod f a
OA.hidden
]
)
Parser CommandP1 -> Parser CommandP1 -> Parser CommandP1
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Mod CommandFields CommandP1 -> Parser CommandP1
forall a. Mod CommandFields a -> Parser a
OA.hsubparser
( [Mod CommandFields CommandP1] -> Mod CommandFields CommandP1
forall a. Monoid a => [a] -> a
mconcat
[ String
-> Parser CommandP1
-> InfoMod CommandP1
-> Mod CommandFields CommandP1
forall a. String -> Parser a -> InfoMod a -> Mod CommandFields a
mkCommand String
"convert" Parser CommandP1
forall {s :: Phase}. Parser (Command s)
convertParser InfoMod CommandP1
forall {a}. InfoMod a
convertTxt,
String
-> Parser CommandP1
-> InfoMod CommandP1
-> Mod CommandFields CommandP1
forall a. String -> Parser a -> InfoMod a -> Mod CommandFields a
mkCommand String
"merge" Parser CommandP1
forall {s :: Phase}. Parser (Command s)
mergeParser InfoMod CommandP1
forall {a}. InfoMod a
mergeTxt,
String -> Mod CommandFields CommandP1
forall a. String -> Mod CommandFields a
OA.commandGroup String
"Transform Commands",
Mod CommandFields CommandP1
forall (f :: * -> *) a. Mod f a
OA.hidden
]
)
where
delTxt :: InfoMod a
delTxt = String -> InfoMod a
forall a. String -> InfoMod a
mkCmdDesc String
"Moves the path(s) to the trash."
permDelTxt :: InfoMod a
permDelTxt =
String -> InfoMod a
forall a. String -> InfoMod a
mkCmdDesc
(String -> InfoMod a) -> String -> InfoMod a
forall a b. (a -> b) -> a -> b
$ [String] -> String
forall a. Monoid a => [a] -> a
mconcat
[ String
"Permanently deletes path(s) from the trash. Can use wildcards ",
String
"to match trash paths e.g. '*foo*bar' matches foobar, xxxfooyyybar, ",
String
"etc. To match a filename with a literal * not representing a ",
String
" wildcard -- e.g. '*foo' -- the * must be escaped (charon perm-delete '\\*foo')."
]
emptyTxt :: InfoMod a
emptyTxt = String -> InfoMod a
forall a. String -> InfoMod a
mkCmdDesc String
"Empties the trash."
restoreTxt :: InfoMod a
restoreTxt =
String -> InfoMod a
forall a. String -> InfoMod a
mkCmdDesc
(String -> InfoMod a) -> String -> InfoMod a
forall a b. (a -> b) -> a -> b
$ [String] -> String
forall a. Monoid a => [a] -> a
mconcat
[ String
"Restores the trash path(s) to their original location. Can use ",
String
"wildcards to match trash paths e.g. '*foo*bar' matches foobar, ",
String
"xxxfooyyybar, etc. To match a filename with a literal * not representing a ",
String
" wildcard -- e.g. '*foo' -- the * must be escaped (charon restore '\\*foo')."
]
listTxt :: InfoMod a
listTxt = String -> InfoMod a
forall a. String -> InfoMod a
mkCmdDesc String
"Lists all trash contents."
metadataTxt :: InfoMod a
metadataTxt = String -> InfoMod a
forall a. String -> InfoMod a
mkCmdDesc String
"Prints trash metadata."
convertTxt :: InfoMod a
convertTxt = String -> InfoMod a
forall a. String -> InfoMod a
mkCmdDesc String
"Converts the backend."
mergeTxt :: InfoMod a
mergeTxt = String -> InfoMod a
forall a. String -> InfoMod a
mkCmdDescNoLine String
"Merges src (implicit or -t) trash home into dest. Collisions will throw an error."
delParser :: Parser (Command s)
delParser = UniqueSeqNE (PathI 'TrashEntryOriginalPath) -> Command s
forall (s :: Phase).
UniqueSeqNE (PathI 'TrashEntryOriginalPath) -> Command s
Delete (UniqueSeqNE (PathI 'TrashEntryOriginalPath) -> Command s)
-> Parser (UniqueSeqNE (PathI 'TrashEntryOriginalPath))
-> Parser (Command s)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser (UniqueSeqNE (PathI 'TrashEntryOriginalPath))
forall (i :: PathIndex). Parser (UniqueSeqNE (PathI i))
pathsParser
permDelParser :: Parser (Command s)
permDelParser = Bool -> UniqueSeqNE (PathI 'TrashEntryFileName) -> Command s
forall (s :: Phase).
Bool -> UniqueSeqNE (PathI 'TrashEntryFileName) -> Command s
PermDelete (Bool -> UniqueSeqNE (PathI 'TrashEntryFileName) -> Command s)
-> Parser Bool
-> Parser (UniqueSeqNE (PathI 'TrashEntryFileName) -> Command s)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Bool
forceParser Parser (UniqueSeqNE (PathI 'TrashEntryFileName) -> Command s)
-> Parser (UniqueSeqNE (PathI 'TrashEntryFileName))
-> Parser (Command s)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser (UniqueSeqNE (PathI 'TrashEntryFileName))
forall (i :: PathIndex). Parser (UniqueSeqNE (PathI i))
pathsParser
emptyParser :: Parser (Command s)
emptyParser = Bool -> Command s
forall (s :: Phase). Bool -> Command s
Empty (Bool -> Command s) -> Parser Bool -> Parser (Command s)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Bool
forceParser
restoreParser :: Parser (Command s)
restoreParser = UniqueSeqNE (PathI 'TrashEntryFileName) -> Command s
forall (s :: Phase).
UniqueSeqNE (PathI 'TrashEntryFileName) -> Command s
Restore (UniqueSeqNE (PathI 'TrashEntryFileName) -> Command s)
-> Parser (UniqueSeqNE (PathI 'TrashEntryFileName))
-> Parser (Command s)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser (UniqueSeqNE (PathI 'TrashEntryFileName))
forall (i :: PathIndex). Parser (UniqueSeqNE (PathI i))
pathsParser
listParser :: Parser CommandP1
listParser =
(ListCmd 'Phase1 -> CommandP1)
-> Parser (ListCmd 'Phase1) -> Parser CommandP1
forall a b. (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ListCmd 'Phase1 -> CommandP1
forall (s :: Phase). ListCmd s -> Command s
List
(Parser (ListCmd 'Phase1) -> Parser CommandP1)
-> Parser (ListCmd 'Phase1) -> Parser CommandP1
forall a b. (a -> b) -> a -> b
$ ListFormatPhase1 -> Maybe Sort -> Maybe Bool -> ListCmd 'Phase1
ListFormatPhaseF 'Phase1
-> MaybePhaseF 'Phase1 Sort
-> MaybePhaseF 'Phase1 Bool
-> ListCmd 'Phase1
forall (p :: Phase).
ListFormatPhaseF p
-> MaybePhaseF p Sort -> MaybePhaseF p Bool -> ListCmd p
MkListCmd
(ListFormatPhase1 -> Maybe Sort -> Maybe Bool -> ListCmd 'Phase1)
-> Parser ListFormatPhase1
-> Parser (Maybe Sort -> Maybe Bool -> ListCmd 'Phase1)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ( Maybe Coloring
-> Maybe ListFormatStyle
-> Maybe ColFormat
-> Maybe ColFormat
-> ListFormatPhase1
MkListFormatPhase1
(Maybe Coloring
-> Maybe ListFormatStyle
-> Maybe ColFormat
-> Maybe ColFormat
-> ListFormatPhase1)
-> Parser (Maybe Coloring)
-> Parser
(Maybe ListFormatStyle
-> Maybe ColFormat -> Maybe ColFormat -> ListFormatPhase1)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser (Maybe Coloring)
coloringParser
Parser
(Maybe ListFormatStyle
-> Maybe ColFormat -> Maybe ColFormat -> ListFormatPhase1)
-> Parser (Maybe ListFormatStyle)
-> Parser (Maybe ColFormat -> Maybe ColFormat -> ListFormatPhase1)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser (Maybe ListFormatStyle)
listFormatStyleParser
Parser (Maybe ColFormat -> Maybe ColFormat -> ListFormatPhase1)
-> Parser (Maybe ColFormat)
-> Parser (Maybe ColFormat -> ListFormatPhase1)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser (Maybe ColFormat)
nameTruncParser
Parser (Maybe ColFormat -> ListFormatPhase1)
-> Parser (Maybe ColFormat) -> Parser ListFormatPhase1
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser (Maybe ColFormat)
origTruncParser
)
Parser (Maybe Sort -> Maybe Bool -> ListCmd 'Phase1)
-> Parser (Maybe Sort) -> Parser (Maybe Bool -> ListCmd 'Phase1)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser (Maybe Sort)
sortParser
Parser (Maybe Bool -> ListCmd 'Phase1)
-> Parser (Maybe Bool) -> Parser (ListCmd 'Phase1)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser (Maybe Bool)
reverseSortParser
metadataParser :: Parser (Command s)
metadataParser = Command s -> Parser (Command s)
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Command s
forall (s :: Phase). Command s
Metadata
convertParser :: Parser (Command s)
convertParser = Backend -> Command s
forall (s :: Phase). Backend -> Command s
Convert (Backend -> Command s) -> Parser Backend -> Parser (Command s)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Backend
backendDestParser
mergeParser :: Parser (Command s)
mergeParser = PathI 'TrashHome -> Command s
forall (s :: Phase). PathI 'TrashHome -> Command s
Merge (PathI 'TrashHome -> Command s)
-> Parser (PathI 'TrashHome) -> Parser (Command s)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser (PathI 'TrashHome)
trashDestParser
listFormatStyleParser :: Parser (Maybe ListFormatStyle)
listFormatStyleParser :: Parser (Maybe ListFormatStyle)
listFormatStyleParser =
Parser ListFormatStyle -> Parser (Maybe ListFormatStyle)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
A.optional
(Parser ListFormatStyle -> Parser (Maybe ListFormatStyle))
-> Parser ListFormatStyle -> Parser (Maybe ListFormatStyle)
forall a b. (a -> b) -> a -> b
$ ReadM ListFormatStyle
-> Mod OptionFields ListFormatStyle -> Parser ListFormatStyle
forall a. ReadM a -> Mod OptionFields a -> Parser a
OA.option (ReadM Text
forall s. IsString s => ReadM s
OA.str ReadM Text
-> (Text -> ReadM ListFormatStyle) -> ReadM ListFormatStyle
forall a b. ReadM a -> (a -> ReadM b) -> ReadM b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> ReadM ListFormatStyle
forall (m :: * -> *). MonadFail m => Text -> m ListFormatStyle
parseListFormat)
(Mod OptionFields ListFormatStyle -> Parser ListFormatStyle)
-> Mod OptionFields ListFormatStyle -> Parser ListFormatStyle
forall a b. (a -> b) -> a -> b
$ [Mod OptionFields ListFormatStyle]
-> Mod OptionFields ListFormatStyle
forall a. Monoid a => [a] -> a
mconcat
[ String -> Mod OptionFields ListFormatStyle
forall (f :: * -> *) a. HasName f => String -> Mod f a
OA.long String
"format",
String -> Mod OptionFields ListFormatStyle
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OA.metavar String
"(m[ulti] | s[ingle] | t[abular])",
Maybe Doc -> Mod OptionFields ListFormatStyle
forall (f :: * -> *) a. Maybe Doc -> Mod f a
OA.helpDoc Maybe Doc
helpTxt
]
where
helpTxt :: Maybe Doc
helpTxt =
[Maybe Doc] -> Maybe Doc
forall a. Monoid a => [a] -> a
mconcat
[ Maybe Doc
intro,
Doc -> Maybe Doc
forall a. a -> Maybe a
Just Doc
Pretty.hardline,
Maybe Doc
multi,
Doc -> Maybe Doc
forall a. a -> Maybe a
Just Doc
Pretty.hardline,
Maybe Doc
single,
Doc -> Maybe Doc
forall a. a -> Maybe a
Just Doc
Pretty.hardline,
Maybe Doc
tabular,
Doc -> Maybe Doc
forall a. a -> Maybe a
Just Doc
Pretty.hardline
]
intro :: Maybe Doc
intro = String -> Maybe Doc
toMDoc String
"Formatting options."
tabular :: Maybe Doc
tabular = Doc -> Maybe Doc
forall a. a -> Maybe a
Just Doc
Pretty.hardline Maybe Doc -> Maybe Doc -> Maybe Doc
forall a. Semigroup a => a -> a -> a
<> String -> Maybe Doc
toMDoc String
"- tabular: The default. Prints a table that tries to intelligently size the table based on available terminal width and filename / original path lengths."
multi :: Maybe Doc
multi = Doc -> Maybe Doc
forall a. a -> Maybe a
Just Doc
Pretty.hardline Maybe Doc -> Maybe Doc -> Maybe Doc
forall a. Semigroup a => a -> a -> a
<> String -> Maybe Doc
toMDoc String
"- multi: Prints each entry across multiple lines."
single :: Maybe Doc
single = Doc -> Maybe Doc
forall a. a -> Maybe a
Just Doc
Pretty.hardline Maybe Doc -> Maybe Doc -> Maybe Doc
forall a. Semigroup a => a -> a -> a
<> String -> Maybe Doc
toMDoc String
"- single: Compact, prints each entry across a single lines"
toMDoc :: String -> Maybe Doc
toMDoc = Chunk Doc -> Maybe Doc
forall a. Chunk a -> Maybe a
Chunk.unChunk (Chunk Doc -> Maybe Doc)
-> (String -> Chunk Doc) -> String -> Maybe Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Chunk Doc
Chunk.paragraph
nameTruncParser :: Parser (Maybe ColFormat)
nameTruncParser :: Parser (Maybe ColFormat)
nameTruncParser = Natural -> Mod OptionFields ColFormat -> Parser (Maybe ColFormat)
colParser Natural
PathData.formatFileNameLenMin Mod OptionFields ColFormat
forall {a}. Mod OptionFields a
fields
where
fields :: Mod OptionFields a
fields =
[Mod OptionFields a] -> Mod OptionFields a
forall a. Monoid a => [a] -> a
mconcat
[ String -> Mod OptionFields a
forall (f :: * -> *) a. HasName f => String -> Mod f a
OA.long String
"name-len",
Char -> Mod OptionFields a
forall (f :: * -> *) a. HasName f => Char -> Mod f a
OA.short Char
'n',
String -> Mod OptionFields a
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OA.metavar String
"(max|NAT)",
String -> Mod OptionFields a
forall (f :: * -> *) a. String -> Mod f a
mkHelp
(String -> Mod OptionFields a) -> String -> Mod OptionFields a
forall a b. (a -> b) -> a -> b
$ [String] -> String
forall a. Monoid a => [a] -> a
mconcat
[ String
"Sets the file name column length to either NAT characters or ",
String
"longest file-name. Only affects the 'tabular' format."
]
]
origTruncParser :: Parser (Maybe ColFormat)
origTruncParser :: Parser (Maybe ColFormat)
origTruncParser = Natural -> Mod OptionFields ColFormat -> Parser (Maybe ColFormat)
colParser Natural
PathData.formatOriginalPathLenMin Mod OptionFields ColFormat
forall {a}. Mod OptionFields a
fields
where
fields :: Mod OptionFields a
fields =
[Mod OptionFields a] -> Mod OptionFields a
forall a. Monoid a => [a] -> a
mconcat
[ String -> Mod OptionFields a
forall (f :: * -> *) a. HasName f => String -> Mod f a
OA.long String
"orig-len",
Char -> Mod OptionFields a
forall (f :: * -> *) a. HasName f => Char -> Mod f a
OA.short Char
'o',
String -> Mod OptionFields a
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OA.metavar String
"(max|NAT)",
String -> Mod OptionFields a
forall (f :: * -> *) a. String -> Mod f a
mkHelp
(String -> Mod OptionFields a) -> String -> Mod OptionFields a
forall a b. (a -> b) -> a -> b
$ [String] -> String
forall a. Monoid a => [a] -> a
mconcat
[ String
"Sets the original-path column length to either NAT characters or ",
String
"longest path. Only affects the 'tabular' format."
]
]
colParser :: Natural -> Mod OptionFields ColFormat -> Parser (Maybe ColFormat)
colParser :: Natural -> Mod OptionFields ColFormat -> Parser (Maybe ColFormat)
colParser Natural
minLen = Parser ColFormat -> Parser (Maybe ColFormat)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
A.optional (Parser ColFormat -> Parser (Maybe ColFormat))
-> (Mod OptionFields ColFormat -> Parser ColFormat)
-> Mod OptionFields ColFormat
-> Parser (Maybe ColFormat)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ReadM ColFormat -> Mod OptionFields ColFormat -> Parser ColFormat
forall a. ReadM a -> Mod OptionFields a -> Parser a
OA.option ReadM ColFormat
readCol
where
readCol :: ReadM ColFormat
readCol =
ReadM String
forall s. IsString s => ReadM s
OA.str ReadM String -> (String -> ReadM ColFormat) -> ReadM ColFormat
forall a b. ReadM a -> (a -> ReadM b) -> ReadM b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
String
"max" -> ColFormat -> ReadM ColFormat
forall a. a -> ReadM a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ColFormat
ColFormatMax
String
other -> case String -> Maybe Natural
forall a. Read a => String -> Maybe a
TR.readMaybe String
other of
Just Natural
n -> ColFormat -> ReadM ColFormat
forall a. a -> ReadM a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ColFormat -> ReadM ColFormat) -> ColFormat -> ReadM ColFormat
forall a b. (a -> b) -> a -> b
$ Natural -> ColFormat
ColFormatFixed Natural
n
Maybe Natural
Nothing ->
String -> ReadM ColFormat
forall a. String -> ReadM a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail
(String -> ReadM ColFormat) -> String -> ReadM ColFormat
forall a b. (a -> b) -> a -> b
$ [String] -> String
forall a. Monoid a => [a] -> a
mconcat
[ String
"Unrecognized col-format. Should either be 'max' or a positive ",
String
"integer < ",
Natural -> String
forall a. Show a => a -> String
show Natural
minLen,
String
". Received: ",
String
other
]
coloringParser :: Parser (Maybe Coloring)
coloringParser :: Parser (Maybe Coloring)
coloringParser =
Parser Coloring -> Parser (Maybe Coloring)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
A.optional
(Parser Coloring -> Parser (Maybe Coloring))
-> Parser Coloring -> Parser (Maybe Coloring)
forall a b. (a -> b) -> a -> b
$ ReadM Coloring -> Mod OptionFields Coloring -> Parser Coloring
forall a. ReadM a -> Mod OptionFields a -> Parser a
OA.option ReadM Coloring
readColoring
(Mod OptionFields Coloring -> Parser Coloring)
-> Mod OptionFields Coloring -> Parser Coloring
forall a b. (a -> b) -> a -> b
$ [Mod OptionFields Coloring] -> Mod OptionFields Coloring
forall a. Monoid a => [a] -> a
mconcat
[ String -> Mod OptionFields Coloring
forall (f :: * -> *) a. HasName f => String -> Mod f a
OA.long String
"color",
String -> Mod OptionFields Coloring
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OA.metavar String
"(t[rue] | f[alse] | d[etect])",
String -> Mod OptionFields Coloring
forall (f :: * -> *) a. String -> Mod f a
mkHelp
(String -> Mod OptionFields Coloring)
-> String -> Mod OptionFields Coloring
forall a b. (a -> b) -> a -> b
$ [String] -> String
forall a. Monoid a => [a] -> a
mconcat
[ String
"Determines if we should color output. Multiline is unaffected."
]
]
where
readColoring :: ReadM Coloring
readColoring =
ReadM String
forall s. IsString s => ReadM s
OA.str ReadM String -> (String -> ReadM Coloring) -> ReadM Coloring
forall a b. ReadM a -> (a -> ReadM b) -> ReadM b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
String
"t" -> Coloring -> ReadM Coloring
forall a. a -> ReadM a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Coloring
ColoringOn
String
"true" -> Coloring -> ReadM Coloring
forall a. a -> ReadM a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Coloring
ColoringOn
String
"f" -> Coloring -> ReadM Coloring
forall a. a -> ReadM a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Coloring
ColoringOff
String
"false" -> Coloring -> ReadM Coloring
forall a. a -> ReadM a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Coloring
ColoringOff
String
"d" -> Coloring -> ReadM Coloring
forall a. a -> ReadM a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Coloring
ColoringDetect
String
"detect" -> Coloring -> ReadM Coloring
forall a. a -> ReadM a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Coloring
ColoringDetect
String
bad -> String -> ReadM Coloring
forall a. String -> ReadM a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> ReadM Coloring) -> String -> ReadM Coloring
forall a b. (a -> b) -> a -> b
$ String
"Unexpected --coloring: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
bad
sortParser :: Parser (Maybe Sort)
sortParser :: Parser (Maybe Sort)
sortParser =
Parser Sort -> Parser (Maybe Sort)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
A.optional
(Parser Sort -> Parser (Maybe Sort))
-> Parser Sort -> Parser (Maybe Sort)
forall a b. (a -> b) -> a -> b
$ ReadM Sort -> Mod OptionFields Sort -> Parser Sort
forall a. ReadM a -> Mod OptionFields a -> Parser a
OA.option
(ReadM Text
forall s. IsString s => ReadM s
OA.str ReadM Text -> (Text -> ReadM Sort) -> ReadM Sort
forall a b. ReadM a -> (a -> ReadM b) -> ReadM b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> ReadM Sort
forall (m :: * -> *). MonadFail m => Text -> m Sort
readSort)
(Mod OptionFields Sort -> Parser Sort)
-> Mod OptionFields Sort -> Parser Sort
forall a b. (a -> b) -> a -> b
$ [Mod OptionFields Sort] -> Mod OptionFields Sort
forall a. Monoid a => [a] -> a
mconcat
[ String -> Mod OptionFields Sort
forall (f :: * -> *) a. HasName f => String -> Mod f a
OA.long String
"sort",
Char -> Mod OptionFields Sort
forall (f :: * -> *) a. HasName f => Char -> Mod f a
OA.short Char
's',
String -> Mod OptionFields Sort
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OA.metavar String
"(name|size)",
String -> Mod OptionFields Sort
forall (f :: * -> *) a. String -> Mod f a
mkHelp String
"How to sort the list. Defaults to name. Does not affect 'single' style."
]
reverseSortParser :: Parser (Maybe Bool)
reverseSortParser :: Parser (Maybe Bool)
reverseSortParser =
Parser Bool -> Parser (Maybe Bool)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
A.optional
(Parser Bool -> Parser (Maybe Bool))
-> Parser Bool -> Parser (Maybe Bool)
forall a b. (a -> b) -> a -> b
$ Bool -> Mod FlagFields Bool -> Parser Bool
forall a. a -> Mod FlagFields a -> Parser a
OA.flag' Bool
True
(Mod FlagFields Bool -> Parser Bool)
-> Mod FlagFields Bool -> Parser Bool
forall a b. (a -> b) -> a -> b
$ [Mod FlagFields Bool] -> Mod FlagFields Bool
forall a. Monoid a => [a] -> a
mconcat
[ String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
OA.long String
"reverse-sort",
Char -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => Char -> Mod f a
OA.short Char
'r',
String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
mkHelp String
helpTxt
]
where
helpTxt :: String
helpTxt = String
"Sorts in the reverse order. Does not affect 'single' style."
forceParser :: Parser Bool
forceParser :: Parser Bool
forceParser =
Mod FlagFields Bool -> Parser Bool
OA.switch
(Mod FlagFields Bool -> Parser Bool)
-> Mod FlagFields Bool -> Parser Bool
forall a b. (a -> b) -> a -> b
$ [Mod FlagFields Bool] -> Mod FlagFields Bool
forall a. Monoid a => [a] -> a
mconcat
[ String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
OA.long String
"force",
Char -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => Char -> Mod f a
OA.short Char
'f',
String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
mkHelp String
helpTxt
]
where
helpTxt :: String
helpTxt = String
"If enabled, will not ask before deleting path(s)."
trashParser :: Parser (Maybe (PathI TrashHome))
trashParser :: Parser (Maybe (PathI 'TrashHome))
trashParser =
Parser (PathI 'TrashHome) -> Parser (Maybe (PathI 'TrashHome))
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
A.optional
(Parser (PathI 'TrashHome) -> Parser (Maybe (PathI 'TrashHome)))
-> Parser (PathI 'TrashHome) -> Parser (Maybe (PathI 'TrashHome))
forall a b. (a -> b) -> a -> b
$ ReadM (PathI 'TrashHome)
-> Mod OptionFields (PathI 'TrashHome) -> Parser (PathI 'TrashHome)
forall a. ReadM a -> Mod OptionFields a -> Parser a
OA.option
((OsPath -> PathI 'TrashHome)
-> ReadM OsPath -> ReadM (PathI 'TrashHome)
forall a b. (a -> b) -> ReadM a -> ReadM b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap OsPath -> PathI 'TrashHome
forall (i :: PathIndex). OsPath -> PathI i
MkPathI ReadM OsPath
osPath)
(Mod OptionFields (PathI 'TrashHome) -> Parser (PathI 'TrashHome))
-> Mod OptionFields (PathI 'TrashHome) -> Parser (PathI 'TrashHome)
forall a b. (a -> b) -> a -> b
$ [Mod OptionFields (PathI 'TrashHome)]
-> Mod OptionFields (PathI 'TrashHome)
forall a. Monoid a => [a] -> a
mconcat
[ String -> Mod OptionFields (PathI 'TrashHome)
forall (f :: * -> *) a. HasName f => String -> Mod f a
OA.long String
"trash-home",
Char -> Mod OptionFields (PathI 'TrashHome)
forall (f :: * -> *) a. HasName f => Char -> Mod f a
OA.short Char
't',
String -> Mod OptionFields (PathI 'TrashHome)
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OA.metavar String
"PATH",
String -> Mod OptionFields (PathI 'TrashHome)
forall (f :: * -> *) a. String -> Mod f a
mkHelp String
helpTxt
]
where
helpTxt :: String
helpTxt =
[String] -> String
forall a. Monoid a => [a] -> a
mconcat
[ String
"Path to the trash directory. This overrides the toml config, if ",
String
"it exists. If neither is given then we use the XDG data directory ",
String
"e.g. ~/.local/share/charon."
]
trashDestParser :: Parser (PathI TrashHome)
trashDestParser :: Parser (PathI 'TrashHome)
trashDestParser =
ReadM (PathI 'TrashHome)
-> Mod OptionFields (PathI 'TrashHome) -> Parser (PathI 'TrashHome)
forall a. ReadM a -> Mod OptionFields a -> Parser a
OA.option
((OsPath -> PathI 'TrashHome)
-> ReadM OsPath -> ReadM (PathI 'TrashHome)
forall a b. (a -> b) -> ReadM a -> ReadM b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap OsPath -> PathI 'TrashHome
forall (i :: PathIndex). OsPath -> PathI i
MkPathI ReadM OsPath
osPath)
(Mod OptionFields (PathI 'TrashHome) -> Parser (PathI 'TrashHome))
-> Mod OptionFields (PathI 'TrashHome) -> Parser (PathI 'TrashHome)
forall a b. (a -> b) -> a -> b
$ [Mod OptionFields (PathI 'TrashHome)]
-> Mod OptionFields (PathI 'TrashHome)
forall a. Monoid a => [a] -> a
mconcat
[ String -> Mod OptionFields (PathI 'TrashHome)
forall (f :: * -> *) a. HasName f => String -> Mod f a
OA.long String
"dest",
Char -> Mod OptionFields (PathI 'TrashHome)
forall (f :: * -> *) a. HasName f => Char -> Mod f a
OA.short Char
'd',
String -> Mod OptionFields (PathI 'TrashHome)
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OA.metavar String
"PATH",
String -> Mod OptionFields (PathI 'TrashHome)
forall (f :: * -> *) a. String -> Mod f a
mkHelp String
helpTxt
]
where
helpTxt :: String
helpTxt = String
"Path to the dest trash directory."
logLevelParser :: Parser (Maybe (Maybe LogLevel))
logLevelParser :: Parser (Maybe (Maybe LogLevel))
logLevelParser =
Parser (Maybe LogLevel) -> Parser (Maybe (Maybe LogLevel))
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
A.optional
(Parser (Maybe LogLevel) -> Parser (Maybe (Maybe LogLevel)))
-> Parser (Maybe LogLevel) -> Parser (Maybe (Maybe LogLevel))
forall a b. (a -> b) -> a -> b
$ ReadM (Maybe LogLevel)
-> Mod OptionFields (Maybe LogLevel) -> Parser (Maybe LogLevel)
forall a. ReadM a -> Mod OptionFields a -> Parser a
OA.option (ReadM Text
forall s. IsString s => ReadM s
OA.str ReadM Text
-> (Text -> ReadM (Maybe LogLevel)) -> ReadM (Maybe LogLevel)
forall a b. ReadM a -> (a -> ReadM b) -> ReadM b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> ReadM (Maybe LogLevel)
forall (m :: * -> *). MonadFail m => Text -> m (Maybe LogLevel)
Utils.readLogLevel)
(Mod OptionFields (Maybe LogLevel) -> Parser (Maybe LogLevel))
-> Mod OptionFields (Maybe LogLevel) -> Parser (Maybe LogLevel)
forall a b. (a -> b) -> a -> b
$ [Mod OptionFields (Maybe LogLevel)]
-> Mod OptionFields (Maybe LogLevel)
forall a. Monoid a => [a] -> a
mconcat
[ String -> Mod OptionFields (Maybe LogLevel)
forall (f :: * -> *) a. HasName f => String -> Mod f a
OA.long String
"log-level",
String -> Mod OptionFields (Maybe LogLevel)
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OA.metavar String
Utils.logLevelStrings,
String -> Mod OptionFields (Maybe LogLevel)
forall (f :: * -> *) a. String -> Mod f a
mkHelp
(String -> Mod OptionFields (Maybe LogLevel))
-> String -> Mod OptionFields (Maybe LogLevel)
forall a b. (a -> b) -> a -> b
$ [String] -> String
forall a. Monoid a => [a] -> a
mconcat
[ String
"The file level in which to log. Defaults to none. Logs are ",
String
"written to the XDG state directory e.g. ~/.local/state/charon."
]
]
pathsParser :: Parser (UniqueSeqNE (PathI i))
pathsParser :: forall (i :: PathIndex). Parser (UniqueSeqNE (PathI i))
pathsParser =
NonEmpty (PathI i) -> UniqueSeqNE (PathI i)
forall a. Hashable a => NonEmpty a -> UniqueSeqNE a
UniqueSeqNE.fromNonEmpty
(NonEmpty (PathI i) -> UniqueSeqNE (PathI i))
-> ([PathI i] -> NonEmpty (PathI i))
-> [PathI i]
-> UniqueSeqNE (PathI i)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [PathI i] -> NonEmpty (PathI i)
forall a. HasCallStack => [a] -> NonEmpty a
unsafeNE
([PathI i] -> UniqueSeqNE (PathI i))
-> Parser [PathI i] -> Parser (UniqueSeqNE (PathI i))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser (PathI i) -> Parser [PathI i]
forall a. Parser a -> Parser [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
OA.some (ReadM (PathI i) -> Mod ArgumentFields (PathI i) -> Parser (PathI i)
forall a. ReadM a -> Mod ArgumentFields a -> Parser a
OA.argument ((OsPath -> PathI i) -> ReadM OsPath -> ReadM (PathI i)
forall a b. (a -> b) -> ReadM a -> ReadM b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap OsPath -> PathI i
forall (i :: PathIndex). OsPath -> PathI i
MkPathI ReadM OsPath
osPath) (String -> Mod ArgumentFields (PathI i)
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OA.metavar String
"PATHS..."))
logSizeModeParser :: Parser (Maybe FileSizeMode)
logSizeModeParser :: Parser (Maybe FileSizeMode)
logSizeModeParser =
Parser FileSizeMode -> Parser (Maybe FileSizeMode)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
OA.optional
(Parser FileSizeMode -> Parser (Maybe FileSizeMode))
-> Parser FileSizeMode -> Parser (Maybe FileSizeMode)
forall a b. (a -> b) -> a -> b
$ ReadM FileSizeMode
-> Mod OptionFields FileSizeMode -> Parser FileSizeMode
forall a. ReadM a -> Mod OptionFields a -> Parser a
OA.option
ReadM FileSizeMode
readFileSize
( [Mod OptionFields FileSizeMode] -> Mod OptionFields FileSizeMode
forall a. Monoid a => [a] -> a
mconcat
[ String -> Mod OptionFields FileSizeMode
forall (f :: * -> *) a. HasName f => String -> Mod f a
OA.long String
"log-size-mode",
String -> Mod OptionFields FileSizeMode
forall (f :: * -> *) a. String -> Mod f a
mkHelp String
helpTxt,
String -> Mod OptionFields FileSizeMode
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OA.metavar String
"(warn SIZE | delete SIZE)"
]
)
where
helpTxt :: String
helpTxt =
[String] -> String
forall a. Monoid a => [a] -> a
mconcat
[ String
"Sets a threshold for the file log size, upon which we either ",
String
"print a warning or delete the file, if it is exceeded. ",
String
"The SIZE should include the value and units e.g. ",
String
"'warn 10 mb', 'warn 5 gigabytes', 'delete 20.5B'."
]
readFileSize :: ReadM FileSizeMode
readFileSize = ReadM Text
forall s. IsString s => ReadM s
OA.str ReadM Text -> (Text -> ReadM FileSizeMode) -> ReadM FileSizeMode
forall a b. ReadM a -> (a -> ReadM b) -> ReadM b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> ReadM FileSizeMode
forall (m :: * -> *). MonadFail m => Text -> m FileSizeMode
parseFileSizeMode
mkCommand :: String -> Parser a -> InfoMod a -> Mod CommandFields a
mkCommand :: forall a. String -> Parser a -> InfoMod a -> Mod CommandFields a
mkCommand String
cmdTxt Parser a
parser InfoMod a
helpTxt = String -> ParserInfo a -> Mod CommandFields a
forall a. String -> ParserInfo a -> Mod CommandFields a
OA.command String
cmdTxt (Parser a -> InfoMod a -> ParserInfo a
forall a. Parser a -> InfoMod a -> ParserInfo a
OA.info Parser a
parser InfoMod a
helpTxt)
unsafeNE :: (HasCallStack) => [a] -> NonEmpty a
unsafeNE :: forall a. HasCallStack => [a] -> NonEmpty a
unsafeNE [] = String -> NonEmpty a
forall a. HasCallStack => String -> a
error String
"Args: Empty list given to unsafeNE"
unsafeNE (a
x : [a]
xs) = a
x a -> [a] -> NonEmpty a
forall a. a -> [a] -> NonEmpty a
:| [a]
xs
mkHelp :: String -> OA.Mod f a
mkHelp :: forall (f :: * -> *) a. String -> Mod f a
mkHelp =
Maybe Doc -> Mod f a
forall (f :: * -> *) a. Maybe Doc -> Mod f a
OA.helpDoc
(Maybe Doc -> Mod f a)
-> (String -> Maybe Doc) -> String -> Mod f a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Doc -> Doc) -> Maybe Doc -> Maybe Doc
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> Doc
Pretty.hardline)
(Maybe Doc -> Maybe Doc)
-> (String -> Maybe Doc) -> String -> Maybe Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Chunk Doc -> Maybe Doc
forall a. Chunk a -> Maybe a
Chunk.unChunk
(Chunk Doc -> Maybe Doc)
-> (String -> Chunk Doc) -> String -> Maybe Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Chunk Doc
Chunk.paragraph
mkCmdDesc :: String -> InfoMod a
mkCmdDesc :: forall a. String -> InfoMod a
mkCmdDesc =
Maybe Doc -> InfoMod a
forall a. Maybe Doc -> InfoMod a
OA.progDescDoc
(Maybe Doc -> InfoMod a)
-> (String -> Maybe Doc) -> String -> InfoMod a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Doc -> Doc) -> Maybe Doc -> Maybe Doc
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> Doc
Pretty.hardline)
(Maybe Doc -> Maybe Doc)
-> (String -> Maybe Doc) -> String -> Maybe Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Chunk Doc -> Maybe Doc
forall a. Chunk a -> Maybe a
Chunk.unChunk
(Chunk Doc -> Maybe Doc)
-> (String -> Chunk Doc) -> String -> Maybe Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Chunk Doc
Chunk.paragraph
mkCmdDescNoLine :: String -> InfoMod a
mkCmdDescNoLine :: forall a. String -> InfoMod a
mkCmdDescNoLine =
Maybe Doc -> InfoMod a
forall a. Maybe Doc -> InfoMod a
OA.progDescDoc
(Maybe Doc -> InfoMod a)
-> (String -> Maybe Doc) -> String -> InfoMod a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Chunk Doc -> Maybe Doc
forall a. Chunk a -> Maybe a
Chunk.unChunk
(Chunk Doc -> Maybe Doc)
-> (String -> Chunk Doc) -> String -> Maybe Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Chunk Doc
Chunk.paragraph