module Hix.Data.GhciConfig where

import Data.Aeson (FromJSON, FromJSONKey)
import GHC.Exts (IsList)

import Hix.Data.ComponentConfig (EnvRunner, PackagesConfig)

newtype RunnerName =
  RunnerName { RunnerName -> Text
unRunnerName :: Text }
  deriving stock (RunnerName -> RunnerName -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RunnerName -> RunnerName -> Bool
$c/= :: RunnerName -> RunnerName -> Bool
== :: RunnerName -> RunnerName -> Bool
$c== :: RunnerName -> RunnerName -> Bool
Eq, Int -> RunnerName -> ShowS
[RunnerName] -> ShowS
RunnerName -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RunnerName] -> ShowS
$cshowList :: [RunnerName] -> ShowS
show :: RunnerName -> String
$cshow :: RunnerName -> String
showsPrec :: Int -> RunnerName -> ShowS
$cshowsPrec :: Int -> RunnerName -> ShowS
Show, forall x. Rep RunnerName x -> RunnerName
forall x. RunnerName -> Rep RunnerName x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RunnerName x -> RunnerName
$cfrom :: forall x. RunnerName -> Rep RunnerName x
Generic)
  deriving newtype (String -> RunnerName
forall a. (String -> a) -> IsString a
fromString :: String -> RunnerName
$cfromString :: String -> RunnerName
IsString, Eq RunnerName
RunnerName -> RunnerName -> Bool
RunnerName -> RunnerName -> Ordering
RunnerName -> RunnerName -> RunnerName
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 :: RunnerName -> RunnerName -> RunnerName
$cmin :: RunnerName -> RunnerName -> RunnerName
max :: RunnerName -> RunnerName -> RunnerName
$cmax :: RunnerName -> RunnerName -> RunnerName
>= :: RunnerName -> RunnerName -> Bool
$c>= :: RunnerName -> RunnerName -> Bool
> :: RunnerName -> RunnerName -> Bool
$c> :: RunnerName -> RunnerName -> Bool
<= :: RunnerName -> RunnerName -> Bool
$c<= :: RunnerName -> RunnerName -> Bool
< :: RunnerName -> RunnerName -> Bool
$c< :: RunnerName -> RunnerName -> Bool
compare :: RunnerName -> RunnerName -> Ordering
$ccompare :: RunnerName -> RunnerName -> Ordering
Ord, FromJSONKeyFunction [RunnerName]
FromJSONKeyFunction RunnerName
forall a.
FromJSONKeyFunction a -> FromJSONKeyFunction [a] -> FromJSONKey a
fromJSONKeyList :: FromJSONKeyFunction [RunnerName]
$cfromJSONKeyList :: FromJSONKeyFunction [RunnerName]
fromJSONKey :: FromJSONKeyFunction RunnerName
$cfromJSONKey :: FromJSONKeyFunction RunnerName
FromJSONKey)

