module Stackctl.Options
( Options
, envParser
, optionsParser
) where
import Stackctl.Prelude
import Data.Semigroup.Generic
import qualified Env
import Options.Applicative
import Stackctl.AutoSSO
import Stackctl.ColorOption
import Stackctl.DirectoryOption
import Stackctl.FilterOption
import Stackctl.VerboseOption
data Options = Options
{ Options -> Maybe DirectoryOption
oDirectory :: Maybe DirectoryOption
, Options -> Maybe FilterOption
oFilter :: Maybe FilterOption
, Options -> Maybe ColorOption
oColor :: Maybe ColorOption
, Options -> Verbosity
oVerbose :: Verbosity
, Options -> Maybe AutoSSOOption
oAutoSSO :: Maybe AutoSSOOption
}
deriving stock (forall x. Rep Options x -> Options
forall x. Options -> Rep Options x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Options x -> Options
$cfrom :: forall x. Options -> Rep Options x
Generic)
deriving (NonEmpty Options -> Options
Options -> Options -> Options
forall b. Integral b => b -> Options -> Options
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
stimes :: forall b. Integral b => b -> Options -> Options
$cstimes :: forall b. Integral b => b -> Options -> Options
sconcat :: NonEmpty Options -> Options
$csconcat :: NonEmpty Options -> Options
<> :: Options -> Options -> Options
$c<> :: Options -> Options -> Options
Semigroup) via GenericSemigroupMonoid Options
directoryL :: Lens' Options (Maybe DirectoryOption)
directoryL :: Lens' Options (Maybe DirectoryOption)
directoryL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Options -> Maybe DirectoryOption
oDirectory forall a b. (a -> b) -> a -> b
$ \Options
x Maybe DirectoryOption
y -> Options
x {oDirectory :: Maybe DirectoryOption
oDirectory = Maybe DirectoryOption
y}
filterL :: Lens' Options (Maybe FilterOption)
filterL :: Lens' Options (Maybe FilterOption)
filterL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Options -> Maybe FilterOption
oFilter forall a b. (a -> b) -> a -> b
$ \Options
x Maybe FilterOption
y -> Options
x {oFilter :: Maybe FilterOption
oFilter = Maybe FilterOption
y}
autoSSOL :: Lens' Options (Maybe AutoSSOOption)
autoSSOL :: Lens' Options (Maybe AutoSSOOption)
autoSSOL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Options -> Maybe AutoSSOOption
oAutoSSO forall a b. (a -> b) -> a -> b
$ \Options
x Maybe AutoSSOOption
y -> Options
x {oAutoSSO :: Maybe AutoSSOOption
oAutoSSO = Maybe AutoSSOOption
y}
instance HasDirectoryOption Options where
directoryOptionL :: Lens' Options DirectoryOption
directoryOptionL = Lens' Options (Maybe DirectoryOption)
directoryL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Lens' (Maybe a) a
maybeLens DirectoryOption
defaultDirectoryOption
instance HasFilterOption Options where
filterOptionL :: Lens' Options FilterOption
filterOptionL = Lens' Options (Maybe FilterOption)
filterL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Lens' (Maybe a) a
maybeLens FilterOption
defaultFilterOption
instance HasColorOption Options where
colorOptionL :: Lens' Options (Maybe ColorOption)
colorOptionL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Options -> Maybe ColorOption
oColor forall a b. (a -> b) -> a -> b
$ \Options
x Maybe ColorOption
y -> Options
x {oColor :: Maybe ColorOption
oColor = Maybe ColorOption
y}
instance HasVerboseOption Options where
verboseOptionL :: Lens' Options Verbosity
verboseOptionL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Options -> Verbosity
oVerbose forall a b. (a -> b) -> a -> b
$ \Options
x Verbosity
y -> Options
x {oVerbose :: Verbosity
oVerbose = Verbosity
y}
instance HasAutoSSOOption Options where
autoSSOOptionL :: Lens' Options AutoSSOOption
autoSSOOptionL = Lens' Options (Maybe AutoSSOOption)
autoSSOL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Lens' (Maybe a) a
maybeLens AutoSSOOption
defaultAutoSSOOption
envParser :: Env.Parser Env.Error Options
envParser :: Parser Error Options
envParser =
forall e a. String -> Parser e a -> Parser e a
Env.prefixed String
"STACKCTL_"
forall a b. (a -> b) -> a -> b
$ Maybe DirectoryOption
-> Maybe FilterOption
-> Maybe ColorOption
-> Verbosity
-> Maybe AutoSSOOption
-> Options
Options
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional Parser Error DirectoryOption
envDirectoryOption
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (String -> Parser Error FilterOption
envFilterOption String
"specifications")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Monoid a => a
mempty
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Monoid a => a
mempty
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional Parser Error AutoSSOOption
envAutoSSOOption
optionsParser :: Parser Options
optionsParser :: Parser Options
optionsParser =
Maybe DirectoryOption
-> Maybe FilterOption
-> Maybe ColorOption
-> Verbosity
-> Maybe AutoSSOOption
-> Options
Options
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional Parser DirectoryOption
directoryOption
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (String -> Parser FilterOption
filterOption String
"specifications")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional Parser ColorOption
colorOption
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Verbosity
verboseOption
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional Parser AutoSSOOption
autoSSOOption