module GitHUD.Config.Types (
  Config(..)
  , defaultConfig
  ) where

import System.IO.Temp (getCanonicalTemporaryDirectory)
import System.IO.Unsafe (unsafePerformIO)
import System.Posix.Daemon (Redirection(DevNull, ToFile))

import GitHUD.Terminal.Types

instance Eq Redirection where
  == :: Redirection -> Redirection -> Bool
(==) Redirection
DevNull Redirection
DevNull = Bool
True
  (==) Redirection
_ Redirection
DevNull = Bool
False
  (==) Redirection
DevNull Redirection
_ = Bool
False
  (==) (ToFile FilePath
a) (ToFile FilePath
b) = FilePath
a FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
b

data Config = Config {
    Config -> Bool
confShowPartRepoIndicator :: Bool
  , Config -> Bool
confShowPartMergeBranchCommitsDiff :: Bool
  , Config -> Bool
confShowPartLocalBranch :: Bool
  , Config -> Bool
confShowPartCommitsToOrigin :: Bool
  , Config -> Bool
confShowPartLocalChangesState :: Bool
  , Config -> Bool
confShowPartStashes :: Bool

  , Config -> FilePath
confRepoIndicator :: String

  , Config -> FilePath
confNoTrackedUpstreamString :: String
  , Config -> Color
confNoTrackedUpstreamStringColor :: Color
  , Config -> ColorIntensity
confNoTrackedUpstreamStringIntensity :: ColorIntensity
  , Config -> FilePath
confNoTrackedUpstreamIndicator :: String
  , Config -> Color
confNoTrackedUpstreamIndicatorColor :: Color
  , Config -> ColorIntensity
confNoTrackedUpstreamIndicatorIntensity :: ColorIntensity

  , Config -> FilePath
confMergeBranchCommitsIndicator :: String
  , Config -> FilePath
confMergeBranchCommitsOnlyPush :: String
  , Config -> FilePath
confMergeBranchCommitsOnlyPull :: String
  , Config -> FilePath
confMergeBranchCommitsBothPullPush :: String
  , Config -> [FilePath]
confMergeBranchIgnoreBranches :: [String]

  , Config -> FilePath
confLocalBranchNamePrefix :: String
  , Config -> FilePath
confLocalBranchNameSuffix :: String
  , Config -> FilePath
confLocalDetachedPrefix :: String
  , Config -> Color
confLocalBranchColor :: Color
  , Config -> ColorIntensity
confLocalBranchIntensity :: ColorIntensity
  , Config -> Color
confLocalDetachedColor :: Color
  , Config -> ColorIntensity
confLocalDetachedIntensity :: ColorIntensity

  , Config -> FilePath
confLocalCommitsPushSuffix :: String
  , Config -> Color
confLocalCommitsPushSuffixColor :: Color
  , Config -> ColorIntensity
confLocalCommitsPushSuffixIntensity :: ColorIntensity
  , Config -> FilePath
confLocalCommitsPullSuffix :: String
  , Config -> Color
confLocalCommitsPullSuffixColor :: Color
  , Config -> ColorIntensity
confLocalCommitsPullSuffixIntensity :: ColorIntensity
  , Config -> FilePath
confLocalCommitsPushPullInfix :: String
  , Config -> Color
confLocalCommitsPushPullInfixColor :: Color
  , Config -> ColorIntensity
confLocalCommitsPushPullInfixIntensity :: ColorIntensity

  , Config -> FilePath
confChangeIndexAddSuffix :: String
  , Config -> Color
confChangeIndexAddSuffixColor :: Color
  , Config -> ColorIntensity
confChangeIndexAddSuffixIntensity :: ColorIntensity
  , Config -> FilePath
confChangeIndexModSuffix :: String
  , Config -> Color
confChangeIndexModSuffixColor :: Color
  , Config -> ColorIntensity
confChangeIndexModSuffixIntensity :: ColorIntensity
  , Config -> FilePath
confChangeIndexDelSuffix :: String
  , Config -> Color
confChangeIndexDelSuffixColor :: Color
  , Config -> ColorIntensity
confChangeIndexDelSuffixIntensity :: ColorIntensity
  , Config -> FilePath
confChangeLocalAddSuffix :: String
  , Config -> Color
confChangeLocalAddSuffixColor :: Color
  , Config -> ColorIntensity
confChangeLocalAddSuffixIntensity :: ColorIntensity
  , Config -> FilePath
confChangeLocalModSuffix :: String
  , Config -> Color
confChangeLocalModSuffixColor :: Color
  , Config -> ColorIntensity
confChangeLocalModSuffixIntensity :: ColorIntensity
  , Config -> FilePath
confChangeLocalDelSuffix :: String
  , Config -> Color
confChangeLocalDelSuffixColor :: Color
  , Config -> ColorIntensity
confChangeLocalDelSuffixIntensity :: ColorIntensity
  , Config -> FilePath
confChangeRenamedSuffix :: String
  , Config -> Color
confChangeRenamedSuffixColor :: Color
  , Config -> ColorIntensity
confChangeRenamedSuffixIntensity :: ColorIntensity
  , Config -> FilePath
confChangeConflictedSuffix :: String
  , Config -> Color
confChangeConflictedSuffixColor :: Color
  , Config -> ColorIntensity
confChangeConflictedSuffixIntensity :: ColorIntensity

  , Config -> FilePath
confStashSuffix :: String
  , Config -> Color
confStashSuffixColor :: Color
  , Config -> ColorIntensity
confStashSuffixIntensity :: ColorIntensity

  , Config -> Bool
confRunFetcherDaemon :: Bool
  , Config -> Int
confGithuddSleepSeconds :: Int
  , Config -> FilePath
confGithuddPidFilePath :: FilePath
  , Config -> FilePath
confGithuddLockFilePath :: FilePath
  , Config -> FilePath
confGithuddSocketFilePath :: FilePath

  , Config -> Redirection
confGithuddLogFilePath :: Redirection
} deriving (Config -> Config -> Bool
(Config -> Config -> Bool)
-> (Config -> Config -> Bool) -> Eq Config
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Config -> Config -> Bool
$c/= :: Config -> Config -> Bool
== :: Config -> Config -> Bool
$c== :: Config -> Config -> Bool
Eq, Int -> Config -> ShowS
[Config] -> ShowS
Config -> FilePath
(Int -> Config -> ShowS)
-> (Config -> FilePath) -> ([Config] -> ShowS) -> Show Config
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [Config] -> ShowS
$cshowList :: [Config] -> ShowS
show :: Config -> FilePath
$cshow :: Config -> FilePath
showsPrec :: Int -> Config -> ShowS
$cshowsPrec :: Int -> Config -> ShowS
Show)