newtype GhciSetupCode =
  GhciSetupCode { GhciSetupCode -> Text
unGhciSetupCode :: Text }
  deriving stock (GhciSetupCode -> GhciSetupCode -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GhciSetupCode -> GhciSetupCode -> Bool
$c/= :: GhciSetupCode -> GhciSetupCode -> Bool
== :: GhciSetupCode -> GhciSetupCode -> Bool
$c== :: GhciSetupCode -> GhciSetupCode -> Bool
Eq, Int -> GhciSetupCode -> ShowS
[GhciSetupCode] -> ShowS
GhciSetupCode -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GhciSetupCode] -> ShowS
$cshowList :: [GhciSetupCode] -> ShowS
show :: GhciSetupCode -> String
$cshow :: GhciSetupCode -> String
showsPrec :: Int -> GhciSetupCode -> ShowS
$cshowsPrec :: Int -> GhciSetupCode -> ShowS
Show, forall x. Rep GhciSetupCode x -> GhciSetupCode
forall x. GhciSetupCode -> Rep GhciSetupCode x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GhciSetupCode x -> GhciSetupCode
$cfrom :: forall x. GhciSetupCode -> Rep GhciSetupCode x
Generic)
  deriving newtype (String -> GhciSetupCode
forall a. (String -> a) -> IsString a
fromString :: String -> GhciSetupCode
$cfromString :: String -> GhciSetupCode
IsString, Eq GhciSetupCode
GhciSetupCode -> GhciSetupCode -> Bool
GhciSetupCode -> GhciSetupCode -> Ordering
GhciSetupCode -> GhciSetupCode -> GhciSetupCode
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 :: GhciSetupCode -> GhciSetupCode -> GhciSetupCode
$cmin :: GhciSetupCode -> GhciSetupCode -> GhciSetupCode
max :: GhciSetupCode -> GhciSetupCode -> GhciSetupCode
$cmax :: GhciSetupCode -> GhciSetupCode -> GhciSetupCode
>= :: GhciSetupCode -> GhciSetupCode -> Bool
$c>= :: GhciSetupCode -> GhciSetupCode -> Bool
> :: GhciSetupCode -> GhciSetupCode -> Bool
$c> :: GhciSetupCode -> GhciSetupCode -> Bool
<= :: GhciSetupCode -> GhciSetupCode -> Bool
$c<= :: GhciSetupCode -> GhciSetupCode -> Bool
< :: GhciSetupCode -> GhciSetupCode -> Bool
$c< :: GhciSetupCode -> GhciSetupCode -> Bool
compare :: GhciSetupCode -> GhciSetupCode -> Ordering
$ccompare :: GhciSetupCode -> GhciSetupCode -> Ordering
Ord, Value -> Parser [GhciSetupCode]
Value -> Parser GhciSetupCode
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [GhciSetupCode]
$cparseJSONList :: Value -> Parser [GhciSetupCode]
parseJSON :: Value -> Parser GhciSetupCode
$cparseJSON :: Value -> Parser GhciSetupCode
FromJSON, NonEmpty GhciSetupCode -> GhciSetupCode
GhciSetupCode -> GhciSetupCode -> GhciSetupCode
forall b. Integral b => b -> GhciSetupCode -> GhciSetupCode
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
stimes :: forall b. Integral b => b -> GhciSetupCode -> GhciSetupCode
$cstimes :: forall b. Integral b => b -> GhciSetupCode -> GhciSetupCode
sconcat :: NonEmpty GhciSetupCode -> GhciSetupCode
$csconcat :: NonEmpty GhciSetupCode -> GhciSetupCode
<> :: GhciSetupCode -> GhciSetupCode -> GhciSetupCode
$c<> :: GhciSetupCode -> GhciSetupCode -> GhciSetupCode
Semigroup, Semigroup GhciSetupCode
GhciSetupCode
[GhciSetupCode] -> GhciSetupCode
GhciSetupCode -> GhciSetupCode -> GhciSetupCode
forall a.
Semigroup a -> a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
mconcat :: [GhciSetupCode] -> GhciSetupCode
$cmconcat :: [GhciSetupCode] -> GhciSetupCode
mappend :: GhciSetupCode -> GhciSetupCode -> GhciSetupCode
$cmappend :: GhciSetupCode -> GhciSetupCode -> GhciSetupCode
mempty :: GhciSetupCode
$cmempty :: GhciSetupCode
Monoid)

newtype GhciRunExpr =
  GhciRunExpr { GhciRunExpr -> Text
unGhciRunExpr :: Text }
  deriving stock (GhciRunExpr -> GhciRunExpr -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GhciRunExpr -> GhciRunExpr -> Bool
$c/= :: GhciRunExpr -> GhciRunExpr -> Bool
== :: GhciRunExpr -> GhciRunExpr -> Bool
$c== :: GhciRunExpr -> GhciRunExpr -> Bool
Eq, Int -> GhciRunExpr -> ShowS
[GhciRunExpr] -> ShowS
GhciRunExpr -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GhciRunExpr] -> ShowS
$cshowList :: [GhciRunExpr] -> ShowS
show :: GhciRunExpr -> String
$cshow :: GhciRunExpr -> String
showsPrec :: Int -> GhciRunExpr -> ShowS
$cshowsPrec :: Int -> GhciRunExpr -> ShowS
Show, forall x. Rep GhciRunExpr x -> GhciRunExpr
forall x. GhciRunExpr -> Rep GhciRunExpr x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GhciRunExpr x -> GhciRunExpr
$cfrom :: forall x. GhciRunExpr -> Rep GhciRunExpr x
Generic)
  deriving newtype (String -> GhciRunExpr
forall a. (String -> a) -> IsString a
fromString :: String -> GhciRunExpr
$cfromString :: String -> GhciRunExpr
IsString, Eq GhciRunExpr
GhciRunExpr -> GhciRunExpr -> Bool
GhciRunExpr -> GhciRunExpr -> Ordering
GhciRunExpr -> GhciRunExpr -> GhciRunExpr
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 :: GhciRunExpr -> GhciRunExpr -> GhciRunExpr
$cmin :: GhciRunExpr -> GhciRunExpr -> GhciRunExpr
max :: GhciRunExpr -> GhciRunExpr -> GhciRunExpr
$cmax :: GhciRunExpr -> GhciRunExpr -> GhciRunExpr
>= :: GhciRunExpr -> GhciRunExpr -> Bool
$c>= :: GhciRunExpr -> GhciRunExpr -> Bool
> :: GhciRunExpr -> GhciRunExpr -> Bool
$c> :: GhciRunExpr -> GhciRunExpr -> Bool
<= :: GhciRunExpr -> GhciRunExpr -> Bool
$c<= :: GhciRunExpr -> GhciRunExpr -> Bool
< :: GhciRunExpr -> GhciRunExpr -> Bool
$c< :: GhciRunExpr -> GhciRunExpr -> Bool
compare :: GhciRunExpr -> GhciRunExpr -> Ordering
$ccompare :: GhciRunExpr -> GhciRunExpr -> Ordering
Ord, Value -> Parser [GhciRunExpr]
Value -> Parser GhciRunExpr
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [GhciRunExpr]
$cparseJSONList :: Value -> Parser [GhciRunExpr]
parseJSON :: Value -> Parser GhciRunExpr
$cparseJSON :: Value -> Parser GhciRunExpr
FromJSON)

