{-# LANGUAGE StrictData #-}
module Nix.Options where
import           Data.Time
data Options = Options
    { Options -> Verbosity
verbose      :: Verbosity
    , Options -> Bool
tracing      :: Bool
    , Options -> Bool
thunks       :: Bool
    , Options -> Bool
values       :: Bool
    , Options -> Bool
showScopes   :: Bool
    , Options -> Maybe FilePath
reduce       :: Maybe FilePath
    , Options -> Bool
reduceSets   :: Bool
    , Options -> Bool
reduceLists  :: Bool
    , Options -> Bool
parse        :: Bool
    , Options -> Bool
parseOnly    :: Bool
    , Options -> Bool
finder       :: Bool
    , Options -> Maybe FilePath
findFile     :: Maybe FilePath
    , Options -> Bool
strict       :: Bool
    , Options -> Bool
evaluate     :: Bool
    , Options -> Bool
json         :: Bool
    , Options -> Bool
xml          :: Bool
    , Options -> Maybe Text
attr         :: Maybe Text
    , Options -> [FilePath]
include      :: [FilePath]
    , Options -> Bool
check        :: Bool
    , Options -> Maybe FilePath
readFrom     :: Maybe FilePath
    , Options -> Bool
cache        :: Bool
    , Options -> Bool
repl         :: Bool
    , Options -> Bool
ignoreErrors :: Bool
    , Options -> Maybe Text
expression   :: Maybe Text
    , Options -> [(Text, Text)]
arg          :: [(Text, Text)]
    , Options -> [(Text, Text)]
argstr       :: [(Text, Text)]
    , Options -> Maybe FilePath
fromFile     :: Maybe FilePath
    , Options -> UTCTime
currentTime  :: UTCTime
    , Options -> [FilePath]
filePaths    :: [FilePath]
    }
    deriving Int -> Options -> ShowS
[Options] -> ShowS
Options -> FilePath
(Int -> Options -> ShowS)
-> (Options -> FilePath) -> ([Options] -> ShowS) -> Show Options
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [Options] -> ShowS
$cshowList :: [Options] -> ShowS
show :: Options -> FilePath
$cshow :: Options -> FilePath
showsPrec :: Int -> Options -> ShowS
$cshowsPrec :: Int -> Options -> ShowS
Show
defaultOptions :: UTCTime -> Options
defaultOptions :: UTCTime -> Options
defaultOptions UTCTime
current = Options :: Verbosity
-> Bool
-> Bool
-> Bool
-> Bool
-> Maybe FilePath
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Maybe FilePath
-> Bool
-> Bool
-> Bool
-> Bool
-> Maybe Text
-> [FilePath]
-> Bool
-> Maybe FilePath
-> Bool
-> Bool
-> Bool
-> Maybe Text
-> [(Text, Text)]
-> [(Text, Text)]
-> Maybe FilePath
-> UTCTime
-> [FilePath]
-> Options
Options { verbose :: Verbosity
verbose      = Verbosity
ErrorsOnly
                                 , tracing :: Bool
tracing      = Bool
False
                                 , thunks :: Bool
thunks       = Bool
False
                                 , values :: Bool
values       = Bool
False
                                 , showScopes :: Bool
showScopes   = Bool
False
                                 , reduce :: Maybe FilePath
reduce       = Maybe FilePath
forall a. Monoid a => a
mempty
                                 , reduceSets :: Bool
reduceSets   = Bool
False
                                 , reduceLists :: Bool
reduceLists  = Bool
False
                                 , parse :: Bool
parse        = Bool
False
                                 , parseOnly :: Bool
parseOnly    = Bool
False
                                 , finder :: Bool
finder       = Bool
False
                                 , findFile :: Maybe FilePath
findFile     = Maybe FilePath
forall a. Monoid a => a
mempty
                                 , strict :: Bool
strict       = Bool
False
                                 , evaluate :: Bool
evaluate     = Bool
False
                                 , json :: Bool
json         = Bool
False
                                 , xml :: Bool
xml          = Bool
False
                                 , attr :: Maybe Text
attr         = Maybe Text
forall a. Monoid a => a
mempty
                                 , include :: [FilePath]
include      = [FilePath]
forall a. Monoid a => a
mempty
                                 , check :: Bool
check        = Bool
False
                                 , readFrom :: Maybe FilePath
readFrom     = Maybe FilePath
forall a. Monoid a => a
mempty
                                 , cache :: Bool
cache        = Bool
False
                                 , repl :: Bool
repl         = Bool
False
                                 , ignoreErrors :: Bool
ignoreErrors = Bool
False
                                 , expression :: Maybe Text
expression   = Maybe Text
forall a. Monoid a => a
mempty
                                 , arg :: [(Text, Text)]
arg          = [(Text, Text)]
forall a. Monoid a => a
mempty
                                 , argstr :: [(Text, Text)]
argstr       = [(Text, Text)]
forall a. Monoid a => a
mempty
                                 , fromFile :: Maybe FilePath
fromFile     = Maybe FilePath
forall a. Monoid a => a
mempty
                                 , currentTime :: UTCTime
currentTime  = UTCTime
current
                                 , filePaths :: [FilePath]
filePaths    = [FilePath]
forall a. Monoid a => a
mempty
                                 }
data Verbosity
    = ErrorsOnly
    | Informational
    | Talkative
    | Chatty
    | DebugInfo
    | Vomit
    deriving (Verbosity -> Verbosity -> Bool
(Verbosity -> Verbosity -> Bool)
-> (Verbosity -> Verbosity -> Bool) -> Eq Verbosity
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Verbosity -> Verbosity -> Bool
$c/= :: Verbosity -> Verbosity -> Bool
== :: Verbosity -> Verbosity -> Bool
$c== :: Verbosity -> Verbosity -> Bool
Eq, Eq Verbosity
Eq Verbosity
-> (Verbosity -> Verbosity -> Ordering)
-> (Verbosity -> Verbosity -> Bool)
-> (Verbosity -> Verbosity -> Bool)
-> (Verbosity -> Verbosity -> Bool)
-> (Verbosity -> Verbosity -> Bool)
-> (Verbosity -> Verbosity -> Verbosity)
-> (Verbosity -> Verbosity -> Verbosity)
-> Ord Verbosity
Verbosity -> Verbosity -> Bool
Verbosity -> Verbosity -> Ordering
Verbosity -> Verbosity -> Verbosity
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Verbosity -> Verbosity -> Verbosity
$cmin :: Verbosity -> Verbosity -> Verbosity
max :: Verbosity -> Verbosity -> Verbosity
$cmax :: Verbosity -> Verbosity -> Verbosity
>= :: Verbosity -> Verbosity -> Bool
$c>= :: Verbosity -> Verbosity -> Bool
> :: Verbosity -> Verbosity -> Bool
$c> :: Verbosity -> Verbosity -> Bool
<= :: Verbosity -> Verbosity -> Bool
$c<= :: Verbosity -> Verbosity -> Bool
< :: Verbosity -> Verbosity -> Bool
$c< :: Verbosity -> Verbosity -> Bool
compare :: Verbosity -> Verbosity -> Ordering
$ccompare :: Verbosity -> Verbosity -> Ordering
$cp1Ord :: Eq Verbosity
Ord, Int -> Verbosity
Verbosity -> Int
Verbosity -> [Verbosity]
Verbosity -> Verbosity
Verbosity -> Verbosity -> [Verbosity]
Verbosity -> Verbosity -> Verbosity -> [Verbosity]
(Verbosity -> Verbosity)
-> (Verbosity -> Verbosity)
-> (Int -> Verbosity)
-> (Verbosity -> Int)
-> (Verbosity -> [Verbosity])
-> (Verbosity -> Verbosity -> [Verbosity])
-> (Verbosity -> Verbosity -> [Verbosity])
-> (Verbosity -> Verbosity -> Verbosity -> [Verbosity])
-> Enum Verbosity
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: Verbosity -> Verbosity -> Verbosity -> [Verbosity]
$cenumFromThenTo :: Verbosity -> Verbosity -> Verbosity -> [Verbosity]
enumFromTo :: Verbosity -> Verbosity -> [Verbosity]
$cenumFromTo :: Verbosity -> Verbosity -> [Verbosity]
enumFromThen :: Verbosity -> Verbosity -> [Verbosity]
$cenumFromThen :: Verbosity -> Verbosity -> [Verbosity]
enumFrom :: Verbosity -> [Verbosity]
$cenumFrom :: Verbosity -> [Verbosity]
fromEnum :: Verbosity -> Int
$cfromEnum :: Verbosity -> Int
toEnum :: Int -> Verbosity
$ctoEnum :: Int -> Verbosity
pred :: Verbosity -> Verbosity
$cpred :: Verbosity -> Verbosity
succ :: Verbosity -> Verbosity
$csucc :: Verbosity -> Verbosity
Enum, Verbosity
Verbosity -> Verbosity -> Bounded Verbosity
forall a. a -> a -> Bounded a
maxBound :: Verbosity
$cmaxBound :: Verbosity
minBound :: Verbosity
$cminBound :: Verbosity
Bounded, Int -> Verbosity -> ShowS
[Verbosity] -> ShowS
Verbosity -> FilePath
(Int -> Verbosity -> ShowS)
-> (Verbosity -> FilePath)
-> ([Verbosity] -> ShowS)
-> Show Verbosity
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [Verbosity] -> ShowS
$cshowList :: [Verbosity] -> ShowS
show :: Verbosity -> FilePath
$cshow :: Verbosity -> FilePath
showsPrec :: Int -> Verbosity -> ShowS
$cshowsPrec :: Int -> Verbosity -> ShowS
Show)