{-# LANGUAGE ApplicativeDo #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
module PFile.CLI
( parserInfo
, parser
, Options (..)
, Command (..)
) where
import Options.Applicative
( Parser
, ParserInfo
, fullDesc
, header
, helper
, info
, long
, progDesc
, short
, subparser
, switch
)
import qualified Options.Applicative
import qualified PFile.CLI.List as List
import qualified PFile.CLI.New as New
import qualified PFile.CLI.Switch as Switch
import qualified PFile.CLI.Unpack as Unpack
import qualified PFile.CLI.Which as Which
import Protolude
parserInfo :: ParserInfo Options
parserInfo :: ParserInfo Options
parserInfo = Parser Options -> InfoMod Options -> ParserInfo Options
forall a. Parser a -> InfoMod a -> ParserInfo a
info (Parser Options
parser Parser Options -> Parser (Options -> Options) -> Parser Options
forall (f :: * -> *) a b. Applicative f => f a -> f (a -> b) -> f b
<**> Parser (Options -> Options)
forall a. Parser (a -> a)
helper)
(InfoMod Options -> ParserInfo Options)
-> InfoMod Options -> ParserInfo Options
forall a b. (a -> b) -> a -> b
$ InfoMod Options
forall a. InfoMod a
fullDesc
InfoMod Options -> InfoMod Options -> InfoMod Options
forall a. Semigroup a => a -> a -> a
<> String -> InfoMod Options
forall a. String -> InfoMod a
header String
"pfile - manage profiles defined for a set of filesystem's objects"
InfoMod Options -> InfoMod Options -> InfoMod Options
forall a. Semigroup a => a -> a -> a
<> String -> InfoMod Options
forall a. String -> InfoMod a
progDesc String
description
where
description :: String
description
= String
"Manage profiles defined for a set of filesystem's objects"
String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
" (directories, directory links, files, file links). Profiles could be"
String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
" defined with `pfile new`. Switch between multiple profiles with"
String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
" `pfile switch`. In order to revert the `pfile new`/`pfile switch`,"
String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
" use `pfile unpack`."
parser :: Parser Options
parser :: Parser Options
parser = do
Bool
verbose <- Mod FlagFields Bool -> Parser Bool
switch (Char -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
'v' Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"verbose")
Command
command <- Mod CommandFields Command -> Parser Command
forall a. Mod CommandFields a -> Parser a
subparser (Mod CommandFields Command -> Parser Command)
-> ([Mod CommandFields Command] -> Mod CommandFields Command)
-> [Mod CommandFields Command]
-> Parser Command
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Mod CommandFields Command] -> Mod CommandFields Command
forall m. Monoid m => [m] -> m
forall (t :: * -> *) m. (Foldable t, Monoid m) => t m -> m
fold ([Mod CommandFields Command] -> Parser Command)
-> [Mod CommandFields Command] -> Parser Command
forall a b. (a -> b) -> a -> b
$
[ String -> ParserInfo Command -> Mod CommandFields Command
forall a. String -> ParserInfo a -> Mod CommandFields a
Options.Applicative.command String
"new" (Options -> Command
New (Options -> Command) -> ParserInfo Options -> ParserInfo Command
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserInfo Options
New.parserInfo)
, String -> ParserInfo Command -> Mod CommandFields Command
forall a. String -> ParserInfo a -> Mod CommandFields a
Options.Applicative.command String
"switch" (Options -> Command
Switch (Options -> Command) -> ParserInfo Options -> ParserInfo Command
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserInfo Options
Switch.parserInfo)
, String -> ParserInfo Command -> Mod CommandFields Command
forall a. String -> ParserInfo a -> Mod CommandFields a
Options.Applicative.command String
"unpack" (Options -> Command
Unpack (Options -> Command) -> ParserInfo Options -> ParserInfo Command
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserInfo Options
Unpack.parserInfo)
, String -> ParserInfo Command -> Mod CommandFields Command
forall a. String -> ParserInfo a -> Mod CommandFields a
Options.Applicative.command String
"ls" (Options -> Command
List (Options -> Command) -> ParserInfo Options -> ParserInfo Command
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserInfo Options
List.parserInfo)
, String -> ParserInfo Command -> Mod CommandFields Command
forall a. String -> ParserInfo a -> Mod CommandFields a
Options.Applicative.command String
"which" (Options -> Command
Which (Options -> Command) -> ParserInfo Options -> ParserInfo Command
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserInfo Options
Which.parserInfo)
]
pure Options {Bool
Command
verbose :: Bool
command :: Command
verbose :: Bool
command :: Command
..}
data Options
= Options
{ Options -> Bool
verbose :: !Bool
, Options -> Command
command :: !Command
}
data Command
= New New.Options
| Switch Switch.Options
| Unpack Unpack.Options
| List List.Options
| Which Which.Options