newtype GhciArgs =
  GhciArgs { GhciArgs -> [Text]
unGhciArgs :: [Text] }
  deriving stock (GhciArgs -> GhciArgs -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GhciArgs -> GhciArgs -> Bool
$c/= :: GhciArgs -> GhciArgs -> Bool
== :: GhciArgs -> GhciArgs -> Bool
$c== :: GhciArgs -> GhciArgs -> Bool
Eq, Int -> GhciArgs -> ShowS
[GhciArgs] -> ShowS
GhciArgs -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GhciArgs] -> ShowS
$cshowList :: [GhciArgs] -> ShowS
show :: GhciArgs -> String
$cshow :: GhciArgs -> String
showsPrec :: Int -> GhciArgs -> ShowS
$cshowsPrec :: Int -> GhciArgs -> ShowS
Show, forall x. Rep GhciArgs x -> GhciArgs
forall x. GhciArgs -> Rep GhciArgs x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GhciArgs x -> GhciArgs
$cfrom :: forall x. GhciArgs -> Rep GhciArgs x
Generic)
  deriving newtype (Int -> [Item GhciArgs] -> GhciArgs
[Item GhciArgs] -> GhciArgs
GhciArgs -> [Item GhciArgs]
forall l.
([Item l] -> l)
-> (Int -> [Item l] -> l) -> (l -> [Item l]) -> IsList l
toList :: GhciArgs -> [Item GhciArgs]
$ctoList :: GhciArgs -> [Item GhciArgs]
fromListN :: Int -> [Item GhciArgs] -> GhciArgs
$cfromListN :: Int -> [Item GhciArgs] -> GhciArgs
fromList :: [Item GhciArgs] -> GhciArgs
$cfromList :: [Item GhciArgs] -> GhciArgs
IsList, Eq GhciArgs
GhciArgs -> GhciArgs -> Bool
GhciArgs -> GhciArgs -> Ordering
GhciArgs -> GhciArgs -> GhciArgs
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 :: GhciArgs -> GhciArgs -> GhciArgs
$cmin :: GhciArgs -> GhciArgs -> GhciArgs
max :: GhciArgs -> GhciArgs -> GhciArgs
$cmax :: GhciArgs -> GhciArgs -> GhciArgs
>= :: GhciArgs -> GhciArgs -> Bool
$c>= :: GhciArgs -> GhciArgs -> Bool
> :: GhciArgs -> GhciArgs -> Bool
$c> :: GhciArgs -> GhciArgs -> Bool
<= :: GhciArgs -> GhciArgs -> Bool
$c<= :: GhciArgs -> GhciArgs -> Bool
< :: GhciArgs -> GhciArgs -> Bool
$c< :: GhciArgs -> GhciArgs -> Bool
compare :: GhciArgs -> GhciArgs -> Ordering
$ccompare :: GhciArgs -> GhciArgs -> Ordering
Ord, Value -> Parser [GhciArgs]
Value -> Parser GhciArgs
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [GhciArgs]
$cparseJSONList :: Value -> Parser [GhciArgs]
parseJSON :: Value -> Parser GhciArgs
$cparseJSON :: Value -> Parser GhciArgs
FromJSON)

