{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingStrategies #-}
module Aura.Settings
( Settings(..)
, logFuncOfL
, BuildConfig(..), BuildSwitch(..)
, buildPathOfL, buildUserOfL, buildSwitchesOfL, allsourcePathOfL, vcsPathOfL
, switch
, Truncation(..)
, defaultBuildDir
, CommonConfig(..), CommonSwitch(..)
, cachePathOfL, logPathOfL
, ColourMode(..)
, shared
, Makepkg(..)
) where
import Aura.Types
import Network.HTTP.Client (Manager)
import RIO
import qualified RIO.Set as S
import qualified RIO.Text as T
data Truncation = None | Head !Word | Tail !Word deriving (Truncation -> Truncation -> Bool
(Truncation -> Truncation -> Bool)
-> (Truncation -> Truncation -> Bool) -> Eq Truncation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Truncation -> Truncation -> Bool
$c/= :: Truncation -> Truncation -> Bool
== :: Truncation -> Truncation -> Bool
$c== :: Truncation -> Truncation -> Bool
Eq, Int -> Truncation -> ShowS
[Truncation] -> ShowS
Truncation -> String
(Int -> Truncation -> ShowS)
-> (Truncation -> String)
-> ([Truncation] -> ShowS)
-> Show Truncation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Truncation] -> ShowS
$cshowList :: [Truncation] -> ShowS
show :: Truncation -> String
$cshow :: Truncation -> String
showsPrec :: Int -> Truncation -> ShowS
$cshowsPrec :: Int -> Truncation -> ShowS
Show)
data Makepkg = IgnoreArch | AllSource | SkipInteg | SkipPGP | NoCheck
deriving (Makepkg -> Makepkg -> Bool
(Makepkg -> Makepkg -> Bool)
-> (Makepkg -> Makepkg -> Bool) -> Eq Makepkg
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Makepkg -> Makepkg -> Bool
$c/= :: Makepkg -> Makepkg -> Bool
== :: Makepkg -> Makepkg -> Bool
$c== :: Makepkg -> Makepkg -> Bool
Eq, Eq Makepkg
Eq Makepkg
-> (Makepkg -> Makepkg -> Ordering)
-> (Makepkg -> Makepkg -> Bool)
-> (Makepkg -> Makepkg -> Bool)
-> (Makepkg -> Makepkg -> Bool)
-> (Makepkg -> Makepkg -> Bool)
-> (Makepkg -> Makepkg -> Makepkg)
-> (Makepkg -> Makepkg -> Makepkg)
-> Ord Makepkg
Makepkg -> Makepkg -> Bool
Makepkg -> Makepkg -> Ordering
Makepkg -> Makepkg -> Makepkg
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 :: Makepkg -> Makepkg -> Makepkg
$cmin :: Makepkg -> Makepkg -> Makepkg
max :: Makepkg -> Makepkg -> Makepkg
$cmax :: Makepkg -> Makepkg -> Makepkg
>= :: Makepkg -> Makepkg -> Bool
$c>= :: Makepkg -> Makepkg -> Bool
> :: Makepkg -> Makepkg -> Bool
$c> :: Makepkg -> Makepkg -> Bool
<= :: Makepkg -> Makepkg -> Bool
$c<= :: Makepkg -> Makepkg -> Bool
< :: Makepkg -> Makepkg -> Bool
$c< :: Makepkg -> Makepkg -> Bool
compare :: Makepkg -> Makepkg -> Ordering
$ccompare :: Makepkg -> Makepkg -> Ordering
$cp1Ord :: Eq Makepkg
Ord, Int -> Makepkg -> ShowS
[Makepkg] -> ShowS
Makepkg -> String
(Int -> Makepkg -> ShowS)
-> (Makepkg -> String) -> ([Makepkg] -> ShowS) -> Show Makepkg
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Makepkg] -> ShowS
$cshowList :: [Makepkg] -> ShowS
show :: Makepkg -> String
$cshow :: Makepkg -> String
showsPrec :: Int -> Makepkg -> ShowS
$cshowsPrec :: Int -> Makepkg -> ShowS
Show)
instance Flagable Makepkg where
asFlag :: Makepkg -> [Text]
asFlag Makepkg
IgnoreArch = [Text
"--ignorearch"]
asFlag Makepkg
AllSource = [Text
"--allsource"]
asFlag Makepkg
SkipInteg = [Text
"--skipinteg"]
asFlag Makepkg
SkipPGP = [Text
"--skippgpcheck"]
asFlag Makepkg
NoCheck = [Text
"--nocheck"]
data CommonConfig = CommonConfig
{ CommonConfig -> Either String String
cachePathOf :: !(Either FilePath FilePath)
, CommonConfig -> Either String String
configPathOf :: !(Either FilePath FilePath)
, CommonConfig -> Either String String
logPathOf :: !(Either FilePath FilePath)
, CommonConfig -> Set CommonSwitch
commonSwitchesOf :: !(Set CommonSwitch) } deriving (Int -> CommonConfig -> ShowS
[CommonConfig] -> ShowS
CommonConfig -> String
(Int -> CommonConfig -> ShowS)
-> (CommonConfig -> String)
-> ([CommonConfig] -> ShowS)
-> Show CommonConfig
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CommonConfig] -> ShowS
$cshowList :: [CommonConfig] -> ShowS
show :: CommonConfig -> String
$cshow :: CommonConfig -> String
showsPrec :: Int -> CommonConfig -> ShowS
$cshowsPrec :: Int -> CommonConfig -> ShowS
Show, (forall x. CommonConfig -> Rep CommonConfig x)
-> (forall x. Rep CommonConfig x -> CommonConfig)
-> Generic CommonConfig
forall x. Rep CommonConfig x -> CommonConfig
forall x. CommonConfig -> Rep CommonConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CommonConfig x -> CommonConfig
$cfrom :: forall x. CommonConfig -> Rep CommonConfig x
Generic)
cachePathOfL :: Lens' CommonConfig (Either FilePath FilePath)
cachePathOfL :: (Either String String -> f (Either String String))
-> CommonConfig -> f CommonConfig
cachePathOfL Either String String -> f (Either String String)
f CommonConfig
cc = (\Either String String
cp -> CommonConfig
cc { cachePathOf :: Either String String
cachePathOf = Either String String
cp }) (Either String String -> CommonConfig)
-> f (Either String String) -> f CommonConfig
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Either String String -> f (Either String String)
f (CommonConfig -> Either String String
cachePathOf CommonConfig
cc)
logPathOfL :: Lens' CommonConfig (Either FilePath FilePath)
logPathOfL :: (Either String String -> f (Either String String))
-> CommonConfig -> f CommonConfig
logPathOfL Either String String -> f (Either String String)
f CommonConfig
cc = (\Either String String
cp -> CommonConfig
cc { logPathOf :: Either String String
logPathOf = Either String String
cp }) (Either String String -> CommonConfig)
-> f (Either String String) -> f CommonConfig
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Either String String -> f (Either String String)
f (CommonConfig -> Either String String
logPathOf CommonConfig
cc)
instance Flagable CommonConfig where
asFlag :: CommonConfig -> [Text]
asFlag (CommonConfig Either String String
cap Either String String
cop Either String String
lfp Set CommonSwitch
cs) =
(String -> [Text])
-> (String -> [Text]) -> Either String String -> [Text]
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either ([Text] -> String -> [Text]
forall a b. a -> b -> a
const []) (\String
p -> [Text
"--cachedir", String -> Text
T.pack String
p]) Either String String
cap
[Text] -> [Text] -> [Text]
forall a. Semigroup a => a -> a -> a
<> (String -> [Text])
-> (String -> [Text]) -> Either String String -> [Text]
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either ([Text] -> String -> [Text]
forall a b. a -> b -> a
const []) (\String
p -> [Text
"--config", String -> Text
T.pack String
p]) Either String String
cop
[Text] -> [Text] -> [Text]
forall a. Semigroup a => a -> a -> a
<> (String -> [Text])
-> (String -> [Text]) -> Either String String -> [Text]
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either ([Text] -> String -> [Text]
forall a b. a -> b -> a
const []) (\String
p -> [Text
"--logfile", String -> Text
T.pack String
p]) Either String String
lfp
[Text] -> [Text] -> [Text]
forall a. Semigroup a => a -> a -> a
<> Set CommonSwitch -> [Text]
forall a. Flagable a => a -> [Text]
asFlag Set CommonSwitch
cs
data CommonSwitch = NoConfirm | NeededOnly | Debug | Colour !ColourMode | Overwrite !Text
deriving (CommonSwitch -> CommonSwitch -> Bool
(CommonSwitch -> CommonSwitch -> Bool)
-> (CommonSwitch -> CommonSwitch -> Bool) -> Eq CommonSwitch
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommonSwitch -> CommonSwitch -> Bool
$c/= :: CommonSwitch -> CommonSwitch -> Bool
== :: CommonSwitch -> CommonSwitch -> Bool
$c== :: CommonSwitch -> CommonSwitch -> Bool
Eq, Eq CommonSwitch
Eq CommonSwitch
-> (CommonSwitch -> CommonSwitch -> Ordering)
-> (CommonSwitch -> CommonSwitch -> Bool)
-> (CommonSwitch -> CommonSwitch -> Bool)
-> (CommonSwitch -> CommonSwitch -> Bool)
-> (CommonSwitch -> CommonSwitch -> Bool)
-> (CommonSwitch -> CommonSwitch -> CommonSwitch)
-> (CommonSwitch -> CommonSwitch -> CommonSwitch)
-> Ord CommonSwitch
CommonSwitch -> CommonSwitch -> Bool
CommonSwitch -> CommonSwitch -> Ordering
CommonSwitch -> CommonSwitch -> CommonSwitch
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 :: CommonSwitch -> CommonSwitch -> CommonSwitch
$cmin :: CommonSwitch -> CommonSwitch -> CommonSwitch
max :: CommonSwitch -> CommonSwitch -> CommonSwitch
$cmax :: CommonSwitch -> CommonSwitch -> CommonSwitch
>= :: CommonSwitch -> CommonSwitch -> Bool
$c>= :: CommonSwitch -> CommonSwitch -> Bool
> :: CommonSwitch -> CommonSwitch -> Bool
$c> :: CommonSwitch -> CommonSwitch -> Bool
<= :: CommonSwitch -> CommonSwitch -> Bool
$c<= :: CommonSwitch -> CommonSwitch -> Bool
< :: CommonSwitch -> CommonSwitch -> Bool
$c< :: CommonSwitch -> CommonSwitch -> Bool
compare :: CommonSwitch -> CommonSwitch -> Ordering
$ccompare :: CommonSwitch -> CommonSwitch -> Ordering
$cp1Ord :: Eq CommonSwitch
Ord, Int -> CommonSwitch -> ShowS
[CommonSwitch] -> ShowS
CommonSwitch -> String
(Int -> CommonSwitch -> ShowS)
-> (CommonSwitch -> String)
-> ([CommonSwitch] -> ShowS)
-> Show CommonSwitch
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CommonSwitch] -> ShowS
$cshowList :: [CommonSwitch] -> ShowS
show :: CommonSwitch -> String
$cshow :: CommonSwitch -> String
showsPrec :: Int -> CommonSwitch -> ShowS
$cshowsPrec :: Int -> CommonSwitch -> ShowS
Show)
instance Flagable CommonSwitch where
asFlag :: CommonSwitch -> [Text]
asFlag CommonSwitch
NoConfirm = [Text
"--noconfirm"]
asFlag CommonSwitch
NeededOnly = [Text
"--needed"]
asFlag CommonSwitch
Debug = [Text
"--debug"]
asFlag (Colour ColourMode
m) = Text
"--color" Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: ColourMode -> [Text]
forall a. Flagable a => a -> [Text]
asFlag ColourMode
m
asFlag (Overwrite Text
t) = Text
"--overwrite" Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: Text -> [Text]
forall a. Flagable a => a -> [Text]
asFlag Text
t
data ColourMode = Never | Always | Auto deriving (ColourMode -> ColourMode -> Bool
(ColourMode -> ColourMode -> Bool)
-> (ColourMode -> ColourMode -> Bool) -> Eq ColourMode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ColourMode -> ColourMode -> Bool
$c/= :: ColourMode -> ColourMode -> Bool
== :: ColourMode -> ColourMode -> Bool
$c== :: ColourMode -> ColourMode -> Bool
Eq, Eq ColourMode
Eq ColourMode
-> (ColourMode -> ColourMode -> Ordering)
-> (ColourMode -> ColourMode -> Bool)
-> (ColourMode -> ColourMode -> Bool)
-> (ColourMode -> ColourMode -> Bool)
-> (ColourMode -> ColourMode -> Bool)
-> (ColourMode -> ColourMode -> ColourMode)
-> (ColourMode -> ColourMode -> ColourMode)
-> Ord ColourMode
ColourMode -> ColourMode -> Bool
ColourMode -> ColourMode -> Ordering
ColourMode -> ColourMode -> ColourMode
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 :: ColourMode -> ColourMode -> ColourMode
$cmin :: ColourMode -> ColourMode -> ColourMode
max :: ColourMode -> ColourMode -> ColourMode
$cmax :: ColourMode -> ColourMode -> ColourMode
>= :: ColourMode -> ColourMode -> Bool
$c>= :: ColourMode -> ColourMode -> Bool
> :: ColourMode -> ColourMode -> Bool
$c> :: ColourMode -> ColourMode -> Bool
<= :: ColourMode -> ColourMode -> Bool
$c<= :: ColourMode -> ColourMode -> Bool
< :: ColourMode -> ColourMode -> Bool
$c< :: ColourMode -> ColourMode -> Bool
compare :: ColourMode -> ColourMode -> Ordering
$ccompare :: ColourMode -> ColourMode -> Ordering
$cp1Ord :: Eq ColourMode
Ord, Int -> ColourMode -> ShowS
[ColourMode] -> ShowS
ColourMode -> String
(Int -> ColourMode -> ShowS)
-> (ColourMode -> String)
-> ([ColourMode] -> ShowS)
-> Show ColourMode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ColourMode] -> ShowS
$cshowList :: [ColourMode] -> ShowS
show :: ColourMode -> String
$cshow :: ColourMode -> String
showsPrec :: Int -> ColourMode -> ShowS
$cshowsPrec :: Int -> ColourMode -> ShowS
Show)
instance Flagable ColourMode where
asFlag :: ColourMode -> [Text]
asFlag ColourMode
Never = [Text
"never"]
asFlag ColourMode
Always = [Text
"always"]
asFlag ColourMode
Auto = [Text
"auto"]
data BuildConfig = BuildConfig
{ BuildConfig -> Set Makepkg
makepkgFlagsOf :: !(Set Makepkg)
, BuildConfig -> Maybe String
buildPathOf :: !(Maybe FilePath)
, BuildConfig -> Maybe User
buildUserOf :: !(Maybe User)
, BuildConfig -> Maybe String
allsourcePathOf :: !(Maybe FilePath)
, BuildConfig -> Maybe String
vcsPathOf :: !(Maybe FilePath)
, BuildConfig -> Truncation
truncationOf :: !Truncation
, BuildConfig -> Set BuildSwitch
buildSwitchesOf :: !(Set BuildSwitch) } deriving (Int -> BuildConfig -> ShowS
[BuildConfig] -> ShowS
BuildConfig -> String
(Int -> BuildConfig -> ShowS)
-> (BuildConfig -> String)
-> ([BuildConfig] -> ShowS)
-> Show BuildConfig
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BuildConfig] -> ShowS
$cshowList :: [BuildConfig] -> ShowS
show :: BuildConfig -> String
$cshow :: BuildConfig -> String
showsPrec :: Int -> BuildConfig -> ShowS
$cshowsPrec :: Int -> BuildConfig -> ShowS
Show)
buildPathOfL :: Lens' BuildConfig (Maybe FilePath)
buildPathOfL :: (Maybe String -> f (Maybe String)) -> BuildConfig -> f BuildConfig
buildPathOfL Maybe String -> f (Maybe String)
f BuildConfig
bc = (\Maybe String
bp -> BuildConfig
bc { buildPathOf :: Maybe String
buildPathOf = Maybe String
bp }) (Maybe String -> BuildConfig) -> f (Maybe String) -> f BuildConfig
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe String -> f (Maybe String)
f (BuildConfig -> Maybe String
buildPathOf BuildConfig
bc)
buildUserOfL :: Lens' BuildConfig (Maybe User)
buildUserOfL :: (Maybe User -> f (Maybe User)) -> BuildConfig -> f BuildConfig
buildUserOfL Maybe User -> f (Maybe User)
f BuildConfig
bc = (\Maybe User
bu -> BuildConfig
bc { buildUserOf :: Maybe User
buildUserOf = Maybe User
bu }) (Maybe User -> BuildConfig) -> f (Maybe User) -> f BuildConfig
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe User -> f (Maybe User)
f (BuildConfig -> Maybe User
buildUserOf BuildConfig
bc)
buildSwitchesOfL :: Lens' BuildConfig (Set BuildSwitch)
buildSwitchesOfL :: (Set BuildSwitch -> f (Set BuildSwitch))
-> BuildConfig -> f BuildConfig
buildSwitchesOfL Set BuildSwitch -> f (Set BuildSwitch)
f BuildConfig
bc = (\Set BuildSwitch
bs -> BuildConfig
bc { buildSwitchesOf :: Set BuildSwitch
buildSwitchesOf = Set BuildSwitch
bs }) (Set BuildSwitch -> BuildConfig)
-> f (Set BuildSwitch) -> f BuildConfig
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Set BuildSwitch -> f (Set BuildSwitch)
f (BuildConfig -> Set BuildSwitch
buildSwitchesOf BuildConfig
bc)
allsourcePathOfL :: Lens' BuildConfig (Maybe FilePath)
allsourcePathOfL :: (Maybe String -> f (Maybe String)) -> BuildConfig -> f BuildConfig
allsourcePathOfL Maybe String -> f (Maybe String)
f BuildConfig
bc = (\Maybe String
pth -> BuildConfig
bc { allsourcePathOf :: Maybe String
allsourcePathOf = Maybe String
pth }) (Maybe String -> BuildConfig) -> f (Maybe String) -> f BuildConfig
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe String -> f (Maybe String)
f (BuildConfig -> Maybe String
allsourcePathOf BuildConfig
bc)
vcsPathOfL :: Lens' BuildConfig (Maybe FilePath)
vcsPathOfL :: (Maybe String -> f (Maybe String)) -> BuildConfig -> f BuildConfig
vcsPathOfL Maybe String -> f (Maybe String)
f BuildConfig
bc = (\Maybe String
pth -> BuildConfig
bc { vcsPathOf :: Maybe String
vcsPathOf = Maybe String
pth }) (Maybe String -> BuildConfig) -> f (Maybe String) -> f BuildConfig
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe String -> f (Maybe String)
f (BuildConfig -> Maybe String
vcsPathOf BuildConfig
bc)
data BuildSwitch
= AsDeps
| DeleteBuildDir
| DeleteMakeDeps
| DiffPkgbuilds
| DontSuppressMakepkg
| DryRun
| ForceBuilding
| HotEdit
| LowVerbosity
| NoPkgbuildCheck
| RebuildDevel
| SkipDepCheck
| SortAlphabetically
deriving (BuildSwitch -> BuildSwitch -> Bool
(BuildSwitch -> BuildSwitch -> Bool)
-> (BuildSwitch -> BuildSwitch -> Bool) -> Eq BuildSwitch
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BuildSwitch -> BuildSwitch -> Bool
$c/= :: BuildSwitch -> BuildSwitch -> Bool
== :: BuildSwitch -> BuildSwitch -> Bool
$c== :: BuildSwitch -> BuildSwitch -> Bool
Eq, Eq BuildSwitch
Eq BuildSwitch
-> (BuildSwitch -> BuildSwitch -> Ordering)
-> (BuildSwitch -> BuildSwitch -> Bool)
-> (BuildSwitch -> BuildSwitch -> Bool)
-> (BuildSwitch -> BuildSwitch -> Bool)
-> (BuildSwitch -> BuildSwitch -> Bool)
-> (BuildSwitch -> BuildSwitch -> BuildSwitch)
-> (BuildSwitch -> BuildSwitch -> BuildSwitch)
-> Ord BuildSwitch
BuildSwitch -> BuildSwitch -> Bool
BuildSwitch -> BuildSwitch -> Ordering
BuildSwitch -> BuildSwitch -> BuildSwitch
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 :: BuildSwitch -> BuildSwitch -> BuildSwitch
$cmin :: BuildSwitch -> BuildSwitch -> BuildSwitch
max :: BuildSwitch -> BuildSwitch -> BuildSwitch
$cmax :: BuildSwitch -> BuildSwitch -> BuildSwitch
>= :: BuildSwitch -> BuildSwitch -> Bool
$c>= :: BuildSwitch -> BuildSwitch -> Bool
> :: BuildSwitch -> BuildSwitch -> Bool
$c> :: BuildSwitch -> BuildSwitch -> Bool
<= :: BuildSwitch -> BuildSwitch -> Bool
$c<= :: BuildSwitch -> BuildSwitch -> Bool
< :: BuildSwitch -> BuildSwitch -> Bool
$c< :: BuildSwitch -> BuildSwitch -> Bool
compare :: BuildSwitch -> BuildSwitch -> Ordering
$ccompare :: BuildSwitch -> BuildSwitch -> Ordering
$cp1Ord :: Eq BuildSwitch
Ord, Int -> BuildSwitch -> ShowS
[BuildSwitch] -> ShowS
BuildSwitch -> String
(Int -> BuildSwitch -> ShowS)
-> (BuildSwitch -> String)
-> ([BuildSwitch] -> ShowS)
-> Show BuildSwitch
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BuildSwitch] -> ShowS
$cshowList :: [BuildSwitch] -> ShowS
show :: BuildSwitch -> String
$cshow :: BuildSwitch -> String
showsPrec :: Int -> BuildSwitch -> ShowS
$cshowsPrec :: Int -> BuildSwitch -> ShowS
Show)
switch :: Settings -> BuildSwitch -> Bool
switch :: Settings -> BuildSwitch -> Bool
switch Settings
ss BuildSwitch
bs = BuildSwitch -> Set BuildSwitch -> Bool
forall a. Ord a => a -> Set a -> Bool
S.member BuildSwitch
bs (Set BuildSwitch -> Bool)
-> (BuildConfig -> Set BuildSwitch) -> BuildConfig -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuildConfig -> Set BuildSwitch
buildSwitchesOf (BuildConfig -> Bool) -> BuildConfig -> Bool
forall a b. (a -> b) -> a -> b
$ Settings -> BuildConfig
buildConfigOf Settings
ss
shared :: Settings -> CommonSwitch -> Bool
shared :: Settings -> CommonSwitch -> Bool
shared Settings
ss CommonSwitch
c = CommonSwitch -> Set CommonSwitch -> Bool
forall a. Ord a => a -> Set a -> Bool
S.member CommonSwitch
c (Set CommonSwitch -> Bool)
-> (CommonConfig -> Set CommonSwitch) -> CommonConfig -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CommonConfig -> Set CommonSwitch
commonSwitchesOf (CommonConfig -> Bool) -> CommonConfig -> Bool
forall a b. (a -> b) -> a -> b
$ Settings -> CommonConfig
commonConfigOf Settings
ss
data Settings = Settings
{ Settings -> Manager
managerOf :: !Manager
, Settings -> Environment
envOf :: !Environment
, Settings -> Language
langOf :: !Language
, Settings -> String
editorOf :: !FilePath
, Settings -> Bool
isTerminal :: !Bool
, Settings -> Set PkgName
ignoresOf :: !(Set PkgName)
, Settings -> CommonConfig
commonConfigOf :: !CommonConfig
, Settings -> BuildConfig
buildConfigOf :: !BuildConfig
, Settings -> LogLevel
logLevelOf :: !LogLevel
, Settings -> LogFunc
logFuncOf :: !LogFunc }
deriving stock ((forall x. Settings -> Rep Settings x)
-> (forall x. Rep Settings x -> Settings) -> Generic Settings
forall x. Rep Settings x -> Settings
forall x. Settings -> Rep Settings x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Settings x -> Settings
$cfrom :: forall x. Settings -> Rep Settings x
Generic)
logFuncOfL :: Lens' Settings LogFunc
logFuncOfL :: (LogFunc -> f LogFunc) -> Settings -> f Settings
logFuncOfL LogFunc -> f LogFunc
f Settings
s = (\LogFunc
lf -> Settings
s { logFuncOf :: LogFunc
logFuncOf = LogFunc
lf }) (LogFunc -> Settings) -> f LogFunc -> f Settings
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LogFunc -> f LogFunc
f (Settings -> LogFunc
logFuncOf Settings
s)
defaultBuildDir :: FilePath
defaultBuildDir :: String
defaultBuildDir = String
"/tmp"