{-# options_haddock prune #-}
module Helic.Data.NetConfig where
import Polysemy.Time.Json (json)
import Helic.Data.Host (Host)
newtype Timeout =
  Timeout { Timeout -> Int
unTimeout :: Int }
  deriving stock (Timeout -> Timeout -> Bool
(Timeout -> Timeout -> Bool)
-> (Timeout -> Timeout -> Bool) -> Eq Timeout
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Timeout -> Timeout -> Bool
$c/= :: Timeout -> Timeout -> Bool
== :: Timeout -> Timeout -> Bool
$c== :: Timeout -> Timeout -> Bool
Eq, Int -> Timeout -> ShowS
[Timeout] -> ShowS
Timeout -> String
(Int -> Timeout -> ShowS)
-> (Timeout -> String) -> ([Timeout] -> ShowS) -> Show Timeout
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Timeout] -> ShowS
$cshowList :: [Timeout] -> ShowS
show :: Timeout -> String
$cshow :: Timeout -> String
showsPrec :: Int -> Timeout -> ShowS
$cshowsPrec :: Int -> Timeout -> ShowS
Show, (forall x. Timeout -> Rep Timeout x)
-> (forall x. Rep Timeout x -> Timeout) -> Generic Timeout
forall x. Rep Timeout x -> Timeout
forall x. Timeout -> Rep Timeout x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Timeout x -> Timeout
$cfrom :: forall x. Timeout -> Rep Timeout x
Generic)
  deriving newtype (Integer -> Timeout
Timeout -> Timeout
Timeout -> Timeout -> Timeout
(Timeout -> Timeout -> Timeout)
-> (Timeout -> Timeout -> Timeout)
-> (Timeout -> Timeout -> Timeout)
-> (Timeout -> Timeout)
-> (Timeout -> Timeout)
-> (Timeout -> Timeout)
-> (Integer -> Timeout)
-> Num Timeout
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> Timeout
$cfromInteger :: Integer -> Timeout
signum :: Timeout -> Timeout
$csignum :: Timeout -> Timeout
abs :: Timeout -> Timeout
$cabs :: Timeout -> Timeout
negate :: Timeout -> Timeout
$cnegate :: Timeout -> Timeout
* :: Timeout -> Timeout -> Timeout
$c* :: Timeout -> Timeout -> Timeout
- :: Timeout -> Timeout -> Timeout
$c- :: Timeout -> Timeout -> Timeout
+ :: Timeout -> Timeout -> Timeout
$c+ :: Timeout -> Timeout -> Timeout
Num, Num Timeout
Ord Timeout
Num Timeout -> Ord Timeout -> (Timeout -> Rational) -> Real Timeout
Timeout -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: Timeout -> Rational
$ctoRational :: Timeout -> Rational
$cp2Real :: Ord Timeout
$cp1Real :: Num Timeout
Real, Int -> Timeout
Timeout -> Int
Timeout -> [Timeout]
Timeout -> Timeout
Timeout -> Timeout -> [Timeout]
Timeout -> Timeout -> Timeout -> [Timeout]
(Timeout -> Timeout)
-> (Timeout -> Timeout)
-> (Int -> Timeout)
-> (Timeout -> Int)
-> (Timeout -> [Timeout])
-> (Timeout -> Timeout -> [Timeout])
-> (Timeout -> Timeout -> [Timeout])
-> (Timeout -> Timeout -> Timeout -> [Timeout])
-> Enum Timeout
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 :: Timeout -> Timeout -> Timeout -> [Timeout]
$cenumFromThenTo :: Timeout -> Timeout -> Timeout -> [Timeout]
enumFromTo :: Timeout -> Timeout -> [Timeout]
$cenumFromTo :: Timeout -> Timeout -> [Timeout]
enumFromThen :: Timeout -> Timeout -> [Timeout]
$cenumFromThen :: Timeout -> Timeout -> [Timeout]
enumFrom :: Timeout -> [Timeout]
$cenumFrom :: Timeout -> [Timeout]
fromEnum :: Timeout -> Int
$cfromEnum :: Timeout -> Int
toEnum :: Int -> Timeout
$ctoEnum :: Int -> Timeout
pred :: Timeout -> Timeout
$cpred :: Timeout -> Timeout
succ :: Timeout -> Timeout
$csucc :: Timeout -> Timeout
Enum, Enum Timeout
Real Timeout
Real Timeout
-> Enum Timeout
-> (Timeout -> Timeout -> Timeout)
-> (Timeout -> Timeout -> Timeout)
-> (Timeout -> Timeout -> Timeout)
-> (Timeout -> Timeout -> Timeout)
-> (Timeout -> Timeout -> (Timeout, Timeout))
-> (Timeout -> Timeout -> (Timeout, Timeout))
-> (Timeout -> Integer)
-> Integral Timeout
Timeout -> Integer
Timeout -> Timeout -> (Timeout, Timeout)
Timeout -> Timeout -> Timeout
forall a.
Real a
-> Enum a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
toInteger :: Timeout -> Integer
$ctoInteger :: Timeout -> Integer
divMod :: Timeout -> Timeout -> (Timeout, Timeout)
$cdivMod :: Timeout -> Timeout -> (Timeout, Timeout)
quotRem :: Timeout -> Timeout -> (Timeout, Timeout)
$cquotRem :: Timeout -> Timeout -> (Timeout, Timeout)
mod :: Timeout -> Timeout -> Timeout
$cmod :: Timeout -> Timeout -> Timeout
div :: Timeout -> Timeout -> Timeout
$cdiv :: Timeout -> Timeout -> Timeout
rem :: Timeout -> Timeout -> Timeout
$crem :: Timeout -> Timeout -> Timeout
quot :: Timeout -> Timeout -> Timeout
$cquot :: Timeout -> Timeout -> Timeout
$cp2Integral :: Enum Timeout
$cp1Integral :: Real Timeout
Integral, Eq Timeout
Eq Timeout
-> (Timeout -> Timeout -> Ordering)
-> (Timeout -> Timeout -> Bool)
-> (Timeout -> Timeout -> Bool)
-> (Timeout -> Timeout -> Bool)
-> (Timeout -> Timeout -> Bool)
-> (Timeout -> Timeout -> Timeout)
-> (Timeout -> Timeout -> Timeout)
-> Ord Timeout
Timeout -> Timeout -> Bool
Timeout -> Timeout -> Ordering
Timeout -> Timeout -> Timeout
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 :: Timeout -> Timeout -> Timeout
$cmin :: Timeout -> Timeout -> Timeout
max :: Timeout -> Timeout -> Timeout
$cmax :: Timeout -> Timeout -> Timeout
>= :: Timeout -> Timeout -> Bool
$c>= :: Timeout -> Timeout -> Bool
> :: Timeout -> Timeout -> Bool
$c> :: Timeout -> Timeout -> Bool
<= :: Timeout -> Timeout -> Bool
$c<= :: Timeout -> Timeout -> Bool
< :: Timeout -> Timeout -> Bool
$c< :: Timeout -> Timeout -> Bool
compare :: Timeout -> Timeout -> Ordering
$ccompare :: Timeout -> Timeout -> Ordering
$cp1Ord :: Eq Timeout
Ord)
json ''Timeout
data NetConfig =
  NetConfig {
    NetConfig -> Maybe Int
port :: Maybe Int,
    NetConfig -> Maybe Timeout
timeout :: Maybe Timeout,
    NetConfig -> Maybe [Host]
hosts :: Maybe [Host]
  }
  deriving stock (NetConfig -> NetConfig -> Bool
(NetConfig -> NetConfig -> Bool)
-> (NetConfig -> NetConfig -> Bool) -> Eq NetConfig
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NetConfig -> NetConfig -> Bool
$c/= :: NetConfig -> NetConfig -> Bool
== :: NetConfig -> NetConfig -> Bool
$c== :: NetConfig -> NetConfig -> Bool
Eq, Int -> NetConfig -> ShowS
[NetConfig] -> ShowS
NetConfig -> String
(Int -> NetConfig -> ShowS)
-> (NetConfig -> String)
-> ([NetConfig] -> ShowS)
-> Show NetConfig
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NetConfig] -> ShowS
$cshowList :: [NetConfig] -> ShowS
show :: NetConfig -> String
$cshow :: NetConfig -> String
showsPrec :: Int -> NetConfig -> ShowS
$cshowsPrec :: Int -> NetConfig -> ShowS
Show, (forall x. NetConfig -> Rep NetConfig x)
-> (forall x. Rep NetConfig x -> NetConfig) -> Generic NetConfig
forall x. Rep NetConfig x -> NetConfig
forall x. NetConfig -> Rep NetConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep NetConfig x -> NetConfig
$cfrom :: forall x. NetConfig -> Rep NetConfig x
Generic)
  deriving anyclass (NetConfig
NetConfig -> Default NetConfig
forall a. a -> Default a
def :: NetConfig
$cdef :: NetConfig
Default)
json ''NetConfig