newtype ChangeDir =
  ChangeDir { ChangeDir -> Bool
unChangeDir :: Bool }
  deriving stock (ChangeDir -> ChangeDir -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ChangeDir -> ChangeDir -> Bool
$c/= :: ChangeDir -> ChangeDir -> Bool
== :: ChangeDir -> ChangeDir -> Bool
$c== :: ChangeDir -> ChangeDir -> Bool
Eq, Int -> ChangeDir -> ShowS
[ChangeDir] -> ShowS
ChangeDir -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChangeDir] -> ShowS
$cshowList :: [ChangeDir] -> ShowS
show :: ChangeDir -> String
$cshow :: ChangeDir -> String
showsPrec :: Int -> ChangeDir -> ShowS
$cshowsPrec :: Int -> ChangeDir -> ShowS
Show, forall x. Rep ChangeDir x -> ChangeDir
forall x. ChangeDir -> Rep ChangeDir x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ChangeDir x -> ChangeDir
$cfrom :: forall x. ChangeDir -> Rep ChangeDir x
Generic)

data EnvConfig =
  EnvConfig {
    EnvConfig -> PackagesConfig
packages :: PackagesConfig,
    EnvConfig -> EnvRunner
defaultEnv :: EnvRunner
  }
  deriving stock (EnvConfig -> EnvConfig -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EnvConfig -> EnvConfig -> Bool
$c/= :: EnvConfig -> EnvConfig -> Bool
== :: EnvConfig -> EnvConfig -> Bool
$c== :: EnvConfig -> EnvConfig -> Bool
Eq, Int -> EnvConfig -> ShowS
[EnvConfig] -> ShowS
EnvConfig -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EnvConfig] -> ShowS
$cshowList :: [EnvConfig] -> ShowS
show :: EnvConfig -> String
$cshow :: EnvConfig -> String
showsPrec :: Int -> EnvConfig -> ShowS
$cshowsPrec :: Int -> EnvConfig -> ShowS
Show, forall x. Rep EnvConfig x -> EnvConfig
forall x. EnvConfig -> Rep EnvConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EnvConfig x -> EnvConfig
$cfrom :: forall x. EnvConfig -> Rep EnvConfig x
Generic)
  deriving anyclass (Value -> Parser [EnvConfig]
Value -> Parser EnvConfig
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [EnvConfig]
$cparseJSONList :: Value -> Parser [EnvConfig]
parseJSON :: Value -> Parser EnvConfig
$cparseJSON :: Value -> Parser EnvConfig
FromJSON)

data GhciConfig =
  GhciConfig {
    GhciConfig -> PackagesConfig
packages :: PackagesConfig,
    GhciConfig -> Map RunnerName GhciSetupCode
setup :: Map RunnerName GhciSetupCode,
    GhciConfig -> Map RunnerName GhciRunExpr
run :: Map RunnerName GhciRunExpr,
    GhciConfig -> GhciArgs
args :: GhciArgs
  }
  deriving stock (GhciConfig -> GhciConfig -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GhciConfig -> GhciConfig -> Bool
$c/= :: GhciConfig -> GhciConfig -> Bool
== :: GhciConfig -> GhciConfig -> Bool
$c== :: GhciConfig -> GhciConfig -> Bool
Eq, Int -> GhciConfig -> ShowS
[GhciConfig] -> ShowS
GhciConfig -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GhciConfig] -> ShowS
$cshowList :: [GhciConfig] -> ShowS
show :: GhciConfig -> String
$cshow :: GhciConfig -> String
showsPrec :: Int -> GhciConfig -> ShowS
$cshowsPrec :: Int -> GhciConfig -> ShowS
Show, forall x. Rep GhciConfig x -> GhciConfig
forall x. GhciConfig -> Rep GhciConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GhciConfig x -> GhciConfig
$cfrom :: forall x. GhciConfig -> Rep GhciConfig x
Generic)
  deriving anyclass (Value -> Parser [GhciConfig]
Value -> Parser GhciConfig
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [GhciConfig]
$cparseJSONList :: Value -> Parser [GhciConfig]
parseJSON :: Value -> Parser GhciConfig
$cparseJSON :: Value -> Parser GhciConfig
FromJSON)