tempDir :: String
tempDir :: FilePath
tempDir = IO FilePath -> FilePath
forall a. IO a -> a
unsafePerformIO IO FilePath
getCanonicalTemporaryDirectory

defaultConfig :: Config
defaultConfig :: Config
defaultConfig = Config :: Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> FilePath
-> FilePath
-> Color
-> ColorIntensity
-> FilePath
-> Color
-> ColorIntensity
-> FilePath
-> FilePath
-> FilePath
-> FilePath
-> [FilePath]
-> FilePath
-> FilePath
-> FilePath
-> Color
-> ColorIntensity
-> Color
-> ColorIntensity
-> FilePath
-> Color
-> ColorIntensity
-> FilePath
-> Color
-> ColorIntensity
-> FilePath
-> Color
-> ColorIntensity
-> FilePath
-> Color
-> ColorIntensity
-> FilePath
-> Color
-> ColorIntensity
-> FilePath
-> Color
-> ColorIntensity
-> FilePath
-> Color
-> ColorIntensity
-> FilePath
-> Color
-> ColorIntensity
-> FilePath
-> Color
-> ColorIntensity
-> FilePath
-> Color
-> ColorIntensity
-> FilePath
-> Color
-> ColorIntensity
-> FilePath
-> Color
-> ColorIntensity
-> Bool
-> Int
-> FilePath
-> FilePath
-> FilePath
-> Redirection
-> Config
Config {
    confShowPartRepoIndicator :: Bool
confShowPartRepoIndicator = Bool
True
  , confShowPartMergeBranchCommitsDiff :: Bool
confShowPartMergeBranchCommitsDiff = Bool
True
  , confShowPartLocalBranch :: Bool
confShowPartLocalBranch = Bool
True
  , confShowPartCommitsToOrigin :: Bool
confShowPartCommitsToOrigin = Bool
True
  , confShowPartLocalChangesState :: Bool
confShowPartLocalChangesState = Bool
True
  , confShowPartStashes :: Bool
confShowPartStashes = Bool
True

  , confRepoIndicator :: FilePath
confRepoIndicator = FilePath
"ᚴ"

  , confNoTrackedUpstreamString :: FilePath
confNoTrackedUpstreamString = FilePath
"upstream"
  , confNoTrackedUpstreamStringColor :: Color
confNoTrackedUpstreamStringColor = Color
Red
  , confNoTrackedUpstreamStringIntensity :: ColorIntensity
confNoTrackedUpstreamStringIntensity = ColorIntensity
Vivid
  , confNoTrackedUpstreamIndicator :: FilePath
confNoTrackedUpstreamIndicator = FilePath
"\9889"
  , confNoTrackedUpstreamIndicatorColor :: Color
confNoTrackedUpstreamIndicatorColor = Color
Red
  , confNoTrackedUpstreamIndicatorIntensity :: ColorIntensity
confNoTrackedUpstreamIndicatorIntensity = ColorIntensity
Vivid

  , confMergeBranchCommitsIndicator :: FilePath
confMergeBranchCommitsIndicator = FilePath
"\120366"
  , confMergeBranchCommitsOnlyPush :: FilePath
confMergeBranchCommitsOnlyPush = FilePath
"\8592"
  , confMergeBranchCommitsOnlyPull :: FilePath
confMergeBranchCommitsOnlyPull = FilePath
"\8594"
  , confMergeBranchCommitsBothPullPush :: FilePath
confMergeBranchCommitsBothPullPush = FilePath
"\8644"
  , confMergeBranchIgnoreBranches :: [FilePath]
confMergeBranchIgnoreBranches = [FilePath
"gh-pages"]

  , confLocalBranchNamePrefix :: FilePath
confLocalBranchNamePrefix = FilePath
"["
  , confLocalBranchNameSuffix :: FilePath
confLocalBranchNameSuffix = FilePath
"]"
  , confLocalDetachedPrefix :: FilePath
confLocalDetachedPrefix = FilePath
"detached@"
  , confLocalBranchColor :: Color
confLocalBranchColor = Color
NoColor
  , confLocalBranchIntensity :: ColorIntensity
confLocalBranchIntensity = ColorIntensity
Vivid
  , confLocalDetachedColor :: Color
confLocalDetachedColor = Color
Yellow
  , confLocalDetachedIntensity :: ColorIntensity
confLocalDetachedIntensity = ColorIntensity
Vivid

  , confLocalCommitsPushSuffix :: FilePath
confLocalCommitsPushSuffix = FilePath
"\8593"
  , confLocalCommitsPushSuffixColor :: Color
confLocalCommitsPushSuffixColor = Color
Green
  , confLocalCommitsPushSuffixIntensity :: ColorIntensity
confLocalCommitsPushSuffixIntensity = ColorIntensity
Vivid
  , confLocalCommitsPullSuffix :: FilePath
confLocalCommitsPullSuffix = FilePath
"\8595"
  , confLocalCommitsPullSuffixColor :: Color
confLocalCommitsPullSuffixColor = Color
Red
  , confLocalCommitsPullSuffixIntensity :: ColorIntensity
confLocalCommitsPullSuffixIntensity = ColorIntensity
Vivid
  , confLocalCommitsPushPullInfix :: FilePath
confLocalCommitsPushPullInfix = FilePath
"⥯"
  , confLocalCommitsPushPullInfixColor :: Color
confLocalCommitsPushPullInfixColor = Color
Green
  , confLocalCommitsPushPullInfixIntensity :: ColorIntensity
confLocalCommitsPushPullInfixIntensity = ColorIntensity
Vivid

  , confChangeIndexAddSuffix :: FilePath
confChangeIndexAddSuffix = FilePath
"A"
  , confChangeIndexAddSuffixColor :: Color
confChangeIndexAddSuffixColor = Color
Green
  , confChangeIndexAddSuffixIntensity :: ColorIntensity
confChangeIndexAddSuffixIntensity = ColorIntensity
Vivid
  , confChangeIndexModSuffix :: FilePath
confChangeIndexModSuffix = FilePath
"M"
  , confChangeIndexModSuffixColor :: Color
confChangeIndexModSuffixColor = Color
Green
  , confChangeIndexModSuffixIntensity :: ColorIntensity
confChangeIndexModSuffixIntensity = ColorIntensity
Vivid
  , confChangeIndexDelSuffix :: FilePath
confChangeIndexDelSuffix = FilePath
"D"
  , confChangeIndexDelSuffixColor :: Color
confChangeIndexDelSuffixColor = Color
Green
  , confChangeIndexDelSuffixIntensity :: ColorIntensity
confChangeIndexDelSuffixIntensity = ColorIntensity
Vivid
  , confChangeLocalAddSuffix :: FilePath
confChangeLocalAddSuffix = FilePath
"A"
  , confChangeLocalAddSuffixColor :: Color
confChangeLocalAddSuffixColor = Color
White
  , confChangeLocalAddSuffixIntensity :: ColorIntensity
confChangeLocalAddSuffixIntensity = ColorIntensity
Vivid
  , confChangeLocalModSuffix :: FilePath
confChangeLocalModSuffix = FilePath
"M"
  , confChangeLocalModSuffixColor :: Color
confChangeLocalModSuffixColor = Color
Red
  , confChangeLocalModSuffixIntensity :: ColorIntensity
confChangeLocalModSuffixIntensity = ColorIntensity
Vivid
  , confChangeLocalDelSuffix :: FilePath
confChangeLocalDelSuffix = FilePath
"D"
  , confChangeLocalDelSuffixColor :: Color
confChangeLocalDelSuffixColor = Color
Red
  , confChangeLocalDelSuffixIntensity :: ColorIntensity
confChangeLocalDelSuffixIntensity = ColorIntensity
Vivid
  , confChangeRenamedSuffix :: FilePath
confChangeRenamedSuffix = FilePath
"R"
  , confChangeRenamedSuffixColor :: Color
confChangeRenamedSuffixColor = Color
Green
  , confChangeRenamedSuffixIntensity :: ColorIntensity
confChangeRenamedSuffixIntensity = ColorIntensity
Vivid
  , confChangeConflictedSuffix :: FilePath
confChangeConflictedSuffix = FilePath
"C"
  , confChangeConflictedSuffixColor :: Color
confChangeConflictedSuffixColor = Color
Green
  , confChangeConflictedSuffixIntensity :: ColorIntensity
confChangeConflictedSuffixIntensity = ColorIntensity
Vivid

  , confStashSuffix :: FilePath
confStashSuffix = FilePath
"≡"
  , confStashSuffixColor :: Color
confStashSuffixColor = Color
Green
  , confStashSuffixIntensity :: ColorIntensity
confStashSuffixIntensity = ColorIntensity
Vivid

  , confRunFetcherDaemon :: Bool
confRunFetcherDaemon = Bool
True
  , confGithuddSleepSeconds :: Int
confGithuddSleepSeconds = Int
30
  , confGithuddPidFilePath :: FilePath
confGithuddPidFilePath = FilePath
tempDir FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
"/githudd.pid"
  , confGithuddLockFilePath :: FilePath
confGithuddLockFilePath = FilePath
tempDir FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
"/githudd.lock"
  , confGithuddSocketFilePath :: FilePath
confGithuddSocketFilePath = FilePath
tempDir FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
"/githudd.socket"

  , confGithuddLogFilePath :: Redirection
confGithuddLogFilePath = Redirection
DevNull
}