{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE UndecidableInstances #-}
module Database.Bloodhound.Internal.Client where
import Bloodhound.Import
import qualified Data.Aeson.KeyMap as X
import qualified Data.HashMap.Strict as HM
import Data.Map.Strict (Map)
import Data.Maybe (mapMaybe)
import qualified Data.SemVer as SemVer
import qualified Data.Text as T
import qualified Data.Traversable as DT
import qualified Data.Vector as V
import GHC.Enum
import Network.HTTP.Client
import Text.Read (Read (..))
import qualified Text.Read as TR
import Database.Bloodhound.Internal.Analysis
import Database.Bloodhound.Internal.Newtypes
import Database.Bloodhound.Internal.Query
import Database.Bloodhound.Internal.StringlyTyped
data BHEnv = BHEnv { BHEnv -> Server
bhServer :: Server
, BHEnv -> Manager
bhManager :: Manager
, BHEnv -> Request -> IO Request
bhRequestHook :: Request -> IO Request
}
instance (Functor m, Applicative m, MonadIO m) => MonadBH (ReaderT BHEnv m) where
getBHEnv :: ReaderT BHEnv m BHEnv
getBHEnv = ReaderT BHEnv m BHEnv
forall r (m :: * -> *). MonadReader r m => m r
ask
newtype Server = Server Text deriving (Server -> Server -> Bool
(Server -> Server -> Bool)
-> (Server -> Server -> Bool) -> Eq Server
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Server -> Server -> Bool
$c/= :: Server -> Server -> Bool
== :: Server -> Server -> Bool
$c== :: Server -> Server -> Bool
Eq, Int -> Server -> ShowS
[Server] -> ShowS
Server -> String
(Int -> Server -> ShowS)
-> (Server -> String) -> ([Server] -> ShowS) -> Show Server
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Server] -> ShowS
$cshowList :: [Server] -> ShowS
show :: Server -> String
$cshow :: Server -> String
showsPrec :: Int -> Server -> ShowS
$cshowsPrec :: Int -> Server -> ShowS
Show, Value -> Parser [Server]
Value -> Parser Server
(Value -> Parser Server)
-> (Value -> Parser [Server]) -> FromJSON Server
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [Server]
$cparseJSONList :: Value -> Parser [Server]
parseJSON :: Value -> Parser Server
$cparseJSON :: Value -> Parser Server
FromJSON)
class (Functor m, Applicative m, MonadIO m) => MonadBH m where
getBHEnv :: m BHEnv
mkBHEnv :: Server -> Manager -> BHEnv
mkBHEnv :: Server -> Manager -> BHEnv
mkBHEnv Server
s Manager
m = Server -> Manager -> (Request -> IO Request) -> BHEnv
BHEnv Server
s Manager
m Request -> IO Request
forall (m :: * -> *) a. Monad m => a -> m a
return
newtype BH m a = BH {
BH m a -> ReaderT BHEnv m a
unBH :: ReaderT BHEnv m a
} deriving ( a -> BH m b -> BH m a
(a -> b) -> BH m a -> BH m b
(forall a b. (a -> b) -> BH m a -> BH m b)
-> (forall a b. a -> BH m b -> BH m a) -> Functor (BH m)
forall a b. a -> BH m b -> BH m a
forall a b. (a -> b) -> BH m a -> BH m b
forall (m :: * -> *) a b. Functor m => a -> BH m b -> BH m a
forall (m :: * -> *) a b. Functor m => (a -> b) -> BH m a -> BH m b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> BH m b -> BH m a
$c<$ :: forall (m :: * -> *) a b. Functor m => a -> BH m b -> BH m a
fmap :: (a -> b) -> BH m a -> BH m b
$cfmap :: forall (m :: * -> *) a b. Functor m => (a -> b) -> BH m a -> BH m b
Functor
, Functor (BH m)
a -> BH m a
Functor (BH m)
-> (forall a. a -> BH m a)
-> (forall a b. BH m (a -> b) -> BH m a -> BH m b)
-> (forall a b c. (a -> b -> c) -> BH m a -> BH m b -> BH m c)
-> (forall a b. BH m a -> BH m b -> BH m b)
-> (forall a b. BH m a -> BH m b -> BH m a)
-> Applicative (BH m)
BH m a -> BH m b -> BH m b
BH m a -> BH m b -> BH m a
BH m (a -> b) -> BH m a -> BH m b
(a -> b -> c) -> BH m a -> BH m b -> BH m c
forall a. a -> BH m a
forall a b. BH m a -> BH m b -> BH m a
forall a b. BH m a -> BH m b -> BH m b
forall a b. BH m (a -> b) -> BH m a -> BH m b
forall a b c. (a -> b -> c) -> BH m a -> BH m b -> BH m c
forall (f :: * -> *).
Functor f
-> (forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
forall (m :: * -> *). Applicative m => Functor (BH m)
forall (m :: * -> *) a. Applicative m => a -> BH m a
forall (m :: * -> *) a b.
Applicative m =>
BH m a -> BH m b -> BH m a
forall (m :: * -> *) a b.
Applicative m =>
BH m a -> BH m b -> BH m b
forall (m :: * -> *) a b.
Applicative m =>
BH m (a -> b) -> BH m a -> BH m b
forall (m :: * -> *) a b c.
Applicative m =>
(a -> b -> c) -> BH m a -> BH m b -> BH m c
<* :: BH m a -> BH m b -> BH m a
$c<* :: forall (m :: * -> *) a b.
Applicative m =>
BH m a -> BH m b -> BH m a
*> :: BH m a -> BH m b -> BH m b
$c*> :: forall (m :: * -> *) a b.
Applicative m =>
BH m a -> BH m b -> BH m b
liftA2 :: (a -> b -> c) -> BH m a -> BH m b -> BH m c
$cliftA2 :: forall (m :: * -> *) a b c.
Applicative m =>
(a -> b -> c) -> BH m a -> BH m b -> BH m c
<*> :: BH m (a -> b) -> BH m a -> BH m b
$c<*> :: forall (m :: * -> *) a b.
Applicative m =>
BH m (a -> b) -> BH m a -> BH m b
pure :: a -> BH m a
$cpure :: forall (m :: * -> *) a. Applicative m => a -> BH m a
$cp1Applicative :: forall (m :: * -> *). Applicative m => Functor (BH m)
Applicative
, Applicative (BH m)
a -> BH m a
Applicative (BH m)
-> (forall a b. BH m a -> (a -> BH m b) -> BH m b)
-> (forall a b. BH m a -> BH m b -> BH m b)
-> (forall a. a -> BH m a)
-> Monad (BH m)
BH m a -> (a -> BH m b) -> BH m b
BH m a -> BH m b -> BH m b
forall a. a -> BH m a
forall a b. BH m a -> BH m b -> BH m b
forall a b. BH m a -> (a -> BH m b) -> BH m b
forall (m :: * -> *). Monad m => Applicative (BH m)
forall (m :: * -> *) a. Monad m => a -> BH m a
forall (m :: * -> *) a b. Monad m => BH m a -> BH m b -> BH m b
forall (m :: * -> *) a b.
Monad m =>
BH m a -> (a -> BH m b) -> BH m b
forall (m :: * -> *).
Applicative m
-> (forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
return :: a -> BH m a
$creturn :: forall (m :: * -> *) a. Monad m => a -> BH m a
>> :: BH m a -> BH m b -> BH m b
$c>> :: forall (m :: * -> *) a b. Monad m => BH m a -> BH m b -> BH m b
>>= :: BH m a -> (a -> BH m b) -> BH m b
$c>>= :: forall (m :: * -> *) a b.
Monad m =>
BH m a -> (a -> BH m b) -> BH m b
$cp1Monad :: forall (m :: * -> *). Monad m => Applicative (BH m)
Monad
, Monad (BH m)
Monad (BH m) -> (forall a. IO a -> BH m a) -> MonadIO (BH m)
IO a -> BH m a
forall a. IO a -> BH m a
forall (m :: * -> *).
Monad m -> (forall a. IO a -> m a) -> MonadIO m
forall (m :: * -> *). MonadIO m => Monad (BH m)
forall (m :: * -> *) a. MonadIO m => IO a -> BH m a
liftIO :: IO a -> BH m a
$cliftIO :: forall (m :: * -> *) a. MonadIO m => IO a -> BH m a
$cp1MonadIO :: forall (m :: * -> *). MonadIO m => Monad (BH m)
MonadIO
, MonadState s
, MonadWriter w
, MonadError e
, Applicative (BH m)
BH m a
Applicative (BH m)
-> (forall a. BH m a)
-> (forall a. BH m a -> BH m a -> BH m a)
-> (forall a. BH m a -> BH m [a])
-> (forall a. BH m a -> BH m [a])
-> Alternative (BH m)
BH m a -> BH m a -> BH m a
BH m a -> BH m [a]
BH m a -> BH m [a]
forall a. BH m a
forall a. BH m a -> BH m [a]
forall a. BH m a -> BH m a -> BH m a
forall (f :: * -> *).
Applicative f
-> (forall a. f a)
-> (forall a. f a -> f a -> f a)
-> (forall a. f a -> f [a])
-> (forall a. f a -> f [a])
-> Alternative f
forall (m :: * -> *). Alternative m => Applicative (BH m)
forall (m :: * -> *) a. Alternative m => BH m a
forall (m :: * -> *) a. Alternative m => BH m a -> BH m [a]
forall (m :: * -> *) a. Alternative m => BH m a -> BH m a -> BH m a
many :: BH m a -> BH m [a]
$cmany :: forall (m :: * -> *) a. Alternative m => BH m a -> BH m [a]
some :: BH m a -> BH m [a]
$csome :: forall (m :: * -> *) a. Alternative m => BH m a -> BH m [a]
<|> :: BH m a -> BH m a -> BH m a
$c<|> :: forall (m :: * -> *) a. Alternative m => BH m a -> BH m a -> BH m a
empty :: BH m a
$cempty :: forall (m :: * -> *) a. Alternative m => BH m a
$cp1Alternative :: forall (m :: * -> *). Alternative m => Applicative (BH m)
Alternative
, Monad (BH m)
Alternative (BH m)
BH m a
Alternative (BH m)
-> Monad (BH m)
-> (forall a. BH m a)
-> (forall a. BH m a -> BH m a -> BH m a)
-> MonadPlus (BH m)
BH m a -> BH m a -> BH m a
forall a. BH m a
forall a. BH m a -> BH m a -> BH m a
forall (m :: * -> *).
Alternative m
-> Monad m
-> (forall a. m a)
-> (forall a. m a -> m a -> m a)
-> MonadPlus m
forall (m :: * -> *). MonadPlus m => Monad (BH m)
forall (m :: * -> *). MonadPlus m => Alternative (BH m)
forall (m :: * -> *) a. MonadPlus m => BH m a
forall (m :: * -> *) a. MonadPlus m => BH m a -> BH m a -> BH m a
mplus :: BH m a -> BH m a -> BH m a
$cmplus :: forall (m :: * -> *) a. MonadPlus m => BH m a -> BH m a -> BH m a
mzero :: BH m a
$cmzero :: forall (m :: * -> *) a. MonadPlus m => BH m a
$cp2MonadPlus :: forall (m :: * -> *). MonadPlus m => Monad (BH m)
$cp1MonadPlus :: forall (m :: * -> *). MonadPlus m => Alternative (BH m)
MonadPlus
, Monad (BH m)
Monad (BH m)
-> (forall a. (a -> BH m a) -> BH m a) -> MonadFix (BH m)
(a -> BH m a) -> BH m a
forall a. (a -> BH m a) -> BH m a
forall (m :: * -> *).
Monad m -> (forall a. (a -> m a) -> m a) -> MonadFix m
forall (m :: * -> *). MonadFix m => Monad (BH m)
forall (m :: * -> *) a. MonadFix m => (a -> BH m a) -> BH m a
mfix :: (a -> BH m a) -> BH m a
$cmfix :: forall (m :: * -> *) a. MonadFix m => (a -> BH m a) -> BH m a
$cp1MonadFix :: forall (m :: * -> *). MonadFix m => Monad (BH m)
MonadFix
, Monad (BH m)
e -> BH m a
Monad (BH m)
-> (forall e a. Exception e => e -> BH m a) -> MonadThrow (BH m)
forall e a. Exception e => e -> BH m a
forall (m :: * -> *).
Monad m -> (forall e a. Exception e => e -> m a) -> MonadThrow m
forall (m :: * -> *). MonadThrow m => Monad (BH m)
forall (m :: * -> *) e a.
(MonadThrow m, Exception e) =>
e -> BH m a
throwM :: e -> BH m a
$cthrowM :: forall (m :: * -> *) e a.
(MonadThrow m, Exception e) =>
e -> BH m a
$cp1MonadThrow :: forall (m :: * -> *). MonadThrow m => Monad (BH m)
MonadThrow
, MonadThrow (BH m)
MonadThrow (BH m)
-> (forall e a. Exception e => BH m a -> (e -> BH m a) -> BH m a)
-> MonadCatch (BH m)
BH m a -> (e -> BH m a) -> BH m a
forall e a. Exception e => BH m a -> (e -> BH m a) -> BH m a
forall (m :: * -> *).
MonadThrow m
-> (forall e a. Exception e => m a -> (e -> m a) -> m a)
-> MonadCatch m
forall (m :: * -> *). MonadCatch m => MonadThrow (BH m)
forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
BH m a -> (e -> BH m a) -> BH m a
catch :: BH m a -> (e -> BH m a) -> BH m a
$ccatch :: forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
BH m a -> (e -> BH m a) -> BH m a
$cp1MonadCatch :: forall (m :: * -> *). MonadCatch m => MonadThrow (BH m)
MonadCatch
#if defined(MIN_VERSION_GLASGOW_HASKELL)
#if MIN_VERSION_GLASGOW_HASKELL(8,6,0,0)
, Monad (BH m)
Monad (BH m) -> (forall a. String -> BH m a) -> MonadFail (BH m)
String -> BH m a
forall a. String -> BH m a
forall (m :: * -> *).
Monad m -> (forall a. String -> m a) -> MonadFail m
forall (m :: * -> *). MonadFail m => Monad (BH m)
forall (m :: * -> *) a. MonadFail m => String -> BH m a
fail :: String -> BH m a
$cfail :: forall (m :: * -> *) a. MonadFail m => String -> BH m a
$cp1MonadFail :: forall (m :: * -> *). MonadFail m => Monad (BH m)
MonadFail
#endif
#endif
, MonadCatch (BH m)
MonadCatch (BH m)
-> (forall b. ((forall a. BH m a -> BH m a) -> BH m b) -> BH m b)
-> (forall b. ((forall a. BH m a -> BH m a) -> BH m b) -> BH m b)
-> (forall a b c.
BH m a
-> (a -> ExitCase b -> BH m c) -> (a -> BH m b) -> BH m (b, c))
-> MonadMask (BH m)
BH m a
-> (a -> ExitCase b -> BH m c) -> (a -> BH m b) -> BH m (b, c)
((forall a. BH m a -> BH m a) -> BH m b) -> BH m b
((forall a. BH m a -> BH m a) -> BH m b) -> BH m b
forall b. ((forall a. BH m a -> BH m a) -> BH m b) -> BH m b
forall a b c.
BH m a
-> (a -> ExitCase b -> BH m c) -> (a -> BH m b) -> BH m (b, c)
forall (m :: * -> *).
MonadCatch m
-> (forall b. ((forall a. m a -> m a) -> m b) -> m b)
-> (forall b. ((forall a. m a -> m a) -> m b) -> m b)
-> (forall a b c.
m a -> (a -> ExitCase b -> m c) -> (a -> m b) -> m (b, c))
-> MonadMask m
forall (m :: * -> *). MonadMask m => MonadCatch (BH m)
forall (m :: * -> *) b.
MonadMask m =>
((forall a. BH m a -> BH m a) -> BH m b) -> BH m b
forall (m :: * -> *) a b c.
MonadMask m =>
BH m a
-> (a -> ExitCase b -> BH m c) -> (a -> BH m b) -> BH m (b, c)
generalBracket :: BH m a
-> (a -> ExitCase b -> BH m c) -> (a -> BH m b) -> BH m (b, c)
$cgeneralBracket :: forall (m :: * -> *) a b c.
MonadMask m =>
BH m a
-> (a -> ExitCase b -> BH m c) -> (a -> BH m b) -> BH m (b, c)
uninterruptibleMask :: ((forall a. BH m a -> BH m a) -> BH m b) -> BH m b
$cuninterruptibleMask :: forall (m :: * -> *) b.
MonadMask m =>
((forall a. BH m a -> BH m a) -> BH m b) -> BH m b
mask :: ((forall a. BH m a -> BH m a) -> BH m b) -> BH m b
$cmask :: forall (m :: * -> *) b.
MonadMask m =>
((forall a. BH m a -> BH m a) -> BH m b) -> BH m b
$cp1MonadMask :: forall (m :: * -> *). MonadMask m => MonadCatch (BH m)
MonadMask)
instance MonadTrans BH where
lift :: m a -> BH m a
lift = ReaderT BHEnv m a -> BH m a
forall (m :: * -> *) a. ReaderT BHEnv m a -> BH m a
BH (ReaderT BHEnv m a -> BH m a)
-> (m a -> ReaderT BHEnv m a) -> m a -> BH m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. m a -> ReaderT BHEnv m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift
instance (MonadReader r m) => MonadReader r (BH m) where
ask :: BH m r
ask = m r -> BH m r
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift m r
forall r (m :: * -> *). MonadReader r m => m r
ask
local :: (r -> r) -> BH m a -> BH m a
local r -> r
f (BH (ReaderT BHEnv -> m a
m)) = ReaderT BHEnv m a -> BH m a
forall (m :: * -> *) a. ReaderT BHEnv m a -> BH m a
BH (ReaderT BHEnv m a -> BH m a) -> ReaderT BHEnv m a -> BH m a
forall a b. (a -> b) -> a -> b
$ (BHEnv -> m a) -> ReaderT BHEnv m a
forall r (m :: * -> *) a. (r -> m a) -> ReaderT r m a
ReaderT ((BHEnv -> m a) -> ReaderT BHEnv m a)
-> (BHEnv -> m a) -> ReaderT BHEnv m a
forall a b. (a -> b) -> a -> b
$ \BHEnv
r ->
(r -> r) -> m a -> m a
forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local r -> r
f (BHEnv -> m a
m BHEnv
r)
instance (Functor m, Applicative m, MonadIO m) => MonadBH (BH m) where
getBHEnv :: BH m BHEnv
getBHEnv = ReaderT BHEnv m BHEnv -> BH m BHEnv
forall (m :: * -> *) a. ReaderT BHEnv m a -> BH m a
BH ReaderT BHEnv m BHEnv
forall (m :: * -> *). MonadBH m => m BHEnv
getBHEnv
runBH :: BHEnv -> BH m a -> m a
runBH :: BHEnv -> BH m a -> m a
runBH BHEnv
e BH m a
f = ReaderT BHEnv m a -> BHEnv -> m a
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT (BH m a -> ReaderT BHEnv m a
forall (m :: * -> *) a. BH m a -> ReaderT BHEnv m a
unBH BH m a
f) BHEnv
e
data Version = Version { Version -> VersionNumber
number :: VersionNumber
, Version -> BuildHash
build_hash :: BuildHash
, Version -> UTCTime
build_date :: UTCTime
, Version -> Bool
build_snapshot :: Bool
, Version -> VersionNumber
lucene_version :: VersionNumber }
deriving (Version -> Version -> Bool
(Version -> Version -> Bool)
-> (Version -> Version -> Bool) -> Eq Version
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Version -> Version -> Bool
$c/= :: Version -> Version -> Bool
== :: Version -> Version -> Bool
$c== :: Version -> Version -> Bool
Eq, Int -> Version -> ShowS
[Version] -> ShowS
Version -> String
(Int -> Version -> ShowS)
-> (Version -> String) -> ([Version] -> ShowS) -> Show Version
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Version] -> ShowS
$cshowList :: [Version] -> ShowS
show :: Version -> String
$cshow :: Version -> String
showsPrec :: Int -> Version -> ShowS
$cshowsPrec :: Int -> Version -> ShowS
Show)
newtype VersionNumber = VersionNumber
{ VersionNumber -> Version
versionNumber :: SemVer.Version }
deriving (VersionNumber -> VersionNumber -> Bool
(VersionNumber -> VersionNumber -> Bool)
-> (VersionNumber -> VersionNumber -> Bool) -> Eq VersionNumber
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VersionNumber -> VersionNumber -> Bool
$c/= :: VersionNumber -> VersionNumber -> Bool
== :: VersionNumber -> VersionNumber -> Bool
$c== :: VersionNumber -> VersionNumber -> Bool
Eq, Eq VersionNumber
Eq VersionNumber
-> (VersionNumber -> VersionNumber -> Ordering)
-> (VersionNumber -> VersionNumber -> Bool)
-> (VersionNumber -> VersionNumber -> Bool)
-> (VersionNumber -> VersionNumber -> Bool)
-> (VersionNumber -> VersionNumber -> Bool)
-> (VersionNumber -> VersionNumber -> VersionNumber)
-> (VersionNumber -> VersionNumber -> VersionNumber)
-> Ord VersionNumber
VersionNumber -> VersionNumber -> Bool
VersionNumber -> VersionNumber -> Ordering
VersionNumber -> VersionNumber -> VersionNumber
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 :: VersionNumber -> VersionNumber -> VersionNumber
$cmin :: VersionNumber -> VersionNumber -> VersionNumber
max :: VersionNumber -> VersionNumber -> VersionNumber
$cmax :: VersionNumber -> VersionNumber -> VersionNumber
>= :: VersionNumber -> VersionNumber -> Bool
$c>= :: VersionNumber -> VersionNumber -> Bool
> :: VersionNumber -> VersionNumber -> Bool
$c> :: VersionNumber -> VersionNumber -> Bool
<= :: VersionNumber -> VersionNumber -> Bool
$c<= :: VersionNumber -> VersionNumber -> Bool
< :: VersionNumber -> VersionNumber -> Bool
$c< :: VersionNumber -> VersionNumber -> Bool
compare :: VersionNumber -> VersionNumber -> Ordering
$ccompare :: VersionNumber -> VersionNumber -> Ordering
$cp1Ord :: Eq VersionNumber
Ord, Int -> VersionNumber -> ShowS
[VersionNumber] -> ShowS
VersionNumber -> String
(Int -> VersionNumber -> ShowS)
-> (VersionNumber -> String)
-> ([VersionNumber] -> ShowS)
-> Show VersionNumber
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VersionNumber] -> ShowS
$cshowList :: [VersionNumber] -> ShowS
show :: VersionNumber -> String
$cshow :: VersionNumber -> String
showsPrec :: Int -> VersionNumber -> ShowS
$cshowsPrec :: Int -> VersionNumber -> ShowS
Show)
data Status = Status
{ Status -> Text
name :: Text
, Status -> Text
cluster_name :: Text
, Status -> Text
cluster_uuid :: Text
, Status -> Version
version :: Version
, Status -> Text
tagline :: Text }
deriving (Status -> Status -> Bool
(Status -> Status -> Bool)
-> (Status -> Status -> Bool) -> Eq Status
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Status -> Status -> Bool
$c/= :: Status -> Status -> Bool
== :: Status -> Status -> Bool
$c== :: Status -> Status -> Bool
Eq, Int -> Status -> ShowS
[Status] -> ShowS
Status -> String
(Int -> Status -> ShowS)
-> (Status -> String) -> ([Status] -> ShowS) -> Show Status
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Status] -> ShowS
$cshowList :: [Status] -> ShowS
show :: Status -> String
$cshow :: Status -> String
showsPrec :: Int -> Status -> ShowS
$cshowsPrec :: Int -> Status -> ShowS
Show)
instance FromJSON Status where
parseJSON :: Value -> Parser Status
parseJSON (Object Object
v) = Text -> Text -> Text -> Version -> Text -> Status
Status (Text -> Text -> Text -> Version -> Text -> Status)
-> Parser Text
-> Parser (Text -> Text -> Version -> Text -> Status)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
Object
v Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"name" Parser (Text -> Text -> Version -> Text -> Status)
-> Parser Text -> Parser (Text -> Version -> Text -> Status)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
Object
v Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"cluster_name" Parser (Text -> Version -> Text -> Status)
-> Parser Text -> Parser (Version -> Text -> Status)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
Object
v Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"cluster_uuid" Parser (Version -> Text -> Status)
-> Parser Version -> Parser (Text -> Status)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
Object
v Object -> Key -> Parser Version
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"version" Parser (Text -> Status) -> Parser Text -> Parser Status
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
Object
v Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"tagline"
parseJSON Value
_ = Parser Status
forall (f :: * -> *) a. Alternative f => f a
empty
data IndexSettings = IndexSettings
{ IndexSettings -> ShardCount
indexShards :: ShardCount
, IndexSettings -> ReplicaCount
indexReplicas :: ReplicaCount
, IndexSettings -> IndexMappingsLimits
indexMappingsLimits :: IndexMappingsLimits }
deriving (IndexSettings -> IndexSettings -> Bool
(IndexSettings -> IndexSettings -> Bool)
-> (IndexSettings -> IndexSettings -> Bool) -> Eq IndexSettings
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IndexSettings -> IndexSettings -> Bool
$c/= :: IndexSettings -> IndexSettings -> Bool
== :: IndexSettings -> IndexSettings -> Bool
$c== :: IndexSettings -> IndexSettings -> Bool
Eq, Int -> IndexSettings -> ShowS
[IndexSettings] -> ShowS
IndexSettings -> String
(Int -> IndexSettings -> ShowS)
-> (IndexSettings -> String)
-> ([IndexSettings] -> ShowS)
-> Show IndexSettings
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IndexSettings] -> ShowS
$cshowList :: [IndexSettings] -> ShowS
show :: IndexSettings -> String
$cshow :: IndexSettings -> String
showsPrec :: Int -> IndexSettings -> ShowS
$cshowsPrec :: Int -> IndexSettings -> ShowS
Show)
instance ToJSON IndexSettings where
toJSON :: IndexSettings -> Value
toJSON (IndexSettings ShardCount
s ReplicaCount
r IndexMappingsLimits
l) = [Pair] -> Value
object [Key
"settings" Key -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.=
[Pair] -> Value
object [Key
"index" Key -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.=
[Pair] -> Value
object [Key
"number_of_shards" Key -> ShardCount -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= ShardCount
s, Key
"number_of_replicas" Key -> ReplicaCount -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= ReplicaCount
r, Key
"mapping" Key -> IndexMappingsLimits -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= IndexMappingsLimits
l]
]
]
instance FromJSON IndexSettings where
parseJSON :: Value -> Parser IndexSettings
parseJSON = String
-> (Object -> Parser IndexSettings)
-> Value
-> Parser IndexSettings
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"IndexSettings" Object -> Parser IndexSettings
parse
where parse :: Object -> Parser IndexSettings
parse Object
o = do Object
s <- Object
o Object -> Key -> Parser Object
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"settings"
Object
i <- Object
s Object -> Key -> Parser Object
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"index"
ShardCount -> ReplicaCount -> IndexMappingsLimits -> IndexSettings
IndexSettings (ShardCount
-> ReplicaCount -> IndexMappingsLimits -> IndexSettings)
-> Parser ShardCount
-> Parser (ReplicaCount -> IndexMappingsLimits -> IndexSettings)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
i Object -> Key -> Parser ShardCount
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"number_of_shards"
Parser (ReplicaCount -> IndexMappingsLimits -> IndexSettings)
-> Parser ReplicaCount
-> Parser (IndexMappingsLimits -> IndexSettings)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
i Object -> Key -> Parser ReplicaCount
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"number_of_replicas"
Parser (IndexMappingsLimits -> IndexSettings)
-> Parser IndexMappingsLimits -> Parser IndexSettings
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
i Object -> Key -> Parser (Maybe IndexMappingsLimits)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"mapping" Parser (Maybe IndexMappingsLimits)
-> IndexMappingsLimits -> Parser IndexMappingsLimits
forall a. Parser (Maybe a) -> a -> Parser a
.!= IndexMappingsLimits
defaultIndexMappingsLimits
defaultIndexSettings :: IndexSettings
defaultIndexSettings :: IndexSettings
defaultIndexSettings = ShardCount -> ReplicaCount -> IndexMappingsLimits -> IndexSettings
IndexSettings (Int -> ShardCount
ShardCount Int
3) (Int -> ReplicaCount
ReplicaCount Int
2) IndexMappingsLimits
defaultIndexMappingsLimits
data IndexMappingsLimits = IndexMappingsLimits
{ IndexMappingsLimits -> Maybe Int
indexMappingsLimitDepth :: Maybe Int
, IndexMappingsLimits -> Maybe Int
indexMappingsLimitNestedFields :: Maybe Int
, IndexMappingsLimits -> Maybe Int
indexMappingsLimitNestedObjects :: Maybe Int
, IndexMappingsLimits -> Maybe Int
indexMappingsLimitFieldNameLength :: Maybe Int }
deriving (IndexMappingsLimits -> IndexMappingsLimits -> Bool
(IndexMappingsLimits -> IndexMappingsLimits -> Bool)
-> (IndexMappingsLimits -> IndexMappingsLimits -> Bool)
-> Eq IndexMappingsLimits
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IndexMappingsLimits -> IndexMappingsLimits -> Bool
$c/= :: IndexMappingsLimits -> IndexMappingsLimits -> Bool
== :: IndexMappingsLimits -> IndexMappingsLimits -> Bool
$c== :: IndexMappingsLimits -> IndexMappingsLimits -> Bool
Eq, Int -> IndexMappingsLimits -> ShowS
[IndexMappingsLimits] -> ShowS
IndexMappingsLimits -> String
(Int -> IndexMappingsLimits -> ShowS)
-> (IndexMappingsLimits -> String)
-> ([IndexMappingsLimits] -> ShowS)
-> Show IndexMappingsLimits
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IndexMappingsLimits] -> ShowS
$cshowList :: [IndexMappingsLimits] -> ShowS
show :: IndexMappingsLimits -> String
$cshow :: IndexMappingsLimits -> String
showsPrec :: Int -> IndexMappingsLimits -> ShowS
$cshowsPrec :: Int -> IndexMappingsLimits -> ShowS
Show)
instance ToJSON IndexMappingsLimits where
toJSON :: IndexMappingsLimits -> Value
toJSON (IndexMappingsLimits Maybe Int
d Maybe Int
f Maybe Int
o Maybe Int
n) = [Pair] -> Value
object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$
((Key, Maybe Int) -> Maybe Pair) -> [(Key, Maybe Int)] -> [Pair]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (Key, Maybe Int) -> Maybe Pair
forall (f :: * -> *) b v.
(Functor f, KeyValue b, ToJSON v) =>
(Key, f v) -> f b
go
[ (Key
"depth.limit", Maybe Int
d)
, (Key
"nested_fields.limit", Maybe Int
f)
, (Key
"nested_objects.limit", Maybe Int
o)
, (Key
"field_name_length.limit", Maybe Int
n)]
where go :: (Key, f v) -> f b
go (Key
name, f v
value) = (Key
name Key -> v -> b
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.=) (v -> b) -> f v -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> f v
value
instance FromJSON IndexMappingsLimits where
parseJSON :: Value -> Parser IndexMappingsLimits
parseJSON = String
-> (Object -> Parser IndexMappingsLimits)
-> Value
-> Parser IndexMappingsLimits
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"IndexMappingsLimits" ((Object -> Parser IndexMappingsLimits)
-> Value -> Parser IndexMappingsLimits)
-> (Object -> Parser IndexMappingsLimits)
-> Value
-> Parser IndexMappingsLimits
forall a b. (a -> b) -> a -> b
$ \Object
o ->
Maybe Int
-> Maybe Int -> Maybe Int -> Maybe Int -> IndexMappingsLimits
IndexMappingsLimits
(Maybe Int
-> Maybe Int -> Maybe Int -> Maybe Int -> IndexMappingsLimits)
-> Parser (Maybe Int)
-> Parser
(Maybe Int -> Maybe Int -> Maybe Int -> IndexMappingsLimits)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:?? Key
"depth"
Parser (Maybe Int -> Maybe Int -> Maybe Int -> IndexMappingsLimits)
-> Parser (Maybe Int)
-> Parser (Maybe Int -> Maybe Int -> IndexMappingsLimits)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:?? Key
"nested_fields"
Parser (Maybe Int -> Maybe Int -> IndexMappingsLimits)
-> Parser (Maybe Int) -> Parser (Maybe Int -> IndexMappingsLimits)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:?? Key
"nested_objects"
Parser (Maybe Int -> IndexMappingsLimits)
-> Parser (Maybe Int) -> Parser IndexMappingsLimits
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:?? Key
"field_name_length"
where Object
o .:?? :: Object -> Key -> Parser (Maybe a)
.:?? Key
name = Parser a -> Parser (Maybe a)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Parser a -> Parser (Maybe a)) -> Parser a -> Parser (Maybe a)
forall a b. (a -> b) -> a -> b
$ do
Object
f <- Object
o Object -> Key -> Parser Object
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
name
Object
f Object -> Key -> Parser a
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"limit"
defaultIndexMappingsLimits :: IndexMappingsLimits
defaultIndexMappingsLimits :: IndexMappingsLimits
defaultIndexMappingsLimits = Maybe Int
-> Maybe Int -> Maybe Int -> Maybe Int -> IndexMappingsLimits
IndexMappingsLimits Maybe Int
forall a. Maybe a
Nothing Maybe Int
forall a. Maybe a
Nothing Maybe Int
forall a. Maybe a
Nothing Maybe Int
forall a. Maybe a
Nothing
data ForceMergeIndexSettings =
ForceMergeIndexSettings { ForceMergeIndexSettings -> Maybe Int
maxNumSegments :: Maybe Int
, ForceMergeIndexSettings -> Bool
onlyExpungeDeletes :: Bool
, ForceMergeIndexSettings -> Bool
flushAfterOptimize :: Bool
} deriving (ForceMergeIndexSettings -> ForceMergeIndexSettings -> Bool
(ForceMergeIndexSettings -> ForceMergeIndexSettings -> Bool)
-> (ForceMergeIndexSettings -> ForceMergeIndexSettings -> Bool)
-> Eq ForceMergeIndexSettings
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ForceMergeIndexSettings -> ForceMergeIndexSettings -> Bool
$c/= :: ForceMergeIndexSettings -> ForceMergeIndexSettings -> Bool
== :: ForceMergeIndexSettings -> ForceMergeIndexSettings -> Bool
$c== :: ForceMergeIndexSettings -> ForceMergeIndexSettings -> Bool
Eq, Int -> ForceMergeIndexSettings -> ShowS
[ForceMergeIndexSettings] -> ShowS
ForceMergeIndexSettings -> String
(Int -> ForceMergeIndexSettings -> ShowS)
-> (ForceMergeIndexSettings -> String)
-> ([ForceMergeIndexSettings] -> ShowS)
-> Show ForceMergeIndexSettings
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ForceMergeIndexSettings] -> ShowS
$cshowList :: [ForceMergeIndexSettings] -> ShowS
show :: ForceMergeIndexSettings -> String
$cshow :: ForceMergeIndexSettings -> String
showsPrec :: Int -> ForceMergeIndexSettings -> ShowS
$cshowsPrec :: Int -> ForceMergeIndexSettings -> ShowS
Show)
defaultForceMergeIndexSettings :: ForceMergeIndexSettings
defaultForceMergeIndexSettings :: ForceMergeIndexSettings
defaultForceMergeIndexSettings = Maybe Int -> Bool -> Bool -> ForceMergeIndexSettings
ForceMergeIndexSettings Maybe Int
forall a. Maybe a
Nothing Bool
False Bool
True
data UpdatableIndexSetting = NumberOfReplicas ReplicaCount
| AutoExpandReplicas ReplicaBounds
| BlocksReadOnly Bool
| BlocksRead Bool
| BlocksWrite Bool
| BlocksMetaData Bool
| RefreshInterval NominalDiffTime
| IndexConcurrency Int
| FailOnMergeFailure Bool
| TranslogFlushThresholdOps Int
| TranslogFlushThresholdSize Bytes
| TranslogFlushThresholdPeriod NominalDiffTime
| TranslogDisableFlush Bool
| CacheFilterMaxSize (Maybe Bytes)
| CacheFilterExpire (Maybe NominalDiffTime)
| GatewaySnapshotInterval NominalDiffTime
| RoutingAllocationInclude (NonEmpty NodeAttrFilter)
| RoutingAllocationExclude (NonEmpty NodeAttrFilter)
| RoutingAllocationRequire (NonEmpty NodeAttrFilter)
| RoutingAllocationEnable AllocationPolicy
| RoutingAllocationShardsPerNode ShardCount
| RecoveryInitialShards InitialShardCount
| GCDeletes NominalDiffTime
| TTLDisablePurge Bool
| TranslogFSType FSType
| CompressionSetting Compression
| IndexCompoundFormat CompoundFormat
| IndexCompoundOnFlush Bool
| WarmerEnabled Bool
| MappingTotalFieldsLimit Int
| AnalysisSetting Analysis
| UnassignedNodeLeftDelayedTimeout NominalDiffTime
deriving (UpdatableIndexSetting -> UpdatableIndexSetting -> Bool
(UpdatableIndexSetting -> UpdatableIndexSetting -> Bool)
-> (UpdatableIndexSetting -> UpdatableIndexSetting -> Bool)
-> Eq UpdatableIndexSetting
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdatableIndexSetting -> UpdatableIndexSetting -> Bool
$c/= :: UpdatableIndexSetting -> UpdatableIndexSetting -> Bool
== :: UpdatableIndexSetting -> UpdatableIndexSetting -> Bool
$c== :: UpdatableIndexSetting -> UpdatableIndexSetting -> Bool
Eq, Int -> UpdatableIndexSetting -> ShowS
[UpdatableIndexSetting] -> ShowS
UpdatableIndexSetting -> String
(Int -> UpdatableIndexSetting -> ShowS)
-> (UpdatableIndexSetting -> String)
-> ([UpdatableIndexSetting] -> ShowS)
-> Show UpdatableIndexSetting
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdatableIndexSetting] -> ShowS
$cshowList :: [UpdatableIndexSetting] -> ShowS
show :: UpdatableIndexSetting -> String
$cshow :: UpdatableIndexSetting -> String
showsPrec :: Int -> UpdatableIndexSetting -> ShowS
$cshowsPrec :: Int -> UpdatableIndexSetting -> ShowS
Show)
attrFilterJSON :: NonEmpty NodeAttrFilter -> Value
attrFilterJSON :: NonEmpty NodeAttrFilter -> Value
attrFilterJSON NonEmpty NodeAttrFilter
fs = [Pair] -> Value
object [ Text -> Key
fromText Text
n Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text -> [Text] -> Text
T.intercalate Text
"," (NonEmpty Text -> [Text]
forall a. NonEmpty a -> [a]
toList NonEmpty Text
vs)
| NodeAttrFilter (NodeAttrName Text
n) NonEmpty Text
vs <- NonEmpty NodeAttrFilter -> [NodeAttrFilter]
forall a. NonEmpty a -> [a]
toList NonEmpty NodeAttrFilter
fs]
parseAttrFilter :: Value -> Parser (NonEmpty NodeAttrFilter)
parseAttrFilter :: Value -> Parser (NonEmpty NodeAttrFilter)
parseAttrFilter = String
-> (Object -> Parser (NonEmpty NodeAttrFilter))
-> Value
-> Parser (NonEmpty NodeAttrFilter)
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"NonEmpty NodeAttrFilter" Object -> Parser (NonEmpty NodeAttrFilter)
parse
where parse :: Object -> Parser (NonEmpty NodeAttrFilter)
parse Object
o = case Object -> [Pair]
forall v. KeyMap v -> [(Key, v)]
X.toList Object
o of
[] -> String -> Parser (NonEmpty NodeAttrFilter)
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Expected non-empty list of NodeAttrFilters"
Pair
x:[Pair]
xs -> (Pair -> Parser NodeAttrFilter)
-> NonEmpty Pair -> Parser (NonEmpty NodeAttrFilter)
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
DT.mapM ((Key -> Value -> Parser NodeAttrFilter)
-> Pair -> Parser NodeAttrFilter
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Key -> Value -> Parser NodeAttrFilter
parse') (Pair
x Pair -> [Pair] -> NonEmpty Pair
forall a. a -> [a] -> NonEmpty a
:| [Pair]
xs)
parse' :: Key -> Value -> Parser NodeAttrFilter
parse' Key
n = String
-> (Text -> Parser NodeAttrFilter)
-> Value
-> Parser NodeAttrFilter
forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"Text" ((Text -> Parser NodeAttrFilter) -> Value -> Parser NodeAttrFilter)
-> (Text -> Parser NodeAttrFilter)
-> Value
-> Parser NodeAttrFilter
forall a b. (a -> b) -> a -> b
$ \Text
t ->
case Text -> Text -> [Text]
T.splitOn Text
"," Text
t of
Text
fv:[Text]
fvs -> NodeAttrFilter -> Parser NodeAttrFilter
forall (m :: * -> *) a. Monad m => a -> m a
return (NodeAttrName -> NonEmpty Text -> NodeAttrFilter
NodeAttrFilter (Text -> NodeAttrName
NodeAttrName (Text -> NodeAttrName) -> Text -> NodeAttrName
forall a b. (a -> b) -> a -> b
$ Key -> Text
toText Key
n) (Text
fv Text -> [Text] -> NonEmpty Text
forall a. a -> [a] -> NonEmpty a
:| [Text]
fvs))
[] -> String -> Parser NodeAttrFilter
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Expected non-empty list of filter values"
instance ToJSON UpdatableIndexSetting where
toJSON :: UpdatableIndexSetting -> Value
toJSON (NumberOfReplicas ReplicaCount
x) = NonEmpty Key -> ReplicaCount -> Value
forall a. ToJSON a => NonEmpty Key -> a -> Value
oPath (Key
"index" Key -> [Key] -> NonEmpty Key
forall a. a -> [a] -> NonEmpty a
:| [Key
"number_of_replicas"]) ReplicaCount
x
toJSON (AutoExpandReplicas ReplicaBounds
x) = NonEmpty Key -> ReplicaBounds -> Value
forall a. ToJSON a => NonEmpty Key -> a -> Value
oPath (Key
"index" Key -> [Key] -> NonEmpty Key
forall a. a -> [a] -> NonEmpty a
:| [Key
"auto_expand_replicas"]) ReplicaBounds
x
toJSON (RefreshInterval NominalDiffTime
x) = NonEmpty Key -> NominalDiffTimeJSON -> Value
forall a. ToJSON a => NonEmpty Key -> a -> Value
oPath (Key
"index" Key -> [Key] -> NonEmpty Key
forall a. a -> [a] -> NonEmpty a
:| [Key
"refresh_interval"]) (NominalDiffTime -> NominalDiffTimeJSON
NominalDiffTimeJSON NominalDiffTime
x)
toJSON (IndexConcurrency Int
x) = NonEmpty Key -> Int -> Value
forall a. ToJSON a => NonEmpty Key -> a -> Value
oPath (Key
"index" Key -> [Key] -> NonEmpty Key
forall a. a -> [a] -> NonEmpty a
:| [Key
"concurrency"]) Int
x
toJSON (FailOnMergeFailure Bool
x) = NonEmpty Key -> Bool -> Value
forall a. ToJSON a => NonEmpty Key -> a -> Value
oPath (Key
"index" Key -> [Key] -> NonEmpty Key
forall a. a -> [a] -> NonEmpty a
:| [Key
"fail_on_merge_failure"]) Bool
x
toJSON (TranslogFlushThresholdOps Int
x) = NonEmpty Key -> Int -> Value
forall a. ToJSON a => NonEmpty Key -> a -> Value
oPath (Key
"index" Key -> [Key] -> NonEmpty Key
forall a. a -> [a] -> NonEmpty a
:| [Key
"translog", Key
"flush_threshold_ops"]) Int
x
toJSON (TranslogFlushThresholdSize Bytes
x) = NonEmpty Key -> Bytes -> Value
forall a. ToJSON a => NonEmpty Key -> a -> Value
oPath (Key
"index" Key -> [Key] -> NonEmpty Key
forall a. a -> [a] -> NonEmpty a
:| [Key
"translog", Key
"flush_threshold_size"]) Bytes
x
toJSON (TranslogFlushThresholdPeriod NominalDiffTime
x) = NonEmpty Key -> NominalDiffTimeJSON -> Value
forall a. ToJSON a => NonEmpty Key -> a -> Value
oPath (Key
"index" Key -> [Key] -> NonEmpty Key
forall a. a -> [a] -> NonEmpty a
:| [Key
"translog", Key
"flush_threshold_period"]) (NominalDiffTime -> NominalDiffTimeJSON
NominalDiffTimeJSON NominalDiffTime
x)
toJSON (TranslogDisableFlush Bool
x) = NonEmpty Key -> Bool -> Value
forall a. ToJSON a => NonEmpty Key -> a -> Value
oPath (Key
"index" Key -> [Key] -> NonEmpty Key
forall a. a -> [a] -> NonEmpty a
:| [Key
"translog", Key
"disable_flush"]) Bool
x
toJSON (CacheFilterMaxSize Maybe Bytes
x) = NonEmpty Key -> Maybe Bytes -> Value
forall a. ToJSON a => NonEmpty Key -> a -> Value
oPath (Key
"index" Key -> [Key] -> NonEmpty Key
forall a. a -> [a] -> NonEmpty a
:| [Key
"cache", Key
"filter", Key
"max_size"]) Maybe Bytes
x
toJSON (CacheFilterExpire Maybe NominalDiffTime
x) = NonEmpty Key -> Maybe NominalDiffTimeJSON -> Value
forall a. ToJSON a => NonEmpty Key -> a -> Value
oPath (Key
"index" Key -> [Key] -> NonEmpty Key
forall a. a -> [a] -> NonEmpty a
:| [Key
"cache", Key
"filter", Key
"expire"]) (NominalDiffTime -> NominalDiffTimeJSON
NominalDiffTimeJSON (NominalDiffTime -> NominalDiffTimeJSON)
-> Maybe NominalDiffTime -> Maybe NominalDiffTimeJSON
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe NominalDiffTime
x)
toJSON (GatewaySnapshotInterval NominalDiffTime
x) = NonEmpty Key -> NominalDiffTimeJSON -> Value
forall a. ToJSON a => NonEmpty Key -> a -> Value
oPath (Key
"index" Key -> [Key] -> NonEmpty Key
forall a. a -> [a] -> NonEmpty a
:| [Key
"gateway", Key
"snapshot_interval"]) (NominalDiffTime -> NominalDiffTimeJSON
NominalDiffTimeJSON NominalDiffTime
x)
toJSON (RoutingAllocationInclude NonEmpty NodeAttrFilter
fs) = NonEmpty Key -> Value -> Value
forall a. ToJSON a => NonEmpty Key -> a -> Value
oPath (Key
"index" Key -> [Key] -> NonEmpty Key
forall a. a -> [a] -> NonEmpty a
:| [Key
"routing", Key
"allocation", Key
"include"]) (NonEmpty NodeAttrFilter -> Value
attrFilterJSON NonEmpty NodeAttrFilter
fs)
toJSON (RoutingAllocationExclude NonEmpty NodeAttrFilter
fs) = NonEmpty Key -> Value -> Value
forall a. ToJSON a => NonEmpty Key -> a -> Value
oPath (Key
"index" Key -> [Key] -> NonEmpty Key
forall a. a -> [a] -> NonEmpty a
:| [Key
"routing", Key
"allocation", Key
"exclude"]) (NonEmpty NodeAttrFilter -> Value
attrFilterJSON NonEmpty NodeAttrFilter
fs)
toJSON (RoutingAllocationRequire NonEmpty NodeAttrFilter
fs) = NonEmpty Key -> Value -> Value
forall a. ToJSON a => NonEmpty Key -> a -> Value
oPath (Key
"index" Key -> [Key] -> NonEmpty Key
forall a. a -> [a] -> NonEmpty a
:| [Key
"routing", Key
"allocation", Key
"require"]) (NonEmpty NodeAttrFilter -> Value
attrFilterJSON NonEmpty NodeAttrFilter
fs)
toJSON (RoutingAllocationEnable AllocationPolicy
x) = NonEmpty Key -> AllocationPolicy -> Value
forall a. ToJSON a => NonEmpty Key -> a -> Value
oPath (Key
"index" Key -> [Key] -> NonEmpty Key
forall a. a -> [a] -> NonEmpty a
:| [Key
"routing", Key
"allocation", Key
"enable"]) AllocationPolicy
x
toJSON (RoutingAllocationShardsPerNode ShardCount
x) = NonEmpty Key -> ShardCount -> Value
forall a. ToJSON a => NonEmpty Key -> a -> Value
oPath (Key
"index" Key -> [Key] -> NonEmpty Key
forall a. a -> [a] -> NonEmpty a
:| [Key
"routing", Key
"allocation", Key
"total_shards_per_node"]) ShardCount
x
toJSON (RecoveryInitialShards InitialShardCount
x) = NonEmpty Key -> InitialShardCount -> Value
forall a. ToJSON a => NonEmpty Key -> a -> Value
oPath (Key
"index" Key -> [Key] -> NonEmpty Key
forall a. a -> [a] -> NonEmpty a
:| [Key
"recovery", Key
"initial_shards"]) InitialShardCount
x
toJSON (GCDeletes NominalDiffTime
x) = NonEmpty Key -> NominalDiffTimeJSON -> Value
forall a. ToJSON a => NonEmpty Key -> a -> Value
oPath (Key
"index" Key -> [Key] -> NonEmpty Key
forall a. a -> [a] -> NonEmpty a
:| [Key
"gc_deletes"]) (NominalDiffTime -> NominalDiffTimeJSON
NominalDiffTimeJSON NominalDiffTime
x)
toJSON (TTLDisablePurge Bool
x) = NonEmpty Key -> Bool -> Value
forall a. ToJSON a => NonEmpty Key -> a -> Value
oPath (Key
"index" Key -> [Key] -> NonEmpty Key
forall a. a -> [a] -> NonEmpty a
:| [Key
"ttl", Key
"disable_purge"]) Bool
x
toJSON (TranslogFSType FSType
x) = NonEmpty Key -> FSType -> Value
forall a. ToJSON a => NonEmpty Key -> a -> Value
oPath (Key
"index" Key -> [Key] -> NonEmpty Key
forall a. a -> [a] -> NonEmpty a
:| [Key
"translog", Key
"fs", Key
"type"]) FSType
x
toJSON (CompressionSetting Compression
x) = NonEmpty Key -> Compression -> Value
forall a. ToJSON a => NonEmpty Key -> a -> Value
oPath (Key
"index" Key -> [Key] -> NonEmpty Key
forall a. a -> [a] -> NonEmpty a
:| [Key
"codec"]) Compression
x
toJSON (IndexCompoundFormat CompoundFormat
x) = NonEmpty Key -> CompoundFormat -> Value
forall a. ToJSON a => NonEmpty Key -> a -> Value
oPath (Key
"index" Key -> [Key] -> NonEmpty Key
forall a. a -> [a] -> NonEmpty a
:| [Key
"compound_format"]) CompoundFormat
x
toJSON (IndexCompoundOnFlush Bool
x) = NonEmpty Key -> Bool -> Value
forall a. ToJSON a => NonEmpty Key -> a -> Value
oPath (Key
"index" Key -> [Key] -> NonEmpty Key
forall a. a -> [a] -> NonEmpty a
:| [Key
"compound_on_flush"]) Bool
x
toJSON (WarmerEnabled Bool
x) = NonEmpty Key -> Bool -> Value
forall a. ToJSON a => NonEmpty Key -> a -> Value
oPath (Key
"index" Key -> [Key] -> NonEmpty Key
forall a. a -> [a] -> NonEmpty a
:| [Key
"warmer", Key
"enabled"]) Bool
x
toJSON (BlocksReadOnly Bool
x) = NonEmpty Key -> Bool -> Value
forall a. ToJSON a => NonEmpty Key -> a -> Value
oPath (Key
"blocks" Key -> [Key] -> NonEmpty Key
forall a. a -> [a] -> NonEmpty a
:| [Key
"read_only"]) Bool
x
toJSON (BlocksRead Bool
x) = NonEmpty Key -> Bool -> Value
forall a. ToJSON a => NonEmpty Key -> a -> Value
oPath (Key
"blocks" Key -> [Key] -> NonEmpty Key
forall a. a -> [a] -> NonEmpty a
:| [Key
"read"]) Bool
x
toJSON (BlocksWrite Bool
x) = NonEmpty Key -> Bool -> Value
forall a. ToJSON a => NonEmpty Key -> a -> Value
oPath (Key
"blocks" Key -> [Key] -> NonEmpty Key
forall a. a -> [a] -> NonEmpty a
:| [Key
"write"]) Bool
x
toJSON (BlocksMetaData Bool
x) = NonEmpty Key -> Bool -> Value
forall a. ToJSON a => NonEmpty Key -> a -> Value
oPath (Key
"blocks" Key -> [Key] -> NonEmpty Key
forall a. a -> [a] -> NonEmpty a
:| [Key
"metadata"]) Bool
x
toJSON (MappingTotalFieldsLimit Int
x) = NonEmpty Key -> Int -> Value
forall a. ToJSON a => NonEmpty Key -> a -> Value
oPath (Key
"index" Key -> [Key] -> NonEmpty Key
forall a. a -> [a] -> NonEmpty a
:| [Key
"mapping",Key
"total_fields",Key
"limit"]) Int
x
toJSON (AnalysisSetting Analysis
x) = NonEmpty Key -> Analysis -> Value
forall a. ToJSON a => NonEmpty Key -> a -> Value
oPath (Key
"index" Key -> [Key] -> NonEmpty Key
forall a. a -> [a] -> NonEmpty a
:| [Key
"analysis"]) Analysis
x
toJSON (UnassignedNodeLeftDelayedTimeout NominalDiffTime
x) = NonEmpty Key -> NominalDiffTimeJSON -> Value
forall a. ToJSON a => NonEmpty Key -> a -> Value
oPath (Key
"index" Key -> [Key] -> NonEmpty Key
forall a. a -> [a] -> NonEmpty a
:| [Key
"unassigned",Key
"node_left",Key
"delayed_timeout"]) (NominalDiffTime -> NominalDiffTimeJSON
NominalDiffTimeJSON NominalDiffTime
x)
instance FromJSON UpdatableIndexSetting where
parseJSON :: Value -> Parser UpdatableIndexSetting
parseJSON = String
-> (Object -> Parser UpdatableIndexSetting)
-> Value
-> Parser UpdatableIndexSetting
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"UpdatableIndexSetting" Object -> Parser UpdatableIndexSetting
parse
where parse :: Object -> Parser UpdatableIndexSetting
parse Object
o = ReplicaCount -> Parser UpdatableIndexSetting
numberOfReplicas (ReplicaCount -> Parser UpdatableIndexSetting)
-> [Key] -> Parser UpdatableIndexSetting
forall a b. FromJSON a => (a -> Parser b) -> [Key] -> Parser b
`taggedAt` [Key
"index", Key
"number_of_replicas"]
Parser UpdatableIndexSetting
-> Parser UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ReplicaBounds -> Parser UpdatableIndexSetting
autoExpandReplicas (ReplicaBounds -> Parser UpdatableIndexSetting)
-> [Key] -> Parser UpdatableIndexSetting
forall a b. FromJSON a => (a -> Parser b) -> [Key] -> Parser b
`taggedAt` [Key
"index", Key
"auto_expand_replicas"]
Parser UpdatableIndexSetting
-> Parser UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> NominalDiffTimeJSON -> Parser UpdatableIndexSetting
refreshInterval (NominalDiffTimeJSON -> Parser UpdatableIndexSetting)
-> [Key] -> Parser UpdatableIndexSetting
forall a b. FromJSON a => (a -> Parser b) -> [Key] -> Parser b
`taggedAt` [Key
"index", Key
"refresh_interval"]
Parser UpdatableIndexSetting
-> Parser UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Int -> Parser UpdatableIndexSetting
indexConcurrency (Int -> Parser UpdatableIndexSetting)
-> [Key] -> Parser UpdatableIndexSetting
forall a b. FromJSON a => (a -> Parser b) -> [Key] -> Parser b
`taggedAt` [Key
"index", Key
"concurrency"]
Parser UpdatableIndexSetting
-> Parser UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Bool -> Parser UpdatableIndexSetting
failOnMergeFailure (Bool -> Parser UpdatableIndexSetting)
-> [Key] -> Parser UpdatableIndexSetting
forall a b. FromJSON a => (a -> Parser b) -> [Key] -> Parser b
`taggedAt` [Key
"index", Key
"fail_on_merge_failure"]
Parser UpdatableIndexSetting
-> Parser UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Int -> Parser UpdatableIndexSetting
translogFlushThresholdOps (Int -> Parser UpdatableIndexSetting)
-> [Key] -> Parser UpdatableIndexSetting
forall a b. FromJSON a => (a -> Parser b) -> [Key] -> Parser b
`taggedAt` [Key
"index", Key
"translog", Key
"flush_threshold_ops"]
Parser UpdatableIndexSetting
-> Parser UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Bytes -> Parser UpdatableIndexSetting
translogFlushThresholdSize (Bytes -> Parser UpdatableIndexSetting)
-> [Key] -> Parser UpdatableIndexSetting
forall a b. FromJSON a => (a -> Parser b) -> [Key] -> Parser b
`taggedAt` [Key
"index", Key
"translog", Key
"flush_threshold_size"]
Parser UpdatableIndexSetting
-> Parser UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> NominalDiffTimeJSON -> Parser UpdatableIndexSetting
translogFlushThresholdPeriod (NominalDiffTimeJSON -> Parser UpdatableIndexSetting)
-> [Key] -> Parser UpdatableIndexSetting
forall a b. FromJSON a => (a -> Parser b) -> [Key] -> Parser b
`taggedAt` [Key
"index", Key
"translog", Key
"flush_threshold_period"]
Parser UpdatableIndexSetting
-> Parser UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Bool -> Parser UpdatableIndexSetting
translogDisableFlush (Bool -> Parser UpdatableIndexSetting)
-> [Key] -> Parser UpdatableIndexSetting
forall a b. FromJSON a => (a -> Parser b) -> [Key] -> Parser b
`taggedAt` [Key
"index", Key
"translog", Key
"disable_flush"]
Parser UpdatableIndexSetting
-> Parser UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe Bytes -> Parser UpdatableIndexSetting
cacheFilterMaxSize (Maybe Bytes -> Parser UpdatableIndexSetting)
-> [Key] -> Parser UpdatableIndexSetting
forall a b. FromJSON a => (a -> Parser b) -> [Key] -> Parser b
`taggedAt` [Key
"index", Key
"cache", Key
"filter", Key
"max_size"]
Parser UpdatableIndexSetting
-> Parser UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe NominalDiffTimeJSON -> Parser UpdatableIndexSetting
cacheFilterExpire (Maybe NominalDiffTimeJSON -> Parser UpdatableIndexSetting)
-> [Key] -> Parser UpdatableIndexSetting
forall a b. FromJSON a => (a -> Parser b) -> [Key] -> Parser b
`taggedAt` [Key
"index", Key
"cache", Key
"filter", Key
"expire"]
Parser UpdatableIndexSetting
-> Parser UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> NominalDiffTimeJSON -> Parser UpdatableIndexSetting
gatewaySnapshotInterval (NominalDiffTimeJSON -> Parser UpdatableIndexSetting)
-> [Key] -> Parser UpdatableIndexSetting
forall a b. FromJSON a => (a -> Parser b) -> [Key] -> Parser b
`taggedAt` [Key
"index", Key
"gateway", Key
"snapshot_interval"]
Parser UpdatableIndexSetting
-> Parser UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Value -> Parser UpdatableIndexSetting
routingAllocationInclude (Value -> Parser UpdatableIndexSetting)
-> [Key] -> Parser UpdatableIndexSetting
forall a b. FromJSON a => (a -> Parser b) -> [Key] -> Parser b
`taggedAt` [Key
"index", Key
"routing", Key
"allocation", Key
"include"]
Parser UpdatableIndexSetting
-> Parser UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Value -> Parser UpdatableIndexSetting
routingAllocationExclude (Value -> Parser UpdatableIndexSetting)
-> [Key] -> Parser UpdatableIndexSetting
forall a b. FromJSON a => (a -> Parser b) -> [Key] -> Parser b
`taggedAt` [Key
"index", Key
"routing", Key
"allocation", Key
"exclude"]
Parser UpdatableIndexSetting
-> Parser UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Value -> Parser UpdatableIndexSetting
routingAllocationRequire (Value -> Parser UpdatableIndexSetting)
-> [Key] -> Parser UpdatableIndexSetting
forall a b. FromJSON a => (a -> Parser b) -> [Key] -> Parser b
`taggedAt` [Key
"index", Key
"routing", Key
"allocation", Key
"require"]
Parser UpdatableIndexSetting
-> Parser UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> AllocationPolicy -> Parser UpdatableIndexSetting
routingAllocationEnable (AllocationPolicy -> Parser UpdatableIndexSetting)
-> [Key] -> Parser UpdatableIndexSetting
forall a b. FromJSON a => (a -> Parser b) -> [Key] -> Parser b
`taggedAt` [Key
"index", Key
"routing", Key
"allocation", Key
"enable"]
Parser UpdatableIndexSetting
-> Parser UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ShardCount -> Parser UpdatableIndexSetting
routingAllocationShardsPerNode (ShardCount -> Parser UpdatableIndexSetting)
-> [Key] -> Parser UpdatableIndexSetting
forall a b. FromJSON a => (a -> Parser b) -> [Key] -> Parser b
`taggedAt` [Key
"index", Key
"routing", Key
"allocation", Key
"total_shards_per_node"]
Parser UpdatableIndexSetting
-> Parser UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> InitialShardCount -> Parser UpdatableIndexSetting
recoveryInitialShards (InitialShardCount -> Parser UpdatableIndexSetting)
-> [Key] -> Parser UpdatableIndexSetting
forall a b. FromJSON a => (a -> Parser b) -> [Key] -> Parser b
`taggedAt` [Key
"index", Key
"recovery", Key
"initial_shards"]
Parser UpdatableIndexSetting
-> Parser UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> NominalDiffTimeJSON -> Parser UpdatableIndexSetting
gcDeletes (NominalDiffTimeJSON -> Parser UpdatableIndexSetting)
-> [Key] -> Parser UpdatableIndexSetting
forall a b. FromJSON a => (a -> Parser b) -> [Key] -> Parser b
`taggedAt` [Key
"index", Key
"gc_deletes"]
Parser UpdatableIndexSetting
-> Parser UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Bool -> Parser UpdatableIndexSetting
ttlDisablePurge (Bool -> Parser UpdatableIndexSetting)
-> [Key] -> Parser UpdatableIndexSetting
forall a b. FromJSON a => (a -> Parser b) -> [Key] -> Parser b
`taggedAt` [Key
"index", Key
"ttl", Key
"disable_purge"]
Parser UpdatableIndexSetting
-> Parser UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> FSType -> Parser UpdatableIndexSetting
translogFSType (FSType -> Parser UpdatableIndexSetting)
-> [Key] -> Parser UpdatableIndexSetting
forall a b. FromJSON a => (a -> Parser b) -> [Key] -> Parser b
`taggedAt` [Key
"index", Key
"translog", Key
"fs", Key
"type"]
Parser UpdatableIndexSetting
-> Parser UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Compression -> Parser UpdatableIndexSetting
compressionSetting (Compression -> Parser UpdatableIndexSetting)
-> [Key] -> Parser UpdatableIndexSetting
forall a b. FromJSON a => (a -> Parser b) -> [Key] -> Parser b
`taggedAt` [Key
"index", Key
"codec"]
Parser UpdatableIndexSetting
-> Parser UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> CompoundFormat -> Parser UpdatableIndexSetting
compoundFormat (CompoundFormat -> Parser UpdatableIndexSetting)
-> [Key] -> Parser UpdatableIndexSetting
forall a b. FromJSON a => (a -> Parser b) -> [Key] -> Parser b
`taggedAt` [Key
"index", Key
"compound_format"]
Parser UpdatableIndexSetting
-> Parser UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Bool -> Parser UpdatableIndexSetting
compoundOnFlush (Bool -> Parser UpdatableIndexSetting)
-> [Key] -> Parser UpdatableIndexSetting
forall a b. FromJSON a => (a -> Parser b) -> [Key] -> Parser b
`taggedAt` [Key
"index", Key
"compound_on_flush"]
Parser UpdatableIndexSetting
-> Parser UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Bool -> Parser UpdatableIndexSetting
warmerEnabled (Bool -> Parser UpdatableIndexSetting)
-> [Key] -> Parser UpdatableIndexSetting
forall a b. FromJSON a => (a -> Parser b) -> [Key] -> Parser b
`taggedAt` [Key
"index", Key
"warmer", Key
"enabled"]
Parser UpdatableIndexSetting
-> Parser UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Bool -> Parser UpdatableIndexSetting
blocksReadOnly (Bool -> Parser UpdatableIndexSetting)
-> [Key] -> Parser UpdatableIndexSetting
forall a b. FromJSON a => (a -> Parser b) -> [Key] -> Parser b
`taggedAt` [Key
"blocks", Key
"read_only"]
Parser UpdatableIndexSetting
-> Parser UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Bool -> Parser UpdatableIndexSetting
blocksRead (Bool -> Parser UpdatableIndexSetting)
-> [Key] -> Parser UpdatableIndexSetting
forall a b. FromJSON a => (a -> Parser b) -> [Key] -> Parser b
`taggedAt` [Key
"blocks", Key
"read"]
Parser UpdatableIndexSetting
-> Parser UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Bool -> Parser UpdatableIndexSetting
blocksWrite (Bool -> Parser UpdatableIndexSetting)
-> [Key] -> Parser UpdatableIndexSetting
forall a b. FromJSON a => (a -> Parser b) -> [Key] -> Parser b
`taggedAt` [Key
"blocks", Key
"write"]
Parser UpdatableIndexSetting
-> Parser UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Bool -> Parser UpdatableIndexSetting
blocksMetaData (Bool -> Parser UpdatableIndexSetting)
-> [Key] -> Parser UpdatableIndexSetting
forall a b. FromJSON a => (a -> Parser b) -> [Key] -> Parser b
`taggedAt` [Key
"blocks", Key
"metadata"]
Parser UpdatableIndexSetting
-> Parser UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Int -> Parser UpdatableIndexSetting
mappingTotalFieldsLimit (Int -> Parser UpdatableIndexSetting)
-> [Key] -> Parser UpdatableIndexSetting
forall a b. FromJSON a => (a -> Parser b) -> [Key] -> Parser b
`taggedAt` [Key
"index", Key
"mapping", Key
"total_fields", Key
"limit"]
Parser UpdatableIndexSetting
-> Parser UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Analysis -> Parser UpdatableIndexSetting
analysisSetting (Analysis -> Parser UpdatableIndexSetting)
-> [Key] -> Parser UpdatableIndexSetting
forall a b. FromJSON a => (a -> Parser b) -> [Key] -> Parser b
`taggedAt` [Key
"index", Key
"analysis"]
Parser UpdatableIndexSetting
-> Parser UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> NominalDiffTimeJSON -> Parser UpdatableIndexSetting
unassignedNodeLeftDelayedTimeout (NominalDiffTimeJSON -> Parser UpdatableIndexSetting)
-> [Key] -> Parser UpdatableIndexSetting
forall a b. FromJSON a => (a -> Parser b) -> [Key] -> Parser b
`taggedAt` [Key
"index", Key
"unassigned", Key
"node_left", Key
"delayed_timeout"]
where taggedAt :: (a -> Parser b) -> [Key] -> Parser b
taggedAt a -> Parser b
f [Key]
ks = (a -> Parser b) -> Value -> [Key] -> Parser b
forall a b.
FromJSON a =>
(a -> Parser b) -> Value -> [Key] -> Parser b
taggedAt' a -> Parser b
f (Object -> Value
Object Object
o) [Key]
ks
taggedAt' :: (a -> Parser b) -> Value -> [Key] -> Parser b
taggedAt' a -> Parser b
f Value
v [] =
a -> Parser b
f (a -> Parser b) -> Parser a -> Parser b
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< (Value -> Parser a
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Value -> Parser a
forall a. FromJSON a => Value -> Parser a
parseJSON (Value -> Value
unStringlyTypeJSON Value
v))
taggedAt' a -> Parser b
f Value
v (Key
k:[Key]
ks) =
String -> (Object -> Parser b) -> Value -> Parser b
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Object" (\Object
o -> do Value
v' <- Object
o Object -> Key -> Parser Value
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
k
(a -> Parser b) -> Value -> [Key] -> Parser b
taggedAt' a -> Parser b
f Value
v' [Key]
ks) Value
v
numberOfReplicas :: ReplicaCount -> Parser UpdatableIndexSetting
numberOfReplicas = UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Applicative f => a -> f a
pure (UpdatableIndexSetting -> Parser UpdatableIndexSetting)
-> (ReplicaCount -> UpdatableIndexSetting)
-> ReplicaCount
-> Parser UpdatableIndexSetting
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ReplicaCount -> UpdatableIndexSetting
NumberOfReplicas
autoExpandReplicas :: ReplicaBounds -> Parser UpdatableIndexSetting
autoExpandReplicas = UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Applicative f => a -> f a
pure (UpdatableIndexSetting -> Parser UpdatableIndexSetting)
-> (ReplicaBounds -> UpdatableIndexSetting)
-> ReplicaBounds
-> Parser UpdatableIndexSetting
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ReplicaBounds -> UpdatableIndexSetting
AutoExpandReplicas
refreshInterval :: NominalDiffTimeJSON -> Parser UpdatableIndexSetting
refreshInterval = UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Applicative f => a -> f a
pure (UpdatableIndexSetting -> Parser UpdatableIndexSetting)
-> (NominalDiffTimeJSON -> UpdatableIndexSetting)
-> NominalDiffTimeJSON
-> Parser UpdatableIndexSetting
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NominalDiffTime -> UpdatableIndexSetting
RefreshInterval (NominalDiffTime -> UpdatableIndexSetting)
-> (NominalDiffTimeJSON -> NominalDiffTime)
-> NominalDiffTimeJSON
-> UpdatableIndexSetting
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NominalDiffTimeJSON -> NominalDiffTime
ndtJSON
indexConcurrency :: Int -> Parser UpdatableIndexSetting
indexConcurrency = UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Applicative f => a -> f a
pure (UpdatableIndexSetting -> Parser UpdatableIndexSetting)
-> (Int -> UpdatableIndexSetting)
-> Int
-> Parser UpdatableIndexSetting
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> UpdatableIndexSetting
IndexConcurrency
failOnMergeFailure :: Bool -> Parser UpdatableIndexSetting
failOnMergeFailure = UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Applicative f => a -> f a
pure (UpdatableIndexSetting -> Parser UpdatableIndexSetting)
-> (Bool -> UpdatableIndexSetting)
-> Bool
-> Parser UpdatableIndexSetting
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> UpdatableIndexSetting
FailOnMergeFailure
translogFlushThresholdOps :: Int -> Parser UpdatableIndexSetting
translogFlushThresholdOps = UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Applicative f => a -> f a
pure (UpdatableIndexSetting -> Parser UpdatableIndexSetting)
-> (Int -> UpdatableIndexSetting)
-> Int
-> Parser UpdatableIndexSetting
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> UpdatableIndexSetting
TranslogFlushThresholdOps
translogFlushThresholdSize :: Bytes -> Parser UpdatableIndexSetting
translogFlushThresholdSize = UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Applicative f => a -> f a
pure (UpdatableIndexSetting -> Parser UpdatableIndexSetting)
-> (Bytes -> UpdatableIndexSetting)
-> Bytes
-> Parser UpdatableIndexSetting
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bytes -> UpdatableIndexSetting
TranslogFlushThresholdSize
translogFlushThresholdPeriod :: NominalDiffTimeJSON -> Parser UpdatableIndexSetting
translogFlushThresholdPeriod = UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Applicative f => a -> f a
pure (UpdatableIndexSetting -> Parser UpdatableIndexSetting)
-> (NominalDiffTimeJSON -> UpdatableIndexSetting)
-> NominalDiffTimeJSON
-> Parser UpdatableIndexSetting
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NominalDiffTime -> UpdatableIndexSetting
TranslogFlushThresholdPeriod (NominalDiffTime -> UpdatableIndexSetting)
-> (NominalDiffTimeJSON -> NominalDiffTime)
-> NominalDiffTimeJSON
-> UpdatableIndexSetting
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NominalDiffTimeJSON -> NominalDiffTime
ndtJSON
translogDisableFlush :: Bool -> Parser UpdatableIndexSetting
translogDisableFlush = UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Applicative f => a -> f a
pure (UpdatableIndexSetting -> Parser UpdatableIndexSetting)
-> (Bool -> UpdatableIndexSetting)
-> Bool
-> Parser UpdatableIndexSetting
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> UpdatableIndexSetting
TranslogDisableFlush
cacheFilterMaxSize :: Maybe Bytes -> Parser UpdatableIndexSetting
cacheFilterMaxSize = UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Applicative f => a -> f a
pure (UpdatableIndexSetting -> Parser UpdatableIndexSetting)
-> (Maybe Bytes -> UpdatableIndexSetting)
-> Maybe Bytes
-> Parser UpdatableIndexSetting
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe Bytes -> UpdatableIndexSetting
CacheFilterMaxSize
cacheFilterExpire :: Maybe NominalDiffTimeJSON -> Parser UpdatableIndexSetting
cacheFilterExpire = UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Applicative f => a -> f a
pure (UpdatableIndexSetting -> Parser UpdatableIndexSetting)
-> (Maybe NominalDiffTimeJSON -> UpdatableIndexSetting)
-> Maybe NominalDiffTimeJSON
-> Parser UpdatableIndexSetting
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe NominalDiffTime -> UpdatableIndexSetting
CacheFilterExpire (Maybe NominalDiffTime -> UpdatableIndexSetting)
-> (Maybe NominalDiffTimeJSON -> Maybe NominalDiffTime)
-> Maybe NominalDiffTimeJSON
-> UpdatableIndexSetting
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (NominalDiffTimeJSON -> NominalDiffTime)
-> Maybe NominalDiffTimeJSON -> Maybe NominalDiffTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap NominalDiffTimeJSON -> NominalDiffTime
ndtJSON
gatewaySnapshotInterval :: NominalDiffTimeJSON -> Parser UpdatableIndexSetting
gatewaySnapshotInterval = UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Applicative f => a -> f a
pure (UpdatableIndexSetting -> Parser UpdatableIndexSetting)
-> (NominalDiffTimeJSON -> UpdatableIndexSetting)
-> NominalDiffTimeJSON
-> Parser UpdatableIndexSetting
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NominalDiffTime -> UpdatableIndexSetting
GatewaySnapshotInterval (NominalDiffTime -> UpdatableIndexSetting)
-> (NominalDiffTimeJSON -> NominalDiffTime)
-> NominalDiffTimeJSON
-> UpdatableIndexSetting
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NominalDiffTimeJSON -> NominalDiffTime
ndtJSON
routingAllocationInclude :: Value -> Parser UpdatableIndexSetting
routingAllocationInclude = (NonEmpty NodeAttrFilter -> UpdatableIndexSetting)
-> Parser (NonEmpty NodeAttrFilter) -> Parser UpdatableIndexSetting
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap NonEmpty NodeAttrFilter -> UpdatableIndexSetting
RoutingAllocationInclude (Parser (NonEmpty NodeAttrFilter) -> Parser UpdatableIndexSetting)
-> (Value -> Parser (NonEmpty NodeAttrFilter))
-> Value
-> Parser UpdatableIndexSetting
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> Parser (NonEmpty NodeAttrFilter)
parseAttrFilter
routingAllocationExclude :: Value -> Parser UpdatableIndexSetting
routingAllocationExclude = (NonEmpty NodeAttrFilter -> UpdatableIndexSetting)
-> Parser (NonEmpty NodeAttrFilter) -> Parser UpdatableIndexSetting
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap NonEmpty NodeAttrFilter -> UpdatableIndexSetting
RoutingAllocationExclude (Parser (NonEmpty NodeAttrFilter) -> Parser UpdatableIndexSetting)
-> (Value -> Parser (NonEmpty NodeAttrFilter))
-> Value
-> Parser UpdatableIndexSetting
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> Parser (NonEmpty NodeAttrFilter)
parseAttrFilter
routingAllocationRequire :: Value -> Parser UpdatableIndexSetting
routingAllocationRequire = (NonEmpty NodeAttrFilter -> UpdatableIndexSetting)
-> Parser (NonEmpty NodeAttrFilter) -> Parser UpdatableIndexSetting
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap NonEmpty NodeAttrFilter -> UpdatableIndexSetting
RoutingAllocationRequire (Parser (NonEmpty NodeAttrFilter) -> Parser UpdatableIndexSetting)
-> (Value -> Parser (NonEmpty NodeAttrFilter))
-> Value
-> Parser UpdatableIndexSetting
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> Parser (NonEmpty NodeAttrFilter)
parseAttrFilter
routingAllocationEnable :: AllocationPolicy -> Parser UpdatableIndexSetting
routingAllocationEnable = UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Applicative f => a -> f a
pure (UpdatableIndexSetting -> Parser UpdatableIndexSetting)
-> (AllocationPolicy -> UpdatableIndexSetting)
-> AllocationPolicy
-> Parser UpdatableIndexSetting
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AllocationPolicy -> UpdatableIndexSetting
RoutingAllocationEnable
routingAllocationShardsPerNode :: ShardCount -> Parser UpdatableIndexSetting
routingAllocationShardsPerNode = UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Applicative f => a -> f a
pure (UpdatableIndexSetting -> Parser UpdatableIndexSetting)
-> (ShardCount -> UpdatableIndexSetting)
-> ShardCount
-> Parser UpdatableIndexSetting
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShardCount -> UpdatableIndexSetting
RoutingAllocationShardsPerNode
recoveryInitialShards :: InitialShardCount -> Parser UpdatableIndexSetting
recoveryInitialShards = UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Applicative f => a -> f a
pure (UpdatableIndexSetting -> Parser UpdatableIndexSetting)
-> (InitialShardCount -> UpdatableIndexSetting)
-> InitialShardCount
-> Parser UpdatableIndexSetting
forall b c a. (b -> c) -> (a -> b) -> a -> c
. InitialShardCount -> UpdatableIndexSetting
RecoveryInitialShards
gcDeletes :: NominalDiffTimeJSON -> Parser UpdatableIndexSetting
gcDeletes = UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Applicative f => a -> f a
pure (UpdatableIndexSetting -> Parser UpdatableIndexSetting)
-> (NominalDiffTimeJSON -> UpdatableIndexSetting)
-> NominalDiffTimeJSON
-> Parser UpdatableIndexSetting
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NominalDiffTime -> UpdatableIndexSetting
GCDeletes (NominalDiffTime -> UpdatableIndexSetting)
-> (NominalDiffTimeJSON -> NominalDiffTime)
-> NominalDiffTimeJSON
-> UpdatableIndexSetting
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NominalDiffTimeJSON -> NominalDiffTime
ndtJSON
ttlDisablePurge :: Bool -> Parser UpdatableIndexSetting
ttlDisablePurge = UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Applicative f => a -> f a
pure (UpdatableIndexSetting -> Parser UpdatableIndexSetting)
-> (Bool -> UpdatableIndexSetting)
-> Bool
-> Parser UpdatableIndexSetting
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> UpdatableIndexSetting
TTLDisablePurge
translogFSType :: FSType -> Parser UpdatableIndexSetting
translogFSType = UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Applicative f => a -> f a
pure (UpdatableIndexSetting -> Parser UpdatableIndexSetting)
-> (FSType -> UpdatableIndexSetting)
-> FSType
-> Parser UpdatableIndexSetting
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FSType -> UpdatableIndexSetting
TranslogFSType
compressionSetting :: Compression -> Parser UpdatableIndexSetting
compressionSetting = UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Applicative f => a -> f a
pure (UpdatableIndexSetting -> Parser UpdatableIndexSetting)
-> (Compression -> UpdatableIndexSetting)
-> Compression
-> Parser UpdatableIndexSetting
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Compression -> UpdatableIndexSetting
CompressionSetting
compoundFormat :: CompoundFormat -> Parser UpdatableIndexSetting
compoundFormat = UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Applicative f => a -> f a
pure (UpdatableIndexSetting -> Parser UpdatableIndexSetting)
-> (CompoundFormat -> UpdatableIndexSetting)
-> CompoundFormat
-> Parser UpdatableIndexSetting
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CompoundFormat -> UpdatableIndexSetting
IndexCompoundFormat
compoundOnFlush :: Bool -> Parser UpdatableIndexSetting
compoundOnFlush = UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Applicative f => a -> f a
pure (UpdatableIndexSetting -> Parser UpdatableIndexSetting)
-> (Bool -> UpdatableIndexSetting)
-> Bool
-> Parser UpdatableIndexSetting
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> UpdatableIndexSetting
IndexCompoundOnFlush
warmerEnabled :: Bool -> Parser UpdatableIndexSetting
warmerEnabled = UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Applicative f => a -> f a
pure (UpdatableIndexSetting -> Parser UpdatableIndexSetting)
-> (Bool -> UpdatableIndexSetting)
-> Bool
-> Parser UpdatableIndexSetting
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> UpdatableIndexSetting
WarmerEnabled
blocksReadOnly :: Bool -> Parser UpdatableIndexSetting
blocksReadOnly = UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Applicative f => a -> f a
pure (UpdatableIndexSetting -> Parser UpdatableIndexSetting)
-> (Bool -> UpdatableIndexSetting)
-> Bool
-> Parser UpdatableIndexSetting
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> UpdatableIndexSetting
BlocksReadOnly
blocksRead :: Bool -> Parser UpdatableIndexSetting
blocksRead = UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Applicative f => a -> f a
pure (UpdatableIndexSetting -> Parser UpdatableIndexSetting)
-> (Bool -> UpdatableIndexSetting)
-> Bool
-> Parser UpdatableIndexSetting
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> UpdatableIndexSetting
BlocksRead
blocksWrite :: Bool -> Parser UpdatableIndexSetting
blocksWrite = UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Applicative f => a -> f a
pure (UpdatableIndexSetting -> Parser UpdatableIndexSetting)
-> (Bool -> UpdatableIndexSetting)
-> Bool
-> Parser UpdatableIndexSetting
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> UpdatableIndexSetting
BlocksWrite
blocksMetaData :: Bool -> Parser UpdatableIndexSetting
blocksMetaData = UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Applicative f => a -> f a
pure (UpdatableIndexSetting -> Parser UpdatableIndexSetting)
-> (Bool -> UpdatableIndexSetting)
-> Bool
-> Parser UpdatableIndexSetting
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> UpdatableIndexSetting
BlocksMetaData
mappingTotalFieldsLimit :: Int -> Parser UpdatableIndexSetting
mappingTotalFieldsLimit = UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Applicative f => a -> f a
pure (UpdatableIndexSetting -> Parser UpdatableIndexSetting)
-> (Int -> UpdatableIndexSetting)
-> Int
-> Parser UpdatableIndexSetting
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> UpdatableIndexSetting
MappingTotalFieldsLimit
analysisSetting :: Analysis -> Parser UpdatableIndexSetting
analysisSetting = UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Applicative f => a -> f a
pure (UpdatableIndexSetting -> Parser UpdatableIndexSetting)
-> (Analysis -> UpdatableIndexSetting)
-> Analysis
-> Parser UpdatableIndexSetting
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Analysis -> UpdatableIndexSetting
AnalysisSetting
unassignedNodeLeftDelayedTimeout :: NominalDiffTimeJSON -> Parser UpdatableIndexSetting
unassignedNodeLeftDelayedTimeout = UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Applicative f => a -> f a
pure (UpdatableIndexSetting -> Parser UpdatableIndexSetting)
-> (NominalDiffTimeJSON -> UpdatableIndexSetting)
-> NominalDiffTimeJSON
-> Parser UpdatableIndexSetting
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NominalDiffTime -> UpdatableIndexSetting
UnassignedNodeLeftDelayedTimeout (NominalDiffTime -> UpdatableIndexSetting)
-> (NominalDiffTimeJSON -> NominalDiffTime)
-> NominalDiffTimeJSON
-> UpdatableIndexSetting
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NominalDiffTimeJSON -> NominalDiffTime
ndtJSON
data ReplicaBounds = ReplicasBounded Int Int
| ReplicasLowerBounded Int
| ReplicasUnbounded
deriving (ReplicaBounds -> ReplicaBounds -> Bool
(ReplicaBounds -> ReplicaBounds -> Bool)
-> (ReplicaBounds -> ReplicaBounds -> Bool) -> Eq ReplicaBounds
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ReplicaBounds -> ReplicaBounds -> Bool
$c/= :: ReplicaBounds -> ReplicaBounds -> Bool
== :: ReplicaBounds -> ReplicaBounds -> Bool
$c== :: ReplicaBounds -> ReplicaBounds -> Bool
Eq, Int -> ReplicaBounds -> ShowS
[ReplicaBounds] -> ShowS
ReplicaBounds -> String
(Int -> ReplicaBounds -> ShowS)
-> (ReplicaBounds -> String)
-> ([ReplicaBounds] -> ShowS)
-> Show ReplicaBounds
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ReplicaBounds] -> ShowS
$cshowList :: [ReplicaBounds] -> ShowS
show :: ReplicaBounds -> String
$cshow :: ReplicaBounds -> String
showsPrec :: Int -> ReplicaBounds -> ShowS
$cshowsPrec :: Int -> ReplicaBounds -> ShowS
Show)
instance ToJSON ReplicaBounds where
toJSON :: ReplicaBounds -> Value
toJSON (ReplicasBounded Int
a Int
b) = Text -> Value
String (Int -> Text
forall a. Show a => a -> Text
showText Int
a Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"-" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Int -> Text
forall a. Show a => a -> Text
showText Int
b)
toJSON (ReplicasLowerBounded Int
a) = Text -> Value
String (Int -> Text
forall a. Show a => a -> Text
showText Int
a Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"-all")
toJSON ReplicaBounds
ReplicasUnbounded = Bool -> Value
Bool Bool
False
instance FromJSON ReplicaBounds where
parseJSON :: Value -> Parser ReplicaBounds
parseJSON Value
v = String
-> (Text -> Parser ReplicaBounds) -> Value -> Parser ReplicaBounds
forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"ReplicaBounds" Text -> Parser ReplicaBounds
parseText Value
v
Parser ReplicaBounds
-> Parser ReplicaBounds -> Parser ReplicaBounds
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> String
-> (Bool -> Parser ReplicaBounds) -> Value -> Parser ReplicaBounds
forall a. String -> (Bool -> Parser a) -> Value -> Parser a
withBool String
"ReplicaBounds" Bool -> Parser ReplicaBounds
forall (f :: * -> *). MonadFail f => Bool -> f ReplicaBounds
parseBool Value
v
where parseText :: Text -> Parser ReplicaBounds
parseText Text
t = case Text -> Text -> [Text]
T.splitOn Text
"-" Text
t of
[Text
a, Text
"all"] -> Int -> ReplicaBounds
ReplicasLowerBounded (Int -> ReplicaBounds) -> Parser Int -> Parser ReplicaBounds
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Parser Int
forall a. Read a => Text -> Parser a
parseReadText Text
a
[Text
a, Text
b] -> Int -> Int -> ReplicaBounds
ReplicasBounded (Int -> Int -> ReplicaBounds)
-> Parser Int -> Parser (Int -> ReplicaBounds)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Parser Int
forall a. Read a => Text -> Parser a
parseReadText Text
a
Parser (Int -> ReplicaBounds) -> Parser Int -> Parser ReplicaBounds
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Parser Int
forall a. Read a => Text -> Parser a
parseReadText Text
b
[Text]
_ -> String -> Parser ReplicaBounds
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String
"Could not parse ReplicaBounds: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Text -> String
forall a. Show a => a -> String
show Text
t)
parseBool :: Bool -> f ReplicaBounds
parseBool Bool
False = ReplicaBounds -> f ReplicaBounds
forall (f :: * -> *) a. Applicative f => a -> f a
pure ReplicaBounds
ReplicasUnbounded
parseBool Bool
_ = String -> f ReplicaBounds
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"ReplicasUnbounded cannot be represented with True"
data Compression
= CompressionDefault
| CompressionBest
deriving (Compression -> Compression -> Bool
(Compression -> Compression -> Bool)
-> (Compression -> Compression -> Bool) -> Eq Compression
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Compression -> Compression -> Bool
$c/= :: Compression -> Compression -> Bool
== :: Compression -> Compression -> Bool
$c== :: Compression -> Compression -> Bool
Eq,Int -> Compression -> ShowS
[Compression] -> ShowS
Compression -> String
(Int -> Compression -> ShowS)
-> (Compression -> String)
-> ([Compression] -> ShowS)
-> Show Compression
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Compression] -> ShowS
$cshowList :: [Compression] -> ShowS
show :: Compression -> String
$cshow :: Compression -> String
showsPrec :: Int -> Compression -> ShowS
$cshowsPrec :: Int -> Compression -> ShowS
Show)
instance ToJSON Compression where
toJSON :: Compression -> Value
toJSON Compression
x = case Compression
x of
Compression
CompressionDefault -> Text -> Value
forall a. ToJSON a => a -> Value
toJSON (Text
"default" :: Text)
Compression
CompressionBest -> Text -> Value
forall a. ToJSON a => a -> Value
toJSON (Text
"best_compression" :: Text)
instance FromJSON Compression where
parseJSON :: Value -> Parser Compression
parseJSON = String
-> (Text -> Parser Compression) -> Value -> Parser Compression
forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"Compression" ((Text -> Parser Compression) -> Value -> Parser Compression)
-> (Text -> Parser Compression) -> Value -> Parser Compression
forall a b. (a -> b) -> a -> b
$ \Text
t -> case Text
t of
Text
"default" -> Compression -> Parser Compression
forall (m :: * -> *) a. Monad m => a -> m a
return Compression
CompressionDefault
Text
"best_compression" -> Compression -> Parser Compression
forall (m :: * -> *) a. Monad m => a -> m a
return Compression
CompressionBest
Text
_ -> String -> Parser Compression
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"invalid compression codec"
newtype Bytes =
Bytes Int
deriving (Bytes -> Bytes -> Bool
(Bytes -> Bytes -> Bool) -> (Bytes -> Bytes -> Bool) -> Eq Bytes
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Bytes -> Bytes -> Bool
$c/= :: Bytes -> Bytes -> Bool
== :: Bytes -> Bytes -> Bool
$c== :: Bytes -> Bytes -> Bool
Eq, Int -> Bytes -> ShowS
[Bytes] -> ShowS
Bytes -> String
(Int -> Bytes -> ShowS)
-> (Bytes -> String) -> ([Bytes] -> ShowS) -> Show Bytes
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Bytes] -> ShowS
$cshowList :: [Bytes] -> ShowS
show :: Bytes -> String
$cshow :: Bytes -> String
showsPrec :: Int -> Bytes -> ShowS
$cshowsPrec :: Int -> Bytes -> ShowS
Show, Eq Bytes
Eq Bytes
-> (Bytes -> Bytes -> Ordering)
-> (Bytes -> Bytes -> Bool)
-> (Bytes -> Bytes -> Bool)
-> (Bytes -> Bytes -> Bool)
-> (Bytes -> Bytes -> Bool)
-> (Bytes -> Bytes -> Bytes)
-> (Bytes -> Bytes -> Bytes)
-> Ord Bytes
Bytes -> Bytes -> Bool
Bytes -> Bytes -> Ordering
Bytes -> Bytes -> Bytes
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 :: Bytes -> Bytes -> Bytes
$cmin :: Bytes -> Bytes -> Bytes
max :: Bytes -> Bytes -> Bytes
$cmax :: Bytes -> Bytes -> Bytes
>= :: Bytes -> Bytes -> Bool
$c>= :: Bytes -> Bytes -> Bool
> :: Bytes -> Bytes -> Bool
$c> :: Bytes -> Bytes -> Bool
<= :: Bytes -> Bytes -> Bool
$c<= :: Bytes -> Bytes -> Bool
< :: Bytes -> Bytes -> Bool
$c< :: Bytes -> Bytes -> Bool
compare :: Bytes -> Bytes -> Ordering
$ccompare :: Bytes -> Bytes -> Ordering
$cp1Ord :: Eq Bytes
Ord, [Bytes] -> Encoding
[Bytes] -> Value
Bytes -> Encoding
Bytes -> Value
(Bytes -> Value)
-> (Bytes -> Encoding)
-> ([Bytes] -> Value)
-> ([Bytes] -> Encoding)
-> ToJSON Bytes
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [Bytes] -> Encoding
$ctoEncodingList :: [Bytes] -> Encoding
toJSONList :: [Bytes] -> Value
$ctoJSONList :: [Bytes] -> Value
toEncoding :: Bytes -> Encoding
$ctoEncoding :: Bytes -> Encoding
toJSON :: Bytes -> Value
$ctoJSON :: Bytes -> Value
ToJSON, Value -> Parser [Bytes]
Value -> Parser Bytes
(Value -> Parser Bytes)
-> (Value -> Parser [Bytes]) -> FromJSON Bytes
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [Bytes]
$cparseJSONList :: Value -> Parser [Bytes]
parseJSON :: Value -> Parser Bytes
$cparseJSON :: Value -> Parser Bytes
FromJSON)
gigabytes :: Int -> Bytes
gigabytes :: Int -> Bytes
gigabytes Int
n = Int -> Bytes
megabytes (Int
1000 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
n)
megabytes :: Int -> Bytes
megabytes :: Int -> Bytes
megabytes Int
n = Int -> Bytes
kilobytes (Int
1000 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
n)
kilobytes :: Int -> Bytes
kilobytes :: Int -> Bytes
kilobytes Int
n = Int -> Bytes
Bytes (Int
1000 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
n)
data FSType = FSSimple
| FSBuffered deriving (FSType -> FSType -> Bool
(FSType -> FSType -> Bool)
-> (FSType -> FSType -> Bool) -> Eq FSType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FSType -> FSType -> Bool
$c/= :: FSType -> FSType -> Bool
== :: FSType -> FSType -> Bool
$c== :: FSType -> FSType -> Bool
Eq, Int -> FSType -> ShowS
[FSType] -> ShowS
FSType -> String
(Int -> FSType -> ShowS)
-> (FSType -> String) -> ([FSType] -> ShowS) -> Show FSType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FSType] -> ShowS
$cshowList :: [FSType] -> ShowS
show :: FSType -> String
$cshow :: FSType -> String
showsPrec :: Int -> FSType -> ShowS
$cshowsPrec :: Int -> FSType -> ShowS
Show)
instance ToJSON FSType where
toJSON :: FSType -> Value
toJSON FSType
FSSimple = Value
"simple"
toJSON FSType
FSBuffered = Value
"buffered"
instance FromJSON FSType where
parseJSON :: Value -> Parser FSType
parseJSON = String -> (Text -> Parser FSType) -> Value -> Parser FSType
forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"FSType" Text -> Parser FSType
forall a (f :: * -> *).
(Eq a, IsString a, MonadFail f, Show a) =>
a -> f FSType
parse
where parse :: a -> f FSType
parse a
"simple" = FSType -> f FSType
forall (f :: * -> *) a. Applicative f => a -> f a
pure FSType
FSSimple
parse a
"buffered" = FSType -> f FSType
forall (f :: * -> *) a. Applicative f => a -> f a
pure FSType
FSBuffered
parse a
t = String -> f FSType
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String
"Invalid FSType: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> a -> String
forall a. Show a => a -> String
show a
t)
data InitialShardCount = QuorumShards
| QuorumMinus1Shards
| FullShards
| FullMinus1Shards
| ExplicitShards Int
deriving (InitialShardCount -> InitialShardCount -> Bool
(InitialShardCount -> InitialShardCount -> Bool)
-> (InitialShardCount -> InitialShardCount -> Bool)
-> Eq InitialShardCount
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InitialShardCount -> InitialShardCount -> Bool
$c/= :: InitialShardCount -> InitialShardCount -> Bool
== :: InitialShardCount -> InitialShardCount -> Bool
$c== :: InitialShardCount -> InitialShardCount -> Bool
Eq, Int -> InitialShardCount -> ShowS
[InitialShardCount] -> ShowS
InitialShardCount -> String
(Int -> InitialShardCount -> ShowS)
-> (InitialShardCount -> String)
-> ([InitialShardCount] -> ShowS)
-> Show InitialShardCount
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InitialShardCount] -> ShowS
$cshowList :: [InitialShardCount] -> ShowS
show :: InitialShardCount -> String
$cshow :: InitialShardCount -> String
showsPrec :: Int -> InitialShardCount -> ShowS
$cshowsPrec :: Int -> InitialShardCount -> ShowS
Show)
instance FromJSON InitialShardCount where
parseJSON :: Value -> Parser InitialShardCount
parseJSON Value
v = String
-> (Text -> Parser InitialShardCount)
-> Value
-> Parser InitialShardCount
forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"InitialShardCount" Text -> Parser InitialShardCount
forall a (f :: * -> *).
(Eq a, IsString a, MonadPlus f) =>
a -> f InitialShardCount
parseText Value
v
Parser InitialShardCount
-> Parser InitialShardCount -> Parser InitialShardCount
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Int -> InitialShardCount
ExplicitShards (Int -> InitialShardCount)
-> Parser Int -> Parser InitialShardCount
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser Int
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v
where parseText :: a -> f InitialShardCount
parseText a
"quorum" = InitialShardCount -> f InitialShardCount
forall (f :: * -> *) a. Applicative f => a -> f a
pure InitialShardCount
QuorumShards
parseText a
"quorum-1" = InitialShardCount -> f InitialShardCount
forall (f :: * -> *) a. Applicative f => a -> f a
pure InitialShardCount
QuorumMinus1Shards
parseText a
"full" = InitialShardCount -> f InitialShardCount
forall (f :: * -> *) a. Applicative f => a -> f a
pure InitialShardCount
FullShards
parseText a
"full-1" = InitialShardCount -> f InitialShardCount
forall (f :: * -> *) a. Applicative f => a -> f a
pure InitialShardCount
FullMinus1Shards
parseText a
_ = f InitialShardCount
forall (m :: * -> *) a. MonadPlus m => m a
mzero
instance ToJSON InitialShardCount where
toJSON :: InitialShardCount -> Value
toJSON InitialShardCount
QuorumShards = Text -> Value
String Text
"quorum"
toJSON InitialShardCount
QuorumMinus1Shards = Text -> Value
String Text
"quorum-1"
toJSON InitialShardCount
FullShards = Text -> Value
String Text
"full"
toJSON InitialShardCount
FullMinus1Shards = Text -> Value
String Text
"full-1"
toJSON (ExplicitShards Int
x) = Int -> Value
forall a. ToJSON a => a -> Value
toJSON Int
x
data NodeAttrFilter = NodeAttrFilter
{ NodeAttrFilter -> NodeAttrName
nodeAttrFilterName :: NodeAttrName
, NodeAttrFilter -> NonEmpty Text
nodeAttrFilterValues :: NonEmpty Text }
deriving (NodeAttrFilter -> NodeAttrFilter -> Bool
(NodeAttrFilter -> NodeAttrFilter -> Bool)
-> (NodeAttrFilter -> NodeAttrFilter -> Bool) -> Eq NodeAttrFilter
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NodeAttrFilter -> NodeAttrFilter -> Bool
$c/= :: NodeAttrFilter -> NodeAttrFilter -> Bool
== :: NodeAttrFilter -> NodeAttrFilter -> Bool
$c== :: NodeAttrFilter -> NodeAttrFilter -> Bool
Eq, Eq NodeAttrFilter
Eq NodeAttrFilter
-> (NodeAttrFilter -> NodeAttrFilter -> Ordering)
-> (NodeAttrFilter -> NodeAttrFilter -> Bool)
-> (NodeAttrFilter -> NodeAttrFilter -> Bool)
-> (NodeAttrFilter -> NodeAttrFilter -> Bool)
-> (NodeAttrFilter -> NodeAttrFilter -> Bool)
-> (NodeAttrFilter -> NodeAttrFilter -> NodeAttrFilter)
-> (NodeAttrFilter -> NodeAttrFilter -> NodeAttrFilter)
-> Ord NodeAttrFilter
NodeAttrFilter -> NodeAttrFilter -> Bool
NodeAttrFilter -> NodeAttrFilter -> Ordering
NodeAttrFilter -> NodeAttrFilter -> NodeAttrFilter
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 :: NodeAttrFilter -> NodeAttrFilter -> NodeAttrFilter
$cmin :: NodeAttrFilter -> NodeAttrFilter -> NodeAttrFilter
max :: NodeAttrFilter -> NodeAttrFilter -> NodeAttrFilter
$cmax :: NodeAttrFilter -> NodeAttrFilter -> NodeAttrFilter
>= :: NodeAttrFilter -> NodeAttrFilter -> Bool
$c>= :: NodeAttrFilter -> NodeAttrFilter -> Bool
> :: NodeAttrFilter -> NodeAttrFilter -> Bool
$c> :: NodeAttrFilter -> NodeAttrFilter -> Bool
<= :: NodeAttrFilter -> NodeAttrFilter -> Bool
$c<= :: NodeAttrFilter -> NodeAttrFilter -> Bool
< :: NodeAttrFilter -> NodeAttrFilter -> Bool
$c< :: NodeAttrFilter -> NodeAttrFilter -> Bool
compare :: NodeAttrFilter -> NodeAttrFilter -> Ordering
$ccompare :: NodeAttrFilter -> NodeAttrFilter -> Ordering
$cp1Ord :: Eq NodeAttrFilter
Ord, Int -> NodeAttrFilter -> ShowS
[NodeAttrFilter] -> ShowS
NodeAttrFilter -> String
(Int -> NodeAttrFilter -> ShowS)
-> (NodeAttrFilter -> String)
-> ([NodeAttrFilter] -> ShowS)
-> Show NodeAttrFilter
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NodeAttrFilter] -> ShowS
$cshowList :: [NodeAttrFilter] -> ShowS
show :: NodeAttrFilter -> String
$cshow :: NodeAttrFilter -> String
showsPrec :: Int -> NodeAttrFilter -> ShowS
$cshowsPrec :: Int -> NodeAttrFilter -> ShowS
Show)
newtype NodeAttrName = NodeAttrName Text deriving (NodeAttrName -> NodeAttrName -> Bool
(NodeAttrName -> NodeAttrName -> Bool)
-> (NodeAttrName -> NodeAttrName -> Bool) -> Eq NodeAttrName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NodeAttrName -> NodeAttrName -> Bool
$c/= :: NodeAttrName -> NodeAttrName -> Bool
== :: NodeAttrName -> NodeAttrName -> Bool
$c== :: NodeAttrName -> NodeAttrName -> Bool
Eq, Eq NodeAttrName
Eq NodeAttrName
-> (NodeAttrName -> NodeAttrName -> Ordering)
-> (NodeAttrName -> NodeAttrName -> Bool)
-> (NodeAttrName -> NodeAttrName -> Bool)
-> (NodeAttrName -> NodeAttrName -> Bool)
-> (NodeAttrName -> NodeAttrName -> Bool)
-> (NodeAttrName -> NodeAttrName -> NodeAttrName)
-> (NodeAttrName -> NodeAttrName -> NodeAttrName)
-> Ord NodeAttrName
NodeAttrName -> NodeAttrName -> Bool
NodeAttrName -> NodeAttrName -> Ordering
NodeAttrName -> NodeAttrName -> NodeAttrName
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 :: NodeAttrName -> NodeAttrName -> NodeAttrName
$cmin :: NodeAttrName -> NodeAttrName -> NodeAttrName
max :: NodeAttrName -> NodeAttrName -> NodeAttrName
$cmax :: NodeAttrName -> NodeAttrName -> NodeAttrName
>= :: NodeAttrName -> NodeAttrName -> Bool
$c>= :: NodeAttrName -> NodeAttrName -> Bool
> :: NodeAttrName -> NodeAttrName -> Bool
$c> :: NodeAttrName -> NodeAttrName -> Bool
<= :: NodeAttrName -> NodeAttrName -> Bool
$c<= :: NodeAttrName -> NodeAttrName -> Bool
< :: NodeAttrName -> NodeAttrName -> Bool
$c< :: NodeAttrName -> NodeAttrName -> Bool
compare :: NodeAttrName -> NodeAttrName -> Ordering
$ccompare :: NodeAttrName -> NodeAttrName -> Ordering
$cp1Ord :: Eq NodeAttrName
Ord, Int -> NodeAttrName -> ShowS
[NodeAttrName] -> ShowS
NodeAttrName -> String
(Int -> NodeAttrName -> ShowS)
-> (NodeAttrName -> String)
-> ([NodeAttrName] -> ShowS)
-> Show NodeAttrName
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NodeAttrName] -> ShowS
$cshowList :: [NodeAttrName] -> ShowS
show :: NodeAttrName -> String
$cshow :: NodeAttrName -> String
showsPrec :: Int -> NodeAttrName -> ShowS
$cshowsPrec :: Int -> NodeAttrName -> ShowS
Show)
data CompoundFormat = CompoundFileFormat Bool
| MergeSegmentVsTotalIndex Double
deriving (CompoundFormat -> CompoundFormat -> Bool
(CompoundFormat -> CompoundFormat -> Bool)
-> (CompoundFormat -> CompoundFormat -> Bool) -> Eq CompoundFormat
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CompoundFormat -> CompoundFormat -> Bool
$c/= :: CompoundFormat -> CompoundFormat -> Bool
== :: CompoundFormat -> CompoundFormat -> Bool
$c== :: CompoundFormat -> CompoundFormat -> Bool
Eq, Int -> CompoundFormat -> ShowS
[CompoundFormat] -> ShowS
CompoundFormat -> String
(Int -> CompoundFormat -> ShowS)
-> (CompoundFormat -> String)
-> ([CompoundFormat] -> ShowS)
-> Show CompoundFormat
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CompoundFormat] -> ShowS
$cshowList :: [CompoundFormat] -> ShowS
show :: CompoundFormat -> String
$cshow :: CompoundFormat -> String
showsPrec :: Int -> CompoundFormat -> ShowS
$cshowsPrec :: Int -> CompoundFormat -> ShowS
Show)
instance ToJSON CompoundFormat where
toJSON :: CompoundFormat -> Value
toJSON (CompoundFileFormat Bool
x) = Bool -> Value
Bool Bool
x
toJSON (MergeSegmentVsTotalIndex Double
x) = Double -> Value
forall a. ToJSON a => a -> Value
toJSON Double
x
instance FromJSON CompoundFormat where
parseJSON :: Value -> Parser CompoundFormat
parseJSON Value
v = Bool -> CompoundFormat
CompoundFileFormat (Bool -> CompoundFormat) -> Parser Bool -> Parser CompoundFormat
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser Bool
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v
Parser CompoundFormat
-> Parser CompoundFormat -> Parser CompoundFormat
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Double -> CompoundFormat
MergeSegmentVsTotalIndex (Double -> CompoundFormat)
-> Parser Double -> Parser CompoundFormat
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser Double
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v
newtype NominalDiffTimeJSON =
NominalDiffTimeJSON { NominalDiffTimeJSON -> NominalDiffTime
ndtJSON :: NominalDiffTime }
instance ToJSON NominalDiffTimeJSON where
toJSON :: NominalDiffTimeJSON -> Value
toJSON (NominalDiffTimeJSON NominalDiffTime
t) = Text -> Value
String (Integer -> Text
forall a. Show a => a -> Text
showText (NominalDiffTime -> Integer
forall a b. (RealFrac a, Integral b) => a -> b
round NominalDiffTime
t :: Integer) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"s")
instance FromJSON NominalDiffTimeJSON where
parseJSON :: Value -> Parser NominalDiffTimeJSON
parseJSON = String
-> (Text -> Parser NominalDiffTimeJSON)
-> Value
-> Parser NominalDiffTimeJSON
forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"NominalDiffTime" Text -> Parser NominalDiffTimeJSON
parse
where parse :: Text -> Parser NominalDiffTimeJSON
parse Text
t = case Int -> Text -> Text
T.takeEnd Int
1 Text
t of
Text
"s" -> NominalDiffTime -> NominalDiffTimeJSON
NominalDiffTimeJSON (NominalDiffTime -> NominalDiffTimeJSON)
-> (Integer -> NominalDiffTime) -> Integer -> NominalDiffTimeJSON
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> NominalDiffTime
forall a. Num a => Integer -> a
fromInteger (Integer -> NominalDiffTimeJSON)
-> Parser Integer -> Parser NominalDiffTimeJSON
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Parser Integer
forall a. Read a => Text -> Parser a
parseReadText (Int -> Text -> Text
T.dropEnd Int
1 Text
t)
Text
_ -> String -> Parser NominalDiffTimeJSON
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Invalid or missing NominalDiffTime unit (expected s)"
data IndexSettingsSummary = IndexSettingsSummary
{ IndexSettingsSummary -> IndexName
sSummaryIndexName :: IndexName
, IndexSettingsSummary -> IndexSettings
sSummaryFixedSettings :: IndexSettings
, IndexSettingsSummary -> [UpdatableIndexSetting]
sSummaryUpdateable :: [UpdatableIndexSetting]}
deriving (IndexSettingsSummary -> IndexSettingsSummary -> Bool
(IndexSettingsSummary -> IndexSettingsSummary -> Bool)
-> (IndexSettingsSummary -> IndexSettingsSummary -> Bool)
-> Eq IndexSettingsSummary
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IndexSettingsSummary -> IndexSettingsSummary -> Bool
$c/= :: IndexSettingsSummary -> IndexSettingsSummary -> Bool
== :: IndexSettingsSummary -> IndexSettingsSummary -> Bool
$c== :: IndexSettingsSummary -> IndexSettingsSummary -> Bool
Eq, Int -> IndexSettingsSummary -> ShowS
[IndexSettingsSummary] -> ShowS
IndexSettingsSummary -> String
(Int -> IndexSettingsSummary -> ShowS)
-> (IndexSettingsSummary -> String)
-> ([IndexSettingsSummary] -> ShowS)
-> Show IndexSettingsSummary
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IndexSettingsSummary] -> ShowS
$cshowList :: [IndexSettingsSummary] -> ShowS
show :: IndexSettingsSummary -> String
$cshow :: IndexSettingsSummary -> String
showsPrec :: Int -> IndexSettingsSummary -> ShowS
$cshowsPrec :: Int -> IndexSettingsSummary -> ShowS
Show)
parseSettings :: Object -> Parser [UpdatableIndexSetting]
parseSettings :: Object -> Parser [UpdatableIndexSetting]
parseSettings Object
o = do
HashMap Key Value
o' <- Object
o Object -> Key -> Parser (HashMap Key Value)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"index"
[Maybe UpdatableIndexSetting]
parses <- [Pair]
-> (Pair -> Parser (Maybe UpdatableIndexSetting))
-> Parser [Maybe UpdatableIndexSetting]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM (HashMap Key Value -> [Pair]
forall k v. HashMap k v -> [(k, v)]
HM.toList HashMap Key Value
o') ((Pair -> Parser (Maybe UpdatableIndexSetting))
-> Parser [Maybe UpdatableIndexSetting])
-> (Pair -> Parser (Maybe UpdatableIndexSetting))
-> Parser [Maybe UpdatableIndexSetting]
forall a b. (a -> b) -> a -> b
$ \(Key
k, Value
v) -> do
let atRoot :: Value
atRoot = Object -> Value
Object (Key -> Value -> Object
forall v. Key -> v -> KeyMap v
X.singleton Key
k Value
v)
let atIndex :: Value
atIndex = Object -> Value
Object (Key -> Value -> Object
forall v. Key -> v -> KeyMap v
X.singleton Key
"index" Value
atRoot)
Parser UpdatableIndexSetting
-> Parser (Maybe UpdatableIndexSetting)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Value -> Parser UpdatableIndexSetting
forall a. FromJSON a => Value -> Parser a
parseJSON Value
atRoot Parser UpdatableIndexSetting
-> Parser UpdatableIndexSetting -> Parser UpdatableIndexSetting
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Value -> Parser UpdatableIndexSetting
forall a. FromJSON a => Value -> Parser a
parseJSON Value
atIndex)
[UpdatableIndexSetting] -> Parser [UpdatableIndexSetting]
forall (m :: * -> *) a. Monad m => a -> m a
return ([Maybe UpdatableIndexSetting] -> [UpdatableIndexSetting]
forall a. [Maybe a] -> [a]
catMaybes [Maybe UpdatableIndexSetting]
parses)
instance FromJSON IndexSettingsSummary where
parseJSON :: Value -> Parser IndexSettingsSummary
parseJSON = String
-> (Object -> Parser IndexSettingsSummary)
-> Value
-> Parser IndexSettingsSummary
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"IndexSettingsSummary" Object -> Parser IndexSettingsSummary
parse
where parse :: Object -> Parser IndexSettingsSummary
parse Object
o = case Object -> [Pair]
forall v. KeyMap v -> [(Key, v)]
X.toList Object
o of
[(Key
ixn, v :: Value
v@(Object Object
o'))] -> IndexName
-> IndexSettings -> [UpdatableIndexSetting] -> IndexSettingsSummary
IndexSettingsSummary (Text -> IndexName
IndexName (Text -> IndexName) -> Text -> IndexName
forall a b. (a -> b) -> a -> b
$ Key -> Text
toText Key
ixn)
(IndexSettings -> [UpdatableIndexSetting] -> IndexSettingsSummary)
-> Parser IndexSettings
-> Parser ([UpdatableIndexSetting] -> IndexSettingsSummary)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser IndexSettings
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v
Parser ([UpdatableIndexSetting] -> IndexSettingsSummary)
-> Parser [UpdatableIndexSetting] -> Parser IndexSettingsSummary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (([UpdatableIndexSetting] -> [UpdatableIndexSetting])
-> Parser [UpdatableIndexSetting] -> Parser [UpdatableIndexSetting]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((UpdatableIndexSetting -> Bool)
-> [UpdatableIndexSetting] -> [UpdatableIndexSetting]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool)
-> (UpdatableIndexSetting -> Bool) -> UpdatableIndexSetting -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UpdatableIndexSetting -> Bool
redundant)) (Parser [UpdatableIndexSetting] -> Parser [UpdatableIndexSetting])
-> (Object -> Parser [UpdatableIndexSetting])
-> Object
-> Parser [UpdatableIndexSetting]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Object -> Parser [UpdatableIndexSetting]
parseSettings (Object -> Parser [UpdatableIndexSetting])
-> Parser Object -> Parser [UpdatableIndexSetting]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Object
o' Object -> Key -> Parser Object
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"settings")
[Pair]
_ -> String -> Parser IndexSettingsSummary
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Expected single-key object with index name"
redundant :: UpdatableIndexSetting -> Bool
redundant (NumberOfReplicas ReplicaCount
_) = Bool
True
redundant UpdatableIndexSetting
_ = Bool
False
type Reply = Network.HTTP.Client.Response LByteString
data OpenCloseIndex = OpenIndex | CloseIndex deriving (OpenCloseIndex -> OpenCloseIndex -> Bool
(OpenCloseIndex -> OpenCloseIndex -> Bool)
-> (OpenCloseIndex -> OpenCloseIndex -> Bool) -> Eq OpenCloseIndex
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OpenCloseIndex -> OpenCloseIndex -> Bool
$c/= :: OpenCloseIndex -> OpenCloseIndex -> Bool
== :: OpenCloseIndex -> OpenCloseIndex -> Bool
$c== :: OpenCloseIndex -> OpenCloseIndex -> Bool
Eq, Int -> OpenCloseIndex -> ShowS
[OpenCloseIndex] -> ShowS
OpenCloseIndex -> String
(Int -> OpenCloseIndex -> ShowS)
-> (OpenCloseIndex -> String)
-> ([OpenCloseIndex] -> ShowS)
-> Show OpenCloseIndex
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OpenCloseIndex] -> ShowS
$cshowList :: [OpenCloseIndex] -> ShowS
show :: OpenCloseIndex -> String
$cshow :: OpenCloseIndex -> String
showsPrec :: Int -> OpenCloseIndex -> ShowS
$cshowsPrec :: Int -> OpenCloseIndex -> ShowS
Show)
data FieldType = GeoPointType
| GeoShapeType
| FloatType
| IntegerType
| LongType
| ShortType
| ByteType deriving (FieldType -> FieldType -> Bool
(FieldType -> FieldType -> Bool)
-> (FieldType -> FieldType -> Bool) -> Eq FieldType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FieldType -> FieldType -> Bool
$c/= :: FieldType -> FieldType -> Bool
== :: FieldType -> FieldType -> Bool
$c== :: FieldType -> FieldType -> Bool
Eq, Int -> FieldType -> ShowS
[FieldType] -> ShowS
FieldType -> String
(Int -> FieldType -> ShowS)
-> (FieldType -> String)
-> ([FieldType] -> ShowS)
-> Show FieldType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FieldType] -> ShowS
$cshowList :: [FieldType] -> ShowS
show :: FieldType -> String
$cshow :: FieldType -> String
showsPrec :: Int -> FieldType -> ShowS
$cshowsPrec :: Int -> FieldType -> ShowS
Show)
newtype FieldDefinition = FieldDefinition
{ FieldDefinition -> FieldType
fieldType :: FieldType
} deriving (FieldDefinition -> FieldDefinition -> Bool
(FieldDefinition -> FieldDefinition -> Bool)
-> (FieldDefinition -> FieldDefinition -> Bool)
-> Eq FieldDefinition
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FieldDefinition -> FieldDefinition -> Bool
$c/= :: FieldDefinition -> FieldDefinition -> Bool
== :: FieldDefinition -> FieldDefinition -> Bool
$c== :: FieldDefinition -> FieldDefinition -> Bool
Eq, Int -> FieldDefinition -> ShowS
[FieldDefinition] -> ShowS
FieldDefinition -> String
(Int -> FieldDefinition -> ShowS)
-> (FieldDefinition -> String)
-> ([FieldDefinition] -> ShowS)
-> Show FieldDefinition
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FieldDefinition] -> ShowS
$cshowList :: [FieldDefinition] -> ShowS
show :: FieldDefinition -> String
$cshow :: FieldDefinition -> String
showsPrec :: Int -> FieldDefinition -> ShowS
$cshowsPrec :: Int -> FieldDefinition -> ShowS
Show)
data IndexTemplate =
IndexTemplate { IndexTemplate -> [IndexPattern]
templatePatterns :: [IndexPattern]
, IndexTemplate -> Maybe IndexSettings
templateSettings :: Maybe IndexSettings
, IndexTemplate -> Value
templateMappings :: Value
}
instance ToJSON IndexTemplate where
toJSON :: IndexTemplate -> Value
toJSON (IndexTemplate [IndexPattern]
p Maybe IndexSettings
s Value
m) = Value -> Value -> Value
merge
([Pair] -> Value
object [ Key
"index_patterns" Key -> [IndexPattern] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [IndexPattern]
p
, Key
"mappings" Key -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Value
m
])
(Maybe IndexSettings -> Value
forall a. ToJSON a => a -> Value
toJSON Maybe IndexSettings
s)
where
merge :: Value -> Value -> Value
merge (Object Object
o1) (Object Object
o2) = Object -> Value
forall a. ToJSON a => a -> Value
toJSON (Object -> Value) -> Object -> Value
forall a b. (a -> b) -> a -> b
$ Object -> Object -> Object
forall v. KeyMap v -> KeyMap v -> KeyMap v
X.union Object
o1 Object
o2
merge Value
o Value
Null = Value
o
merge Value
_ Value
_ = Value
forall a. HasCallStack => a
undefined
data MappingField =
MappingField { MappingField -> FieldName
mappingFieldName :: FieldName
, MappingField -> FieldDefinition
fieldDefinition :: FieldDefinition }
deriving (MappingField -> MappingField -> Bool
(MappingField -> MappingField -> Bool)
-> (MappingField -> MappingField -> Bool) -> Eq MappingField
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MappingField -> MappingField -> Bool
$c/= :: MappingField -> MappingField -> Bool
== :: MappingField -> MappingField -> Bool
$c== :: MappingField -> MappingField -> Bool
Eq, Int -> MappingField -> ShowS
[MappingField] -> ShowS
MappingField -> String
(Int -> MappingField -> ShowS)
-> (MappingField -> String)
-> ([MappingField] -> ShowS)
-> Show MappingField
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MappingField] -> ShowS
$cshowList :: [MappingField] -> ShowS
show :: MappingField -> String
$cshow :: MappingField -> String
showsPrec :: Int -> MappingField -> ShowS
$cshowsPrec :: Int -> MappingField -> ShowS
Show)
newtype Mapping =
Mapping { Mapping -> [MappingField]
mappingFields :: [MappingField] }
deriving (Mapping -> Mapping -> Bool
(Mapping -> Mapping -> Bool)
-> (Mapping -> Mapping -> Bool) -> Eq Mapping
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Mapping -> Mapping -> Bool
$c/= :: Mapping -> Mapping -> Bool
== :: Mapping -> Mapping -> Bool
$c== :: Mapping -> Mapping -> Bool
Eq, Int -> Mapping -> ShowS
[Mapping] -> ShowS
Mapping -> String
(Int -> Mapping -> ShowS)
-> (Mapping -> String) -> ([Mapping] -> ShowS) -> Show Mapping
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Mapping] -> ShowS
$cshowList :: [Mapping] -> ShowS
show :: Mapping -> String
$cshow :: Mapping -> String
showsPrec :: Int -> Mapping -> ShowS
$cshowsPrec :: Int -> Mapping -> ShowS
Show)
data UpsertActionMetadata
= UA_RetryOnConflict Int
| UA_Version Int
deriving (UpsertActionMetadata -> UpsertActionMetadata -> Bool
(UpsertActionMetadata -> UpsertActionMetadata -> Bool)
-> (UpsertActionMetadata -> UpsertActionMetadata -> Bool)
-> Eq UpsertActionMetadata
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpsertActionMetadata -> UpsertActionMetadata -> Bool
$c/= :: UpsertActionMetadata -> UpsertActionMetadata -> Bool
== :: UpsertActionMetadata -> UpsertActionMetadata -> Bool
$c== :: UpsertActionMetadata -> UpsertActionMetadata -> Bool
Eq, Int -> UpsertActionMetadata -> ShowS
[UpsertActionMetadata] -> ShowS
UpsertActionMetadata -> String
(Int -> UpsertActionMetadata -> ShowS)
-> (UpsertActionMetadata -> String)
-> ([UpsertActionMetadata] -> ShowS)
-> Show UpsertActionMetadata
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpsertActionMetadata] -> ShowS
$cshowList :: [UpsertActionMetadata] -> ShowS
show :: UpsertActionMetadata -> String
$cshow :: UpsertActionMetadata -> String
showsPrec :: Int -> UpsertActionMetadata -> ShowS
$cshowsPrec :: Int -> UpsertActionMetadata -> ShowS
Show)
buildUpsertActionMetadata :: UpsertActionMetadata -> Pair
buildUpsertActionMetadata :: UpsertActionMetadata -> Pair
buildUpsertActionMetadata (UA_RetryOnConflict Int
i) = Key
"retry_on_conflict" Key -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Int
i
buildUpsertActionMetadata (UA_Version Int
i) = Key
"_version" Key -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Int
i
data UpsertPayload
= UpsertDoc Value
| UpsertScript Bool Script Value
deriving (UpsertPayload -> UpsertPayload -> Bool
(UpsertPayload -> UpsertPayload -> Bool)
-> (UpsertPayload -> UpsertPayload -> Bool) -> Eq UpsertPayload
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpsertPayload -> UpsertPayload -> Bool
$c/= :: UpsertPayload -> UpsertPayload -> Bool
== :: UpsertPayload -> UpsertPayload -> Bool
$c== :: UpsertPayload -> UpsertPayload -> Bool
Eq, Int -> UpsertPayload -> ShowS
[UpsertPayload] -> ShowS
UpsertPayload -> String
(Int -> UpsertPayload -> ShowS)
-> (UpsertPayload -> String)
-> ([UpsertPayload] -> ShowS)
-> Show UpsertPayload
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpsertPayload] -> ShowS
$cshowList :: [UpsertPayload] -> ShowS
show :: UpsertPayload -> String
$cshow :: UpsertPayload -> String
showsPrec :: Int -> UpsertPayload -> ShowS
$cshowsPrec :: Int -> UpsertPayload -> ShowS
Show)
data AllocationPolicy = AllocAll
| AllocPrimaries
| AllocNewPrimaries
| AllocNone
deriving (AllocationPolicy -> AllocationPolicy -> Bool
(AllocationPolicy -> AllocationPolicy -> Bool)
-> (AllocationPolicy -> AllocationPolicy -> Bool)
-> Eq AllocationPolicy
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AllocationPolicy -> AllocationPolicy -> Bool
$c/= :: AllocationPolicy -> AllocationPolicy -> Bool
== :: AllocationPolicy -> AllocationPolicy -> Bool
$c== :: AllocationPolicy -> AllocationPolicy -> Bool
Eq, Int -> AllocationPolicy -> ShowS
[AllocationPolicy] -> ShowS
AllocationPolicy -> String
(Int -> AllocationPolicy -> ShowS)
-> (AllocationPolicy -> String)
-> ([AllocationPolicy] -> ShowS)
-> Show AllocationPolicy
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AllocationPolicy] -> ShowS
$cshowList :: [AllocationPolicy] -> ShowS
show :: AllocationPolicy -> String
$cshow :: AllocationPolicy -> String
showsPrec :: Int -> AllocationPolicy -> ShowS
$cshowsPrec :: Int -> AllocationPolicy -> ShowS
Show)
instance ToJSON AllocationPolicy where
toJSON :: AllocationPolicy -> Value
toJSON AllocationPolicy
AllocAll = Text -> Value
String Text
"all"
toJSON AllocationPolicy
AllocPrimaries = Text -> Value
String Text
"primaries"
toJSON AllocationPolicy
AllocNewPrimaries = Text -> Value
String Text
"new_primaries"
toJSON AllocationPolicy
AllocNone = Text -> Value
String Text
"none"
instance FromJSON AllocationPolicy where
parseJSON :: Value -> Parser AllocationPolicy
parseJSON = String
-> (Text -> Parser AllocationPolicy)
-> Value
-> Parser AllocationPolicy
forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"AllocationPolicy" Text -> Parser AllocationPolicy
forall a (f :: * -> *).
(Eq a, IsString a, MonadFail f, Show a) =>
a -> f AllocationPolicy
parse
where parse :: a -> f AllocationPolicy
parse a
"all" = AllocationPolicy -> f AllocationPolicy
forall (f :: * -> *) a. Applicative f => a -> f a
pure AllocationPolicy
AllocAll
parse a
"primaries" = AllocationPolicy -> f AllocationPolicy
forall (f :: * -> *) a. Applicative f => a -> f a
pure AllocationPolicy
AllocPrimaries
parse a
"new_primaries" = AllocationPolicy -> f AllocationPolicy
forall (f :: * -> *) a. Applicative f => a -> f a
pure AllocationPolicy
AllocNewPrimaries
parse a
"none" = AllocationPolicy -> f AllocationPolicy
forall (f :: * -> *) a. Applicative f => a -> f a
pure AllocationPolicy
AllocNone
parse a
t = String -> f AllocationPolicy
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String
"Invlaid AllocationPolicy: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> a -> String
forall a. Show a => a -> String
show a
t)
data BulkOperation =
BulkIndex IndexName DocId Value
| BulkIndexAuto IndexName Value
| BulkIndexEncodingAuto IndexName Encoding
| BulkCreate IndexName DocId Value
| BulkCreateEncoding IndexName DocId Encoding
| BulkDelete IndexName DocId
| BulkUpdate IndexName DocId Value
| BulkUpsert IndexName DocId UpsertPayload [UpsertActionMetadata]
deriving (BulkOperation -> BulkOperation -> Bool
(BulkOperation -> BulkOperation -> Bool)
-> (BulkOperation -> BulkOperation -> Bool) -> Eq BulkOperation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BulkOperation -> BulkOperation -> Bool
$c/= :: BulkOperation -> BulkOperation -> Bool
== :: BulkOperation -> BulkOperation -> Bool
$c== :: BulkOperation -> BulkOperation -> Bool
Eq, Int -> BulkOperation -> ShowS
[BulkOperation] -> ShowS
BulkOperation -> String
(Int -> BulkOperation -> ShowS)
-> (BulkOperation -> String)
-> ([BulkOperation] -> ShowS)
-> Show BulkOperation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BulkOperation] -> ShowS
$cshowList :: [BulkOperation] -> ShowS
show :: BulkOperation -> String
$cshow :: BulkOperation -> String
showsPrec :: Int -> BulkOperation -> ShowS
$cshowsPrec :: Int -> BulkOperation -> ShowS
Show)
data EsResult a = EsResult { EsResult a -> Text
_index :: Text
, EsResult a -> Text
_type :: Text
, EsResult a -> Text
_id :: Text
, EsResult a -> Maybe (EsResultFound a)
foundResult :: Maybe (EsResultFound a)} deriving (EsResult a -> EsResult a -> Bool
(EsResult a -> EsResult a -> Bool)
-> (EsResult a -> EsResult a -> Bool) -> Eq (EsResult a)
forall a. Eq a => EsResult a -> EsResult a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EsResult a -> EsResult a -> Bool
$c/= :: forall a. Eq a => EsResult a -> EsResult a -> Bool
== :: EsResult a -> EsResult a -> Bool
$c== :: forall a. Eq a => EsResult a -> EsResult a -> Bool
Eq, Int -> EsResult a -> ShowS
[EsResult a] -> ShowS
EsResult a -> String
(Int -> EsResult a -> ShowS)
-> (EsResult a -> String)
-> ([EsResult a] -> ShowS)
-> Show (EsResult a)
forall a. Show a => Int -> EsResult a -> ShowS
forall a. Show a => [EsResult a] -> ShowS
forall a. Show a => EsResult a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EsResult a] -> ShowS
$cshowList :: forall a. Show a => [EsResult a] -> ShowS
show :: EsResult a -> String
$cshow :: forall a. Show a => EsResult a -> String
showsPrec :: Int -> EsResult a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> EsResult a -> ShowS
Show)
data EsResultFound a =
EsResultFound { EsResultFound a -> DocVersion
_version :: DocVersion
, EsResultFound a -> a
_source :: a }
deriving (EsResultFound a -> EsResultFound a -> Bool
(EsResultFound a -> EsResultFound a -> Bool)
-> (EsResultFound a -> EsResultFound a -> Bool)
-> Eq (EsResultFound a)
forall a. Eq a => EsResultFound a -> EsResultFound a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EsResultFound a -> EsResultFound a -> Bool
$c/= :: forall a. Eq a => EsResultFound a -> EsResultFound a -> Bool
== :: EsResultFound a -> EsResultFound a -> Bool
$c== :: forall a. Eq a => EsResultFound a -> EsResultFound a -> Bool
Eq, Int -> EsResultFound a -> ShowS
[EsResultFound a] -> ShowS
EsResultFound a -> String
(Int -> EsResultFound a -> ShowS)
-> (EsResultFound a -> String)
-> ([EsResultFound a] -> ShowS)
-> Show (EsResultFound a)
forall a. Show a => Int -> EsResultFound a -> ShowS
forall a. Show a => [EsResultFound a] -> ShowS
forall a. Show a => EsResultFound a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EsResultFound a] -> ShowS
$cshowList :: forall a. Show a => [EsResultFound a] -> ShowS
show :: EsResultFound a -> String
$cshow :: forall a. Show a => EsResultFound a -> String
showsPrec :: Int -> EsResultFound a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> EsResultFound a -> ShowS
Show)
instance (FromJSON a) => FromJSON (EsResult a) where
parseJSON :: Value -> Parser (EsResult a)
parseJSON jsonVal :: Value
jsonVal@(Object Object
v) = do
Bool
found <- Object
v Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"found" Parser (Maybe Bool) -> Bool -> Parser Bool
forall a. Parser (Maybe a) -> a -> Parser a
.!= Bool
False
Maybe (EsResultFound a)
fr <- if Bool
found
then Value -> Parser (Maybe (EsResultFound a))
forall a. FromJSON a => Value -> Parser a
parseJSON Value
jsonVal
else Maybe (EsResultFound a) -> Parser (Maybe (EsResultFound a))
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe (EsResultFound a)
forall a. Maybe a
Nothing
Text -> Text -> Text -> Maybe (EsResultFound a) -> EsResult a
forall a.
Text -> Text -> Text -> Maybe (EsResultFound a) -> EsResult a
EsResult (Text -> Text -> Text -> Maybe (EsResultFound a) -> EsResult a)
-> Parser Text
-> Parser (Text -> Text -> Maybe (EsResultFound a) -> EsResult a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"_index" Parser (Text -> Text -> Maybe (EsResultFound a) -> EsResult a)
-> Parser Text
-> Parser (Text -> Maybe (EsResultFound a) -> EsResult a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
Object
v Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"_type" Parser (Text -> Maybe (EsResultFound a) -> EsResult a)
-> Parser Text -> Parser (Maybe (EsResultFound a) -> EsResult a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
Object
v Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"_id" Parser (Maybe (EsResultFound a) -> EsResult a)
-> Parser (Maybe (EsResultFound a)) -> Parser (EsResult a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
Maybe (EsResultFound a) -> Parser (Maybe (EsResultFound a))
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe (EsResultFound a)
fr
parseJSON Value
_ = Parser (EsResult a)
forall (f :: * -> *) a. Alternative f => f a
empty
instance (FromJSON a) => FromJSON (EsResultFound a) where
parseJSON :: Value -> Parser (EsResultFound a)
parseJSON (Object Object
v) = DocVersion -> a -> EsResultFound a
forall a. DocVersion -> a -> EsResultFound a
EsResultFound (DocVersion -> a -> EsResultFound a)
-> Parser DocVersion -> Parser (a -> EsResultFound a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
Object
v Object -> Key -> Parser DocVersion
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"_version" Parser (a -> EsResultFound a)
-> Parser a -> Parser (EsResultFound a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
Object
v Object -> Key -> Parser a
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"_source"
parseJSON Value
_ = Parser (EsResultFound a)
forall (f :: * -> *) a. Alternative f => f a
empty
data EsError =
EsError { EsError -> Int
errorStatus :: Int
, EsError -> Text
errorMessage :: Text }
deriving (EsError -> EsError -> Bool
(EsError -> EsError -> Bool)
-> (EsError -> EsError -> Bool) -> Eq EsError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EsError -> EsError -> Bool
$c/= :: EsError -> EsError -> Bool
== :: EsError -> EsError -> Bool
$c== :: EsError -> EsError -> Bool
Eq, Int -> EsError -> ShowS
[EsError] -> ShowS
EsError -> String
(Int -> EsError -> ShowS)
-> (EsError -> String) -> ([EsError] -> ShowS) -> Show EsError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EsError] -> ShowS
$cshowList :: [EsError] -> ShowS
show :: EsError -> String
$cshow :: EsError -> String
showsPrec :: Int -> EsError -> ShowS
$cshowsPrec :: Int -> EsError -> ShowS
Show)
instance FromJSON EsError where
parseJSON :: Value -> Parser EsError
parseJSON (Object Object
v) = Int -> Text -> EsError
EsError (Int -> Text -> EsError) -> Parser Int -> Parser (Text -> EsError)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
Object
v Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"status" Parser (Text -> EsError) -> Parser Text -> Parser EsError
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
(Object
v Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"error" Parser Text -> Parser Text -> Parser Text
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Object
v Object -> Key -> Parser Object
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"error" Parser Object -> (Object -> Parser Text) -> Parser Text
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"reason")))
parseJSON Value
_ = Parser EsError
forall (f :: * -> *) a. Alternative f => f a
empty
data EsProtocolException = EsProtocolException
{ EsProtocolException -> Text
esProtoExMessage :: !Text
, EsProtocolException -> LByteString
esProtoExBody :: !LByteString
} deriving (EsProtocolException -> EsProtocolException -> Bool
(EsProtocolException -> EsProtocolException -> Bool)
-> (EsProtocolException -> EsProtocolException -> Bool)
-> Eq EsProtocolException
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EsProtocolException -> EsProtocolException -> Bool
$c/= :: EsProtocolException -> EsProtocolException -> Bool
== :: EsProtocolException -> EsProtocolException -> Bool
$c== :: EsProtocolException -> EsProtocolException -> Bool
Eq, Int -> EsProtocolException -> ShowS
[EsProtocolException] -> ShowS
EsProtocolException -> String
(Int -> EsProtocolException -> ShowS)
-> (EsProtocolException -> String)
-> ([EsProtocolException] -> ShowS)
-> Show EsProtocolException
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EsProtocolException] -> ShowS
$cshowList :: [EsProtocolException] -> ShowS
show :: EsProtocolException -> String
$cshow :: EsProtocolException -> String
showsPrec :: Int -> EsProtocolException -> ShowS
$cshowsPrec :: Int -> EsProtocolException -> ShowS
Show)
instance Exception EsProtocolException
data IndexAlias = IndexAlias { IndexAlias -> IndexName
srcIndex :: IndexName
, IndexAlias -> IndexAliasName
indexAlias :: IndexAliasName } deriving (IndexAlias -> IndexAlias -> Bool
(IndexAlias -> IndexAlias -> Bool)
-> (IndexAlias -> IndexAlias -> Bool) -> Eq IndexAlias
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IndexAlias -> IndexAlias -> Bool
$c/= :: IndexAlias -> IndexAlias -> Bool
== :: IndexAlias -> IndexAlias -> Bool
$c== :: IndexAlias -> IndexAlias -> Bool
Eq, Int -> IndexAlias -> ShowS
[IndexAlias] -> ShowS
IndexAlias -> String
(Int -> IndexAlias -> ShowS)
-> (IndexAlias -> String)
-> ([IndexAlias] -> ShowS)
-> Show IndexAlias
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IndexAlias] -> ShowS
$cshowList :: [IndexAlias] -> ShowS
show :: IndexAlias -> String
$cshow :: IndexAlias -> String
showsPrec :: Int -> IndexAlias -> ShowS
$cshowsPrec :: Int -> IndexAlias -> ShowS
Show)
data IndexAliasAction =
AddAlias IndexAlias IndexAliasCreate
| RemoveAlias IndexAlias
deriving (IndexAliasAction -> IndexAliasAction -> Bool
(IndexAliasAction -> IndexAliasAction -> Bool)
-> (IndexAliasAction -> IndexAliasAction -> Bool)
-> Eq IndexAliasAction
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IndexAliasAction -> IndexAliasAction -> Bool
$c/= :: IndexAliasAction -> IndexAliasAction -> Bool
== :: IndexAliasAction -> IndexAliasAction -> Bool
$c== :: IndexAliasAction -> IndexAliasAction -> Bool
Eq, Int -> IndexAliasAction -> ShowS
[IndexAliasAction] -> ShowS
IndexAliasAction -> String
(Int -> IndexAliasAction -> ShowS)
-> (IndexAliasAction -> String)
-> ([IndexAliasAction] -> ShowS)
-> Show IndexAliasAction
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IndexAliasAction] -> ShowS
$cshowList :: [IndexAliasAction] -> ShowS
show :: IndexAliasAction -> String
$cshow :: IndexAliasAction -> String
showsPrec :: Int -> IndexAliasAction -> ShowS
$cshowsPrec :: Int -> IndexAliasAction -> ShowS
Show)
data IndexAliasCreate =
IndexAliasCreate { IndexAliasCreate -> Maybe AliasRouting
aliasCreateRouting :: Maybe AliasRouting
, IndexAliasCreate -> Maybe Filter
aliasCreateFilter :: Maybe Filter}
deriving (IndexAliasCreate -> IndexAliasCreate -> Bool
(IndexAliasCreate -> IndexAliasCreate -> Bool)
-> (IndexAliasCreate -> IndexAliasCreate -> Bool)
-> Eq IndexAliasCreate
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IndexAliasCreate -> IndexAliasCreate -> Bool
$c/= :: IndexAliasCreate -> IndexAliasCreate -> Bool
== :: IndexAliasCreate -> IndexAliasCreate -> Bool
$c== :: IndexAliasCreate -> IndexAliasCreate -> Bool
Eq, Int -> IndexAliasCreate -> ShowS
[IndexAliasCreate] -> ShowS
IndexAliasCreate -> String
(Int -> IndexAliasCreate -> ShowS)
-> (IndexAliasCreate -> String)
-> ([IndexAliasCreate] -> ShowS)
-> Show IndexAliasCreate
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IndexAliasCreate] -> ShowS
$cshowList :: [IndexAliasCreate] -> ShowS
show :: IndexAliasCreate -> String
$cshow :: IndexAliasCreate -> String
showsPrec :: Int -> IndexAliasCreate -> ShowS
$cshowsPrec :: Int -> IndexAliasCreate -> ShowS
Show)
data AliasRouting =
AllAliasRouting RoutingValue
| GranularAliasRouting (Maybe SearchAliasRouting) (Maybe IndexAliasRouting)
deriving (AliasRouting -> AliasRouting -> Bool
(AliasRouting -> AliasRouting -> Bool)
-> (AliasRouting -> AliasRouting -> Bool) -> Eq AliasRouting
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AliasRouting -> AliasRouting -> Bool
$c/= :: AliasRouting -> AliasRouting -> Bool
== :: AliasRouting -> AliasRouting -> Bool
$c== :: AliasRouting -> AliasRouting -> Bool
Eq, Int -> AliasRouting -> ShowS
[AliasRouting] -> ShowS
AliasRouting -> String
(Int -> AliasRouting -> ShowS)
-> (AliasRouting -> String)
-> ([AliasRouting] -> ShowS)
-> Show AliasRouting
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AliasRouting] -> ShowS
$cshowList :: [AliasRouting] -> ShowS
show :: AliasRouting -> String
$cshow :: AliasRouting -> String
showsPrec :: Int -> AliasRouting -> ShowS
$cshowsPrec :: Int -> AliasRouting -> ShowS
Show)
newtype SearchAliasRouting =
SearchAliasRouting (NonEmpty RoutingValue)
deriving (SearchAliasRouting -> SearchAliasRouting -> Bool
(SearchAliasRouting -> SearchAliasRouting -> Bool)
-> (SearchAliasRouting -> SearchAliasRouting -> Bool)
-> Eq SearchAliasRouting
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SearchAliasRouting -> SearchAliasRouting -> Bool
$c/= :: SearchAliasRouting -> SearchAliasRouting -> Bool
== :: SearchAliasRouting -> SearchAliasRouting -> Bool
$c== :: SearchAliasRouting -> SearchAliasRouting -> Bool
Eq, Int -> SearchAliasRouting -> ShowS
[SearchAliasRouting] -> ShowS
SearchAliasRouting -> String
(Int -> SearchAliasRouting -> ShowS)
-> (SearchAliasRouting -> String)
-> ([SearchAliasRouting] -> ShowS)
-> Show SearchAliasRouting
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SearchAliasRouting] -> ShowS
$cshowList :: [SearchAliasRouting] -> ShowS
show :: SearchAliasRouting -> String
$cshow :: SearchAliasRouting -> String
showsPrec :: Int -> SearchAliasRouting -> ShowS
$cshowsPrec :: Int -> SearchAliasRouting -> ShowS
Show)
instance ToJSON SearchAliasRouting where
toJSON :: SearchAliasRouting -> Value
toJSON (SearchAliasRouting NonEmpty RoutingValue
rvs) = Text -> Value
forall a. ToJSON a => a -> Value
toJSON (Text -> [Text] -> Text
T.intercalate Text
"," (RoutingValue -> Text
routingValue (RoutingValue -> Text) -> [RoutingValue] -> [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> NonEmpty RoutingValue -> [RoutingValue]
forall a. NonEmpty a -> [a]
toList NonEmpty RoutingValue
rvs))
instance FromJSON SearchAliasRouting where
parseJSON :: Value -> Parser SearchAliasRouting
parseJSON = String
-> (Text -> Parser SearchAliasRouting)
-> Value
-> Parser SearchAliasRouting
forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"SearchAliasRouting" Text -> Parser SearchAliasRouting
parse
where parse :: Text -> Parser SearchAliasRouting
parse Text
t = NonEmpty RoutingValue -> SearchAliasRouting
SearchAliasRouting (NonEmpty RoutingValue -> SearchAliasRouting)
-> Parser (NonEmpty RoutingValue) -> Parser SearchAliasRouting
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Value] -> Parser (NonEmpty RoutingValue)
forall a. FromJSON a => [Value] -> Parser (NonEmpty a)
parseNEJSON (Text -> Value
String (Text -> Value) -> [Text] -> [Value]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Text -> [Text]
T.splitOn Text
"," Text
t)
newtype IndexAliasRouting =
IndexAliasRouting RoutingValue
deriving (IndexAliasRouting -> IndexAliasRouting -> Bool
(IndexAliasRouting -> IndexAliasRouting -> Bool)
-> (IndexAliasRouting -> IndexAliasRouting -> Bool)
-> Eq IndexAliasRouting
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IndexAliasRouting -> IndexAliasRouting -> Bool
$c/= :: IndexAliasRouting -> IndexAliasRouting -> Bool
== :: IndexAliasRouting -> IndexAliasRouting -> Bool
$c== :: IndexAliasRouting -> IndexAliasRouting -> Bool
Eq, Int -> IndexAliasRouting -> ShowS
[IndexAliasRouting] -> ShowS
IndexAliasRouting -> String
(Int -> IndexAliasRouting -> ShowS)
-> (IndexAliasRouting -> String)
-> ([IndexAliasRouting] -> ShowS)
-> Show IndexAliasRouting
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IndexAliasRouting] -> ShowS
$cshowList :: [IndexAliasRouting] -> ShowS
show :: IndexAliasRouting -> String
$cshow :: IndexAliasRouting -> String
showsPrec :: Int -> IndexAliasRouting -> ShowS
$cshowsPrec :: Int -> IndexAliasRouting -> ShowS
Show, [IndexAliasRouting] -> Encoding
[IndexAliasRouting] -> Value
IndexAliasRouting -> Encoding
IndexAliasRouting -> Value
(IndexAliasRouting -> Value)
-> (IndexAliasRouting -> Encoding)
-> ([IndexAliasRouting] -> Value)
-> ([IndexAliasRouting] -> Encoding)
-> ToJSON IndexAliasRouting
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [IndexAliasRouting] -> Encoding
$ctoEncodingList :: [IndexAliasRouting] -> Encoding
toJSONList :: [IndexAliasRouting] -> Value
$ctoJSONList :: [IndexAliasRouting] -> Value
toEncoding :: IndexAliasRouting -> Encoding
$ctoEncoding :: IndexAliasRouting -> Encoding
toJSON :: IndexAliasRouting -> Value
$ctoJSON :: IndexAliasRouting -> Value
ToJSON, Value -> Parser [IndexAliasRouting]
Value -> Parser IndexAliasRouting
(Value -> Parser IndexAliasRouting)
-> (Value -> Parser [IndexAliasRouting])
-> FromJSON IndexAliasRouting
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [IndexAliasRouting]
$cparseJSONList :: Value -> Parser [IndexAliasRouting]
parseJSON :: Value -> Parser IndexAliasRouting
$cparseJSON :: Value -> Parser IndexAliasRouting
FromJSON)
newtype RoutingValue =
RoutingValue { RoutingValue -> Text
routingValue :: Text }
deriving (RoutingValue -> RoutingValue -> Bool
(RoutingValue -> RoutingValue -> Bool)
-> (RoutingValue -> RoutingValue -> Bool) -> Eq RoutingValue
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RoutingValue -> RoutingValue -> Bool
$c/= :: RoutingValue -> RoutingValue -> Bool
== :: RoutingValue -> RoutingValue -> Bool
$c== :: RoutingValue -> RoutingValue -> Bool
Eq, Int -> RoutingValue -> ShowS
[RoutingValue] -> ShowS
RoutingValue -> String
(Int -> RoutingValue -> ShowS)
-> (RoutingValue -> String)
-> ([RoutingValue] -> ShowS)
-> Show RoutingValue
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RoutingValue] -> ShowS
$cshowList :: [RoutingValue] -> ShowS
show :: RoutingValue -> String
$cshow :: RoutingValue -> String
showsPrec :: Int -> RoutingValue -> ShowS
$cshowsPrec :: Int -> RoutingValue -> ShowS
Show, [RoutingValue] -> Encoding
[RoutingValue] -> Value
RoutingValue -> Encoding
RoutingValue -> Value
(RoutingValue -> Value)
-> (RoutingValue -> Encoding)
-> ([RoutingValue] -> Value)
-> ([RoutingValue] -> Encoding)
-> ToJSON RoutingValue
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [RoutingValue] -> Encoding
$ctoEncodingList :: [RoutingValue] -> Encoding
toJSONList :: [RoutingValue] -> Value
$ctoJSONList :: [RoutingValue] -> Value
toEncoding :: RoutingValue -> Encoding
$ctoEncoding :: RoutingValue -> Encoding
toJSON :: RoutingValue -> Value
$ctoJSON :: RoutingValue -> Value
ToJSON, Value -> Parser [RoutingValue]
Value -> Parser RoutingValue
(Value -> Parser RoutingValue)
-> (Value -> Parser [RoutingValue]) -> FromJSON RoutingValue
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [RoutingValue]
$cparseJSONList :: Value -> Parser [RoutingValue]
parseJSON :: Value -> Parser RoutingValue
$cparseJSON :: Value -> Parser RoutingValue
FromJSON)
newtype IndexAliasesSummary =
IndexAliasesSummary { IndexAliasesSummary -> [IndexAliasSummary]
indexAliasesSummary :: [IndexAliasSummary] }
deriving (IndexAliasesSummary -> IndexAliasesSummary -> Bool
(IndexAliasesSummary -> IndexAliasesSummary -> Bool)
-> (IndexAliasesSummary -> IndexAliasesSummary -> Bool)
-> Eq IndexAliasesSummary
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IndexAliasesSummary -> IndexAliasesSummary -> Bool
$c/= :: IndexAliasesSummary -> IndexAliasesSummary -> Bool
== :: IndexAliasesSummary -> IndexAliasesSummary -> Bool
$c== :: IndexAliasesSummary -> IndexAliasesSummary -> Bool
Eq, Int -> IndexAliasesSummary -> ShowS
[IndexAliasesSummary] -> ShowS
IndexAliasesSummary -> String
(Int -> IndexAliasesSummary -> ShowS)
-> (IndexAliasesSummary -> String)
-> ([IndexAliasesSummary] -> ShowS)
-> Show IndexAliasesSummary
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IndexAliasesSummary] -> ShowS
$cshowList :: [IndexAliasesSummary] -> ShowS
show :: IndexAliasesSummary -> String
$cshow :: IndexAliasesSummary -> String
showsPrec :: Int -> IndexAliasesSummary -> ShowS
$cshowsPrec :: Int -> IndexAliasesSummary -> ShowS
Show)
instance FromJSON IndexAliasesSummary where
parseJSON :: Value -> Parser IndexAliasesSummary
parseJSON = String
-> (Object -> Parser IndexAliasesSummary)
-> Value
-> Parser IndexAliasesSummary
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"IndexAliasesSummary" Object -> Parser IndexAliasesSummary
parse
where parse :: Object -> Parser IndexAliasesSummary
parse Object
o = [IndexAliasSummary] -> IndexAliasesSummary
IndexAliasesSummary ([IndexAliasSummary] -> IndexAliasesSummary)
-> ([[IndexAliasSummary]] -> [IndexAliasSummary])
-> [[IndexAliasSummary]]
-> IndexAliasesSummary
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[IndexAliasSummary]] -> [IndexAliasSummary]
forall a. Monoid a => [a] -> a
mconcat ([[IndexAliasSummary]] -> IndexAliasesSummary)
-> Parser [[IndexAliasSummary]] -> Parser IndexAliasesSummary
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Pair -> Parser [IndexAliasSummary])
-> [Pair] -> Parser [[IndexAliasSummary]]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((Key -> Value -> Parser [IndexAliasSummary])
-> Pair -> Parser [IndexAliasSummary]
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Key -> Value -> Parser [IndexAliasSummary]
go) (Object -> [Pair]
forall v. KeyMap v -> [(Key, v)]
X.toList Object
o)
go :: Key -> Value -> Parser [IndexAliasSummary]
go Key
ixn = String
-> (Object -> Parser [IndexAliasSummary])
-> Value
-> Parser [IndexAliasSummary]
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"index aliases" ((Object -> Parser [IndexAliasSummary])
-> Value -> Parser [IndexAliasSummary])
-> (Object -> Parser [IndexAliasSummary])
-> Value
-> Parser [IndexAliasSummary]
forall a b. (a -> b) -> a -> b
$ \Object
ia -> do
HashMap Key Value
aliases <- Object
ia Object -> Key -> Parser (Maybe (HashMap Key Value))
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"aliases" Parser (Maybe (HashMap Key Value))
-> HashMap Key Value -> Parser (HashMap Key Value)
forall a. Parser (Maybe a) -> a -> Parser a
.!= HashMap Key Value
forall a. Monoid a => a
mempty
[Pair]
-> (Pair -> Parser IndexAliasSummary) -> Parser [IndexAliasSummary]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM (HashMap Key Value -> [Pair]
forall k v. HashMap k v -> [(k, v)]
HM.toList HashMap Key Value
aliases) ((Pair -> Parser IndexAliasSummary) -> Parser [IndexAliasSummary])
-> (Pair -> Parser IndexAliasSummary) -> Parser [IndexAliasSummary]
forall a b. (a -> b) -> a -> b
$ \(Key
aName, Value
v) -> do
let indexAlias :: IndexAlias
indexAlias = IndexName -> IndexAliasName -> IndexAlias
IndexAlias (Text -> IndexName
IndexName (Text -> IndexName) -> Text -> IndexName
forall a b. (a -> b) -> a -> b
$ Key -> Text
toText Key
ixn) (IndexName -> IndexAliasName
IndexAliasName (Text -> IndexName
IndexName (Text -> IndexName) -> Text -> IndexName
forall a b. (a -> b) -> a -> b
$ Key -> Text
toText Key
aName))
IndexAlias -> IndexAliasCreate -> IndexAliasSummary
IndexAliasSummary IndexAlias
indexAlias (IndexAliasCreate -> IndexAliasSummary)
-> Parser IndexAliasCreate -> Parser IndexAliasSummary
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser IndexAliasCreate
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v
instance ToJSON IndexAliasAction where
toJSON :: IndexAliasAction -> Value
toJSON (AddAlias IndexAlias
ia IndexAliasCreate
opts) = [Pair] -> Value
object [Key
"add" Key -> Object -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= (Object
iaObj Object -> Object -> Object
forall a. Semigroup a => a -> a -> a
<> Object
optsObj)]
where Object Object
iaObj = IndexAlias -> Value
forall a. ToJSON a => a -> Value
toJSON IndexAlias
ia
Object Object
optsObj = IndexAliasCreate -> Value
forall a. ToJSON a => a -> Value
toJSON IndexAliasCreate
opts
toJSON (RemoveAlias IndexAlias
ia) = [Pair] -> Value
object [Key
"remove" Key -> Object -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Object
iaObj]
where Object Object
iaObj = IndexAlias -> Value
forall a. ToJSON a => a -> Value
toJSON IndexAlias
ia
instance ToJSON IndexAlias where
toJSON :: IndexAlias -> Value
toJSON IndexAlias {IndexAliasName
IndexName
indexAlias :: IndexAliasName
srcIndex :: IndexName
indexAlias :: IndexAlias -> IndexAliasName
srcIndex :: IndexAlias -> IndexName
..} = [Pair] -> Value
object [Key
"index" Key -> IndexName -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= IndexName
srcIndex
, Key
"alias" Key -> IndexAliasName -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= IndexAliasName
indexAlias
]
instance ToJSON IndexAliasCreate where
toJSON :: IndexAliasCreate -> Value
toJSON IndexAliasCreate {Maybe Filter
Maybe AliasRouting
aliasCreateFilter :: Maybe Filter
aliasCreateRouting :: Maybe AliasRouting
aliasCreateFilter :: IndexAliasCreate -> Maybe Filter
aliasCreateRouting :: IndexAliasCreate -> Maybe AliasRouting
..} = Object -> Value
Object (Object
filterObj Object -> Object -> Object
forall a. Semigroup a => a -> a -> a
<> Object
routingObj)
where filterObj :: Object
filterObj = Object -> (Filter -> Object) -> Maybe Filter -> Object
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Object
forall a. Monoid a => a
mempty (Key -> Value -> Object
forall v. Key -> v -> KeyMap v
X.singleton Key
"filter" (Value -> Object) -> (Filter -> Value) -> Filter -> Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Filter -> Value
forall a. ToJSON a => a -> Value
toJSON) Maybe Filter
aliasCreateFilter
Object Object
routingObj = Value -> (AliasRouting -> Value) -> Maybe AliasRouting -> Value
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Object -> Value
Object Object
forall a. Monoid a => a
mempty) AliasRouting -> Value
forall a. ToJSON a => a -> Value
toJSON Maybe AliasRouting
aliasCreateRouting
instance ToJSON AliasRouting where
toJSON :: AliasRouting -> Value
toJSON (AllAliasRouting RoutingValue
v) = [Pair] -> Value
object [Key
"routing" Key -> RoutingValue -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= RoutingValue
v]
toJSON (GranularAliasRouting Maybe SearchAliasRouting
srch Maybe IndexAliasRouting
idx) = [Pair] -> Value
object ([Maybe Pair] -> [Pair]
forall a. [Maybe a] -> [a]
catMaybes [Maybe Pair]
prs)
where prs :: [Maybe Pair]
prs = [(Key
"search_routing" Key -> SearchAliasRouting -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.=) (SearchAliasRouting -> Pair)
-> Maybe SearchAliasRouting -> Maybe Pair
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe SearchAliasRouting
srch
,(Key
"index_routing" Key -> IndexAliasRouting -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.=) (IndexAliasRouting -> Pair)
-> Maybe IndexAliasRouting -> Maybe Pair
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe IndexAliasRouting
idx]
instance FromJSON AliasRouting where
parseJSON :: Value -> Parser AliasRouting
parseJSON = String
-> (Object -> Parser AliasRouting) -> Value -> Parser AliasRouting
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"AliasRouting" Object -> Parser AliasRouting
parse
where parse :: Object -> Parser AliasRouting
parse Object
o = Object -> Parser AliasRouting
parseAll Object
o Parser AliasRouting -> Parser AliasRouting -> Parser AliasRouting
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Object -> Parser AliasRouting
parseGranular Object
o
parseAll :: Object -> Parser AliasRouting
parseAll Object
o = RoutingValue -> AliasRouting
AllAliasRouting (RoutingValue -> AliasRouting)
-> Parser RoutingValue -> Parser AliasRouting
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser RoutingValue
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"routing"
parseGranular :: Object -> Parser AliasRouting
parseGranular Object
o = do
Maybe SearchAliasRouting
sr <- Object
o Object -> Key -> Parser (Maybe SearchAliasRouting)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"search_routing"
Maybe IndexAliasRouting
ir <- Object
o Object -> Key -> Parser (Maybe IndexAliasRouting)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"index_routing"
if Maybe SearchAliasRouting -> Bool
forall a. Maybe a -> Bool
isNothing Maybe SearchAliasRouting
sr Bool -> Bool -> Bool
&& Maybe IndexAliasRouting -> Bool
forall a. Maybe a -> Bool
isNothing Maybe IndexAliasRouting
ir
then String -> Parser AliasRouting
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Both search_routing and index_routing can't be blank"
else AliasRouting -> Parser AliasRouting
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe SearchAliasRouting -> Maybe IndexAliasRouting -> AliasRouting
GranularAliasRouting Maybe SearchAliasRouting
sr Maybe IndexAliasRouting
ir)
instance FromJSON IndexAliasCreate where
parseJSON :: Value -> Parser IndexAliasCreate
parseJSON Value
v = String
-> (Object -> Parser IndexAliasCreate)
-> Value
-> Parser IndexAliasCreate
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"IndexAliasCreate" Object -> Parser IndexAliasCreate
parse Value
v
where parse :: Object -> Parser IndexAliasCreate
parse Object
o = Maybe AliasRouting -> Maybe Filter -> IndexAliasCreate
IndexAliasCreate (Maybe AliasRouting -> Maybe Filter -> IndexAliasCreate)
-> Parser (Maybe AliasRouting)
-> Parser (Maybe Filter -> IndexAliasCreate)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser AliasRouting -> Parser (Maybe AliasRouting)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Value -> Parser AliasRouting
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v)
Parser (Maybe Filter -> IndexAliasCreate)
-> Parser (Maybe Filter) -> Parser IndexAliasCreate
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Filter)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"filter"
data IndexAliasSummary = IndexAliasSummary
{ IndexAliasSummary -> IndexAlias
indexAliasSummaryAlias :: IndexAlias
, IndexAliasSummary -> IndexAliasCreate
indexAliasSummaryCreate :: IndexAliasCreate }
deriving (IndexAliasSummary -> IndexAliasSummary -> Bool
(IndexAliasSummary -> IndexAliasSummary -> Bool)
-> (IndexAliasSummary -> IndexAliasSummary -> Bool)
-> Eq IndexAliasSummary
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IndexAliasSummary -> IndexAliasSummary -> Bool
$c/= :: IndexAliasSummary -> IndexAliasSummary -> Bool
== :: IndexAliasSummary -> IndexAliasSummary -> Bool
$c== :: IndexAliasSummary -> IndexAliasSummary -> Bool
Eq, Int -> IndexAliasSummary -> ShowS
[IndexAliasSummary] -> ShowS
IndexAliasSummary -> String
(Int -> IndexAliasSummary -> ShowS)
-> (IndexAliasSummary -> String)
-> ([IndexAliasSummary] -> ShowS)
-> Show IndexAliasSummary
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IndexAliasSummary] -> ShowS
$cshowList :: [IndexAliasSummary] -> ShowS
show :: IndexAliasSummary -> String
$cshow :: IndexAliasSummary -> String
showsPrec :: Int -> IndexAliasSummary -> ShowS
$cshowsPrec :: Int -> IndexAliasSummary -> ShowS
Show)
newtype DocVersion = DocVersion {
DocVersion -> Int
docVersionNumber :: Int
} deriving (DocVersion -> DocVersion -> Bool
(DocVersion -> DocVersion -> Bool)
-> (DocVersion -> DocVersion -> Bool) -> Eq DocVersion
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DocVersion -> DocVersion -> Bool
$c/= :: DocVersion -> DocVersion -> Bool
== :: DocVersion -> DocVersion -> Bool
$c== :: DocVersion -> DocVersion -> Bool
Eq, Int -> DocVersion -> ShowS
[DocVersion] -> ShowS
DocVersion -> String
(Int -> DocVersion -> ShowS)
-> (DocVersion -> String)
-> ([DocVersion] -> ShowS)
-> Show DocVersion
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DocVersion] -> ShowS
$cshowList :: [DocVersion] -> ShowS
show :: DocVersion -> String
$cshow :: DocVersion -> String
showsPrec :: Int -> DocVersion -> ShowS
$cshowsPrec :: Int -> DocVersion -> ShowS
Show, Eq DocVersion
Eq DocVersion
-> (DocVersion -> DocVersion -> Ordering)
-> (DocVersion -> DocVersion -> Bool)
-> (DocVersion -> DocVersion -> Bool)
-> (DocVersion -> DocVersion -> Bool)
-> (DocVersion -> DocVersion -> Bool)
-> (DocVersion -> DocVersion -> DocVersion)
-> (DocVersion -> DocVersion -> DocVersion)
-> Ord DocVersion
DocVersion -> DocVersion -> Bool
DocVersion -> DocVersion -> Ordering
DocVersion -> DocVersion -> DocVersion
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 :: DocVersion -> DocVersion -> DocVersion
$cmin :: DocVersion -> DocVersion -> DocVersion
max :: DocVersion -> DocVersion -> DocVersion
$cmax :: DocVersion -> DocVersion -> DocVersion
>= :: DocVersion -> DocVersion -> Bool
$c>= :: DocVersion -> DocVersion -> Bool
> :: DocVersion -> DocVersion -> Bool
$c> :: DocVersion -> DocVersion -> Bool
<= :: DocVersion -> DocVersion -> Bool
$c<= :: DocVersion -> DocVersion -> Bool
< :: DocVersion -> DocVersion -> Bool
$c< :: DocVersion -> DocVersion -> Bool
compare :: DocVersion -> DocVersion -> Ordering
$ccompare :: DocVersion -> DocVersion -> Ordering
$cp1Ord :: Eq DocVersion
Ord, [DocVersion] -> Encoding
[DocVersion] -> Value
DocVersion -> Encoding
DocVersion -> Value
(DocVersion -> Value)
-> (DocVersion -> Encoding)
-> ([DocVersion] -> Value)
-> ([DocVersion] -> Encoding)
-> ToJSON DocVersion
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [DocVersion] -> Encoding
$ctoEncodingList :: [DocVersion] -> Encoding
toJSONList :: [DocVersion] -> Value
$ctoJSONList :: [DocVersion] -> Value
toEncoding :: DocVersion -> Encoding
$ctoEncoding :: DocVersion -> Encoding
toJSON :: DocVersion -> Value
$ctoJSON :: DocVersion -> Value
ToJSON)
mkDocVersion :: Int -> Maybe DocVersion
mkDocVersion :: Int -> Maybe DocVersion
mkDocVersion Int
i
| Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= DocVersion -> Int
docVersionNumber DocVersion
forall a. Bounded a => a
minBound
Bool -> Bool -> Bool
&& Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= DocVersion -> Int
docVersionNumber DocVersion
forall a. Bounded a => a
maxBound =
DocVersion -> Maybe DocVersion
forall a. a -> Maybe a
Just (DocVersion -> Maybe DocVersion) -> DocVersion -> Maybe DocVersion
forall a b. (a -> b) -> a -> b
$ Int -> DocVersion
DocVersion Int
i
| Bool
otherwise = Maybe DocVersion
forall a. Maybe a
Nothing
instance Bounded DocVersion where
minBound :: DocVersion
minBound = Int -> DocVersion
DocVersion Int
1
maxBound :: DocVersion
maxBound = Int -> DocVersion
DocVersion Int
9200000000000000000
instance Enum DocVersion where
succ :: DocVersion -> DocVersion
succ DocVersion
x
| DocVersion
x DocVersion -> DocVersion -> Bool
forall a. Eq a => a -> a -> Bool
/= DocVersion
forall a. Bounded a => a
maxBound = Int -> DocVersion
DocVersion (Int -> Int
forall a. Enum a => a -> a
succ (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$ DocVersion -> Int
docVersionNumber DocVersion
x)
| Bool
otherwise = String -> DocVersion
forall a. String -> a
succError String
"DocVersion"
pred :: DocVersion -> DocVersion
pred DocVersion
x
| DocVersion
x DocVersion -> DocVersion -> Bool
forall a. Eq a => a -> a -> Bool
/= DocVersion
forall a. Bounded a => a
minBound = Int -> DocVersion
DocVersion (Int -> Int
forall a. Enum a => a -> a
pred (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$ DocVersion -> Int
docVersionNumber DocVersion
x)
| Bool
otherwise = String -> DocVersion
forall a. String -> a
predError String
"DocVersion"
toEnum :: Int -> DocVersion
toEnum Int
i =
DocVersion -> Maybe DocVersion -> DocVersion
forall a. a -> Maybe a -> a
fromMaybe (String -> DocVersion
forall a. HasCallStack => String -> a
error (String -> DocVersion) -> String -> DocVersion
forall a b. (a -> b) -> a -> b
$ Int -> String
forall a. Show a => a -> String
show Int
i String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" out of DocVersion range") (Maybe DocVersion -> DocVersion) -> Maybe DocVersion -> DocVersion
forall a b. (a -> b) -> a -> b
$ Int -> Maybe DocVersion
mkDocVersion Int
i
fromEnum :: DocVersion -> Int
fromEnum = DocVersion -> Int
docVersionNumber
enumFrom :: DocVersion -> [DocVersion]
enumFrom = DocVersion -> [DocVersion]
forall a. (Enum a, Bounded a) => a -> [a]
boundedEnumFrom
enumFromThen :: DocVersion -> DocVersion -> [DocVersion]
enumFromThen = DocVersion -> DocVersion -> [DocVersion]
forall a. (Enum a, Bounded a) => a -> a -> [a]
boundedEnumFromThen
instance FromJSON DocVersion where
parseJSON :: Value -> Parser DocVersion
parseJSON Value
v = do
Int
i <- Value -> Parser Int
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v
Parser DocVersion
-> (DocVersion -> Parser DocVersion)
-> Maybe DocVersion
-> Parser DocVersion
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (String -> Parser DocVersion
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"DocVersion out of range") DocVersion -> Parser DocVersion
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe DocVersion -> Parser DocVersion)
-> Maybe DocVersion -> Parser DocVersion
forall a b. (a -> b) -> a -> b
$ Int -> Maybe DocVersion
mkDocVersion Int
i
newtype ExternalDocVersion = ExternalDocVersion DocVersion
deriving (ExternalDocVersion -> ExternalDocVersion -> Bool
(ExternalDocVersion -> ExternalDocVersion -> Bool)
-> (ExternalDocVersion -> ExternalDocVersion -> Bool)
-> Eq ExternalDocVersion
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExternalDocVersion -> ExternalDocVersion -> Bool
$c/= :: ExternalDocVersion -> ExternalDocVersion -> Bool
== :: ExternalDocVersion -> ExternalDocVersion -> Bool
$c== :: ExternalDocVersion -> ExternalDocVersion -> Bool
Eq, Int -> ExternalDocVersion -> ShowS
[ExternalDocVersion] -> ShowS
ExternalDocVersion -> String
(Int -> ExternalDocVersion -> ShowS)
-> (ExternalDocVersion -> String)
-> ([ExternalDocVersion] -> ShowS)
-> Show ExternalDocVersion
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ExternalDocVersion] -> ShowS
$cshowList :: [ExternalDocVersion] -> ShowS
show :: ExternalDocVersion -> String
$cshow :: ExternalDocVersion -> String
showsPrec :: Int -> ExternalDocVersion -> ShowS
$cshowsPrec :: Int -> ExternalDocVersion -> ShowS
Show, Eq ExternalDocVersion
Eq ExternalDocVersion
-> (ExternalDocVersion -> ExternalDocVersion -> Ordering)
-> (ExternalDocVersion -> ExternalDocVersion -> Bool)
-> (ExternalDocVersion -> ExternalDocVersion -> Bool)
-> (ExternalDocVersion -> ExternalDocVersion -> Bool)
-> (ExternalDocVersion -> ExternalDocVersion -> Bool)
-> (ExternalDocVersion -> ExternalDocVersion -> ExternalDocVersion)
-> (ExternalDocVersion -> ExternalDocVersion -> ExternalDocVersion)
-> Ord ExternalDocVersion
ExternalDocVersion -> ExternalDocVersion -> Bool
ExternalDocVersion -> ExternalDocVersion -> Ordering
ExternalDocVersion -> ExternalDocVersion -> ExternalDocVersion
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 :: ExternalDocVersion -> ExternalDocVersion -> ExternalDocVersion
$cmin :: ExternalDocVersion -> ExternalDocVersion -> ExternalDocVersion
max :: ExternalDocVersion -> ExternalDocVersion -> ExternalDocVersion
$cmax :: ExternalDocVersion -> ExternalDocVersion -> ExternalDocVersion
>= :: ExternalDocVersion -> ExternalDocVersion -> Bool
$c>= :: ExternalDocVersion -> ExternalDocVersion -> Bool
> :: ExternalDocVersion -> ExternalDocVersion -> Bool
$c> :: ExternalDocVersion -> ExternalDocVersion -> Bool
<= :: ExternalDocVersion -> ExternalDocVersion -> Bool
$c<= :: ExternalDocVersion -> ExternalDocVersion -> Bool
< :: ExternalDocVersion -> ExternalDocVersion -> Bool
$c< :: ExternalDocVersion -> ExternalDocVersion -> Bool
compare :: ExternalDocVersion -> ExternalDocVersion -> Ordering
$ccompare :: ExternalDocVersion -> ExternalDocVersion -> Ordering
$cp1Ord :: Eq ExternalDocVersion
Ord, ExternalDocVersion
ExternalDocVersion
-> ExternalDocVersion -> Bounded ExternalDocVersion
forall a. a -> a -> Bounded a
maxBound :: ExternalDocVersion
$cmaxBound :: ExternalDocVersion
minBound :: ExternalDocVersion
$cminBound :: ExternalDocVersion
Bounded, Int -> ExternalDocVersion
ExternalDocVersion -> Int
ExternalDocVersion -> [ExternalDocVersion]
ExternalDocVersion -> ExternalDocVersion
ExternalDocVersion -> ExternalDocVersion -> [ExternalDocVersion]
ExternalDocVersion
-> ExternalDocVersion -> ExternalDocVersion -> [ExternalDocVersion]
(ExternalDocVersion -> ExternalDocVersion)
-> (ExternalDocVersion -> ExternalDocVersion)
-> (Int -> ExternalDocVersion)
-> (ExternalDocVersion -> Int)
-> (ExternalDocVersion -> [ExternalDocVersion])
-> (ExternalDocVersion
-> ExternalDocVersion -> [ExternalDocVersion])
-> (ExternalDocVersion
-> ExternalDocVersion -> [ExternalDocVersion])
-> (ExternalDocVersion
-> ExternalDocVersion
-> ExternalDocVersion
-> [ExternalDocVersion])
-> Enum ExternalDocVersion
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 :: ExternalDocVersion
-> ExternalDocVersion -> ExternalDocVersion -> [ExternalDocVersion]
$cenumFromThenTo :: ExternalDocVersion
-> ExternalDocVersion -> ExternalDocVersion -> [ExternalDocVersion]
enumFromTo :: ExternalDocVersion -> ExternalDocVersion -> [ExternalDocVersion]
$cenumFromTo :: ExternalDocVersion -> ExternalDocVersion -> [ExternalDocVersion]
enumFromThen :: ExternalDocVersion -> ExternalDocVersion -> [ExternalDocVersion]
$cenumFromThen :: ExternalDocVersion -> ExternalDocVersion -> [ExternalDocVersion]
enumFrom :: ExternalDocVersion -> [ExternalDocVersion]
$cenumFrom :: ExternalDocVersion -> [ExternalDocVersion]
fromEnum :: ExternalDocVersion -> Int
$cfromEnum :: ExternalDocVersion -> Int
toEnum :: Int -> ExternalDocVersion
$ctoEnum :: Int -> ExternalDocVersion
pred :: ExternalDocVersion -> ExternalDocVersion
$cpred :: ExternalDocVersion -> ExternalDocVersion
succ :: ExternalDocVersion -> ExternalDocVersion
$csucc :: ExternalDocVersion -> ExternalDocVersion
Enum, [ExternalDocVersion] -> Encoding
[ExternalDocVersion] -> Value
ExternalDocVersion -> Encoding
ExternalDocVersion -> Value
(ExternalDocVersion -> Value)
-> (ExternalDocVersion -> Encoding)
-> ([ExternalDocVersion] -> Value)
-> ([ExternalDocVersion] -> Encoding)
-> ToJSON ExternalDocVersion
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [ExternalDocVersion] -> Encoding
$ctoEncodingList :: [ExternalDocVersion] -> Encoding
toJSONList :: [ExternalDocVersion] -> Value
$ctoJSONList :: [ExternalDocVersion] -> Value
toEncoding :: ExternalDocVersion -> Encoding
$ctoEncoding :: ExternalDocVersion -> Encoding
toJSON :: ExternalDocVersion -> Value
$ctoJSON :: ExternalDocVersion -> Value
ToJSON)
data VersionControl = NoVersionControl
| InternalVersion DocVersion
| ExternalGT ExternalDocVersion
| ExternalGTE ExternalDocVersion
| ForceVersion ExternalDocVersion
deriving (VersionControl -> VersionControl -> Bool
(VersionControl -> VersionControl -> Bool)
-> (VersionControl -> VersionControl -> Bool) -> Eq VersionControl
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VersionControl -> VersionControl -> Bool
$c/= :: VersionControl -> VersionControl -> Bool
== :: VersionControl -> VersionControl -> Bool
$c== :: VersionControl -> VersionControl -> Bool
Eq, Int -> VersionControl -> ShowS
[VersionControl] -> ShowS
VersionControl -> String
(Int -> VersionControl -> ShowS)
-> (VersionControl -> String)
-> ([VersionControl] -> ShowS)
-> Show VersionControl
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VersionControl] -> ShowS
$cshowList :: [VersionControl] -> ShowS
show :: VersionControl -> String
$cshow :: VersionControl -> String
showsPrec :: Int -> VersionControl -> ShowS
$cshowsPrec :: Int -> VersionControl -> ShowS
Show, Eq VersionControl
Eq VersionControl
-> (VersionControl -> VersionControl -> Ordering)
-> (VersionControl -> VersionControl -> Bool)
-> (VersionControl -> VersionControl -> Bool)
-> (VersionControl -> VersionControl -> Bool)
-> (VersionControl -> VersionControl -> Bool)
-> (VersionControl -> VersionControl -> VersionControl)
-> (VersionControl -> VersionControl -> VersionControl)
-> Ord VersionControl
VersionControl -> VersionControl -> Bool
VersionControl -> VersionControl -> Ordering
VersionControl -> VersionControl -> VersionControl
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 :: VersionControl -> VersionControl -> VersionControl
$cmin :: VersionControl -> VersionControl -> VersionControl
max :: VersionControl -> VersionControl -> VersionControl
$cmax :: VersionControl -> VersionControl -> VersionControl
>= :: VersionControl -> VersionControl -> Bool
$c>= :: VersionControl -> VersionControl -> Bool
> :: VersionControl -> VersionControl -> Bool
$c> :: VersionControl -> VersionControl -> Bool
<= :: VersionControl -> VersionControl -> Bool
$c<= :: VersionControl -> VersionControl -> Bool
< :: VersionControl -> VersionControl -> Bool
$c< :: VersionControl -> VersionControl -> Bool
compare :: VersionControl -> VersionControl -> Ordering
$ccompare :: VersionControl -> VersionControl -> Ordering
$cp1Ord :: Eq VersionControl
Ord)
data JoinRelation
= ParentDocument FieldName RelationName
| ChildDocument FieldName RelationName DocId
deriving (Int -> JoinRelation -> ShowS
[JoinRelation] -> ShowS
JoinRelation -> String
(Int -> JoinRelation -> ShowS)
-> (JoinRelation -> String)
-> ([JoinRelation] -> ShowS)
-> Show JoinRelation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [JoinRelation] -> ShowS
$cshowList :: [JoinRelation] -> ShowS
show :: JoinRelation -> String
$cshow :: JoinRelation -> String
showsPrec :: Int -> JoinRelation -> ShowS
$cshowsPrec :: Int -> JoinRelation -> ShowS
Show, JoinRelation -> JoinRelation -> Bool
(JoinRelation -> JoinRelation -> Bool)
-> (JoinRelation -> JoinRelation -> Bool) -> Eq JoinRelation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: JoinRelation -> JoinRelation -> Bool
$c/= :: JoinRelation -> JoinRelation -> Bool
== :: JoinRelation -> JoinRelation -> Bool
$c== :: JoinRelation -> JoinRelation -> Bool
Eq)
data IndexDocumentSettings =
IndexDocumentSettings { IndexDocumentSettings -> VersionControl
idsVersionControl :: VersionControl
, IndexDocumentSettings -> Maybe JoinRelation
idsJoinRelation :: Maybe JoinRelation
} deriving (IndexDocumentSettings -> IndexDocumentSettings -> Bool
(IndexDocumentSettings -> IndexDocumentSettings -> Bool)
-> (IndexDocumentSettings -> IndexDocumentSettings -> Bool)
-> Eq IndexDocumentSettings
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IndexDocumentSettings -> IndexDocumentSettings -> Bool
$c/= :: IndexDocumentSettings -> IndexDocumentSettings -> Bool
== :: IndexDocumentSettings -> IndexDocumentSettings -> Bool
$c== :: IndexDocumentSettings -> IndexDocumentSettings -> Bool
Eq, Int -> IndexDocumentSettings -> ShowS
[IndexDocumentSettings] -> ShowS
IndexDocumentSettings -> String
(Int -> IndexDocumentSettings -> ShowS)
-> (IndexDocumentSettings -> String)
-> ([IndexDocumentSettings] -> ShowS)
-> Show IndexDocumentSettings
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IndexDocumentSettings] -> ShowS
$cshowList :: [IndexDocumentSettings] -> ShowS
show :: IndexDocumentSettings -> String
$cshow :: IndexDocumentSettings -> String
showsPrec :: Int -> IndexDocumentSettings -> ShowS
$cshowsPrec :: Int -> IndexDocumentSettings -> ShowS
Show)
defaultIndexDocumentSettings :: IndexDocumentSettings
defaultIndexDocumentSettings :: IndexDocumentSettings
defaultIndexDocumentSettings = VersionControl -> Maybe JoinRelation -> IndexDocumentSettings
IndexDocumentSettings VersionControl
NoVersionControl Maybe JoinRelation
forall a. Maybe a
Nothing
data IndexSelection =
IndexList (NonEmpty IndexName)
| AllIndexes
deriving (IndexSelection -> IndexSelection -> Bool
(IndexSelection -> IndexSelection -> Bool)
-> (IndexSelection -> IndexSelection -> Bool) -> Eq IndexSelection
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IndexSelection -> IndexSelection -> Bool
$c/= :: IndexSelection -> IndexSelection -> Bool
== :: IndexSelection -> IndexSelection -> Bool
$c== :: IndexSelection -> IndexSelection -> Bool
Eq, Int -> IndexSelection -> ShowS
[IndexSelection] -> ShowS
IndexSelection -> String
(Int -> IndexSelection -> ShowS)
-> (IndexSelection -> String)
-> ([IndexSelection] -> ShowS)
-> Show IndexSelection
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IndexSelection] -> ShowS
$cshowList :: [IndexSelection] -> ShowS
show :: IndexSelection -> String
$cshow :: IndexSelection -> String
showsPrec :: Int -> IndexSelection -> ShowS
$cshowsPrec :: Int -> IndexSelection -> ShowS
Show)
data NodeSelection =
LocalNode
| NodeList (NonEmpty NodeSelector)
| AllNodes
deriving (NodeSelection -> NodeSelection -> Bool
(NodeSelection -> NodeSelection -> Bool)
-> (NodeSelection -> NodeSelection -> Bool) -> Eq NodeSelection
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NodeSelection -> NodeSelection -> Bool
$c/= :: NodeSelection -> NodeSelection -> Bool
== :: NodeSelection -> NodeSelection -> Bool
$c== :: NodeSelection -> NodeSelection -> Bool
Eq, Int -> NodeSelection -> ShowS
[NodeSelection] -> ShowS
NodeSelection -> String
(Int -> NodeSelection -> ShowS)
-> (NodeSelection -> String)
-> ([NodeSelection] -> ShowS)
-> Show NodeSelection
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NodeSelection] -> ShowS
$cshowList :: [NodeSelection] -> ShowS
show :: NodeSelection -> String
$cshow :: NodeSelection -> String
showsPrec :: Int -> NodeSelection -> ShowS
$cshowsPrec :: Int -> NodeSelection -> ShowS
Show)
data NodeSelector =
NodeByName NodeName
| NodeByFullNodeId FullNodeId
| NodeByHost Server
| NodeByAttribute NodeAttrName Text
deriving (NodeSelector -> NodeSelector -> Bool
(NodeSelector -> NodeSelector -> Bool)
-> (NodeSelector -> NodeSelector -> Bool) -> Eq NodeSelector
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NodeSelector -> NodeSelector -> Bool
$c/= :: NodeSelector -> NodeSelector -> Bool
== :: NodeSelector -> NodeSelector -> Bool
$c== :: NodeSelector -> NodeSelector -> Bool
Eq, Int -> NodeSelector -> ShowS
[NodeSelector] -> ShowS
NodeSelector -> String
(Int -> NodeSelector -> ShowS)
-> (NodeSelector -> String)
-> ([NodeSelector] -> ShowS)
-> Show NodeSelector
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NodeSelector] -> ShowS
$cshowList :: [NodeSelector] -> ShowS
show :: NodeSelector -> String
$cshow :: NodeSelector -> String
showsPrec :: Int -> NodeSelector -> ShowS
$cshowsPrec :: Int -> NodeSelector -> ShowS
Show)
newtype TemplateName = TemplateName Text deriving (TemplateName -> TemplateName -> Bool
(TemplateName -> TemplateName -> Bool)
-> (TemplateName -> TemplateName -> Bool) -> Eq TemplateName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TemplateName -> TemplateName -> Bool
$c/= :: TemplateName -> TemplateName -> Bool
== :: TemplateName -> TemplateName -> Bool
$c== :: TemplateName -> TemplateName -> Bool
Eq, Int -> TemplateName -> ShowS
[TemplateName] -> ShowS
TemplateName -> String
(Int -> TemplateName -> ShowS)
-> (TemplateName -> String)
-> ([TemplateName] -> ShowS)
-> Show TemplateName
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TemplateName] -> ShowS
$cshowList :: [TemplateName] -> ShowS
show :: TemplateName -> String
$cshow :: TemplateName -> String
showsPrec :: Int -> TemplateName -> ShowS
$cshowsPrec :: Int -> TemplateName -> ShowS
Show, [TemplateName] -> Encoding
[TemplateName] -> Value
TemplateName -> Encoding
TemplateName -> Value
(TemplateName -> Value)
-> (TemplateName -> Encoding)
-> ([TemplateName] -> Value)
-> ([TemplateName] -> Encoding)
-> ToJSON TemplateName
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [TemplateName] -> Encoding
$ctoEncodingList :: [TemplateName] -> Encoding
toJSONList :: [TemplateName] -> Value
$ctoJSONList :: [TemplateName] -> Value
toEncoding :: TemplateName -> Encoding
$ctoEncoding :: TemplateName -> Encoding
toJSON :: TemplateName -> Value
$ctoJSON :: TemplateName -> Value
ToJSON, Value -> Parser [TemplateName]
Value -> Parser TemplateName
(Value -> Parser TemplateName)
-> (Value -> Parser [TemplateName]) -> FromJSON TemplateName
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [TemplateName]
$cparseJSONList :: Value -> Parser [TemplateName]
parseJSON :: Value -> Parser TemplateName
$cparseJSON :: Value -> Parser TemplateName
FromJSON)
newtype IndexPattern = IndexPattern Text deriving (IndexPattern -> IndexPattern -> Bool
(IndexPattern -> IndexPattern -> Bool)
-> (IndexPattern -> IndexPattern -> Bool) -> Eq IndexPattern
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IndexPattern -> IndexPattern -> Bool
$c/= :: IndexPattern -> IndexPattern -> Bool
== :: IndexPattern -> IndexPattern -> Bool
$c== :: IndexPattern -> IndexPattern -> Bool
Eq, Int -> IndexPattern -> ShowS
[IndexPattern] -> ShowS
IndexPattern -> String
(Int -> IndexPattern -> ShowS)
-> (IndexPattern -> String)
-> ([IndexPattern] -> ShowS)
-> Show IndexPattern
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IndexPattern] -> ShowS
$cshowList :: [IndexPattern] -> ShowS
show :: IndexPattern -> String
$cshow :: IndexPattern -> String
showsPrec :: Int -> IndexPattern -> ShowS
$cshowsPrec :: Int -> IndexPattern -> ShowS
Show, [IndexPattern] -> Encoding
[IndexPattern] -> Value
IndexPattern -> Encoding
IndexPattern -> Value
(IndexPattern -> Value)
-> (IndexPattern -> Encoding)
-> ([IndexPattern] -> Value)
-> ([IndexPattern] -> Encoding)
-> ToJSON IndexPattern
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [IndexPattern] -> Encoding
$ctoEncodingList :: [IndexPattern] -> Encoding
toJSONList :: [IndexPattern] -> Value
$ctoJSONList :: [IndexPattern] -> Value
toEncoding :: IndexPattern -> Encoding
$ctoEncoding :: IndexPattern -> Encoding
toJSON :: IndexPattern -> Value
$ctoJSON :: IndexPattern -> Value
ToJSON, Value -> Parser [IndexPattern]
Value -> Parser IndexPattern
(Value -> Parser IndexPattern)
-> (Value -> Parser [IndexPattern]) -> FromJSON IndexPattern
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [IndexPattern]
$cparseJSONList :: Value -> Parser [IndexPattern]
parseJSON :: Value -> Parser IndexPattern
$cparseJSON :: Value -> Parser IndexPattern
FromJSON)
newtype EsUsername = EsUsername { EsUsername -> Text
esUsername :: Text } deriving (ReadPrec [EsUsername]
ReadPrec EsUsername
Int -> ReadS EsUsername
ReadS [EsUsername]
(Int -> ReadS EsUsername)
-> ReadS [EsUsername]
-> ReadPrec EsUsername
-> ReadPrec [EsUsername]
-> Read EsUsername
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EsUsername]
$creadListPrec :: ReadPrec [EsUsername]
readPrec :: ReadPrec EsUsername
$creadPrec :: ReadPrec EsUsername
readList :: ReadS [EsUsername]
$creadList :: ReadS [EsUsername]
readsPrec :: Int -> ReadS EsUsername
$creadsPrec :: Int -> ReadS EsUsername
Read, Int -> EsUsername -> ShowS
[EsUsername] -> ShowS
EsUsername -> String
(Int -> EsUsername -> ShowS)
-> (EsUsername -> String)
-> ([EsUsername] -> ShowS)
-> Show EsUsername
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EsUsername] -> ShowS
$cshowList :: [EsUsername] -> ShowS
show :: EsUsername -> String
$cshow :: EsUsername -> String
showsPrec :: Int -> EsUsername -> ShowS
$cshowsPrec :: Int -> EsUsername -> ShowS
Show, EsUsername -> EsUsername -> Bool
(EsUsername -> EsUsername -> Bool)
-> (EsUsername -> EsUsername -> Bool) -> Eq EsUsername
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EsUsername -> EsUsername -> Bool
$c/= :: EsUsername -> EsUsername -> Bool
== :: EsUsername -> EsUsername -> Bool
$c== :: EsUsername -> EsUsername -> Bool
Eq)
newtype EsPassword = EsPassword { EsPassword -> Text
esPassword :: Text } deriving (ReadPrec [EsPassword]
ReadPrec EsPassword
Int -> ReadS EsPassword
ReadS [EsPassword]
(Int -> ReadS EsPassword)
-> ReadS [EsPassword]
-> ReadPrec EsPassword
-> ReadPrec [EsPassword]
-> Read EsPassword
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EsPassword]
$creadListPrec :: ReadPrec [EsPassword]
readPrec :: ReadPrec EsPassword
$creadPrec :: ReadPrec EsPassword
readList :: ReadS [EsPassword]
$creadList :: ReadS [EsPassword]
readsPrec :: Int -> ReadS EsPassword
$creadsPrec :: Int -> ReadS EsPassword
Read, Int -> EsPassword -> ShowS
[EsPassword] -> ShowS
EsPassword -> String
(Int -> EsPassword -> ShowS)
-> (EsPassword -> String)
-> ([EsPassword] -> ShowS)
-> Show EsPassword
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EsPassword] -> ShowS
$cshowList :: [EsPassword] -> ShowS
show :: EsPassword -> String
$cshow :: EsPassword -> String
showsPrec :: Int -> EsPassword -> ShowS
$cshowsPrec :: Int -> EsPassword -> ShowS
Show, EsPassword -> EsPassword -> Bool
(EsPassword -> EsPassword -> Bool)
-> (EsPassword -> EsPassword -> Bool) -> Eq EsPassword
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EsPassword -> EsPassword -> Bool
$c/= :: EsPassword -> EsPassword -> Bool
== :: EsPassword -> EsPassword -> Bool
$c== :: EsPassword -> EsPassword -> Bool
Eq)
data SnapshotRepoSelection =
SnapshotRepoList (NonEmpty SnapshotRepoPattern)
| AllSnapshotRepos
deriving (SnapshotRepoSelection -> SnapshotRepoSelection -> Bool
(SnapshotRepoSelection -> SnapshotRepoSelection -> Bool)
-> (SnapshotRepoSelection -> SnapshotRepoSelection -> Bool)
-> Eq SnapshotRepoSelection
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SnapshotRepoSelection -> SnapshotRepoSelection -> Bool
$c/= :: SnapshotRepoSelection -> SnapshotRepoSelection -> Bool
== :: SnapshotRepoSelection -> SnapshotRepoSelection -> Bool
$c== :: SnapshotRepoSelection -> SnapshotRepoSelection -> Bool
Eq, Int -> SnapshotRepoSelection -> ShowS
[SnapshotRepoSelection] -> ShowS
SnapshotRepoSelection -> String
(Int -> SnapshotRepoSelection -> ShowS)
-> (SnapshotRepoSelection -> String)
-> ([SnapshotRepoSelection] -> ShowS)
-> Show SnapshotRepoSelection
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SnapshotRepoSelection] -> ShowS
$cshowList :: [SnapshotRepoSelection] -> ShowS
show :: SnapshotRepoSelection -> String
$cshow :: SnapshotRepoSelection -> String
showsPrec :: Int -> SnapshotRepoSelection -> ShowS
$cshowsPrec :: Int -> SnapshotRepoSelection -> ShowS
Show)
data SnapshotRepoPattern =
ExactRepo SnapshotRepoName
| RepoPattern Text
deriving (SnapshotRepoPattern -> SnapshotRepoPattern -> Bool
(SnapshotRepoPattern -> SnapshotRepoPattern -> Bool)
-> (SnapshotRepoPattern -> SnapshotRepoPattern -> Bool)
-> Eq SnapshotRepoPattern
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SnapshotRepoPattern -> SnapshotRepoPattern -> Bool
$c/= :: SnapshotRepoPattern -> SnapshotRepoPattern -> Bool
== :: SnapshotRepoPattern -> SnapshotRepoPattern -> Bool
$c== :: SnapshotRepoPattern -> SnapshotRepoPattern -> Bool
Eq, Int -> SnapshotRepoPattern -> ShowS
[SnapshotRepoPattern] -> ShowS
SnapshotRepoPattern -> String
(Int -> SnapshotRepoPattern -> ShowS)
-> (SnapshotRepoPattern -> String)
-> ([SnapshotRepoPattern] -> ShowS)
-> Show SnapshotRepoPattern
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SnapshotRepoPattern] -> ShowS
$cshowList :: [SnapshotRepoPattern] -> ShowS
show :: SnapshotRepoPattern -> String
$cshow :: SnapshotRepoPattern -> String
showsPrec :: Int -> SnapshotRepoPattern -> ShowS
$cshowsPrec :: Int -> SnapshotRepoPattern -> ShowS
Show)
newtype SnapshotRepoName =
SnapshotRepoName { SnapshotRepoName -> Text
snapshotRepoName :: Text }
deriving (SnapshotRepoName -> SnapshotRepoName -> Bool
(SnapshotRepoName -> SnapshotRepoName -> Bool)
-> (SnapshotRepoName -> SnapshotRepoName -> Bool)
-> Eq SnapshotRepoName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SnapshotRepoName -> SnapshotRepoName -> Bool
$c/= :: SnapshotRepoName -> SnapshotRepoName -> Bool
== :: SnapshotRepoName -> SnapshotRepoName -> Bool
$c== :: SnapshotRepoName -> SnapshotRepoName -> Bool
Eq, Eq SnapshotRepoName
Eq SnapshotRepoName
-> (SnapshotRepoName -> SnapshotRepoName -> Ordering)
-> (SnapshotRepoName -> SnapshotRepoName -> Bool)
-> (SnapshotRepoName -> SnapshotRepoName -> Bool)
-> (SnapshotRepoName -> SnapshotRepoName -> Bool)
-> (SnapshotRepoName -> SnapshotRepoName -> Bool)
-> (SnapshotRepoName -> SnapshotRepoName -> SnapshotRepoName)
-> (SnapshotRepoName -> SnapshotRepoName -> SnapshotRepoName)
-> Ord SnapshotRepoName
SnapshotRepoName -> SnapshotRepoName -> Bool
SnapshotRepoName -> SnapshotRepoName -> Ordering
SnapshotRepoName -> SnapshotRepoName -> SnapshotRepoName
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 :: SnapshotRepoName -> SnapshotRepoName -> SnapshotRepoName
$cmin :: SnapshotRepoName -> SnapshotRepoName -> SnapshotRepoName
max :: SnapshotRepoName -> SnapshotRepoName -> SnapshotRepoName
$cmax :: SnapshotRepoName -> SnapshotRepoName -> SnapshotRepoName
>= :: SnapshotRepoName -> SnapshotRepoName -> Bool
$c>= :: SnapshotRepoName -> SnapshotRepoName -> Bool
> :: SnapshotRepoName -> SnapshotRepoName -> Bool
$c> :: SnapshotRepoName -> SnapshotRepoName -> Bool
<= :: SnapshotRepoName -> SnapshotRepoName -> Bool
$c<= :: SnapshotRepoName -> SnapshotRepoName -> Bool
< :: SnapshotRepoName -> SnapshotRepoName -> Bool
$c< :: SnapshotRepoName -> SnapshotRepoName -> Bool
compare :: SnapshotRepoName -> SnapshotRepoName -> Ordering
$ccompare :: SnapshotRepoName -> SnapshotRepoName -> Ordering
$cp1Ord :: Eq SnapshotRepoName
Ord, Int -> SnapshotRepoName -> ShowS
[SnapshotRepoName] -> ShowS
SnapshotRepoName -> String
(Int -> SnapshotRepoName -> ShowS)
-> (SnapshotRepoName -> String)
-> ([SnapshotRepoName] -> ShowS)
-> Show SnapshotRepoName
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SnapshotRepoName] -> ShowS
$cshowList :: [SnapshotRepoName] -> ShowS
show :: SnapshotRepoName -> String
$cshow :: SnapshotRepoName -> String
showsPrec :: Int -> SnapshotRepoName -> ShowS
$cshowsPrec :: Int -> SnapshotRepoName -> ShowS
Show, [SnapshotRepoName] -> Encoding
[SnapshotRepoName] -> Value
SnapshotRepoName -> Encoding
SnapshotRepoName -> Value
(SnapshotRepoName -> Value)
-> (SnapshotRepoName -> Encoding)
-> ([SnapshotRepoName] -> Value)
-> ([SnapshotRepoName] -> Encoding)
-> ToJSON SnapshotRepoName
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [SnapshotRepoName] -> Encoding
$ctoEncodingList :: [SnapshotRepoName] -> Encoding
toJSONList :: [SnapshotRepoName] -> Value
$ctoJSONList :: [SnapshotRepoName] -> Value
toEncoding :: SnapshotRepoName -> Encoding
$ctoEncoding :: SnapshotRepoName -> Encoding
toJSON :: SnapshotRepoName -> Value
$ctoJSON :: SnapshotRepoName -> Value
ToJSON, Value -> Parser [SnapshotRepoName]
Value -> Parser SnapshotRepoName
(Value -> Parser SnapshotRepoName)
-> (Value -> Parser [SnapshotRepoName])
-> FromJSON SnapshotRepoName
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [SnapshotRepoName]
$cparseJSONList :: Value -> Parser [SnapshotRepoName]
parseJSON :: Value -> Parser SnapshotRepoName
$cparseJSON :: Value -> Parser SnapshotRepoName
FromJSON)
data GenericSnapshotRepo = GenericSnapshotRepo {
GenericSnapshotRepo -> SnapshotRepoName
gSnapshotRepoName :: SnapshotRepoName
, GenericSnapshotRepo -> SnapshotRepoType
gSnapshotRepoType :: SnapshotRepoType
, GenericSnapshotRepo -> GenericSnapshotRepoSettings
gSnapshotRepoSettings :: GenericSnapshotRepoSettings
} deriving (GenericSnapshotRepo -> GenericSnapshotRepo -> Bool
(GenericSnapshotRepo -> GenericSnapshotRepo -> Bool)
-> (GenericSnapshotRepo -> GenericSnapshotRepo -> Bool)
-> Eq GenericSnapshotRepo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GenericSnapshotRepo -> GenericSnapshotRepo -> Bool
$c/= :: GenericSnapshotRepo -> GenericSnapshotRepo -> Bool
== :: GenericSnapshotRepo -> GenericSnapshotRepo -> Bool
$c== :: GenericSnapshotRepo -> GenericSnapshotRepo -> Bool
Eq, Int -> GenericSnapshotRepo -> ShowS
[GenericSnapshotRepo] -> ShowS
GenericSnapshotRepo -> String
(Int -> GenericSnapshotRepo -> ShowS)
-> (GenericSnapshotRepo -> String)
-> ([GenericSnapshotRepo] -> ShowS)
-> Show GenericSnapshotRepo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GenericSnapshotRepo] -> ShowS
$cshowList :: [GenericSnapshotRepo] -> ShowS
show :: GenericSnapshotRepo -> String
$cshow :: GenericSnapshotRepo -> String
showsPrec :: Int -> GenericSnapshotRepo -> ShowS
$cshowsPrec :: Int -> GenericSnapshotRepo -> ShowS
Show)
instance SnapshotRepo GenericSnapshotRepo where
toGSnapshotRepo :: GenericSnapshotRepo -> GenericSnapshotRepo
toGSnapshotRepo = GenericSnapshotRepo -> GenericSnapshotRepo
forall a. a -> a
id
fromGSnapshotRepo :: GenericSnapshotRepo
-> Either SnapshotRepoConversionError GenericSnapshotRepo
fromGSnapshotRepo = GenericSnapshotRepo
-> Either SnapshotRepoConversionError GenericSnapshotRepo
forall a b. b -> Either a b
Right
newtype SnapshotRepoType =
SnapshotRepoType { SnapshotRepoType -> Text
snapshotRepoType :: Text }
deriving (SnapshotRepoType -> SnapshotRepoType -> Bool
(SnapshotRepoType -> SnapshotRepoType -> Bool)
-> (SnapshotRepoType -> SnapshotRepoType -> Bool)
-> Eq SnapshotRepoType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SnapshotRepoType -> SnapshotRepoType -> Bool
$c/= :: SnapshotRepoType -> SnapshotRepoType -> Bool
== :: SnapshotRepoType -> SnapshotRepoType -> Bool
$c== :: SnapshotRepoType -> SnapshotRepoType -> Bool
Eq, Eq SnapshotRepoType
Eq SnapshotRepoType
-> (SnapshotRepoType -> SnapshotRepoType -> Ordering)
-> (SnapshotRepoType -> SnapshotRepoType -> Bool)
-> (SnapshotRepoType -> SnapshotRepoType -> Bool)
-> (SnapshotRepoType -> SnapshotRepoType -> Bool)
-> (SnapshotRepoType -> SnapshotRepoType -> Bool)
-> (SnapshotRepoType -> SnapshotRepoType -> SnapshotRepoType)
-> (SnapshotRepoType -> SnapshotRepoType -> SnapshotRepoType)
-> Ord SnapshotRepoType
SnapshotRepoType -> SnapshotRepoType -> Bool
SnapshotRepoType -> SnapshotRepoType -> Ordering
SnapshotRepoType -> SnapshotRepoType -> SnapshotRepoType
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 :: SnapshotRepoType -> SnapshotRepoType -> SnapshotRepoType
$cmin :: SnapshotRepoType -> SnapshotRepoType -> SnapshotRepoType
max :: SnapshotRepoType -> SnapshotRepoType -> SnapshotRepoType
$cmax :: SnapshotRepoType -> SnapshotRepoType -> SnapshotRepoType
>= :: SnapshotRepoType -> SnapshotRepoType -> Bool
$c>= :: SnapshotRepoType -> SnapshotRepoType -> Bool
> :: SnapshotRepoType -> SnapshotRepoType -> Bool
$c> :: SnapshotRepoType -> SnapshotRepoType -> Bool
<= :: SnapshotRepoType -> SnapshotRepoType -> Bool
$c<= :: SnapshotRepoType -> SnapshotRepoType -> Bool
< :: SnapshotRepoType -> SnapshotRepoType -> Bool
$c< :: SnapshotRepoType -> SnapshotRepoType -> Bool
compare :: SnapshotRepoType -> SnapshotRepoType -> Ordering
$ccompare :: SnapshotRepoType -> SnapshotRepoType -> Ordering
$cp1Ord :: Eq SnapshotRepoType
Ord, Int -> SnapshotRepoType -> ShowS
[SnapshotRepoType] -> ShowS
SnapshotRepoType -> String
(Int -> SnapshotRepoType -> ShowS)
-> (SnapshotRepoType -> String)
-> ([SnapshotRepoType] -> ShowS)
-> Show SnapshotRepoType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SnapshotRepoType] -> ShowS
$cshowList :: [SnapshotRepoType] -> ShowS
show :: SnapshotRepoType -> String
$cshow :: SnapshotRepoType -> String
showsPrec :: Int -> SnapshotRepoType -> ShowS
$cshowsPrec :: Int -> SnapshotRepoType -> ShowS
Show, [SnapshotRepoType] -> Encoding
[SnapshotRepoType] -> Value
SnapshotRepoType -> Encoding
SnapshotRepoType -> Value
(SnapshotRepoType -> Value)
-> (SnapshotRepoType -> Encoding)
-> ([SnapshotRepoType] -> Value)
-> ([SnapshotRepoType] -> Encoding)
-> ToJSON SnapshotRepoType
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [SnapshotRepoType] -> Encoding
$ctoEncodingList :: [SnapshotRepoType] -> Encoding
toJSONList :: [SnapshotRepoType] -> Value
$ctoJSONList :: [SnapshotRepoType] -> Value
toEncoding :: SnapshotRepoType -> Encoding
$ctoEncoding :: SnapshotRepoType -> Encoding
toJSON :: SnapshotRepoType -> Value
$ctoJSON :: SnapshotRepoType -> Value
ToJSON, Value -> Parser [SnapshotRepoType]
Value -> Parser SnapshotRepoType
(Value -> Parser SnapshotRepoType)
-> (Value -> Parser [SnapshotRepoType])
-> FromJSON SnapshotRepoType
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [SnapshotRepoType]
$cparseJSONList :: Value -> Parser [SnapshotRepoType]
parseJSON :: Value -> Parser SnapshotRepoType
$cparseJSON :: Value -> Parser SnapshotRepoType
FromJSON)
newtype GenericSnapshotRepoSettings =
GenericSnapshotRepoSettings { GenericSnapshotRepoSettings -> Object
gSnapshotRepoSettingsObject :: Object }
deriving (GenericSnapshotRepoSettings -> GenericSnapshotRepoSettings -> Bool
(GenericSnapshotRepoSettings
-> GenericSnapshotRepoSettings -> Bool)
-> (GenericSnapshotRepoSettings
-> GenericSnapshotRepoSettings -> Bool)
-> Eq GenericSnapshotRepoSettings
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GenericSnapshotRepoSettings -> GenericSnapshotRepoSettings -> Bool
$c/= :: GenericSnapshotRepoSettings -> GenericSnapshotRepoSettings -> Bool
== :: GenericSnapshotRepoSettings -> GenericSnapshotRepoSettings -> Bool
$c== :: GenericSnapshotRepoSettings -> GenericSnapshotRepoSettings -> Bool
Eq, Int -> GenericSnapshotRepoSettings -> ShowS
[GenericSnapshotRepoSettings] -> ShowS
GenericSnapshotRepoSettings -> String
(Int -> GenericSnapshotRepoSettings -> ShowS)
-> (GenericSnapshotRepoSettings -> String)
-> ([GenericSnapshotRepoSettings] -> ShowS)
-> Show GenericSnapshotRepoSettings
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GenericSnapshotRepoSettings] -> ShowS
$cshowList :: [GenericSnapshotRepoSettings] -> ShowS
show :: GenericSnapshotRepoSettings -> String
$cshow :: GenericSnapshotRepoSettings -> String
showsPrec :: Int -> GenericSnapshotRepoSettings -> ShowS
$cshowsPrec :: Int -> GenericSnapshotRepoSettings -> ShowS
Show, [GenericSnapshotRepoSettings] -> Encoding
[GenericSnapshotRepoSettings] -> Value
GenericSnapshotRepoSettings -> Encoding
GenericSnapshotRepoSettings -> Value
(GenericSnapshotRepoSettings -> Value)
-> (GenericSnapshotRepoSettings -> Encoding)
-> ([GenericSnapshotRepoSettings] -> Value)
-> ([GenericSnapshotRepoSettings] -> Encoding)
-> ToJSON GenericSnapshotRepoSettings
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [GenericSnapshotRepoSettings] -> Encoding
$ctoEncodingList :: [GenericSnapshotRepoSettings] -> Encoding
toJSONList :: [GenericSnapshotRepoSettings] -> Value
$ctoJSONList :: [GenericSnapshotRepoSettings] -> Value
toEncoding :: GenericSnapshotRepoSettings -> Encoding
$ctoEncoding :: GenericSnapshotRepoSettings -> Encoding
toJSON :: GenericSnapshotRepoSettings -> Value
$ctoJSON :: GenericSnapshotRepoSettings -> Value
ToJSON)
instance FromJSON GenericSnapshotRepoSettings where
parseJSON :: Value -> Parser GenericSnapshotRepoSettings
parseJSON = (Object -> GenericSnapshotRepoSettings)
-> Parser Object -> Parser GenericSnapshotRepoSettings
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Object -> GenericSnapshotRepoSettings
GenericSnapshotRepoSettings (Object -> GenericSnapshotRepoSettings)
-> (Object -> Object) -> Object -> GenericSnapshotRepoSettings
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Value -> Value) -> Object -> Object
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Value -> Value
unStringlyTypeJSON)(Parser Object -> Parser GenericSnapshotRepoSettings)
-> (Value -> Parser Object)
-> Value
-> Parser GenericSnapshotRepoSettings
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> Parser Object
forall a. FromJSON a => Value -> Parser a
parseJSON
newtype SnapshotVerification =
SnapshotVerification {
SnapshotVerification -> [SnapshotNodeVerification]
snapshotNodeVerifications :: [SnapshotNodeVerification]
} deriving (SnapshotVerification -> SnapshotVerification -> Bool
(SnapshotVerification -> SnapshotVerification -> Bool)
-> (SnapshotVerification -> SnapshotVerification -> Bool)
-> Eq SnapshotVerification
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SnapshotVerification -> SnapshotVerification -> Bool
$c/= :: SnapshotVerification -> SnapshotVerification -> Bool
== :: SnapshotVerification -> SnapshotVerification -> Bool
$c== :: SnapshotVerification -> SnapshotVerification -> Bool
Eq, Int -> SnapshotVerification -> ShowS
[SnapshotVerification] -> ShowS
SnapshotVerification -> String
(Int -> SnapshotVerification -> ShowS)
-> (SnapshotVerification -> String)
-> ([SnapshotVerification] -> ShowS)
-> Show SnapshotVerification
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SnapshotVerification] -> ShowS
$cshowList :: [SnapshotVerification] -> ShowS
show :: SnapshotVerification -> String
$cshow :: SnapshotVerification -> String
showsPrec :: Int -> SnapshotVerification -> ShowS
$cshowsPrec :: Int -> SnapshotVerification -> ShowS
Show)
instance FromJSON SnapshotVerification where
parseJSON :: Value -> Parser SnapshotVerification
parseJSON = String
-> (Object -> Parser SnapshotVerification)
-> Value
-> Parser SnapshotVerification
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"SnapshotVerification" Object -> Parser SnapshotVerification
parse
where
parse :: Object -> Parser SnapshotVerification
parse Object
o = do
HashMap Text Value
o2 <- Object
o Object -> Key -> Parser (HashMap Text Value)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"nodes"
[SnapshotNodeVerification] -> SnapshotVerification
SnapshotVerification ([SnapshotNodeVerification] -> SnapshotVerification)
-> Parser [SnapshotNodeVerification] -> Parser SnapshotVerification
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((Text, Value) -> Parser SnapshotNodeVerification)
-> [(Text, Value)] -> Parser [SnapshotNodeVerification]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((Text -> Value -> Parser SnapshotNodeVerification)
-> (Text, Value) -> Parser SnapshotNodeVerification
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Text -> Value -> Parser SnapshotNodeVerification
parse') (HashMap Text Value -> [(Text, Value)]
forall k v. HashMap k v -> [(k, v)]
HM.toList HashMap Text Value
o2)
parse' :: Text -> Value -> Parser SnapshotNodeVerification
parse' Text
rawFullId = String
-> (Object -> Parser SnapshotNodeVerification)
-> Value
-> Parser SnapshotNodeVerification
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"SnapshotNodeVerification" ((Object -> Parser SnapshotNodeVerification)
-> Value -> Parser SnapshotNodeVerification)
-> (Object -> Parser SnapshotNodeVerification)
-> Value
-> Parser SnapshotNodeVerification
forall a b. (a -> b) -> a -> b
$ \Object
o ->
FullNodeId -> NodeName -> SnapshotNodeVerification
SnapshotNodeVerification (Text -> FullNodeId
FullNodeId Text
rawFullId) (NodeName -> SnapshotNodeVerification)
-> Parser NodeName -> Parser SnapshotNodeVerification
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser NodeName
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"name"
data SnapshotNodeVerification = SnapshotNodeVerification {
SnapshotNodeVerification -> FullNodeId
snvFullId :: FullNodeId
, SnapshotNodeVerification -> NodeName
snvNodeName :: NodeName
} deriving (SnapshotNodeVerification -> SnapshotNodeVerification -> Bool
(SnapshotNodeVerification -> SnapshotNodeVerification -> Bool)
-> (SnapshotNodeVerification -> SnapshotNodeVerification -> Bool)
-> Eq SnapshotNodeVerification
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SnapshotNodeVerification -> SnapshotNodeVerification -> Bool
$c/= :: SnapshotNodeVerification -> SnapshotNodeVerification -> Bool
== :: SnapshotNodeVerification -> SnapshotNodeVerification -> Bool
$c== :: SnapshotNodeVerification -> SnapshotNodeVerification -> Bool
Eq, Int -> SnapshotNodeVerification -> ShowS
[SnapshotNodeVerification] -> ShowS
SnapshotNodeVerification -> String
(Int -> SnapshotNodeVerification -> ShowS)
-> (SnapshotNodeVerification -> String)
-> ([SnapshotNodeVerification] -> ShowS)
-> Show SnapshotNodeVerification
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SnapshotNodeVerification] -> ShowS
$cshowList :: [SnapshotNodeVerification] -> ShowS
show :: SnapshotNodeVerification -> String
$cshow :: SnapshotNodeVerification -> String
showsPrec :: Int -> SnapshotNodeVerification -> ShowS
$cshowsPrec :: Int -> SnapshotNodeVerification -> ShowS
Show)
newtype FullNodeId = FullNodeId { FullNodeId -> Text
fullNodeId :: Text }
deriving (FullNodeId -> FullNodeId -> Bool
(FullNodeId -> FullNodeId -> Bool)
-> (FullNodeId -> FullNodeId -> Bool) -> Eq FullNodeId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FullNodeId -> FullNodeId -> Bool
$c/= :: FullNodeId -> FullNodeId -> Bool
== :: FullNodeId -> FullNodeId -> Bool
$c== :: FullNodeId -> FullNodeId -> Bool
Eq, Eq FullNodeId
Eq FullNodeId
-> (FullNodeId -> FullNodeId -> Ordering)
-> (FullNodeId -> FullNodeId -> Bool)
-> (FullNodeId -> FullNodeId -> Bool)
-> (FullNodeId -> FullNodeId -> Bool)
-> (FullNodeId -> FullNodeId -> Bool)
-> (FullNodeId -> FullNodeId -> FullNodeId)
-> (FullNodeId -> FullNodeId -> FullNodeId)
-> Ord FullNodeId
FullNodeId -> FullNodeId -> Bool
FullNodeId -> FullNodeId -> Ordering
FullNodeId -> FullNodeId -> FullNodeId
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 :: FullNodeId -> FullNodeId -> FullNodeId
$cmin :: FullNodeId -> FullNodeId -> FullNodeId
max :: FullNodeId -> FullNodeId -> FullNodeId
$cmax :: FullNodeId -> FullNodeId -> FullNodeId
>= :: FullNodeId -> FullNodeId -> Bool
$c>= :: FullNodeId -> FullNodeId -> Bool
> :: FullNodeId -> FullNodeId -> Bool
$c> :: FullNodeId -> FullNodeId -> Bool
<= :: FullNodeId -> FullNodeId -> Bool
$c<= :: FullNodeId -> FullNodeId -> Bool
< :: FullNodeId -> FullNodeId -> Bool
$c< :: FullNodeId -> FullNodeId -> Bool
compare :: FullNodeId -> FullNodeId -> Ordering
$ccompare :: FullNodeId -> FullNodeId -> Ordering
$cp1Ord :: Eq FullNodeId
Ord, Int -> FullNodeId -> ShowS
[FullNodeId] -> ShowS
FullNodeId -> String
(Int -> FullNodeId -> ShowS)
-> (FullNodeId -> String)
-> ([FullNodeId] -> ShowS)
-> Show FullNodeId
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FullNodeId] -> ShowS
$cshowList :: [FullNodeId] -> ShowS
show :: FullNodeId -> String
$cshow :: FullNodeId -> String
showsPrec :: Int -> FullNodeId -> ShowS
$cshowsPrec :: Int -> FullNodeId -> ShowS
Show, Value -> Parser [FullNodeId]
Value -> Parser FullNodeId
(Value -> Parser FullNodeId)
-> (Value -> Parser [FullNodeId]) -> FromJSON FullNodeId
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [FullNodeId]
$cparseJSONList :: Value -> Parser [FullNodeId]
parseJSON :: Value -> Parser FullNodeId
$cparseJSON :: Value -> Parser FullNodeId
FromJSON)
newtype NodeName = NodeName { NodeName -> Text
nodeName :: Text }
deriving (NodeName -> NodeName -> Bool
(NodeName -> NodeName -> Bool)
-> (NodeName -> NodeName -> Bool) -> Eq NodeName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NodeName -> NodeName -> Bool
$c/= :: NodeName -> NodeName -> Bool
== :: NodeName -> NodeName -> Bool
$c== :: NodeName -> NodeName -> Bool
Eq, Eq NodeName
Eq NodeName
-> (NodeName -> NodeName -> Ordering)
-> (NodeName -> NodeName -> Bool)
-> (NodeName -> NodeName -> Bool)
-> (NodeName -> NodeName -> Bool)
-> (NodeName -> NodeName -> Bool)
-> (NodeName -> NodeName -> NodeName)
-> (NodeName -> NodeName -> NodeName)
-> Ord NodeName
NodeName -> NodeName -> Bool
NodeName -> NodeName -> Ordering
NodeName -> NodeName -> NodeName
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 :: NodeName -> NodeName -> NodeName
$cmin :: NodeName -> NodeName -> NodeName
max :: NodeName -> NodeName -> NodeName
$cmax :: NodeName -> NodeName -> NodeName
>= :: NodeName -> NodeName -> Bool
$c>= :: NodeName -> NodeName -> Bool
> :: NodeName -> NodeName -> Bool
$c> :: NodeName -> NodeName -> Bool
<= :: NodeName -> NodeName -> Bool
$c<= :: NodeName -> NodeName -> Bool
< :: NodeName -> NodeName -> Bool
$c< :: NodeName -> NodeName -> Bool
compare :: NodeName -> NodeName -> Ordering
$ccompare :: NodeName -> NodeName -> Ordering
$cp1Ord :: Eq NodeName
Ord, Int -> NodeName -> ShowS
[NodeName] -> ShowS
NodeName -> String
(Int -> NodeName -> ShowS)
-> (NodeName -> String) -> ([NodeName] -> ShowS) -> Show NodeName
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NodeName] -> ShowS
$cshowList :: [NodeName] -> ShowS
show :: NodeName -> String
$cshow :: NodeName -> String
showsPrec :: Int -> NodeName -> ShowS
$cshowsPrec :: Int -> NodeName -> ShowS
Show, Value -> Parser [NodeName]
Value -> Parser NodeName
(Value -> Parser NodeName)
-> (Value -> Parser [NodeName]) -> FromJSON NodeName
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [NodeName]
$cparseJSONList :: Value -> Parser [NodeName]
parseJSON :: Value -> Parser NodeName
$cparseJSON :: Value -> Parser NodeName
FromJSON)
newtype ClusterName = ClusterName { ClusterName -> Text
clusterName :: Text }
deriving (ClusterName -> ClusterName -> Bool
(ClusterName -> ClusterName -> Bool)
-> (ClusterName -> ClusterName -> Bool) -> Eq ClusterName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ClusterName -> ClusterName -> Bool
$c/= :: ClusterName -> ClusterName -> Bool
== :: ClusterName -> ClusterName -> Bool
$c== :: ClusterName -> ClusterName -> Bool
Eq, Eq ClusterName
Eq ClusterName
-> (ClusterName -> ClusterName -> Ordering)
-> (ClusterName -> ClusterName -> Bool)
-> (ClusterName -> ClusterName -> Bool)
-> (ClusterName -> ClusterName -> Bool)
-> (ClusterName -> ClusterName -> Bool)
-> (ClusterName -> ClusterName -> ClusterName)
-> (ClusterName -> ClusterName -> ClusterName)
-> Ord ClusterName
ClusterName -> ClusterName -> Bool
ClusterName -> ClusterName -> Ordering
ClusterName -> ClusterName -> ClusterName
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 :: ClusterName -> ClusterName -> ClusterName
$cmin :: ClusterName -> ClusterName -> ClusterName
max :: ClusterName -> ClusterName -> ClusterName
$cmax :: ClusterName -> ClusterName -> ClusterName
>= :: ClusterName -> ClusterName -> Bool
$c>= :: ClusterName -> ClusterName -> Bool
> :: ClusterName -> ClusterName -> Bool
$c> :: ClusterName -> ClusterName -> Bool
<= :: ClusterName -> ClusterName -> Bool
$c<= :: ClusterName -> ClusterName -> Bool
< :: ClusterName -> ClusterName -> Bool
$c< :: ClusterName -> ClusterName -> Bool
compare :: ClusterName -> ClusterName -> Ordering
$ccompare :: ClusterName -> ClusterName -> Ordering
$cp1Ord :: Eq ClusterName
Ord, Int -> ClusterName -> ShowS
[ClusterName] -> ShowS
ClusterName -> String
(Int -> ClusterName -> ShowS)
-> (ClusterName -> String)
-> ([ClusterName] -> ShowS)
-> Show ClusterName
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ClusterName] -> ShowS
$cshowList :: [ClusterName] -> ShowS
show :: ClusterName -> String
$cshow :: ClusterName -> String
showsPrec :: Int -> ClusterName -> ShowS
$cshowsPrec :: Int -> ClusterName -> ShowS
Show, Value -> Parser [ClusterName]
Value -> Parser ClusterName
(Value -> Parser ClusterName)
-> (Value -> Parser [ClusterName]) -> FromJSON ClusterName
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [ClusterName]
$cparseJSONList :: Value -> Parser [ClusterName]
parseJSON :: Value -> Parser ClusterName
$cparseJSON :: Value -> Parser ClusterName
FromJSON)
data NodesInfo = NodesInfo {
NodesInfo -> [NodeInfo]
nodesInfo :: [NodeInfo]
, NodesInfo -> ClusterName
nodesClusterName :: ClusterName
} deriving (NodesInfo -> NodesInfo -> Bool
(NodesInfo -> NodesInfo -> Bool)
-> (NodesInfo -> NodesInfo -> Bool) -> Eq NodesInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NodesInfo -> NodesInfo -> Bool
$c/= :: NodesInfo -> NodesInfo -> Bool
== :: NodesInfo -> NodesInfo -> Bool
$c== :: NodesInfo -> NodesInfo -> Bool
Eq, Int -> NodesInfo -> ShowS
[NodesInfo] -> ShowS
NodesInfo -> String
(Int -> NodesInfo -> ShowS)
-> (NodesInfo -> String)
-> ([NodesInfo] -> ShowS)
-> Show NodesInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NodesInfo] -> ShowS
$cshowList :: [NodesInfo] -> ShowS
show :: NodesInfo -> String
$cshow :: NodesInfo -> String
showsPrec :: Int -> NodesInfo -> ShowS
$cshowsPrec :: Int -> NodesInfo -> ShowS
Show)
data NodesStats = NodesStats {
NodesStats -> [NodeStats]
nodesStats :: [NodeStats]
, NodesStats -> ClusterName
nodesStatsClusterName :: ClusterName
} deriving (NodesStats -> NodesStats -> Bool
(NodesStats -> NodesStats -> Bool)
-> (NodesStats -> NodesStats -> Bool) -> Eq NodesStats
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NodesStats -> NodesStats -> Bool
$c/= :: NodesStats -> NodesStats -> Bool
== :: NodesStats -> NodesStats -> Bool
$c== :: NodesStats -> NodesStats -> Bool
Eq, Int -> NodesStats -> ShowS
[NodesStats] -> ShowS
NodesStats -> String
(Int -> NodesStats -> ShowS)
-> (NodesStats -> String)
-> ([NodesStats] -> ShowS)
-> Show NodesStats
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NodesStats] -> ShowS
$cshowList :: [NodesStats] -> ShowS
show :: NodesStats -> String
$cshow :: NodesStats -> String
showsPrec :: Int -> NodesStats -> ShowS
$cshowsPrec :: Int -> NodesStats -> ShowS
Show)
data NodeStats = NodeStats {
NodeStats -> NodeName
nodeStatsName :: NodeName
, NodeStats -> FullNodeId
nodeStatsFullId :: FullNodeId
, :: Maybe NodeBreakersStats
, NodeStats -> NodeHTTPStats
nodeStatsHTTP :: NodeHTTPStats
, NodeStats -> NodeTransportStats
nodeStatsTransport :: NodeTransportStats
, NodeStats -> NodeFSStats
nodeStatsFS :: NodeFSStats
, NodeStats -> Maybe NodeNetworkStats
nodeStatsNetwork :: Maybe NodeNetworkStats
, NodeStats -> Map Text NodeThreadPoolStats
nodeStatsThreadPool :: Map Text NodeThreadPoolStats
, NodeStats -> NodeJVMStats
nodeStatsJVM :: NodeJVMStats
, NodeStats -> NodeProcessStats
nodeStatsProcess :: NodeProcessStats
, NodeStats -> NodeOSStats
nodeStatsOS :: NodeOSStats
, NodeStats -> NodeIndicesStats
nodeStatsIndices :: NodeIndicesStats
} deriving (NodeStats -> NodeStats -> Bool
(NodeStats -> NodeStats -> Bool)
-> (NodeStats -> NodeStats -> Bool) -> Eq NodeStats
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NodeStats -> NodeStats -> Bool
$c/= :: NodeStats -> NodeStats -> Bool
== :: NodeStats -> NodeStats -> Bool
$c== :: NodeStats -> NodeStats -> Bool
Eq, Int -> NodeStats -> ShowS
[NodeStats] -> ShowS
NodeStats -> String
(Int -> NodeStats -> ShowS)
-> (NodeStats -> String)
-> ([NodeStats] -> ShowS)
-> Show NodeStats
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NodeStats] -> ShowS
$cshowList :: [NodeStats] -> ShowS
show :: NodeStats -> String
$cshow :: NodeStats -> String
showsPrec :: Int -> NodeStats -> ShowS
$cshowsPrec :: Int -> NodeStats -> ShowS
Show)
data = {
NodeBreakersStats -> NodeBreakerStats
nodeStatsParentBreaker :: NodeBreakerStats
, NodeBreakersStats -> NodeBreakerStats
nodeStatsRequestBreaker :: NodeBreakerStats
, NodeBreakersStats -> NodeBreakerStats
nodeStatsFieldDataBreaker :: NodeBreakerStats
} deriving (NodeBreakersStats -> NodeBreakersStats -> Bool
(NodeBreakersStats -> NodeBreakersStats -> Bool)
-> (NodeBreakersStats -> NodeBreakersStats -> Bool)
-> Eq NodeBreakersStats
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NodeBreakersStats -> NodeBreakersStats -> Bool
$c/= :: NodeBreakersStats -> NodeBreakersStats -> Bool
== :: NodeBreakersStats -> NodeBreakersStats -> Bool
$c== :: NodeBreakersStats -> NodeBreakersStats -> Bool
Eq, Int -> NodeBreakersStats -> ShowS
[NodeBreakersStats] -> ShowS
NodeBreakersStats -> String
(Int -> NodeBreakersStats -> ShowS)
-> (NodeBreakersStats -> String)
-> ([NodeBreakersStats] -> ShowS)
-> Show NodeBreakersStats
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NodeBreakersStats] -> ShowS
$cshowList :: [NodeBreakersStats] -> ShowS
show :: NodeBreakersStats -> String
$cshow :: NodeBreakersStats -> String
showsPrec :: Int -> NodeBreakersStats -> ShowS
$cshowsPrec :: Int -> NodeBreakersStats -> ShowS
Show)
data NodeBreakerStats = NodeBreakerStats {
NodeBreakerStats -> Int
nodeBreakersTripped :: Int
, NodeBreakerStats -> Double
nodeBreakersOverhead :: Double
, NodeBreakerStats -> Bytes
nodeBreakersEstSize :: Bytes
, NodeBreakerStats -> Bytes
nodeBreakersLimitSize :: Bytes
} deriving (NodeBreakerStats -> NodeBreakerStats -> Bool
(NodeBreakerStats -> NodeBreakerStats -> Bool)
-> (NodeBreakerStats -> NodeBreakerStats -> Bool)
-> Eq NodeBreakerStats
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NodeBreakerStats -> NodeBreakerStats -> Bool
$c/= :: NodeBreakerStats -> NodeBreakerStats -> Bool
== :: NodeBreakerStats -> NodeBreakerStats -> Bool
$c== :: NodeBreakerStats -> NodeBreakerStats -> Bool
Eq, Int -> NodeBreakerStats -> ShowS
[NodeBreakerStats] -> ShowS
NodeBreakerStats -> String
(Int -> NodeBreakerStats -> ShowS)
-> (NodeBreakerStats -> String)
-> ([NodeBreakerStats] -> ShowS)
-> Show NodeBreakerStats
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NodeBreakerStats] -> ShowS
$cshowList :: [NodeBreakerStats] -> ShowS
show :: NodeBreakerStats -> String
$cshow :: NodeBreakerStats -> String
showsPrec :: Int -> NodeBreakerStats -> ShowS
$cshowsPrec :: Int -> NodeBreakerStats -> ShowS
Show)
data NodeHTTPStats = NodeHTTPStats {
NodeHTTPStats -> Int
nodeHTTPTotalOpened :: Int
, NodeHTTPStats -> Int
nodeHTTPCurrentOpen :: Int
} deriving (NodeHTTPStats -> NodeHTTPStats -> Bool
(NodeHTTPStats -> NodeHTTPStats -> Bool)
-> (NodeHTTPStats -> NodeHTTPStats -> Bool) -> Eq NodeHTTPStats
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NodeHTTPStats -> NodeHTTPStats -> Bool
$c/= :: NodeHTTPStats -> NodeHTTPStats -> Bool
== :: NodeHTTPStats -> NodeHTTPStats -> Bool
$c== :: NodeHTTPStats -> NodeHTTPStats -> Bool
Eq, Int -> NodeHTTPStats -> ShowS
[NodeHTTPStats] -> ShowS
NodeHTTPStats -> String
(Int -> NodeHTTPStats -> ShowS)
-> (NodeHTTPStats -> String)
-> ([NodeHTTPStats] -> ShowS)
-> Show NodeHTTPStats
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NodeHTTPStats] -> ShowS
$cshowList :: [NodeHTTPStats] -> ShowS
show :: NodeHTTPStats -> String
$cshow :: NodeHTTPStats -> String
showsPrec :: Int -> NodeHTTPStats -> ShowS
$cshowsPrec :: Int -> NodeHTTPStats -> ShowS
Show)
data NodeTransportStats = NodeTransportStats {
NodeTransportStats -> Bytes
nodeTransportTXSize :: Bytes
, NodeTransportStats -> Int
nodeTransportCount :: Int
, NodeTransportStats -> Bytes
nodeTransportRXSize :: Bytes
, NodeTransportStats -> Int
nodeTransportRXCount :: Int
, NodeTransportStats -> Int
nodeTransportServerOpen :: Int
} deriving (NodeTransportStats -> NodeTransportStats -> Bool
(NodeTransportStats -> NodeTransportStats -> Bool)
-> (NodeTransportStats -> NodeTransportStats -> Bool)
-> Eq NodeTransportStats
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NodeTransportStats -> NodeTransportStats -> Bool
$c/= :: NodeTransportStats -> NodeTransportStats -> Bool
== :: NodeTransportStats -> NodeTransportStats -> Bool
$c== :: NodeTransportStats -> NodeTransportStats -> Bool
Eq, Int -> NodeTransportStats -> ShowS
[NodeTransportStats] -> ShowS
NodeTransportStats -> String
(Int -> NodeTransportStats -> ShowS)
-> (NodeTransportStats -> String)
-> ([NodeTransportStats] -> ShowS)
-> Show NodeTransportStats
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NodeTransportStats] -> ShowS
$cshowList :: [NodeTransportStats] -> ShowS
show :: NodeTransportStats -> String
$cshow :: NodeTransportStats -> String
showsPrec :: Int -> NodeTransportStats -> ShowS
$cshowsPrec :: Int -> NodeTransportStats -> ShowS
Show)
data NodeFSStats = NodeFSStats {
NodeFSStats -> [NodeDataPathStats]
nodeFSDataPaths :: [NodeDataPathStats]
, NodeFSStats -> NodeFSTotalStats
nodeFSTotal :: NodeFSTotalStats
, NodeFSStats -> UTCTime
nodeFSTimestamp :: UTCTime
} deriving (NodeFSStats -> NodeFSStats -> Bool
(NodeFSStats -> NodeFSStats -> Bool)
-> (NodeFSStats -> NodeFSStats -> Bool) -> Eq NodeFSStats
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NodeFSStats -> NodeFSStats -> Bool
$c/= :: NodeFSStats -> NodeFSStats -> Bool
== :: NodeFSStats -> NodeFSStats -> Bool
$c== :: NodeFSStats -> NodeFSStats -> Bool
Eq, Int -> NodeFSStats -> ShowS
[NodeFSStats] -> ShowS
NodeFSStats -> String
(Int -> NodeFSStats -> ShowS)
-> (NodeFSStats -> String)
-> ([NodeFSStats] -> ShowS)
-> Show NodeFSStats
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NodeFSStats] -> ShowS
$cshowList :: [NodeFSStats] -> ShowS
show :: NodeFSStats -> String
$cshow :: NodeFSStats -> String
showsPrec :: Int -> NodeFSStats -> ShowS
$cshowsPrec :: Int -> NodeFSStats -> ShowS
Show)
data NodeDataPathStats = NodeDataPathStats {
NodeDataPathStats -> Maybe Double
nodeDataPathDiskServiceTime :: Maybe Double
, NodeDataPathStats -> Maybe Double
nodeDataPathDiskQueue :: Maybe Double
, NodeDataPathStats -> Maybe Bytes
nodeDataPathIOSize :: Maybe Bytes
, NodeDataPathStats -> Maybe Bytes
nodeDataPathWriteSize :: Maybe Bytes
, NodeDataPathStats -> Maybe Bytes
nodeDataPathReadSize :: Maybe Bytes
, NodeDataPathStats -> Maybe Int
nodeDataPathIOOps :: Maybe Int
, NodeDataPathStats -> Maybe Int
nodeDataPathWrites :: Maybe Int
, NodeDataPathStats -> Maybe Int
nodeDataPathReads :: Maybe Int
, NodeDataPathStats -> Bytes
nodeDataPathAvailable :: Bytes
, NodeDataPathStats -> Bytes
nodeDataPathFree :: Bytes
, NodeDataPathStats -> Bytes
nodeDataPathTotal :: Bytes
, NodeDataPathStats -> Maybe Text
nodeDataPathType :: Maybe Text
, NodeDataPathStats -> Maybe Text
nodeDataPathDevice :: Maybe Text
, NodeDataPathStats -> Text
nodeDataPathMount :: Text
, NodeDataPathStats -> Text
nodeDataPathPath :: Text
} deriving (NodeDataPathStats -> NodeDataPathStats -> Bool
(NodeDataPathStats -> NodeDataPathStats -> Bool)
-> (NodeDataPathStats -> NodeDataPathStats -> Bool)
-> Eq NodeDataPathStats
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NodeDataPathStats -> NodeDataPathStats -> Bool
$c/= :: NodeDataPathStats -> NodeDataPathStats -> Bool
== :: NodeDataPathStats -> NodeDataPathStats -> Bool
$c== :: NodeDataPathStats -> NodeDataPathStats -> Bool
Eq, Int -> NodeDataPathStats -> ShowS
[NodeDataPathStats] -> ShowS
NodeDataPathStats -> String
(Int -> NodeDataPathStats -> ShowS)
-> (NodeDataPathStats -> String)
-> ([NodeDataPathStats] -> ShowS)
-> Show NodeDataPathStats
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NodeDataPathStats] -> ShowS
$cshowList :: [NodeDataPathStats] -> ShowS
show :: NodeDataPathStats -> String
$cshow :: NodeDataPathStats -> String
showsPrec :: Int -> NodeDataPathStats -> ShowS
$cshowsPrec :: Int -> NodeDataPathStats -> ShowS
Show)
data NodeFSTotalStats = NodeFSTotalStats {
NodeFSTotalStats -> Maybe Double
nodeFSTotalDiskServiceTime :: Maybe Double
, NodeFSTotalStats -> Maybe Double
nodeFSTotalDiskQueue :: Maybe Double
, NodeFSTotalStats -> Maybe Bytes
nodeFSTotalIOSize :: Maybe Bytes
, NodeFSTotalStats -> Maybe Bytes
nodeFSTotalWriteSize :: Maybe Bytes
, NodeFSTotalStats -> Maybe Bytes
nodeFSTotalReadSize :: Maybe Bytes
, NodeFSTotalStats -> Maybe Int
nodeFSTotalIOOps :: Maybe Int
, NodeFSTotalStats -> Maybe Int
nodeFSTotalWrites :: Maybe Int
, NodeFSTotalStats -> Maybe Int
nodeFSTotalReads :: Maybe Int
, NodeFSTotalStats -> Bytes
nodeFSTotalAvailable :: Bytes
, NodeFSTotalStats -> Bytes
nodeFSTotalFree :: Bytes
, NodeFSTotalStats -> Bytes
nodeFSTotalTotal :: Bytes
} deriving (NodeFSTotalStats -> NodeFSTotalStats -> Bool
(NodeFSTotalStats -> NodeFSTotalStats -> Bool)
-> (NodeFSTotalStats -> NodeFSTotalStats -> Bool)
-> Eq NodeFSTotalStats
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NodeFSTotalStats -> NodeFSTotalStats -> Bool
$c/= :: NodeFSTotalStats -> NodeFSTotalStats -> Bool
== :: NodeFSTotalStats -> NodeFSTotalStats -> Bool
$c== :: NodeFSTotalStats -> NodeFSTotalStats -> Bool
Eq, Int -> NodeFSTotalStats -> ShowS
[NodeFSTotalStats] -> ShowS
NodeFSTotalStats -> String
(Int -> NodeFSTotalStats -> ShowS)
-> (NodeFSTotalStats -> String)
-> ([NodeFSTotalStats] -> ShowS)
-> Show NodeFSTotalStats
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NodeFSTotalStats] -> ShowS
$cshowList :: [NodeFSTotalStats] -> ShowS
show :: NodeFSTotalStats -> String
$cshow :: NodeFSTotalStats -> String
showsPrec :: Int -> NodeFSTotalStats -> ShowS
$cshowsPrec :: Int -> NodeFSTotalStats -> ShowS
Show)
data NodeNetworkStats = NodeNetworkStats {
NodeNetworkStats -> Int
nodeNetTCPOutRSTs :: Int
, NodeNetworkStats -> Int
nodeNetTCPInErrs :: Int
, NodeNetworkStats -> Int
nodeNetTCPAttemptFails :: Int
, NodeNetworkStats -> Int
nodeNetTCPEstabResets :: Int
, NodeNetworkStats -> Int
nodeNetTCPRetransSegs :: Int
, NodeNetworkStats -> Int
nodeNetTCPOutSegs :: Int
, NodeNetworkStats -> Int
nodeNetTCPInSegs :: Int
, NodeNetworkStats -> Int
nodeNetTCPCurrEstab :: Int
, NodeNetworkStats -> Int
nodeNetTCPPassiveOpens :: Int
, NodeNetworkStats -> Int
nodeNetTCPActiveOpens :: Int
} deriving (NodeNetworkStats -> NodeNetworkStats -> Bool
(NodeNetworkStats -> NodeNetworkStats -> Bool)
-> (NodeNetworkStats -> NodeNetworkStats -> Bool)
-> Eq NodeNetworkStats
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NodeNetworkStats -> NodeNetworkStats -> Bool
$c/= :: NodeNetworkStats -> NodeNetworkStats -> Bool
== :: NodeNetworkStats -> NodeNetworkStats -> Bool
$c== :: NodeNetworkStats -> NodeNetworkStats -> Bool
Eq, Int -> NodeNetworkStats -> ShowS
[NodeNetworkStats] -> ShowS
NodeNetworkStats -> String
(Int -> NodeNetworkStats -> ShowS)
-> (NodeNetworkStats -> String)
-> ([NodeNetworkStats] -> ShowS)
-> Show NodeNetworkStats
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NodeNetworkStats] -> ShowS
$cshowList :: [NodeNetworkStats] -> ShowS
show :: NodeNetworkStats -> String
$cshow :: NodeNetworkStats -> String
showsPrec :: Int -> NodeNetworkStats -> ShowS
$cshowsPrec :: Int -> NodeNetworkStats -> ShowS
Show)
data NodeThreadPoolStats = NodeThreadPoolStats {
NodeThreadPoolStats -> Int
nodeThreadPoolCompleted :: Int
, NodeThreadPoolStats -> Int
nodeThreadPoolLargest :: Int
, NodeThreadPoolStats -> Int
nodeThreadPoolRejected :: Int
, NodeThreadPoolStats -> Int
nodeThreadPoolActive :: Int
, NodeThreadPoolStats -> Int
nodeThreadPoolQueue :: Int
, NodeThreadPoolStats -> Int
nodeThreadPoolThreads :: Int
} deriving (NodeThreadPoolStats -> NodeThreadPoolStats -> Bool
(NodeThreadPoolStats -> NodeThreadPoolStats -> Bool)
-> (NodeThreadPoolStats -> NodeThreadPoolStats -> Bool)
-> Eq NodeThreadPoolStats
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NodeThreadPoolStats -> NodeThreadPoolStats -> Bool
$c/= :: NodeThreadPoolStats -> NodeThreadPoolStats -> Bool
== :: NodeThreadPoolStats -> NodeThreadPoolStats -> Bool
$c== :: NodeThreadPoolStats -> NodeThreadPoolStats -> Bool
Eq, Int -> NodeThreadPoolStats -> ShowS
[NodeThreadPoolStats] -> ShowS
NodeThreadPoolStats -> String
(Int -> NodeThreadPoolStats -> ShowS)
-> (NodeThreadPoolStats -> String)
-> ([NodeThreadPoolStats] -> ShowS)
-> Show NodeThreadPoolStats
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NodeThreadPoolStats] -> ShowS
$cshowList :: [NodeThreadPoolStats] -> ShowS
show :: NodeThreadPoolStats -> String
$cshow :: NodeThreadPoolStats -> String
showsPrec :: Int -> NodeThreadPoolStats -> ShowS
$cshowsPrec :: Int -> NodeThreadPoolStats -> ShowS
Show)
data NodeJVMStats = NodeJVMStats {
NodeJVMStats -> JVMBufferPoolStats
nodeJVMStatsMappedBufferPool :: JVMBufferPoolStats
, NodeJVMStats -> JVMBufferPoolStats
nodeJVMStatsDirectBufferPool :: JVMBufferPoolStats
, NodeJVMStats -> JVMGCStats
nodeJVMStatsGCOldCollector :: JVMGCStats
, NodeJVMStats -> JVMGCStats
nodeJVMStatsGCYoungCollector :: JVMGCStats
, NodeJVMStats -> Int
nodeJVMStatsPeakThreadsCount :: Int
, NodeJVMStats -> Int
nodeJVMStatsThreadsCount :: Int
, NodeJVMStats -> JVMPoolStats
nodeJVMStatsOldPool :: JVMPoolStats
, NodeJVMStats -> JVMPoolStats
nodeJVMStatsSurvivorPool :: JVMPoolStats
, NodeJVMStats -> JVMPoolStats
nodeJVMStatsYoungPool :: JVMPoolStats
, NodeJVMStats -> Bytes
nodeJVMStatsNonHeapCommitted :: Bytes
, NodeJVMStats -> Bytes
nodeJVMStatsNonHeapUsed :: Bytes
, NodeJVMStats -> Bytes
nodeJVMStatsHeapMax :: Bytes
, NodeJVMStats -> Bytes
nodeJVMStatsHeapCommitted :: Bytes
, NodeJVMStats -> Int
nodeJVMStatsHeapUsedPercent :: Int
, NodeJVMStats -> Bytes
nodeJVMStatsHeapUsed :: Bytes
, NodeJVMStats -> NominalDiffTime
nodeJVMStatsUptime :: NominalDiffTime
, NodeJVMStats -> UTCTime
nodeJVMStatsTimestamp :: UTCTime
} deriving (NodeJVMStats -> NodeJVMStats -> Bool
(NodeJVMStats -> NodeJVMStats -> Bool)
-> (NodeJVMStats -> NodeJVMStats -> Bool) -> Eq NodeJVMStats
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NodeJVMStats -> NodeJVMStats -> Bool
$c/= :: NodeJVMStats -> NodeJVMStats -> Bool
== :: NodeJVMStats -> NodeJVMStats -> Bool
$c== :: NodeJVMStats -> NodeJVMStats -> Bool
Eq, Int -> NodeJVMStats -> ShowS
[NodeJVMStats] -> ShowS
NodeJVMStats -> String
(Int -> NodeJVMStats -> ShowS)
-> (NodeJVMStats -> String)
-> ([NodeJVMStats] -> ShowS)
-> Show NodeJVMStats
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NodeJVMStats] -> ShowS
$cshowList :: [NodeJVMStats] -> ShowS
show :: NodeJVMStats -> String
$cshow :: NodeJVMStats -> String
showsPrec :: Int -> NodeJVMStats -> ShowS
$cshowsPrec :: Int -> NodeJVMStats -> ShowS
Show)
data JVMBufferPoolStats = JVMBufferPoolStats {
JVMBufferPoolStats -> Bytes
jvmBufferPoolStatsTotalCapacity :: Bytes
, JVMBufferPoolStats -> Bytes
jvmBufferPoolStatsUsed :: Bytes
, JVMBufferPoolStats -> Int
jvmBufferPoolStatsCount :: Int
} deriving (JVMBufferPoolStats -> JVMBufferPoolStats -> Bool
(JVMBufferPoolStats -> JVMBufferPoolStats -> Bool)
-> (JVMBufferPoolStats -> JVMBufferPoolStats -> Bool)
-> Eq JVMBufferPoolStats
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: JVMBufferPoolStats -> JVMBufferPoolStats -> Bool
$c/= :: JVMBufferPoolStats -> JVMBufferPoolStats -> Bool
== :: JVMBufferPoolStats -> JVMBufferPoolStats -> Bool
$c== :: JVMBufferPoolStats -> JVMBufferPoolStats -> Bool
Eq, Int -> JVMBufferPoolStats -> ShowS
[JVMBufferPoolStats] -> ShowS
JVMBufferPoolStats -> String
(Int -> JVMBufferPoolStats -> ShowS)
-> (JVMBufferPoolStats -> String)
-> ([JVMBufferPoolStats] -> ShowS)
-> Show JVMBufferPoolStats
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [JVMBufferPoolStats] -> ShowS
$cshowList :: [JVMBufferPoolStats] -> ShowS
show :: JVMBufferPoolStats -> String
$cshow :: JVMBufferPoolStats -> String
showsPrec :: Int -> JVMBufferPoolStats -> ShowS
$cshowsPrec :: Int -> JVMBufferPoolStats -> ShowS
Show)
data JVMGCStats = JVMGCStats {
JVMGCStats -> NominalDiffTime
jvmGCStatsCollectionTime :: NominalDiffTime
, JVMGCStats -> Int
jvmGCStatsCollectionCount :: Int
} deriving (JVMGCStats -> JVMGCStats -> Bool
(JVMGCStats -> JVMGCStats -> Bool)
-> (JVMGCStats -> JVMGCStats -> Bool) -> Eq JVMGCStats
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: JVMGCStats -> JVMGCStats -> Bool
$c/= :: JVMGCStats -> JVMGCStats -> Bool
== :: JVMGCStats -> JVMGCStats -> Bool
$c== :: JVMGCStats -> JVMGCStats -> Bool
Eq, Int -> JVMGCStats -> ShowS
[JVMGCStats] -> ShowS
JVMGCStats -> String
(Int -> JVMGCStats -> ShowS)
-> (JVMGCStats -> String)
-> ([JVMGCStats] -> ShowS)
-> Show JVMGCStats
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [JVMGCStats] -> ShowS
$cshowList :: [JVMGCStats] -> ShowS
show :: JVMGCStats -> String
$cshow :: JVMGCStats -> String
showsPrec :: Int -> JVMGCStats -> ShowS
$cshowsPrec :: Int -> JVMGCStats -> ShowS
Show)
data JVMPoolStats = JVMPoolStats {
JVMPoolStats -> Bytes
jvmPoolStatsPeakMax :: Bytes
, JVMPoolStats -> Bytes
jvmPoolStatsPeakUsed :: Bytes
, JVMPoolStats -> Bytes
jvmPoolStatsMax :: Bytes
, JVMPoolStats -> Bytes
jvmPoolStatsUsed :: Bytes
} deriving (JVMPoolStats -> JVMPoolStats -> Bool
(JVMPoolStats -> JVMPoolStats -> Bool)
-> (JVMPoolStats -> JVMPoolStats -> Bool) -> Eq JVMPoolStats
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: JVMPoolStats -> JVMPoolStats -> Bool
$c/= :: JVMPoolStats -> JVMPoolStats -> Bool
== :: JVMPoolStats -> JVMPoolStats -> Bool
$c== :: JVMPoolStats -> JVMPoolStats -> Bool
Eq, Int -> JVMPoolStats -> ShowS
[JVMPoolStats] -> ShowS
JVMPoolStats -> String
(Int -> JVMPoolStats -> ShowS)
-> (JVMPoolStats -> String)
-> ([JVMPoolStats] -> ShowS)
-> Show JVMPoolStats
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [JVMPoolStats] -> ShowS
$cshowList :: [JVMPoolStats] -> ShowS
show :: JVMPoolStats -> String
$cshow :: JVMPoolStats -> String
showsPrec :: Int -> JVMPoolStats -> ShowS
$cshowsPrec :: Int -> JVMPoolStats -> ShowS
Show)
data NodeProcessStats = NodeProcessStats {
NodeProcessStats -> UTCTime
nodeProcessTimestamp :: UTCTime
, NodeProcessStats -> Int
nodeProcessOpenFDs :: Int
, NodeProcessStats -> Int
nodeProcessMaxFDs :: Int
, NodeProcessStats -> Int
nodeProcessCPUPercent :: Int
, NodeProcessStats -> NominalDiffTime
nodeProcessCPUTotal :: NominalDiffTime
, NodeProcessStats -> Bytes
nodeProcessMemTotalVirtual :: Bytes
} deriving (NodeProcessStats -> NodeProcessStats -> Bool
(NodeProcessStats -> NodeProcessStats -> Bool)
-> (NodeProcessStats -> NodeProcessStats -> Bool)
-> Eq NodeProcessStats
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NodeProcessStats -> NodeProcessStats -> Bool
$c/= :: NodeProcessStats -> NodeProcessStats -> Bool
== :: NodeProcessStats -> NodeProcessStats -> Bool
$c== :: NodeProcessStats -> NodeProcessStats -> Bool
Eq, Int -> NodeProcessStats -> ShowS
[NodeProcessStats] -> ShowS
NodeProcessStats -> String
(Int -> NodeProcessStats -> ShowS)
-> (NodeProcessStats -> String)
-> ([NodeProcessStats] -> ShowS)
-> Show NodeProcessStats
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NodeProcessStats] -> ShowS
$cshowList :: [NodeProcessStats] -> ShowS
show :: NodeProcessStats -> String
$cshow :: NodeProcessStats -> String
showsPrec :: Int -> NodeProcessStats -> ShowS
$cshowsPrec :: Int -> NodeProcessStats -> ShowS
Show)
data NodeOSStats = NodeOSStats {
NodeOSStats -> UTCTime
nodeOSTimestamp :: UTCTime
, NodeOSStats -> Int
nodeOSCPUPercent :: Int
, NodeOSStats -> Maybe LoadAvgs
nodeOSLoad :: Maybe LoadAvgs
, NodeOSStats -> Bytes
nodeOSMemTotal :: Bytes
, NodeOSStats -> Bytes
nodeOSMemFree :: Bytes
, NodeOSStats -> Int
nodeOSMemFreePercent :: Int
, NodeOSStats -> Bytes
nodeOSMemUsed :: Bytes
, NodeOSStats -> Int
nodeOSMemUsedPercent :: Int
, NodeOSStats -> Bytes
nodeOSSwapTotal :: Bytes
, NodeOSStats -> Bytes
nodeOSSwapFree :: Bytes
, NodeOSStats -> Bytes
nodeOSSwapUsed :: Bytes
} deriving (NodeOSStats -> NodeOSStats -> Bool
(NodeOSStats -> NodeOSStats -> Bool)
-> (NodeOSStats -> NodeOSStats -> Bool) -> Eq NodeOSStats
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NodeOSStats -> NodeOSStats -> Bool
$c/= :: NodeOSStats -> NodeOSStats -> Bool
== :: NodeOSStats -> NodeOSStats -> Bool
$c== :: NodeOSStats -> NodeOSStats -> Bool
Eq, Int -> NodeOSStats -> ShowS
[NodeOSStats] -> ShowS
NodeOSStats -> String
(Int -> NodeOSStats -> ShowS)
-> (NodeOSStats -> String)
-> ([NodeOSStats] -> ShowS)
-> Show NodeOSStats
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NodeOSStats] -> ShowS
$cshowList :: [NodeOSStats] -> ShowS
show :: NodeOSStats -> String
$cshow :: NodeOSStats -> String
showsPrec :: Int -> NodeOSStats -> ShowS
$cshowsPrec :: Int -> NodeOSStats -> ShowS
Show)
data LoadAvgs = LoadAvgs {
LoadAvgs -> Double
loadAvg1Min :: Double
, LoadAvgs -> Double
loadAvg5Min :: Double
, LoadAvgs -> Double
loadAvg15Min :: Double
} deriving (LoadAvgs -> LoadAvgs -> Bool
(LoadAvgs -> LoadAvgs -> Bool)
-> (LoadAvgs -> LoadAvgs -> Bool) -> Eq LoadAvgs
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LoadAvgs -> LoadAvgs -> Bool
$c/= :: LoadAvgs -> LoadAvgs -> Bool
== :: LoadAvgs -> LoadAvgs -> Bool
$c== :: LoadAvgs -> LoadAvgs -> Bool
Eq, Int -> LoadAvgs -> ShowS
[LoadAvgs] -> ShowS
LoadAvgs -> String
(Int -> LoadAvgs -> ShowS)
-> (LoadAvgs -> String) -> ([LoadAvgs] -> ShowS) -> Show LoadAvgs
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LoadAvgs] -> ShowS
$cshowList :: [LoadAvgs] -> ShowS
show :: LoadAvgs -> String
$cshow :: LoadAvgs -> String
showsPrec :: Int -> LoadAvgs -> ShowS
$cshowsPrec :: Int -> LoadAvgs -> ShowS
Show)
data NodeIndicesStats = NodeIndicesStats {
NodeIndicesStats -> Maybe NominalDiffTime
nodeIndicesStatsRecoveryThrottleTime :: Maybe NominalDiffTime
, NodeIndicesStats -> Maybe Int
nodeIndicesStatsRecoveryCurrentAsTarget :: Maybe Int
, NodeIndicesStats -> Maybe Int
nodeIndicesStatsRecoveryCurrentAsSource :: Maybe Int
, NodeIndicesStats -> Maybe Int
nodeIndicesStatsQueryCacheMisses :: Maybe Int
, NodeIndicesStats -> Maybe Int
nodeIndicesStatsQueryCacheHits :: Maybe Int
, NodeIndicesStats -> Maybe Int
nodeIndicesStatsQueryCacheEvictions :: Maybe Int
, NodeIndicesStats -> Maybe Bytes
nodeIndicesStatsQueryCacheSize :: Maybe Bytes
, NodeIndicesStats -> Maybe Int
nodeIndicesStatsSuggestCurrent :: Maybe Int
, NodeIndicesStats -> Maybe NominalDiffTime
nodeIndicesStatsSuggestTime :: Maybe NominalDiffTime
, NodeIndicesStats -> Maybe Int
nodeIndicesStatsSuggestTotal :: Maybe Int
, NodeIndicesStats -> Bytes
nodeIndicesStatsTranslogSize :: Bytes
, NodeIndicesStats -> Int
nodeIndicesStatsTranslogOps :: Int
, NodeIndicesStats -> Maybe Bytes
nodeIndicesStatsSegFixedBitSetMemory :: Maybe Bytes
, NodeIndicesStats -> Bytes
nodeIndicesStatsSegVersionMapMemory :: Bytes
, NodeIndicesStats -> Maybe Bytes
nodeIndicesStatsSegIndexWriterMaxMemory :: Maybe Bytes
, NodeIndicesStats -> Bytes
nodeIndicesStatsSegIndexWriterMemory :: Bytes
, NodeIndicesStats -> Bytes
nodeIndicesStatsSegMemory :: Bytes
, NodeIndicesStats -> Int
nodeIndicesStatsSegCount :: Int
, NodeIndicesStats -> Bytes
nodeIndicesStatsCompletionSize :: Bytes
, NodeIndicesStats -> Maybe Int
nodeIndicesStatsPercolateQueries :: Maybe Int
, NodeIndicesStats -> Maybe Bytes
nodeIndicesStatsPercolateMemory :: Maybe Bytes
, NodeIndicesStats -> Maybe Int
nodeIndicesStatsPercolateCurrent :: Maybe Int
, NodeIndicesStats -> Maybe NominalDiffTime
nodeIndicesStatsPercolateTime :: Maybe NominalDiffTime
, NodeIndicesStats -> Maybe Int
nodeIndicesStatsPercolateTotal :: Maybe Int
, NodeIndicesStats -> Int
nodeIndicesStatsFieldDataEvictions :: Int
, NodeIndicesStats -> Bytes
nodeIndicesStatsFieldDataMemory :: Bytes
, NodeIndicesStats -> NominalDiffTime
nodeIndicesStatsWarmerTotalTime :: NominalDiffTime
, NodeIndicesStats -> Int
nodeIndicesStatsWarmerTotal :: Int
, NodeIndicesStats -> Int
nodeIndicesStatsWarmerCurrent :: Int
, NodeIndicesStats -> NominalDiffTime
nodeIndicesStatsFlushTotalTime :: NominalDiffTime
, NodeIndicesStats -> Int
nodeIndicesStatsFlushTotal :: Int
, NodeIndicesStats -> NominalDiffTime
nodeIndicesStatsRefreshTotalTime :: NominalDiffTime
, NodeIndicesStats -> Int
nodeIndicesStatsRefreshTotal :: Int
, NodeIndicesStats -> Bytes
nodeIndicesStatsMergesTotalSize :: Bytes
, NodeIndicesStats -> Int
nodeIndicesStatsMergesTotalDocs :: Int
, NodeIndicesStats -> NominalDiffTime
nodeIndicesStatsMergesTotalTime :: NominalDiffTime
, NodeIndicesStats -> Int
nodeIndicesStatsMergesTotal :: Int
, NodeIndicesStats -> Bytes
nodeIndicesStatsMergesCurrentSize :: Bytes
, NodeIndicesStats -> Int
nodeIndicesStatsMergesCurrentDocs :: Int
, NodeIndicesStats -> Int
nodeIndicesStatsMergesCurrent :: Int
, NodeIndicesStats -> Int
nodeIndicesStatsSearchFetchCurrent :: Int
, NodeIndicesStats -> NominalDiffTime
nodeIndicesStatsSearchFetchTime :: NominalDiffTime
, NodeIndicesStats -> Int
nodeIndicesStatsSearchFetchTotal :: Int
, NodeIndicesStats -> Int
nodeIndicesStatsSearchQueryCurrent :: Int
, NodeIndicesStats -> NominalDiffTime
nodeIndicesStatsSearchQueryTime :: NominalDiffTime
, NodeIndicesStats -> Int
nodeIndicesStatsSearchQueryTotal :: Int
, NodeIndicesStats -> Int
nodeIndicesStatsSearchOpenContexts :: Int
, NodeIndicesStats -> Int
nodeIndicesStatsGetCurrent :: Int
, NodeIndicesStats -> NominalDiffTime
nodeIndicesStatsGetMissingTime :: NominalDiffTime
, NodeIndicesStats -> Int
nodeIndicesStatsGetMissingTotal :: Int
, NodeIndicesStats -> NominalDiffTime
nodeIndicesStatsGetExistsTime :: NominalDiffTime
, NodeIndicesStats -> Int
nodeIndicesStatsGetExistsTotal :: Int
, NodeIndicesStats -> NominalDiffTime
nodeIndicesStatsGetTime :: NominalDiffTime
, NodeIndicesStats -> Int
nodeIndicesStatsGetTotal :: Int
, NodeIndicesStats -> Maybe NominalDiffTime
nodeIndicesStatsIndexingThrottleTime :: Maybe NominalDiffTime
, NodeIndicesStats -> Maybe Bool
nodeIndicesStatsIndexingIsThrottled :: Maybe Bool
, NodeIndicesStats -> Maybe Int
nodeIndicesStatsIndexingNoopUpdateTotal :: Maybe Int
, NodeIndicesStats -> Int
nodeIndicesStatsIndexingDeleteCurrent :: Int
, NodeIndicesStats -> NominalDiffTime
nodeIndicesStatsIndexingDeleteTime :: NominalDiffTime
, NodeIndicesStats -> Int
nodeIndicesStatsIndexingDeleteTotal :: Int
, NodeIndicesStats -> Int
nodeIndicesStatsIndexingIndexCurrent :: Int
, NodeIndicesStats -> NominalDiffTime
nodeIndicesStatsIndexingIndexTime :: NominalDiffTime
, NodeIndicesStats -> Int
nodeIndicesStatsIndexingTotal :: Int
, NodeIndicesStats -> Maybe NominalDiffTime
nodeIndicesStatsStoreThrottleTime :: Maybe NominalDiffTime
, NodeIndicesStats -> Bytes
nodeIndicesStatsStoreSize :: Bytes
, NodeIndicesStats -> Int
nodeIndicesStatsDocsDeleted :: Int
, NodeIndicesStats -> Int
nodeIndicesStatsDocsCount :: Int
} deriving (NodeIndicesStats -> NodeIndicesStats -> Bool
(NodeIndicesStats -> NodeIndicesStats -> Bool)
-> (NodeIndicesStats -> NodeIndicesStats -> Bool)
-> Eq NodeIndicesStats
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NodeIndicesStats -> NodeIndicesStats -> Bool
$c/= :: NodeIndicesStats -> NodeIndicesStats -> Bool
== :: NodeIndicesStats -> NodeIndicesStats -> Bool
$c== :: NodeIndicesStats -> NodeIndicesStats -> Bool
Eq, Int -> NodeIndicesStats -> ShowS
[NodeIndicesStats] -> ShowS
NodeIndicesStats -> String
(Int -> NodeIndicesStats -> ShowS)
-> (NodeIndicesStats -> String)
-> ([NodeIndicesStats] -> ShowS)
-> Show NodeIndicesStats
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NodeIndicesStats] -> ShowS
$cshowList :: [NodeIndicesStats] -> ShowS
show :: NodeIndicesStats -> String
$cshow :: NodeIndicesStats -> String
showsPrec :: Int -> NodeIndicesStats -> ShowS
$cshowsPrec :: Int -> NodeIndicesStats -> ShowS
Show)
newtype EsAddress = EsAddress { EsAddress -> Text
esAddress :: Text }
deriving (EsAddress -> EsAddress -> Bool
(EsAddress -> EsAddress -> Bool)
-> (EsAddress -> EsAddress -> Bool) -> Eq EsAddress
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EsAddress -> EsAddress -> Bool
$c/= :: EsAddress -> EsAddress -> Bool
== :: EsAddress -> EsAddress -> Bool
$c== :: EsAddress -> EsAddress -> Bool
Eq, Eq EsAddress
Eq EsAddress
-> (EsAddress -> EsAddress -> Ordering)
-> (EsAddress -> EsAddress -> Bool)
-> (EsAddress -> EsAddress -> Bool)
-> (EsAddress -> EsAddress -> Bool)
-> (EsAddress -> EsAddress -> Bool)
-> (EsAddress -> EsAddress -> EsAddress)
-> (EsAddress -> EsAddress -> EsAddress)
-> Ord EsAddress
EsAddress -> EsAddress -> Bool
EsAddress -> EsAddress -> Ordering
EsAddress -> EsAddress -> EsAddress
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 :: EsAddress -> EsAddress -> EsAddress
$cmin :: EsAddress -> EsAddress -> EsAddress
max :: EsAddress -> EsAddress -> EsAddress
$cmax :: EsAddress -> EsAddress -> EsAddress
>= :: EsAddress -> EsAddress -> Bool
$c>= :: EsAddress -> EsAddress -> Bool
> :: EsAddress -> EsAddress -> Bool
$c> :: EsAddress -> EsAddress -> Bool
<= :: EsAddress -> EsAddress -> Bool
$c<= :: EsAddress -> EsAddress -> Bool
< :: EsAddress -> EsAddress -> Bool
$c< :: EsAddress -> EsAddress -> Bool
compare :: EsAddress -> EsAddress -> Ordering
$ccompare :: EsAddress -> EsAddress -> Ordering
$cp1Ord :: Eq EsAddress
Ord, Int -> EsAddress -> ShowS
[EsAddress] -> ShowS
EsAddress -> String
(Int -> EsAddress -> ShowS)
-> (EsAddress -> String)
-> ([EsAddress] -> ShowS)
-> Show EsAddress
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EsAddress] -> ShowS
$cshowList :: [EsAddress] -> ShowS
show :: EsAddress -> String
$cshow :: EsAddress -> String
showsPrec :: Int -> EsAddress -> ShowS
$cshowsPrec :: Int -> EsAddress -> ShowS
Show, Value -> Parser [EsAddress]
Value -> Parser EsAddress
(Value -> Parser EsAddress)
-> (Value -> Parser [EsAddress]) -> FromJSON EsAddress
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [EsAddress]
$cparseJSONList :: Value -> Parser [EsAddress]
parseJSON :: Value -> Parser EsAddress
$cparseJSON :: Value -> Parser EsAddress
FromJSON)
newtype BuildHash = BuildHash { BuildHash -> Text
buildHash :: Text }
deriving (BuildHash -> BuildHash -> Bool
(BuildHash -> BuildHash -> Bool)
-> (BuildHash -> BuildHash -> Bool) -> Eq BuildHash
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BuildHash -> BuildHash -> Bool
$c/= :: BuildHash -> BuildHash -> Bool
== :: BuildHash -> BuildHash -> Bool
$c== :: BuildHash -> BuildHash -> Bool
Eq, Eq BuildHash
Eq BuildHash
-> (BuildHash -> BuildHash -> Ordering)
-> (BuildHash -> BuildHash -> Bool)
-> (BuildHash -> BuildHash -> Bool)
-> (BuildHash -> BuildHash -> Bool)
-> (BuildHash -> BuildHash -> Bool)
-> (BuildHash -> BuildHash -> BuildHash)
-> (BuildHash -> BuildHash -> BuildHash)
-> Ord BuildHash
BuildHash -> BuildHash -> Bool
BuildHash -> BuildHash -> Ordering
BuildHash -> BuildHash -> BuildHash
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 :: BuildHash -> BuildHash -> BuildHash
$cmin :: BuildHash -> BuildHash -> BuildHash
max :: BuildHash -> BuildHash -> BuildHash
$cmax :: BuildHash -> BuildHash -> BuildHash
>= :: BuildHash -> BuildHash -> Bool
$c>= :: BuildHash -> BuildHash -> Bool
> :: BuildHash -> BuildHash -> Bool
$c> :: BuildHash -> BuildHash -> Bool
<= :: BuildHash -> BuildHash -> Bool
$c<= :: BuildHash -> BuildHash -> Bool
< :: BuildHash -> BuildHash -> Bool
$c< :: BuildHash -> BuildHash -> Bool
compare :: BuildHash -> BuildHash -> Ordering
$ccompare :: BuildHash -> BuildHash -> Ordering
$cp1Ord :: Eq BuildHash
Ord, Int -> BuildHash -> ShowS
[BuildHash] -> ShowS
BuildHash -> String
(Int -> BuildHash -> ShowS)
-> (BuildHash -> String)
-> ([BuildHash] -> ShowS)
-> Show BuildHash
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BuildHash] -> ShowS
$cshowList :: [BuildHash] -> ShowS
show :: BuildHash -> String
$cshow :: BuildHash -> String
showsPrec :: Int -> BuildHash -> ShowS
$cshowsPrec :: Int -> BuildHash -> ShowS
Show, Value -> Parser [BuildHash]
Value -> Parser BuildHash
(Value -> Parser BuildHash)
-> (Value -> Parser [BuildHash]) -> FromJSON BuildHash
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [BuildHash]
$cparseJSONList :: Value -> Parser [BuildHash]
parseJSON :: Value -> Parser BuildHash
$cparseJSON :: Value -> Parser BuildHash
FromJSON, [BuildHash] -> Encoding
[BuildHash] -> Value
BuildHash -> Encoding
BuildHash -> Value
(BuildHash -> Value)
-> (BuildHash -> Encoding)
-> ([BuildHash] -> Value)
-> ([BuildHash] -> Encoding)
-> ToJSON BuildHash
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [BuildHash] -> Encoding
$ctoEncodingList :: [BuildHash] -> Encoding
toJSONList :: [BuildHash] -> Value
$ctoJSONList :: [BuildHash] -> Value
toEncoding :: BuildHash -> Encoding
$ctoEncoding :: BuildHash -> Encoding
toJSON :: BuildHash -> Value
$ctoJSON :: BuildHash -> Value
ToJSON)
newtype PluginName = PluginName { PluginName -> Text
pluginName :: Text }
deriving (PluginName -> PluginName -> Bool
(PluginName -> PluginName -> Bool)
-> (PluginName -> PluginName -> Bool) -> Eq PluginName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PluginName -> PluginName -> Bool
$c/= :: PluginName -> PluginName -> Bool
== :: PluginName -> PluginName -> Bool
$c== :: PluginName -> PluginName -> Bool
Eq, Eq PluginName
Eq PluginName
-> (PluginName -> PluginName -> Ordering)
-> (PluginName -> PluginName -> Bool)
-> (PluginName -> PluginName -> Bool)
-> (PluginName -> PluginName -> Bool)
-> (PluginName -> PluginName -> Bool)
-> (PluginName -> PluginName -> PluginName)
-> (PluginName -> PluginName -> PluginName)
-> Ord PluginName
PluginName -> PluginName -> Bool
PluginName -> PluginName -> Ordering
PluginName -> PluginName -> PluginName
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 :: PluginName -> PluginName -> PluginName
$cmin :: PluginName -> PluginName -> PluginName
max :: PluginName -> PluginName -> PluginName
$cmax :: PluginName -> PluginName -> PluginName
>= :: PluginName -> PluginName -> Bool
$c>= :: PluginName -> PluginName -> Bool
> :: PluginName -> PluginName -> Bool
$c> :: PluginName -> PluginName -> Bool
<= :: PluginName -> PluginName -> Bool
$c<= :: PluginName -> PluginName -> Bool
< :: PluginName -> PluginName -> Bool
$c< :: PluginName -> PluginName -> Bool
compare :: PluginName -> PluginName -> Ordering
$ccompare :: PluginName -> PluginName -> Ordering
$cp1Ord :: Eq PluginName
Ord, Int -> PluginName -> ShowS
[PluginName] -> ShowS
PluginName -> String
(Int -> PluginName -> ShowS)
-> (PluginName -> String)
-> ([PluginName] -> ShowS)
-> Show PluginName
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PluginName] -> ShowS
$cshowList :: [PluginName] -> ShowS
show :: PluginName -> String
$cshow :: PluginName -> String
showsPrec :: Int -> PluginName -> ShowS
$cshowsPrec :: Int -> PluginName -> ShowS
Show, Value -> Parser [PluginName]
Value -> Parser PluginName
(Value -> Parser PluginName)
-> (Value -> Parser [PluginName]) -> FromJSON PluginName
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [PluginName]
$cparseJSONList :: Value -> Parser [PluginName]
parseJSON :: Value -> Parser PluginName
$cparseJSON :: Value -> Parser PluginName
FromJSON)
data NodeInfo = NodeInfo {
NodeInfo -> Maybe EsAddress
nodeInfoHTTPAddress :: Maybe EsAddress
, NodeInfo -> BuildHash
nodeInfoBuild :: BuildHash
, NodeInfo -> VersionNumber
nodeInfoESVersion :: VersionNumber
, NodeInfo -> Server
nodeInfoIP :: Server
, NodeInfo -> Server
nodeInfoHost :: Server
, NodeInfo -> EsAddress
nodeInfoTransportAddress :: EsAddress
, NodeInfo -> NodeName
nodeInfoName :: NodeName
, NodeInfo -> FullNodeId
nodeInfoFullId :: FullNodeId
, NodeInfo -> [NodePluginInfo]
nodeInfoPlugins :: [NodePluginInfo]
, NodeInfo -> NodeHTTPInfo
nodeInfoHTTP :: NodeHTTPInfo
, NodeInfo -> NodeTransportInfo
nodeInfoTransport :: NodeTransportInfo
, NodeInfo -> Maybe NodeNetworkInfo
nodeInfoNetwork :: Maybe NodeNetworkInfo
, NodeInfo -> Map Text NodeThreadPoolInfo
nodeInfoThreadPool :: Map Text NodeThreadPoolInfo
, NodeInfo -> NodeJVMInfo
nodeInfoJVM :: NodeJVMInfo
, NodeInfo -> NodeProcessInfo
nodeInfoProcess :: NodeProcessInfo
, NodeInfo -> NodeOSInfo
nodeInfoOS :: NodeOSInfo
, NodeInfo -> Object
nodeInfoSettings :: Object
} deriving (NodeInfo -> NodeInfo -> Bool
(NodeInfo -> NodeInfo -> Bool)
-> (NodeInfo -> NodeInfo -> Bool) -> Eq NodeInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NodeInfo -> NodeInfo -> Bool
$c/= :: NodeInfo -> NodeInfo -> Bool
== :: NodeInfo -> NodeInfo -> Bool
$c== :: NodeInfo -> NodeInfo -> Bool
Eq, Int -> NodeInfo -> ShowS
[NodeInfo] -> ShowS
NodeInfo -> String
(Int -> NodeInfo -> ShowS)
-> (NodeInfo -> String) -> ([NodeInfo] -> ShowS) -> Show NodeInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NodeInfo] -> ShowS
$cshowList :: [NodeInfo] -> ShowS
show :: NodeInfo -> String
$cshow :: NodeInfo -> String
showsPrec :: Int -> NodeInfo -> ShowS
$cshowsPrec :: Int -> NodeInfo -> ShowS
Show)
data NodePluginInfo = NodePluginInfo {
NodePluginInfo -> Maybe Bool
nodePluginSite :: Maybe Bool
, NodePluginInfo -> Maybe Bool
nodePluginJVM :: Maybe Bool
, NodePluginInfo -> Text
nodePluginDescription :: Text
, NodePluginInfo -> MaybeNA VersionNumber
nodePluginVersion :: MaybeNA VersionNumber
, NodePluginInfo -> PluginName
nodePluginName :: PluginName
} deriving (NodePluginInfo -> NodePluginInfo -> Bool
(NodePluginInfo -> NodePluginInfo -> Bool)
-> (NodePluginInfo -> NodePluginInfo -> Bool) -> Eq NodePluginInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NodePluginInfo -> NodePluginInfo -> Bool
$c/= :: NodePluginInfo -> NodePluginInfo -> Bool
== :: NodePluginInfo -> NodePluginInfo -> Bool
$c== :: NodePluginInfo -> NodePluginInfo -> Bool
Eq, Int -> NodePluginInfo -> ShowS
[NodePluginInfo] -> ShowS
NodePluginInfo -> String
(Int -> NodePluginInfo -> ShowS)
-> (NodePluginInfo -> String)
-> ([NodePluginInfo] -> ShowS)
-> Show NodePluginInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NodePluginInfo] -> ShowS
$cshowList :: [NodePluginInfo] -> ShowS
show :: NodePluginInfo -> String
$cshow :: NodePluginInfo -> String
showsPrec :: Int -> NodePluginInfo -> ShowS
$cshowsPrec :: Int -> NodePluginInfo -> ShowS
Show)
data NodeHTTPInfo = NodeHTTPInfo {
NodeHTTPInfo -> Bytes
nodeHTTPMaxContentLength :: Bytes
, NodeHTTPInfo -> EsAddress
nodeHTTPpublishAddress :: EsAddress
, NodeHTTPInfo -> [EsAddress]
nodeHTTPbound_address :: [EsAddress]
} deriving (NodeHTTPInfo -> NodeHTTPInfo -> Bool
(NodeHTTPInfo -> NodeHTTPInfo -> Bool)
-> (NodeHTTPInfo -> NodeHTTPInfo -> Bool) -> Eq NodeHTTPInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NodeHTTPInfo -> NodeHTTPInfo -> Bool
$c/= :: NodeHTTPInfo -> NodeHTTPInfo -> Bool
== :: NodeHTTPInfo -> NodeHTTPInfo -> Bool
$c== :: NodeHTTPInfo -> NodeHTTPInfo -> Bool
Eq, Int -> NodeHTTPInfo -> ShowS
[NodeHTTPInfo] -> ShowS
NodeHTTPInfo -> String
(Int -> NodeHTTPInfo -> ShowS)
-> (NodeHTTPInfo -> String)
-> ([NodeHTTPInfo] -> ShowS)
-> Show NodeHTTPInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NodeHTTPInfo] -> ShowS
$cshowList :: [NodeHTTPInfo] -> ShowS
show :: NodeHTTPInfo -> String
$cshow :: NodeHTTPInfo -> String
showsPrec :: Int -> NodeHTTPInfo -> ShowS
$cshowsPrec :: Int -> NodeHTTPInfo -> ShowS
Show)
data NodeTransportInfo = NodeTransportInfo {
NodeTransportInfo -> [BoundTransportAddress]
nodeTransportProfiles :: [BoundTransportAddress]
, NodeTransportInfo -> EsAddress
nodeTransportPublishAddress :: EsAddress
, NodeTransportInfo -> [EsAddress]
nodeTransportBoundAddress :: [EsAddress]
} deriving (NodeTransportInfo -> NodeTransportInfo -> Bool
(NodeTransportInfo -> NodeTransportInfo -> Bool)
-> (NodeTransportInfo -> NodeTransportInfo -> Bool)
-> Eq NodeTransportInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NodeTransportInfo -> NodeTransportInfo -> Bool
$c/= :: NodeTransportInfo -> NodeTransportInfo -> Bool
== :: NodeTransportInfo -> NodeTransportInfo -> Bool
$c== :: NodeTransportInfo -> NodeTransportInfo -> Bool
Eq, Int -> NodeTransportInfo -> ShowS
[NodeTransportInfo] -> ShowS
NodeTransportInfo -> String
(Int -> NodeTransportInfo -> ShowS)
-> (NodeTransportInfo -> String)
-> ([NodeTransportInfo] -> ShowS)
-> Show NodeTransportInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NodeTransportInfo] -> ShowS
$cshowList :: [NodeTransportInfo] -> ShowS
show :: NodeTransportInfo -> String
$cshow :: NodeTransportInfo -> String
showsPrec :: Int -> NodeTransportInfo -> ShowS
$cshowsPrec :: Int -> NodeTransportInfo -> ShowS
Show)
data BoundTransportAddress = BoundTransportAddress {
BoundTransportAddress -> EsAddress
publishAddress :: EsAddress
, BoundTransportAddress -> [EsAddress]
boundAddress :: [EsAddress]
} deriving (BoundTransportAddress -> BoundTransportAddress -> Bool
(BoundTransportAddress -> BoundTransportAddress -> Bool)
-> (BoundTransportAddress -> BoundTransportAddress -> Bool)
-> Eq BoundTransportAddress
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BoundTransportAddress -> BoundTransportAddress -> Bool
$c/= :: BoundTransportAddress -> BoundTransportAddress -> Bool
== :: BoundTransportAddress -> BoundTransportAddress -> Bool
$c== :: BoundTransportAddress -> BoundTransportAddress -> Bool
Eq, Int -> BoundTransportAddress -> ShowS
[BoundTransportAddress] -> ShowS
BoundTransportAddress -> String
(Int -> BoundTransportAddress -> ShowS)
-> (BoundTransportAddress -> String)
-> ([BoundTransportAddress] -> ShowS)
-> Show BoundTransportAddress
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BoundTransportAddress] -> ShowS
$cshowList :: [BoundTransportAddress] -> ShowS
show :: BoundTransportAddress -> String
$cshow :: BoundTransportAddress -> String
showsPrec :: Int -> BoundTransportAddress -> ShowS
$cshowsPrec :: Int -> BoundTransportAddress -> ShowS
Show)
data NodeNetworkInfo = NodeNetworkInfo {
NodeNetworkInfo -> NodeNetworkInterface
nodeNetworkPrimaryInterface :: NodeNetworkInterface
, NodeNetworkInfo -> NominalDiffTime
nodeNetworkRefreshInterval :: NominalDiffTime
} deriving (NodeNetworkInfo -> NodeNetworkInfo -> Bool
(NodeNetworkInfo -> NodeNetworkInfo -> Bool)
-> (NodeNetworkInfo -> NodeNetworkInfo -> Bool)
-> Eq NodeNetworkInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NodeNetworkInfo -> NodeNetworkInfo -> Bool
$c/= :: NodeNetworkInfo -> NodeNetworkInfo -> Bool
== :: NodeNetworkInfo -> NodeNetworkInfo -> Bool
$c== :: NodeNetworkInfo -> NodeNetworkInfo -> Bool
Eq, Int -> NodeNetworkInfo -> ShowS
[NodeNetworkInfo] -> ShowS
NodeNetworkInfo -> String
(Int -> NodeNetworkInfo -> ShowS)
-> (NodeNetworkInfo -> String)
-> ([NodeNetworkInfo] -> ShowS)
-> Show NodeNetworkInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NodeNetworkInfo] -> ShowS
$cshowList :: [NodeNetworkInfo] -> ShowS
show :: NodeNetworkInfo -> String
$cshow :: NodeNetworkInfo -> String
showsPrec :: Int -> NodeNetworkInfo -> ShowS
$cshowsPrec :: Int -> NodeNetworkInfo -> ShowS
Show)
newtype MacAddress = MacAddress { MacAddress -> Text
macAddress :: Text }
deriving (MacAddress -> MacAddress -> Bool
(MacAddress -> MacAddress -> Bool)
-> (MacAddress -> MacAddress -> Bool) -> Eq MacAddress
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MacAddress -> MacAddress -> Bool
$c/= :: MacAddress -> MacAddress -> Bool
== :: MacAddress -> MacAddress -> Bool
$c== :: MacAddress -> MacAddress -> Bool
Eq, Eq MacAddress
Eq MacAddress
-> (MacAddress -> MacAddress -> Ordering)
-> (MacAddress -> MacAddress -> Bool)
-> (MacAddress -> MacAddress -> Bool)
-> (MacAddress -> MacAddress -> Bool)
-> (MacAddress -> MacAddress -> Bool)
-> (MacAddress -> MacAddress -> MacAddress)
-> (MacAddress -> MacAddress -> MacAddress)
-> Ord MacAddress
MacAddress -> MacAddress -> Bool
MacAddress -> MacAddress -> Ordering
MacAddress -> MacAddress -> MacAddress
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 :: MacAddress -> MacAddress -> MacAddress
$cmin :: MacAddress -> MacAddress -> MacAddress
max :: MacAddress -> MacAddress -> MacAddress
$cmax :: MacAddress -> MacAddress -> MacAddress
>= :: MacAddress -> MacAddress -> Bool
$c>= :: MacAddress -> MacAddress -> Bool
> :: MacAddress -> MacAddress -> Bool
$c> :: MacAddress -> MacAddress -> Bool
<= :: MacAddress -> MacAddress -> Bool
$c<= :: MacAddress -> MacAddress -> Bool
< :: MacAddress -> MacAddress -> Bool
$c< :: MacAddress -> MacAddress -> Bool
compare :: MacAddress -> MacAddress -> Ordering
$ccompare :: MacAddress -> MacAddress -> Ordering
$cp1Ord :: Eq MacAddress
Ord, Int -> MacAddress -> ShowS
[MacAddress] -> ShowS
MacAddress -> String
(Int -> MacAddress -> ShowS)
-> (MacAddress -> String)
-> ([MacAddress] -> ShowS)
-> Show MacAddress
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MacAddress] -> ShowS
$cshowList :: [MacAddress] -> ShowS
show :: MacAddress -> String
$cshow :: MacAddress -> String
showsPrec :: Int -> MacAddress -> ShowS
$cshowsPrec :: Int -> MacAddress -> ShowS
Show, Value -> Parser [MacAddress]
Value -> Parser MacAddress
(Value -> Parser MacAddress)
-> (Value -> Parser [MacAddress]) -> FromJSON MacAddress
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [MacAddress]
$cparseJSONList :: Value -> Parser [MacAddress]
parseJSON :: Value -> Parser MacAddress
$cparseJSON :: Value -> Parser MacAddress
FromJSON)
newtype NetworkInterfaceName = NetworkInterfaceName { NetworkInterfaceName -> Text
networkInterfaceName :: Text }
deriving (NetworkInterfaceName -> NetworkInterfaceName -> Bool
(NetworkInterfaceName -> NetworkInterfaceName -> Bool)
-> (NetworkInterfaceName -> NetworkInterfaceName -> Bool)
-> Eq NetworkInterfaceName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NetworkInterfaceName -> NetworkInterfaceName -> Bool
$c/= :: NetworkInterfaceName -> NetworkInterfaceName -> Bool
== :: NetworkInterfaceName -> NetworkInterfaceName -> Bool
$c== :: NetworkInterfaceName -> NetworkInterfaceName -> Bool
Eq, Eq NetworkInterfaceName
Eq NetworkInterfaceName
-> (NetworkInterfaceName -> NetworkInterfaceName -> Ordering)
-> (NetworkInterfaceName -> NetworkInterfaceName -> Bool)
-> (NetworkInterfaceName -> NetworkInterfaceName -> Bool)
-> (NetworkInterfaceName -> NetworkInterfaceName -> Bool)
-> (NetworkInterfaceName -> NetworkInterfaceName -> Bool)
-> (NetworkInterfaceName
-> NetworkInterfaceName -> NetworkInterfaceName)
-> (NetworkInterfaceName
-> NetworkInterfaceName -> NetworkInterfaceName)
-> Ord NetworkInterfaceName
NetworkInterfaceName -> NetworkInterfaceName -> Bool
NetworkInterfaceName -> NetworkInterfaceName -> Ordering
NetworkInterfaceName
-> NetworkInterfaceName -> NetworkInterfaceName
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 :: NetworkInterfaceName
-> NetworkInterfaceName -> NetworkInterfaceName
$cmin :: NetworkInterfaceName
-> NetworkInterfaceName -> NetworkInterfaceName
max :: NetworkInterfaceName
-> NetworkInterfaceName -> NetworkInterfaceName
$cmax :: NetworkInterfaceName
-> NetworkInterfaceName -> NetworkInterfaceName
>= :: NetworkInterfaceName -> NetworkInterfaceName -> Bool
$c>= :: NetworkInterfaceName -> NetworkInterfaceName -> Bool
> :: NetworkInterfaceName -> NetworkInterfaceName -> Bool
$c> :: NetworkInterfaceName -> NetworkInterfaceName -> Bool
<= :: NetworkInterfaceName -> NetworkInterfaceName -> Bool
$c<= :: NetworkInterfaceName -> NetworkInterfaceName -> Bool
< :: NetworkInterfaceName -> NetworkInterfaceName -> Bool
$c< :: NetworkInterfaceName -> NetworkInterfaceName -> Bool
compare :: NetworkInterfaceName -> NetworkInterfaceName -> Ordering
$ccompare :: NetworkInterfaceName -> NetworkInterfaceName -> Ordering
$cp1Ord :: Eq NetworkInterfaceName
Ord, Int -> NetworkInterfaceName -> ShowS
[NetworkInterfaceName] -> ShowS
NetworkInterfaceName -> String
(Int -> NetworkInterfaceName -> ShowS)
-> (NetworkInterfaceName -> String)
-> ([NetworkInterfaceName] -> ShowS)
-> Show NetworkInterfaceName
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NetworkInterfaceName] -> ShowS
$cshowList :: [NetworkInterfaceName] -> ShowS
show :: NetworkInterfaceName -> String
$cshow :: NetworkInterfaceName -> String
showsPrec :: Int -> NetworkInterfaceName -> ShowS
$cshowsPrec :: Int -> NetworkInterfaceName -> ShowS
Show, Value -> Parser [NetworkInterfaceName]
Value -> Parser NetworkInterfaceName
(Value -> Parser NetworkInterfaceName)
-> (Value -> Parser [NetworkInterfaceName])
-> FromJSON NetworkInterfaceName
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [NetworkInterfaceName]
$cparseJSONList :: Value -> Parser [NetworkInterfaceName]
parseJSON :: Value -> Parser NetworkInterfaceName
$cparseJSON :: Value -> Parser NetworkInterfaceName
FromJSON)
data NodeNetworkInterface = NodeNetworkInterface {
NodeNetworkInterface -> MacAddress
nodeNetIfaceMacAddress :: MacAddress
, NodeNetworkInterface -> NetworkInterfaceName
nodeNetIfaceName :: NetworkInterfaceName
, NodeNetworkInterface -> Server
nodeNetIfaceAddress :: Server
} deriving (NodeNetworkInterface -> NodeNetworkInterface -> Bool
(NodeNetworkInterface -> NodeNetworkInterface -> Bool)
-> (NodeNetworkInterface -> NodeNetworkInterface -> Bool)
-> Eq NodeNetworkInterface
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NodeNetworkInterface -> NodeNetworkInterface -> Bool
$c/= :: NodeNetworkInterface -> NodeNetworkInterface -> Bool
== :: NodeNetworkInterface -> NodeNetworkInterface -> Bool
$c== :: NodeNetworkInterface -> NodeNetworkInterface -> Bool
Eq, Int -> NodeNetworkInterface -> ShowS
[NodeNetworkInterface] -> ShowS
NodeNetworkInterface -> String
(Int -> NodeNetworkInterface -> ShowS)
-> (NodeNetworkInterface -> String)
-> ([NodeNetworkInterface] -> ShowS)
-> Show NodeNetworkInterface
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NodeNetworkInterface] -> ShowS
$cshowList :: [NodeNetworkInterface] -> ShowS
show :: NodeNetworkInterface -> String
$cshow :: NodeNetworkInterface -> String
showsPrec :: Int -> NodeNetworkInterface -> ShowS
$cshowsPrec :: Int -> NodeNetworkInterface -> ShowS
Show)
data ThreadPool = ThreadPool {
ThreadPool -> Text
nodeThreadPoolName :: Text
, ThreadPool -> NodeThreadPoolInfo
nodeThreadPoolInfo :: NodeThreadPoolInfo
} deriving (ThreadPool -> ThreadPool -> Bool
(ThreadPool -> ThreadPool -> Bool)
-> (ThreadPool -> ThreadPool -> Bool) -> Eq ThreadPool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ThreadPool -> ThreadPool -> Bool
$c/= :: ThreadPool -> ThreadPool -> Bool
== :: ThreadPool -> ThreadPool -> Bool
$c== :: ThreadPool -> ThreadPool -> Bool
Eq, Int -> ThreadPool -> ShowS
[ThreadPool] -> ShowS
ThreadPool -> String
(Int -> ThreadPool -> ShowS)
-> (ThreadPool -> String)
-> ([ThreadPool] -> ShowS)
-> Show ThreadPool
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ThreadPool] -> ShowS
$cshowList :: [ThreadPool] -> ShowS
show :: ThreadPool -> String
$cshow :: ThreadPool -> String
showsPrec :: Int -> ThreadPool -> ShowS
$cshowsPrec :: Int -> ThreadPool -> ShowS
Show)
data NodeThreadPoolInfo = NodeThreadPoolInfo {
NodeThreadPoolInfo -> ThreadPoolSize
nodeThreadPoolQueueSize :: ThreadPoolSize
, NodeThreadPoolInfo -> Maybe NominalDiffTime
nodeThreadPoolKeepalive :: Maybe NominalDiffTime
, NodeThreadPoolInfo -> Maybe Int
nodeThreadPoolMin :: Maybe Int
, NodeThreadPoolInfo -> Maybe Int
nodeThreadPoolMax :: Maybe Int
, NodeThreadPoolInfo -> ThreadPoolType
nodeThreadPoolType :: ThreadPoolType
} deriving (NodeThreadPoolInfo -> NodeThreadPoolInfo -> Bool
(NodeThreadPoolInfo -> NodeThreadPoolInfo -> Bool)
-> (NodeThreadPoolInfo -> NodeThreadPoolInfo -> Bool)
-> Eq NodeThreadPoolInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NodeThreadPoolInfo -> NodeThreadPoolInfo -> Bool
$c/= :: NodeThreadPoolInfo -> NodeThreadPoolInfo -> Bool
== :: NodeThreadPoolInfo -> NodeThreadPoolInfo -> Bool
$c== :: NodeThreadPoolInfo -> NodeThreadPoolInfo -> Bool
Eq, Int -> NodeThreadPoolInfo -> ShowS
[NodeThreadPoolInfo] -> ShowS
NodeThreadPoolInfo -> String
(Int -> NodeThreadPoolInfo -> ShowS)
-> (NodeThreadPoolInfo -> String)
-> ([NodeThreadPoolInfo] -> ShowS)
-> Show NodeThreadPoolInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NodeThreadPoolInfo] -> ShowS
$cshowList :: [NodeThreadPoolInfo] -> ShowS
show :: NodeThreadPoolInfo -> String
$cshow :: NodeThreadPoolInfo -> String
showsPrec :: Int -> NodeThreadPoolInfo -> ShowS
$cshowsPrec :: Int -> NodeThreadPoolInfo -> ShowS
Show)
data ThreadPoolSize = ThreadPoolBounded Int
| ThreadPoolUnbounded
deriving (ThreadPoolSize -> ThreadPoolSize -> Bool
(ThreadPoolSize -> ThreadPoolSize -> Bool)
-> (ThreadPoolSize -> ThreadPoolSize -> Bool) -> Eq ThreadPoolSize
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ThreadPoolSize -> ThreadPoolSize -> Bool
$c/= :: ThreadPoolSize -> ThreadPoolSize -> Bool
== :: ThreadPoolSize -> ThreadPoolSize -> Bool
$c== :: ThreadPoolSize -> ThreadPoolSize -> Bool
Eq, Int -> ThreadPoolSize -> ShowS
[ThreadPoolSize] -> ShowS
ThreadPoolSize -> String
(Int -> ThreadPoolSize -> ShowS)
-> (ThreadPoolSize -> String)
-> ([ThreadPoolSize] -> ShowS)
-> Show ThreadPoolSize
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ThreadPoolSize] -> ShowS
$cshowList :: [ThreadPoolSize] -> ShowS
show :: ThreadPoolSize -> String
$cshow :: ThreadPoolSize -> String
showsPrec :: Int -> ThreadPoolSize -> ShowS
$cshowsPrec :: Int -> ThreadPoolSize -> ShowS
Show)
data ThreadPoolType = ThreadPoolScaling
| ThreadPoolFixed
| ThreadPoolCached
| ThreadPoolFixedAutoQueueSize
deriving (ThreadPoolType -> ThreadPoolType -> Bool
(ThreadPoolType -> ThreadPoolType -> Bool)
-> (ThreadPoolType -> ThreadPoolType -> Bool) -> Eq ThreadPoolType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ThreadPoolType -> ThreadPoolType -> Bool
$c/= :: ThreadPoolType -> ThreadPoolType -> Bool
== :: ThreadPoolType -> ThreadPoolType -> Bool
$c== :: ThreadPoolType -> ThreadPoolType -> Bool
Eq, Int -> ThreadPoolType -> ShowS
[ThreadPoolType] -> ShowS
ThreadPoolType -> String
(Int -> ThreadPoolType -> ShowS)
-> (ThreadPoolType -> String)
-> ([ThreadPoolType] -> ShowS)
-> Show ThreadPoolType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ThreadPoolType] -> ShowS
$cshowList :: [ThreadPoolType] -> ShowS
show :: ThreadPoolType -> String
$cshow :: ThreadPoolType -> String
showsPrec :: Int -> ThreadPoolType -> ShowS
$cshowsPrec :: Int -> ThreadPoolType -> ShowS
Show)
data NodeJVMInfo = NodeJVMInfo {
NodeJVMInfo -> [JVMMemoryPool]
nodeJVMInfoMemoryPools :: [JVMMemoryPool]
, NodeJVMInfo -> [JVMGCCollector]
nodeJVMInfoMemoryPoolsGCCollectors :: [JVMGCCollector]
, NodeJVMInfo -> JVMMemoryInfo
nodeJVMInfoMemoryInfo :: JVMMemoryInfo
, NodeJVMInfo -> UTCTime
nodeJVMInfoStartTime :: UTCTime
, NodeJVMInfo -> Text
nodeJVMInfoVMVendor :: Text
, NodeJVMInfo -> VMVersion
nodeJVMVMVersion :: VMVersion
, NodeJVMInfo -> Text
nodeJVMVMName :: Text
, NodeJVMInfo -> JVMVersion
nodeJVMVersion :: JVMVersion
, NodeJVMInfo -> PID
nodeJVMPID :: PID
} deriving (NodeJVMInfo -> NodeJVMInfo -> Bool
(NodeJVMInfo -> NodeJVMInfo -> Bool)
-> (NodeJVMInfo -> NodeJVMInfo -> Bool) -> Eq NodeJVMInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NodeJVMInfo -> NodeJVMInfo -> Bool
$c/= :: NodeJVMInfo -> NodeJVMInfo -> Bool
== :: NodeJVMInfo -> NodeJVMInfo -> Bool
$c== :: NodeJVMInfo -> NodeJVMInfo -> Bool
Eq, Int -> NodeJVMInfo -> ShowS
[NodeJVMInfo] -> ShowS
NodeJVMInfo -> String
(Int -> NodeJVMInfo -> ShowS)
-> (NodeJVMInfo -> String)
-> ([NodeJVMInfo] -> ShowS)
-> Show NodeJVMInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NodeJVMInfo] -> ShowS
$cshowList :: [NodeJVMInfo] -> ShowS
show :: NodeJVMInfo -> String
$cshow :: NodeJVMInfo -> String
showsPrec :: Int -> NodeJVMInfo -> ShowS
$cshowsPrec :: Int -> NodeJVMInfo -> ShowS
Show)
newtype JVMVersion =
JVMVersion { JVMVersion -> Text
unJVMVersion :: Text }
deriving (JVMVersion -> JVMVersion -> Bool
(JVMVersion -> JVMVersion -> Bool)
-> (JVMVersion -> JVMVersion -> Bool) -> Eq JVMVersion
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: JVMVersion -> JVMVersion -> Bool
$c/= :: JVMVersion -> JVMVersion -> Bool
== :: JVMVersion -> JVMVersion -> Bool
$c== :: JVMVersion -> JVMVersion -> Bool
Eq, Int -> JVMVersion -> ShowS
[JVMVersion] -> ShowS
JVMVersion -> String
(Int -> JVMVersion -> ShowS)
-> (JVMVersion -> String)
-> ([JVMVersion] -> ShowS)
-> Show JVMVersion
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [JVMVersion] -> ShowS
$cshowList :: [JVMVersion] -> ShowS
show :: JVMVersion -> String
$cshow :: JVMVersion -> String
showsPrec :: Int -> JVMVersion -> ShowS
$cshowsPrec :: Int -> JVMVersion -> ShowS
Show)
instance FromJSON JVMVersion where
parseJSON :: Value -> Parser JVMVersion
parseJSON = String -> (Text -> Parser JVMVersion) -> Value -> Parser JVMVersion
forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"JVMVersion" (JVMVersion -> Parser JVMVersion
forall (f :: * -> *) a. Applicative f => a -> f a
pure (JVMVersion -> Parser JVMVersion)
-> (Text -> JVMVersion) -> Text -> Parser JVMVersion
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> JVMVersion
JVMVersion)
data JVMMemoryInfo = JVMMemoryInfo {
JVMMemoryInfo -> Bytes
jvmMemoryInfoDirectMax :: Bytes
, JVMMemoryInfo -> Bytes
jvmMemoryInfoNonHeapMax :: Bytes
, JVMMemoryInfo -> Bytes
jvmMemoryInfoNonHeapInit :: Bytes
, JVMMemoryInfo -> Bytes
jvmMemoryInfoHeapMax :: Bytes
, JVMMemoryInfo -> Bytes
jvmMemoryInfoHeapInit :: Bytes
} deriving (JVMMemoryInfo -> JVMMemoryInfo -> Bool
(JVMMemoryInfo -> JVMMemoryInfo -> Bool)
-> (JVMMemoryInfo -> JVMMemoryInfo -> Bool) -> Eq JVMMemoryInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: JVMMemoryInfo -> JVMMemoryInfo -> Bool
$c/= :: JVMMemoryInfo -> JVMMemoryInfo -> Bool
== :: JVMMemoryInfo -> JVMMemoryInfo -> Bool
$c== :: JVMMemoryInfo -> JVMMemoryInfo -> Bool
Eq, Int -> JVMMemoryInfo -> ShowS
[JVMMemoryInfo] -> ShowS
JVMMemoryInfo -> String
(Int -> JVMMemoryInfo -> ShowS)
-> (JVMMemoryInfo -> String)
-> ([JVMMemoryInfo] -> ShowS)
-> Show JVMMemoryInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [JVMMemoryInfo] -> ShowS
$cshowList :: [JVMMemoryInfo] -> ShowS
show :: JVMMemoryInfo -> String
$cshow :: JVMMemoryInfo -> String
showsPrec :: Int -> JVMMemoryInfo -> ShowS
$cshowsPrec :: Int -> JVMMemoryInfo -> ShowS
Show)
newtype VMVersion =
VMVersion { VMVersion -> Text
unVMVersion :: Text }
deriving (VMVersion -> VMVersion -> Bool
(VMVersion -> VMVersion -> Bool)
-> (VMVersion -> VMVersion -> Bool) -> Eq VMVersion
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VMVersion -> VMVersion -> Bool
$c/= :: VMVersion -> VMVersion -> Bool
== :: VMVersion -> VMVersion -> Bool
$c== :: VMVersion -> VMVersion -> Bool
Eq, Int -> VMVersion -> ShowS
[VMVersion] -> ShowS
VMVersion -> String
(Int -> VMVersion -> ShowS)
-> (VMVersion -> String)
-> ([VMVersion] -> ShowS)
-> Show VMVersion
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VMVersion] -> ShowS
$cshowList :: [VMVersion] -> ShowS
show :: VMVersion -> String
$cshow :: VMVersion -> String
showsPrec :: Int -> VMVersion -> ShowS
$cshowsPrec :: Int -> VMVersion -> ShowS
Show)
instance ToJSON VMVersion where
toJSON :: VMVersion -> Value
toJSON = Text -> Value
forall a. ToJSON a => a -> Value
toJSON (Text -> Value) -> (VMVersion -> Text) -> VMVersion -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VMVersion -> Text
unVMVersion
instance FromJSON VMVersion where
parseJSON :: Value -> Parser VMVersion
parseJSON = String -> (Text -> Parser VMVersion) -> Value -> Parser VMVersion
forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"VMVersion" (VMVersion -> Parser VMVersion
forall (f :: * -> *) a. Applicative f => a -> f a
pure (VMVersion -> Parser VMVersion)
-> (Text -> VMVersion) -> Text -> Parser VMVersion
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> VMVersion
VMVersion)
newtype JVMMemoryPool = JVMMemoryPool {
JVMMemoryPool -> Text
jvmMemoryPool :: Text
} deriving (JVMMemoryPool -> JVMMemoryPool -> Bool
(JVMMemoryPool -> JVMMemoryPool -> Bool)
-> (JVMMemoryPool -> JVMMemoryPool -> Bool) -> Eq JVMMemoryPool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: JVMMemoryPool -> JVMMemoryPool -> Bool
$c/= :: JVMMemoryPool -> JVMMemoryPool -> Bool
== :: JVMMemoryPool -> JVMMemoryPool -> Bool
$c== :: JVMMemoryPool -> JVMMemoryPool -> Bool
Eq, Int -> JVMMemoryPool -> ShowS
[JVMMemoryPool] -> ShowS
JVMMemoryPool -> String
(Int -> JVMMemoryPool -> ShowS)
-> (JVMMemoryPool -> String)
-> ([JVMMemoryPool] -> ShowS)
-> Show JVMMemoryPool
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [JVMMemoryPool] -> ShowS
$cshowList :: [JVMMemoryPool] -> ShowS
show :: JVMMemoryPool -> String
$cshow :: JVMMemoryPool -> String
showsPrec :: Int -> JVMMemoryPool -> ShowS
$cshowsPrec :: Int -> JVMMemoryPool -> ShowS
Show, Value -> Parser [JVMMemoryPool]
Value -> Parser JVMMemoryPool
(Value -> Parser JVMMemoryPool)
-> (Value -> Parser [JVMMemoryPool]) -> FromJSON JVMMemoryPool
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [JVMMemoryPool]
$cparseJSONList :: Value -> Parser [JVMMemoryPool]
parseJSON :: Value -> Parser JVMMemoryPool
$cparseJSON :: Value -> Parser JVMMemoryPool
FromJSON)
newtype JVMGCCollector = JVMGCCollector {
JVMGCCollector -> Text
jvmGCCollector :: Text
} deriving (JVMGCCollector -> JVMGCCollector -> Bool
(JVMGCCollector -> JVMGCCollector -> Bool)
-> (JVMGCCollector -> JVMGCCollector -> Bool) -> Eq JVMGCCollector
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: JVMGCCollector -> JVMGCCollector -> Bool
$c/= :: JVMGCCollector -> JVMGCCollector -> Bool
== :: JVMGCCollector -> JVMGCCollector -> Bool
$c== :: JVMGCCollector -> JVMGCCollector -> Bool
Eq, Int -> JVMGCCollector -> ShowS
[JVMGCCollector] -> ShowS
JVMGCCollector -> String
(Int -> JVMGCCollector -> ShowS)
-> (JVMGCCollector -> String)
-> ([JVMGCCollector] -> ShowS)
-> Show JVMGCCollector
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [JVMGCCollector] -> ShowS
$cshowList :: [JVMGCCollector] -> ShowS
show :: JVMGCCollector -> String
$cshow :: JVMGCCollector -> String
showsPrec :: Int -> JVMGCCollector -> ShowS
$cshowsPrec :: Int -> JVMGCCollector -> ShowS
Show, Value -> Parser [JVMGCCollector]
Value -> Parser JVMGCCollector
(Value -> Parser JVMGCCollector)
-> (Value -> Parser [JVMGCCollector]) -> FromJSON JVMGCCollector
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [JVMGCCollector]
$cparseJSONList :: Value -> Parser [JVMGCCollector]
parseJSON :: Value -> Parser JVMGCCollector
$cparseJSON :: Value -> Parser JVMGCCollector
FromJSON)
newtype PID = PID {
PID -> Int
pid :: Int
} deriving (PID -> PID -> Bool
(PID -> PID -> Bool) -> (PID -> PID -> Bool) -> Eq PID
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PID -> PID -> Bool
$c/= :: PID -> PID -> Bool
== :: PID -> PID -> Bool
$c== :: PID -> PID -> Bool
Eq, Int -> PID -> ShowS
[PID] -> ShowS
PID -> String
(Int -> PID -> ShowS)
-> (PID -> String) -> ([PID] -> ShowS) -> Show PID
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PID] -> ShowS
$cshowList :: [PID] -> ShowS
show :: PID -> String
$cshow :: PID -> String
showsPrec :: Int -> PID -> ShowS
$cshowsPrec :: Int -> PID -> ShowS
Show, Value -> Parser [PID]
Value -> Parser PID
(Value -> Parser PID) -> (Value -> Parser [PID]) -> FromJSON PID
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [PID]
$cparseJSONList :: Value -> Parser [PID]
parseJSON :: Value -> Parser PID
$cparseJSON :: Value -> Parser PID
FromJSON)
data NodeOSInfo = NodeOSInfo {
NodeOSInfo -> NominalDiffTime
nodeOSRefreshInterval :: NominalDiffTime
, NodeOSInfo -> Text
nodeOSName :: Text
, NodeOSInfo -> Text
nodeOSArch :: Text
, NodeOSInfo -> Text
nodeOSVersion :: Text
, NodeOSInfo -> Int
nodeOSAvailableProcessors :: Int
, NodeOSInfo -> Int
nodeOSAllocatedProcessors :: Int
} deriving (NodeOSInfo -> NodeOSInfo -> Bool
(NodeOSInfo -> NodeOSInfo -> Bool)
-> (NodeOSInfo -> NodeOSInfo -> Bool) -> Eq NodeOSInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NodeOSInfo -> NodeOSInfo -> Bool
$c/= :: NodeOSInfo -> NodeOSInfo -> Bool
== :: NodeOSInfo -> NodeOSInfo -> Bool
$c== :: NodeOSInfo -> NodeOSInfo -> Bool
Eq, Int -> NodeOSInfo -> ShowS
[NodeOSInfo] -> ShowS
NodeOSInfo -> String
(Int -> NodeOSInfo -> ShowS)
-> (NodeOSInfo -> String)
-> ([NodeOSInfo] -> ShowS)
-> Show NodeOSInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NodeOSInfo] -> ShowS
$cshowList :: [NodeOSInfo] -> ShowS
show :: NodeOSInfo -> String
$cshow :: NodeOSInfo -> String
showsPrec :: Int -> NodeOSInfo -> ShowS
$cshowsPrec :: Int -> NodeOSInfo -> ShowS
Show)
data CPUInfo = CPUInfo {
CPUInfo -> Bytes
cpuCacheSize :: Bytes
, CPUInfo -> Int
cpuCoresPerSocket :: Int
, CPUInfo -> Int
cpuTotalSockets :: Int
, CPUInfo -> Int
cpuTotalCores :: Int
, CPUInfo -> Int
cpuMHZ :: Int
, CPUInfo -> Text
cpuModel :: Text
, CPUInfo -> Text
cpuVendor :: Text
} deriving (CPUInfo -> CPUInfo -> Bool
(CPUInfo -> CPUInfo -> Bool)
-> (CPUInfo -> CPUInfo -> Bool) -> Eq CPUInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CPUInfo -> CPUInfo -> Bool
$c/= :: CPUInfo -> CPUInfo -> Bool
== :: CPUInfo -> CPUInfo -> Bool
$c== :: CPUInfo -> CPUInfo -> Bool
Eq, Int -> CPUInfo -> ShowS
[CPUInfo] -> ShowS
CPUInfo -> String
(Int -> CPUInfo -> ShowS)
-> (CPUInfo -> String) -> ([CPUInfo] -> ShowS) -> Show CPUInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CPUInfo] -> ShowS
$cshowList :: [CPUInfo] -> ShowS
show :: CPUInfo -> String
$cshow :: CPUInfo -> String
showsPrec :: Int -> CPUInfo -> ShowS
$cshowsPrec :: Int -> CPUInfo -> ShowS
Show)
data NodeProcessInfo = NodeProcessInfo {
NodeProcessInfo -> Bool
nodeProcessMLockAll :: Bool
, NodeProcessInfo -> Maybe Int
nodeProcessMaxFileDescriptors :: Maybe Int
, NodeProcessInfo -> PID
nodeProcessId :: PID
, NodeProcessInfo -> NominalDiffTime
nodeProcessRefreshInterval :: NominalDiffTime
} deriving (NodeProcessInfo -> NodeProcessInfo -> Bool
(NodeProcessInfo -> NodeProcessInfo -> Bool)
-> (NodeProcessInfo -> NodeProcessInfo -> Bool)
-> Eq NodeProcessInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NodeProcessInfo -> NodeProcessInfo -> Bool
$c/= :: NodeProcessInfo -> NodeProcessInfo -> Bool
== :: NodeProcessInfo -> NodeProcessInfo -> Bool
$c== :: NodeProcessInfo -> NodeProcessInfo -> Bool
Eq, Int -> NodeProcessInfo -> ShowS
[NodeProcessInfo] -> ShowS
NodeProcessInfo -> String
(Int -> NodeProcessInfo -> ShowS)
-> (NodeProcessInfo -> String)
-> ([NodeProcessInfo] -> ShowS)
-> Show NodeProcessInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NodeProcessInfo] -> ShowS
$cshowList :: [NodeProcessInfo] -> ShowS
show :: NodeProcessInfo -> String
$cshow :: NodeProcessInfo -> String
showsPrec :: Int -> NodeProcessInfo -> ShowS
$cshowsPrec :: Int -> NodeProcessInfo -> ShowS
Show)
data ShardResult =
ShardResult { ShardResult -> Int
shardTotal :: Int
, ShardResult -> Int
shardsSuccessful :: Int
, ShardResult -> Int
shardsSkipped :: Int
, ShardResult -> Int
shardsFailed :: Int } deriving (ShardResult -> ShardResult -> Bool
(ShardResult -> ShardResult -> Bool)
-> (ShardResult -> ShardResult -> Bool) -> Eq ShardResult
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ShardResult -> ShardResult -> Bool
$c/= :: ShardResult -> ShardResult -> Bool
== :: ShardResult -> ShardResult -> Bool
$c== :: ShardResult -> ShardResult -> Bool
Eq, Int -> ShardResult -> ShowS
[ShardResult] -> ShowS
ShardResult -> String
(Int -> ShardResult -> ShowS)
-> (ShardResult -> String)
-> ([ShardResult] -> ShowS)
-> Show ShardResult
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ShardResult] -> ShowS
$cshowList :: [ShardResult] -> ShowS
show :: ShardResult -> String
$cshow :: ShardResult -> String
showsPrec :: Int -> ShardResult -> ShowS
$cshowsPrec :: Int -> ShardResult -> ShowS
Show)
instance FromJSON ShardResult where
parseJSON :: Value -> Parser ShardResult
parseJSON (Object Object
v) = Int -> Int -> Int -> Int -> ShardResult
ShardResult (Int -> Int -> Int -> Int -> ShardResult)
-> Parser Int -> Parser (Int -> Int -> Int -> ShardResult)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
Object
v Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"total" Parser (Int -> Int -> Int -> ShardResult)
-> Parser Int -> Parser (Int -> Int -> ShardResult)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
Object
v Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"successful" Parser (Int -> Int -> ShardResult)
-> Parser Int -> Parser (Int -> ShardResult)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
Object
v Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"skipped" Parser (Int -> ShardResult) -> Parser Int -> Parser ShardResult
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
Object
v Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"failed"
parseJSON Value
_ = Parser ShardResult
forall (f :: * -> *) a. Alternative f => f a
empty
data SnapshotState = SnapshotInit
| SnapshotStarted
| SnapshotSuccess
| SnapshotFailed
| SnapshotAborted
| SnapshotMissing
| SnapshotWaiting
deriving (SnapshotState -> SnapshotState -> Bool
(SnapshotState -> SnapshotState -> Bool)
-> (SnapshotState -> SnapshotState -> Bool) -> Eq SnapshotState
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SnapshotState -> SnapshotState -> Bool
$c/= :: SnapshotState -> SnapshotState -> Bool
== :: SnapshotState -> SnapshotState -> Bool
$c== :: SnapshotState -> SnapshotState -> Bool
Eq, Int -> SnapshotState -> ShowS
[SnapshotState] -> ShowS
SnapshotState -> String
(Int -> SnapshotState -> ShowS)
-> (SnapshotState -> String)
-> ([SnapshotState] -> ShowS)
-> Show SnapshotState
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SnapshotState] -> ShowS
$cshowList :: [SnapshotState] -> ShowS
show :: SnapshotState -> String
$cshow :: SnapshotState -> String
showsPrec :: Int -> SnapshotState -> ShowS
$cshowsPrec :: Int -> SnapshotState -> ShowS
Show)
instance FromJSON SnapshotState where
parseJSON :: Value -> Parser SnapshotState
parseJSON = String
-> (Text -> Parser SnapshotState) -> Value -> Parser SnapshotState
forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"SnapshotState" Text -> Parser SnapshotState
forall (m :: * -> *). MonadFail m => Text -> m SnapshotState
parse
where
parse :: Text -> m SnapshotState
parse Text
"INIT" = SnapshotState -> m SnapshotState
forall (m :: * -> *) a. Monad m => a -> m a
return SnapshotState
SnapshotInit
parse Text
"STARTED" = SnapshotState -> m SnapshotState
forall (m :: * -> *) a. Monad m => a -> m a
return SnapshotState
SnapshotStarted
parse Text
"SUCCESS" = SnapshotState -> m SnapshotState
forall (m :: * -> *) a. Monad m => a -> m a
return SnapshotState
SnapshotSuccess
parse Text
"FAILED" = SnapshotState -> m SnapshotState
forall (m :: * -> *) a. Monad m => a -> m a
return SnapshotState
SnapshotFailed
parse Text
"ABORTED" = SnapshotState -> m SnapshotState
forall (m :: * -> *) a. Monad m => a -> m a
return SnapshotState
SnapshotAborted
parse Text
"MISSING" = SnapshotState -> m SnapshotState
forall (m :: * -> *) a. Monad m => a -> m a
return SnapshotState
SnapshotMissing
parse Text
"WAITING" = SnapshotState -> m SnapshotState
forall (m :: * -> *) a. Monad m => a -> m a
return SnapshotState
SnapshotWaiting
parse Text
t = String -> m SnapshotState
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String
"Invalid snapshot state " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Text -> String
T.unpack Text
t)
data SnapshotRestoreSettings = SnapshotRestoreSettings {
SnapshotRestoreSettings -> Bool
snapRestoreWaitForCompletion :: Bool
, SnapshotRestoreSettings -> Maybe IndexSelection
snapRestoreIndices :: Maybe IndexSelection
, SnapshotRestoreSettings -> Bool
snapRestoreIgnoreUnavailable :: Bool
, SnapshotRestoreSettings -> Bool
snapRestoreIncludeGlobalState :: Bool
, SnapshotRestoreSettings -> Maybe RestoreRenamePattern
snapRestoreRenamePattern :: Maybe RestoreRenamePattern
, SnapshotRestoreSettings -> Maybe (NonEmpty RestoreRenameToken)
snapRestoreRenameReplacement :: Maybe (NonEmpty RestoreRenameToken)
, SnapshotRestoreSettings -> Bool
snapRestorePartial :: Bool
, SnapshotRestoreSettings -> Bool
snapRestoreIncludeAliases :: Bool
, SnapshotRestoreSettings -> Maybe RestoreIndexSettings
snapRestoreIndexSettingsOverrides :: Maybe RestoreIndexSettings
, SnapshotRestoreSettings -> Maybe (NonEmpty Text)
snapRestoreIgnoreIndexSettings :: Maybe (NonEmpty Text)
} deriving (SnapshotRestoreSettings -> SnapshotRestoreSettings -> Bool
(SnapshotRestoreSettings -> SnapshotRestoreSettings -> Bool)
-> (SnapshotRestoreSettings -> SnapshotRestoreSettings -> Bool)
-> Eq SnapshotRestoreSettings
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SnapshotRestoreSettings -> SnapshotRestoreSettings -> Bool
$c/= :: SnapshotRestoreSettings -> SnapshotRestoreSettings -> Bool
== :: SnapshotRestoreSettings -> SnapshotRestoreSettings -> Bool
$c== :: SnapshotRestoreSettings -> SnapshotRestoreSettings -> Bool
Eq, Int -> SnapshotRestoreSettings -> ShowS
[SnapshotRestoreSettings] -> ShowS
SnapshotRestoreSettings -> String
(Int -> SnapshotRestoreSettings -> ShowS)
-> (SnapshotRestoreSettings -> String)
-> ([SnapshotRestoreSettings] -> ShowS)
-> Show SnapshotRestoreSettings
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SnapshotRestoreSettings] -> ShowS
$cshowList :: [SnapshotRestoreSettings] -> ShowS
show :: SnapshotRestoreSettings -> String
$cshow :: SnapshotRestoreSettings -> String
showsPrec :: Int -> SnapshotRestoreSettings -> ShowS
$cshowsPrec :: Int -> SnapshotRestoreSettings -> ShowS
Show)
newtype SnapshotRepoUpdateSettings = SnapshotRepoUpdateSettings
{ SnapshotRepoUpdateSettings -> Bool
repoUpdateVerify :: Bool
} deriving (SnapshotRepoUpdateSettings -> SnapshotRepoUpdateSettings -> Bool
(SnapshotRepoUpdateSettings -> SnapshotRepoUpdateSettings -> Bool)
-> (SnapshotRepoUpdateSettings
-> SnapshotRepoUpdateSettings -> Bool)
-> Eq SnapshotRepoUpdateSettings
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SnapshotRepoUpdateSettings -> SnapshotRepoUpdateSettings -> Bool
$c/= :: SnapshotRepoUpdateSettings -> SnapshotRepoUpdateSettings -> Bool
== :: SnapshotRepoUpdateSettings -> SnapshotRepoUpdateSettings -> Bool
$c== :: SnapshotRepoUpdateSettings -> SnapshotRepoUpdateSettings -> Bool
Eq, Int -> SnapshotRepoUpdateSettings -> ShowS
[SnapshotRepoUpdateSettings] -> ShowS
SnapshotRepoUpdateSettings -> String
(Int -> SnapshotRepoUpdateSettings -> ShowS)
-> (SnapshotRepoUpdateSettings -> String)
-> ([SnapshotRepoUpdateSettings] -> ShowS)
-> Show SnapshotRepoUpdateSettings
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SnapshotRepoUpdateSettings] -> ShowS
$cshowList :: [SnapshotRepoUpdateSettings] -> ShowS
show :: SnapshotRepoUpdateSettings -> String
$cshow :: SnapshotRepoUpdateSettings -> String
showsPrec :: Int -> SnapshotRepoUpdateSettings -> ShowS
$cshowsPrec :: Int -> SnapshotRepoUpdateSettings -> ShowS
Show)
defaultSnapshotRepoUpdateSettings :: SnapshotRepoUpdateSettings
defaultSnapshotRepoUpdateSettings :: SnapshotRepoUpdateSettings
defaultSnapshotRepoUpdateSettings = Bool -> SnapshotRepoUpdateSettings
SnapshotRepoUpdateSettings Bool
True
data FsSnapshotRepo = FsSnapshotRepo {
FsSnapshotRepo -> SnapshotRepoName
fsrName :: SnapshotRepoName
, FsSnapshotRepo -> String
fsrLocation :: FilePath
, FsSnapshotRepo -> Bool
fsrCompressMetadata :: Bool
, FsSnapshotRepo -> Maybe Bytes
fsrChunkSize :: Maybe Bytes
, FsSnapshotRepo -> Maybe Bytes
fsrMaxRestoreBytesPerSec :: Maybe Bytes
, FsSnapshotRepo -> Maybe Bytes
fsrMaxSnapshotBytesPerSec :: Maybe Bytes
} deriving (FsSnapshotRepo -> FsSnapshotRepo -> Bool
(FsSnapshotRepo -> FsSnapshotRepo -> Bool)
-> (FsSnapshotRepo -> FsSnapshotRepo -> Bool) -> Eq FsSnapshotRepo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FsSnapshotRepo -> FsSnapshotRepo -> Bool
$c/= :: FsSnapshotRepo -> FsSnapshotRepo -> Bool
== :: FsSnapshotRepo -> FsSnapshotRepo -> Bool
$c== :: FsSnapshotRepo -> FsSnapshotRepo -> Bool
Eq, Int -> FsSnapshotRepo -> ShowS
[FsSnapshotRepo] -> ShowS
FsSnapshotRepo -> String
(Int -> FsSnapshotRepo -> ShowS)
-> (FsSnapshotRepo -> String)
-> ([FsSnapshotRepo] -> ShowS)
-> Show FsSnapshotRepo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FsSnapshotRepo] -> ShowS
$cshowList :: [FsSnapshotRepo] -> ShowS
show :: FsSnapshotRepo -> String
$cshow :: FsSnapshotRepo -> String
showsPrec :: Int -> FsSnapshotRepo -> ShowS
$cshowsPrec :: Int -> FsSnapshotRepo -> ShowS
Show)
instance SnapshotRepo FsSnapshotRepo where
toGSnapshotRepo :: FsSnapshotRepo -> GenericSnapshotRepo
toGSnapshotRepo FsSnapshotRepo {Bool
String
Maybe Bytes
SnapshotRepoName
fsrMaxSnapshotBytesPerSec :: Maybe Bytes
fsrMaxRestoreBytesPerSec :: Maybe Bytes
fsrChunkSize :: Maybe Bytes
fsrCompressMetadata :: Bool
fsrLocation :: String
fsrName :: SnapshotRepoName
fsrMaxSnapshotBytesPerSec :: FsSnapshotRepo -> Maybe Bytes
fsrMaxRestoreBytesPerSec :: FsSnapshotRepo -> Maybe Bytes
fsrChunkSize :: FsSnapshotRepo -> Maybe Bytes
fsrCompressMetadata :: FsSnapshotRepo -> Bool
fsrLocation :: FsSnapshotRepo -> String
fsrName :: FsSnapshotRepo -> SnapshotRepoName
..} =
SnapshotRepoName
-> SnapshotRepoType
-> GenericSnapshotRepoSettings
-> GenericSnapshotRepo
GenericSnapshotRepo SnapshotRepoName
fsrName SnapshotRepoType
fsRepoType (Object -> GenericSnapshotRepoSettings
GenericSnapshotRepoSettings Object
settings)
where
Object Object
settings = [Pair] -> Value
object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$ [ Key
"location" Key -> String -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= String
fsrLocation
, Key
"compress" Key -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Bool
fsrCompressMetadata
] [Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [Pair]
optionalPairs
optionalPairs :: [Pair]
optionalPairs = [Maybe Pair] -> [Pair]
forall a. [Maybe a] -> [a]
catMaybes [ (Key
"chunk_size" Key -> Bytes -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.=) (Bytes -> Pair) -> Maybe Bytes -> Maybe Pair
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Bytes
fsrChunkSize
, (Key
"max_restore_bytes_per_sec" Key -> Bytes -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.=) (Bytes -> Pair) -> Maybe Bytes -> Maybe Pair
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Bytes
fsrMaxRestoreBytesPerSec
, (Key
"max_snapshot_bytes_per_sec" Key -> Bytes -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.=) (Bytes -> Pair) -> Maybe Bytes -> Maybe Pair
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Bytes
fsrMaxSnapshotBytesPerSec
]
fromGSnapshotRepo :: GenericSnapshotRepo
-> Either SnapshotRepoConversionError FsSnapshotRepo
fromGSnapshotRepo GenericSnapshotRepo {GenericSnapshotRepoSettings
SnapshotRepoType
SnapshotRepoName
gSnapshotRepoSettings :: GenericSnapshotRepoSettings
gSnapshotRepoType :: SnapshotRepoType
gSnapshotRepoName :: SnapshotRepoName
gSnapshotRepoSettings :: GenericSnapshotRepo -> GenericSnapshotRepoSettings
gSnapshotRepoType :: GenericSnapshotRepo -> SnapshotRepoType
gSnapshotRepoName :: GenericSnapshotRepo -> SnapshotRepoName
..}
| SnapshotRepoType
gSnapshotRepoType SnapshotRepoType -> SnapshotRepoType -> Bool
forall a. Eq a => a -> a -> Bool
== SnapshotRepoType
fsRepoType = do
let o :: Object
o = GenericSnapshotRepoSettings -> Object
gSnapshotRepoSettingsObject GenericSnapshotRepoSettings
gSnapshotRepoSettings
Parser FsSnapshotRepo
-> Either SnapshotRepoConversionError FsSnapshotRepo
forall a. Parser a -> Either SnapshotRepoConversionError a
parseRepo (Parser FsSnapshotRepo
-> Either SnapshotRepoConversionError FsSnapshotRepo)
-> Parser FsSnapshotRepo
-> Either SnapshotRepoConversionError FsSnapshotRepo
forall a b. (a -> b) -> a -> b
$
SnapshotRepoName
-> String
-> Bool
-> Maybe Bytes
-> Maybe Bytes
-> Maybe Bytes
-> FsSnapshotRepo
FsSnapshotRepo SnapshotRepoName
gSnapshotRepoName (String
-> Bool
-> Maybe Bytes
-> Maybe Bytes
-> Maybe Bytes
-> FsSnapshotRepo)
-> Parser String
-> Parser
(Bool
-> Maybe Bytes -> Maybe Bytes -> Maybe Bytes -> FsSnapshotRepo)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser String
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"location"
Parser
(Bool
-> Maybe Bytes -> Maybe Bytes -> Maybe Bytes -> FsSnapshotRepo)
-> Parser Bool
-> Parser
(Maybe Bytes -> Maybe Bytes -> Maybe Bytes -> FsSnapshotRepo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"compress" Parser (Maybe Bool) -> Bool -> Parser Bool
forall a. Parser (Maybe a) -> a -> Parser a
.!= Bool
False
Parser
(Maybe Bytes -> Maybe Bytes -> Maybe Bytes -> FsSnapshotRepo)
-> Parser (Maybe Bytes)
-> Parser (Maybe Bytes -> Maybe Bytes -> FsSnapshotRepo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Bytes)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"chunk_size"
Parser (Maybe Bytes -> Maybe Bytes -> FsSnapshotRepo)
-> Parser (Maybe Bytes) -> Parser (Maybe Bytes -> FsSnapshotRepo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Bytes)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"max_restore_bytes_per_sec"
Parser (Maybe Bytes -> FsSnapshotRepo)
-> Parser (Maybe Bytes) -> Parser FsSnapshotRepo
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Bytes)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"max_snapshot_bytes_per_sec"
| Bool
otherwise = SnapshotRepoConversionError
-> Either SnapshotRepoConversionError FsSnapshotRepo
forall a b. a -> Either a b
Left (SnapshotRepoType -> SnapshotRepoType -> SnapshotRepoConversionError
RepoTypeMismatch SnapshotRepoType
fsRepoType SnapshotRepoType
gSnapshotRepoType)
parseRepo :: Parser a -> Either SnapshotRepoConversionError a
parseRepo :: Parser a -> Either SnapshotRepoConversionError a
parseRepo Parser a
parser = case (() -> Parser a) -> () -> Either String a
forall a b. (a -> Parser b) -> a -> Either String b
parseEither (Parser a -> () -> Parser a
forall a b. a -> b -> a
const Parser a
parser) () of
Left String
e -> SnapshotRepoConversionError -> Either SnapshotRepoConversionError a
forall a b. a -> Either a b
Left (Text -> SnapshotRepoConversionError
OtherRepoConversionError (String -> Text
T.pack String
e))
Right a
a -> a -> Either SnapshotRepoConversionError a
forall a b. b -> Either a b
Right a
a
fsRepoType :: SnapshotRepoType
fsRepoType :: SnapshotRepoType
fsRepoType = Text -> SnapshotRepoType
SnapshotRepoType Text
"fs"
class SnapshotRepo r where
toGSnapshotRepo :: r -> GenericSnapshotRepo
fromGSnapshotRepo :: GenericSnapshotRepo -> Either SnapshotRepoConversionError r
data SnapshotRepoConversionError = RepoTypeMismatch SnapshotRepoType SnapshotRepoType
| OtherRepoConversionError Text
deriving (Int -> SnapshotRepoConversionError -> ShowS
[SnapshotRepoConversionError] -> ShowS
SnapshotRepoConversionError -> String
(Int -> SnapshotRepoConversionError -> ShowS)
-> (SnapshotRepoConversionError -> String)
-> ([SnapshotRepoConversionError] -> ShowS)
-> Show SnapshotRepoConversionError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SnapshotRepoConversionError] -> ShowS
$cshowList :: [SnapshotRepoConversionError] -> ShowS
show :: SnapshotRepoConversionError -> String
$cshow :: SnapshotRepoConversionError -> String
showsPrec :: Int -> SnapshotRepoConversionError -> ShowS
$cshowsPrec :: Int -> SnapshotRepoConversionError -> ShowS
Show, SnapshotRepoConversionError -> SnapshotRepoConversionError -> Bool
(SnapshotRepoConversionError
-> SnapshotRepoConversionError -> Bool)
-> (SnapshotRepoConversionError
-> SnapshotRepoConversionError -> Bool)
-> Eq SnapshotRepoConversionError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SnapshotRepoConversionError -> SnapshotRepoConversionError -> Bool
$c/= :: SnapshotRepoConversionError -> SnapshotRepoConversionError -> Bool
== :: SnapshotRepoConversionError -> SnapshotRepoConversionError -> Bool
$c== :: SnapshotRepoConversionError -> SnapshotRepoConversionError -> Bool
Eq)
instance Exception SnapshotRepoConversionError
data SnapshotCreateSettings = SnapshotCreateSettings {
SnapshotCreateSettings -> Bool
snapWaitForCompletion :: Bool
, SnapshotCreateSettings -> Maybe IndexSelection
snapIndices :: Maybe IndexSelection
, SnapshotCreateSettings -> Bool
snapIgnoreUnavailable :: Bool
, SnapshotCreateSettings -> Bool
snapIncludeGlobalState :: Bool
, SnapshotCreateSettings -> Bool
snapPartial :: Bool
} deriving (SnapshotCreateSettings -> SnapshotCreateSettings -> Bool
(SnapshotCreateSettings -> SnapshotCreateSettings -> Bool)
-> (SnapshotCreateSettings -> SnapshotCreateSettings -> Bool)
-> Eq SnapshotCreateSettings
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SnapshotCreateSettings -> SnapshotCreateSettings -> Bool
$c/= :: SnapshotCreateSettings -> SnapshotCreateSettings -> Bool
== :: SnapshotCreateSettings -> SnapshotCreateSettings -> Bool
$c== :: SnapshotCreateSettings -> SnapshotCreateSettings -> Bool
Eq, Int -> SnapshotCreateSettings -> ShowS
[SnapshotCreateSettings] -> ShowS
SnapshotCreateSettings -> String
(Int -> SnapshotCreateSettings -> ShowS)
-> (SnapshotCreateSettings -> String)
-> ([SnapshotCreateSettings] -> ShowS)
-> Show SnapshotCreateSettings
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SnapshotCreateSettings] -> ShowS
$cshowList :: [SnapshotCreateSettings] -> ShowS
show :: SnapshotCreateSettings -> String
$cshow :: SnapshotCreateSettings -> String
showsPrec :: Int -> SnapshotCreateSettings -> ShowS
$cshowsPrec :: Int -> SnapshotCreateSettings -> ShowS
Show)
defaultSnapshotCreateSettings :: SnapshotCreateSettings
defaultSnapshotCreateSettings :: SnapshotCreateSettings
defaultSnapshotCreateSettings = SnapshotCreateSettings :: Bool
-> Maybe IndexSelection
-> Bool
-> Bool
-> Bool
-> SnapshotCreateSettings
SnapshotCreateSettings {
snapWaitForCompletion :: Bool
snapWaitForCompletion = Bool
False
, snapIndices :: Maybe IndexSelection
snapIndices = Maybe IndexSelection
forall a. Maybe a
Nothing
, snapIgnoreUnavailable :: Bool
snapIgnoreUnavailable = Bool
False
, snapIncludeGlobalState :: Bool
snapIncludeGlobalState = Bool
True
, snapPartial :: Bool
snapPartial = Bool
False
}
data SnapshotSelection =
SnapshotList (NonEmpty SnapshotPattern)
| AllSnapshots
deriving (SnapshotSelection -> SnapshotSelection -> Bool
(SnapshotSelection -> SnapshotSelection -> Bool)
-> (SnapshotSelection -> SnapshotSelection -> Bool)
-> Eq SnapshotSelection
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SnapshotSelection -> SnapshotSelection -> Bool
$c/= :: SnapshotSelection -> SnapshotSelection -> Bool
== :: SnapshotSelection -> SnapshotSelection -> Bool
$c== :: SnapshotSelection -> SnapshotSelection -> Bool
Eq, Int -> SnapshotSelection -> ShowS
[SnapshotSelection] -> ShowS
SnapshotSelection -> String
(Int -> SnapshotSelection -> ShowS)
-> (SnapshotSelection -> String)
-> ([SnapshotSelection] -> ShowS)
-> Show SnapshotSelection
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SnapshotSelection] -> ShowS
$cshowList :: [SnapshotSelection] -> ShowS
show :: SnapshotSelection -> String
$cshow :: SnapshotSelection -> String
showsPrec :: Int -> SnapshotSelection -> ShowS
$cshowsPrec :: Int -> SnapshotSelection -> ShowS
Show)
data SnapshotPattern =
ExactSnap SnapshotName
| SnapPattern Text
deriving (SnapshotPattern -> SnapshotPattern -> Bool
(SnapshotPattern -> SnapshotPattern -> Bool)
-> (SnapshotPattern -> SnapshotPattern -> Bool)
-> Eq SnapshotPattern
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SnapshotPattern -> SnapshotPattern -> Bool
$c/= :: SnapshotPattern -> SnapshotPattern -> Bool
== :: SnapshotPattern -> SnapshotPattern -> Bool
$c== :: SnapshotPattern -> SnapshotPattern -> Bool
Eq, Int -> SnapshotPattern -> ShowS
[SnapshotPattern] -> ShowS
SnapshotPattern -> String
(Int -> SnapshotPattern -> ShowS)
-> (SnapshotPattern -> String)
-> ([SnapshotPattern] -> ShowS)
-> Show SnapshotPattern
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SnapshotPattern] -> ShowS
$cshowList :: [SnapshotPattern] -> ShowS
show :: SnapshotPattern -> String
$cshow :: SnapshotPattern -> String
showsPrec :: Int -> SnapshotPattern -> ShowS
$cshowsPrec :: Int -> SnapshotPattern -> ShowS
Show)
data SnapshotInfo = SnapshotInfo {
SnapshotInfo -> ShardResult
snapInfoShards :: ShardResult
, SnapshotInfo -> [SnapshotShardFailure]
snapInfoFailures :: [SnapshotShardFailure]
, SnapshotInfo -> NominalDiffTime
snapInfoDuration :: NominalDiffTime
, SnapshotInfo -> UTCTime
snapInfoEndTime :: UTCTime
, SnapshotInfo -> UTCTime
snapInfoStartTime :: UTCTime
, SnapshotInfo -> SnapshotState
snapInfoState :: SnapshotState
, SnapshotInfo -> [IndexName]
snapInfoIndices :: [IndexName]
, SnapshotInfo -> SnapshotName
snapInfoName :: SnapshotName
} deriving (SnapshotInfo -> SnapshotInfo -> Bool
(SnapshotInfo -> SnapshotInfo -> Bool)
-> (SnapshotInfo -> SnapshotInfo -> Bool) -> Eq SnapshotInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SnapshotInfo -> SnapshotInfo -> Bool
$c/= :: SnapshotInfo -> SnapshotInfo -> Bool
== :: SnapshotInfo -> SnapshotInfo -> Bool
$c== :: SnapshotInfo -> SnapshotInfo -> Bool
Eq, Int -> SnapshotInfo -> ShowS
[SnapshotInfo] -> ShowS
SnapshotInfo -> String
(Int -> SnapshotInfo -> ShowS)
-> (SnapshotInfo -> String)
-> ([SnapshotInfo] -> ShowS)
-> Show SnapshotInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SnapshotInfo] -> ShowS
$cshowList :: [SnapshotInfo] -> ShowS
show :: SnapshotInfo -> String
$cshow :: SnapshotInfo -> String
showsPrec :: Int -> SnapshotInfo -> ShowS
$cshowsPrec :: Int -> SnapshotInfo -> ShowS
Show)
instance FromJSON SnapshotInfo where
parseJSON :: Value -> Parser SnapshotInfo
parseJSON = String
-> (Object -> Parser SnapshotInfo) -> Value -> Parser SnapshotInfo
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"SnapshotInfo" Object -> Parser SnapshotInfo
parse
where
parse :: Object -> Parser SnapshotInfo
parse Object
o = ShardResult
-> [SnapshotShardFailure]
-> NominalDiffTime
-> UTCTime
-> UTCTime
-> SnapshotState
-> [IndexName]
-> SnapshotName
-> SnapshotInfo
SnapshotInfo (ShardResult
-> [SnapshotShardFailure]
-> NominalDiffTime
-> UTCTime
-> UTCTime
-> SnapshotState
-> [IndexName]
-> SnapshotName
-> SnapshotInfo)
-> Parser ShardResult
-> Parser
([SnapshotShardFailure]
-> NominalDiffTime
-> UTCTime
-> UTCTime
-> SnapshotState
-> [IndexName]
-> SnapshotName
-> SnapshotInfo)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser ShardResult
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"shards"
Parser
([SnapshotShardFailure]
-> NominalDiffTime
-> UTCTime
-> UTCTime
-> SnapshotState
-> [IndexName]
-> SnapshotName
-> SnapshotInfo)
-> Parser [SnapshotShardFailure]
-> Parser
(NominalDiffTime
-> UTCTime
-> UTCTime
-> SnapshotState
-> [IndexName]
-> SnapshotName
-> SnapshotInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser [SnapshotShardFailure]
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"failures"
Parser
(NominalDiffTime
-> UTCTime
-> UTCTime
-> SnapshotState
-> [IndexName]
-> SnapshotName
-> SnapshotInfo)
-> Parser NominalDiffTime
-> Parser
(UTCTime
-> UTCTime
-> SnapshotState
-> [IndexName]
-> SnapshotName
-> SnapshotInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (MS -> NominalDiffTime
unMS (MS -> NominalDiffTime) -> Parser MS -> Parser NominalDiffTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser MS
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"duration_in_millis")
Parser
(UTCTime
-> UTCTime
-> SnapshotState
-> [IndexName]
-> SnapshotName
-> SnapshotInfo)
-> Parser UTCTime
-> Parser
(UTCTime
-> SnapshotState -> [IndexName] -> SnapshotName -> SnapshotInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (POSIXMS -> UTCTime
posixMS (POSIXMS -> UTCTime) -> Parser POSIXMS -> Parser UTCTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser POSIXMS
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"end_time_in_millis")
Parser
(UTCTime
-> SnapshotState -> [IndexName] -> SnapshotName -> SnapshotInfo)
-> Parser UTCTime
-> Parser
(SnapshotState -> [IndexName] -> SnapshotName -> SnapshotInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (POSIXMS -> UTCTime
posixMS (POSIXMS -> UTCTime) -> Parser POSIXMS -> Parser UTCTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser POSIXMS
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"start_time_in_millis")
Parser
(SnapshotState -> [IndexName] -> SnapshotName -> SnapshotInfo)
-> Parser SnapshotState
-> Parser ([IndexName] -> SnapshotName -> SnapshotInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser SnapshotState
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"state"
Parser ([IndexName] -> SnapshotName -> SnapshotInfo)
-> Parser [IndexName] -> Parser (SnapshotName -> SnapshotInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser [IndexName]
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"indices"
Parser (SnapshotName -> SnapshotInfo)
-> Parser SnapshotName -> Parser SnapshotInfo
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser SnapshotName
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"snapshot"
data SnapshotShardFailure = SnapshotShardFailure {
SnapshotShardFailure -> IndexName
snapShardFailureIndex :: IndexName
, SnapshotShardFailure -> Maybe NodeName
snapShardFailureNodeId :: Maybe NodeName
, SnapshotShardFailure -> Text
snapShardFailureReason :: Text
, SnapshotShardFailure -> ShardId
snapShardFailureShardId :: ShardId
} deriving (SnapshotShardFailure -> SnapshotShardFailure -> Bool
(SnapshotShardFailure -> SnapshotShardFailure -> Bool)
-> (SnapshotShardFailure -> SnapshotShardFailure -> Bool)
-> Eq SnapshotShardFailure
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SnapshotShardFailure -> SnapshotShardFailure -> Bool
$c/= :: SnapshotShardFailure -> SnapshotShardFailure -> Bool
== :: SnapshotShardFailure -> SnapshotShardFailure -> Bool
$c== :: SnapshotShardFailure -> SnapshotShardFailure -> Bool
Eq, Int -> SnapshotShardFailure -> ShowS
[SnapshotShardFailure] -> ShowS
SnapshotShardFailure -> String
(Int -> SnapshotShardFailure -> ShowS)
-> (SnapshotShardFailure -> String)
-> ([SnapshotShardFailure] -> ShowS)
-> Show SnapshotShardFailure
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SnapshotShardFailure] -> ShowS
$cshowList :: [SnapshotShardFailure] -> ShowS
show :: SnapshotShardFailure -> String
$cshow :: SnapshotShardFailure -> String
showsPrec :: Int -> SnapshotShardFailure -> ShowS
$cshowsPrec :: Int -> SnapshotShardFailure -> ShowS
Show)
instance FromJSON SnapshotShardFailure where
parseJSON :: Value -> Parser SnapshotShardFailure
parseJSON = String
-> (Object -> Parser SnapshotShardFailure)
-> Value
-> Parser SnapshotShardFailure
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"SnapshotShardFailure" Object -> Parser SnapshotShardFailure
parse
where
parse :: Object -> Parser SnapshotShardFailure
parse Object
o = IndexName
-> Maybe NodeName -> Text -> ShardId -> SnapshotShardFailure
SnapshotShardFailure (IndexName
-> Maybe NodeName -> Text -> ShardId -> SnapshotShardFailure)
-> Parser IndexName
-> Parser
(Maybe NodeName -> Text -> ShardId -> SnapshotShardFailure)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser IndexName
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"index"
Parser (Maybe NodeName -> Text -> ShardId -> SnapshotShardFailure)
-> Parser (Maybe NodeName)
-> Parser (Text -> ShardId -> SnapshotShardFailure)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe NodeName)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"node_id"
Parser (Text -> ShardId -> SnapshotShardFailure)
-> Parser Text -> Parser (ShardId -> SnapshotShardFailure)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"reason"
Parser (ShardId -> SnapshotShardFailure)
-> Parser ShardId -> Parser SnapshotShardFailure
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser ShardId
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"shard_id"
newtype RestoreRenamePattern =
RestoreRenamePattern { RestoreRenamePattern -> Text
rrPattern :: Text }
deriving (RestoreRenamePattern -> RestoreRenamePattern -> Bool
(RestoreRenamePattern -> RestoreRenamePattern -> Bool)
-> (RestoreRenamePattern -> RestoreRenamePattern -> Bool)
-> Eq RestoreRenamePattern
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RestoreRenamePattern -> RestoreRenamePattern -> Bool
$c/= :: RestoreRenamePattern -> RestoreRenamePattern -> Bool
== :: RestoreRenamePattern -> RestoreRenamePattern -> Bool
$c== :: RestoreRenamePattern -> RestoreRenamePattern -> Bool
Eq, Int -> RestoreRenamePattern -> ShowS
[RestoreRenamePattern] -> ShowS
RestoreRenamePattern -> String
(Int -> RestoreRenamePattern -> ShowS)
-> (RestoreRenamePattern -> String)
-> ([RestoreRenamePattern] -> ShowS)
-> Show RestoreRenamePattern
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RestoreRenamePattern] -> ShowS
$cshowList :: [RestoreRenamePattern] -> ShowS
show :: RestoreRenamePattern -> String
$cshow :: RestoreRenamePattern -> String
showsPrec :: Int -> RestoreRenamePattern -> ShowS
$cshowsPrec :: Int -> RestoreRenamePattern -> ShowS
Show, Eq RestoreRenamePattern
Eq RestoreRenamePattern
-> (RestoreRenamePattern -> RestoreRenamePattern -> Ordering)
-> (RestoreRenamePattern -> RestoreRenamePattern -> Bool)
-> (RestoreRenamePattern -> RestoreRenamePattern -> Bool)
-> (RestoreRenamePattern -> RestoreRenamePattern -> Bool)
-> (RestoreRenamePattern -> RestoreRenamePattern -> Bool)
-> (RestoreRenamePattern
-> RestoreRenamePattern -> RestoreRenamePattern)
-> (RestoreRenamePattern
-> RestoreRenamePattern -> RestoreRenamePattern)
-> Ord RestoreRenamePattern
RestoreRenamePattern -> RestoreRenamePattern -> Bool
RestoreRenamePattern -> RestoreRenamePattern -> Ordering
RestoreRenamePattern
-> RestoreRenamePattern -> RestoreRenamePattern
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 :: RestoreRenamePattern
-> RestoreRenamePattern -> RestoreRenamePattern
$cmin :: RestoreRenamePattern
-> RestoreRenamePattern -> RestoreRenamePattern
max :: RestoreRenamePattern
-> RestoreRenamePattern -> RestoreRenamePattern
$cmax :: RestoreRenamePattern
-> RestoreRenamePattern -> RestoreRenamePattern
>= :: RestoreRenamePattern -> RestoreRenamePattern -> Bool
$c>= :: RestoreRenamePattern -> RestoreRenamePattern -> Bool
> :: RestoreRenamePattern -> RestoreRenamePattern -> Bool
$c> :: RestoreRenamePattern -> RestoreRenamePattern -> Bool
<= :: RestoreRenamePattern -> RestoreRenamePattern -> Bool
$c<= :: RestoreRenamePattern -> RestoreRenamePattern -> Bool
< :: RestoreRenamePattern -> RestoreRenamePattern -> Bool
$c< :: RestoreRenamePattern -> RestoreRenamePattern -> Bool
compare :: RestoreRenamePattern -> RestoreRenamePattern -> Ordering
$ccompare :: RestoreRenamePattern -> RestoreRenamePattern -> Ordering
$cp1Ord :: Eq RestoreRenamePattern
Ord, [RestoreRenamePattern] -> Encoding
[RestoreRenamePattern] -> Value
RestoreRenamePattern -> Encoding
RestoreRenamePattern -> Value
(RestoreRenamePattern -> Value)
-> (RestoreRenamePattern -> Encoding)
-> ([RestoreRenamePattern] -> Value)
-> ([RestoreRenamePattern] -> Encoding)
-> ToJSON RestoreRenamePattern
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [RestoreRenamePattern] -> Encoding
$ctoEncodingList :: [RestoreRenamePattern] -> Encoding
toJSONList :: [RestoreRenamePattern] -> Value
$ctoJSONList :: [RestoreRenamePattern] -> Value
toEncoding :: RestoreRenamePattern -> Encoding
$ctoEncoding :: RestoreRenamePattern -> Encoding
toJSON :: RestoreRenamePattern -> Value
$ctoJSON :: RestoreRenamePattern -> Value
ToJSON)
data RestoreRenameToken = RRTLit Text
| RRSubWholeMatch
| RRSubGroup RRGroupRefNum
deriving (RestoreRenameToken -> RestoreRenameToken -> Bool
(RestoreRenameToken -> RestoreRenameToken -> Bool)
-> (RestoreRenameToken -> RestoreRenameToken -> Bool)
-> Eq RestoreRenameToken
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RestoreRenameToken -> RestoreRenameToken -> Bool
$c/= :: RestoreRenameToken -> RestoreRenameToken -> Bool
== :: RestoreRenameToken -> RestoreRenameToken -> Bool
$c== :: RestoreRenameToken -> RestoreRenameToken -> Bool
Eq, Int -> RestoreRenameToken -> ShowS
[RestoreRenameToken] -> ShowS
RestoreRenameToken -> String
(Int -> RestoreRenameToken -> ShowS)
-> (RestoreRenameToken -> String)
-> ([RestoreRenameToken] -> ShowS)
-> Show RestoreRenameToken
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RestoreRenameToken] -> ShowS
$cshowList :: [RestoreRenameToken] -> ShowS
show :: RestoreRenameToken -> String
$cshow :: RestoreRenameToken -> String
showsPrec :: Int -> RestoreRenameToken -> ShowS
$cshowsPrec :: Int -> RestoreRenameToken -> ShowS
Show)
newtype RRGroupRefNum =
RRGroupRefNum { RRGroupRefNum -> Int
rrGroupRefNum :: Int }
deriving (RRGroupRefNum -> RRGroupRefNum -> Bool
(RRGroupRefNum -> RRGroupRefNum -> Bool)
-> (RRGroupRefNum -> RRGroupRefNum -> Bool) -> Eq RRGroupRefNum
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RRGroupRefNum -> RRGroupRefNum -> Bool
$c/= :: RRGroupRefNum -> RRGroupRefNum -> Bool
== :: RRGroupRefNum -> RRGroupRefNum -> Bool
$c== :: RRGroupRefNum -> RRGroupRefNum -> Bool
Eq, Eq RRGroupRefNum
Eq RRGroupRefNum
-> (RRGroupRefNum -> RRGroupRefNum -> Ordering)
-> (RRGroupRefNum -> RRGroupRefNum -> Bool)
-> (RRGroupRefNum -> RRGroupRefNum -> Bool)
-> (RRGroupRefNum -> RRGroupRefNum -> Bool)
-> (RRGroupRefNum -> RRGroupRefNum -> Bool)
-> (RRGroupRefNum -> RRGroupRefNum -> RRGroupRefNum)
-> (RRGroupRefNum -> RRGroupRefNum -> RRGroupRefNum)
-> Ord RRGroupRefNum
RRGroupRefNum -> RRGroupRefNum -> Bool
RRGroupRefNum -> RRGroupRefNum -> Ordering
RRGroupRefNum -> RRGroupRefNum -> RRGroupRefNum
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 :: RRGroupRefNum -> RRGroupRefNum -> RRGroupRefNum
$cmin :: RRGroupRefNum -> RRGroupRefNum -> RRGroupRefNum
max :: RRGroupRefNum -> RRGroupRefNum -> RRGroupRefNum
$cmax :: RRGroupRefNum -> RRGroupRefNum -> RRGroupRefNum
>= :: RRGroupRefNum -> RRGroupRefNum -> Bool
$c>= :: RRGroupRefNum -> RRGroupRefNum -> Bool
> :: RRGroupRefNum -> RRGroupRefNum -> Bool
$c> :: RRGroupRefNum -> RRGroupRefNum -> Bool
<= :: RRGroupRefNum -> RRGroupRefNum -> Bool
$c<= :: RRGroupRefNum -> RRGroupRefNum -> Bool
< :: RRGroupRefNum -> RRGroupRefNum -> Bool
$c< :: RRGroupRefNum -> RRGroupRefNum -> Bool
compare :: RRGroupRefNum -> RRGroupRefNum -> Ordering
$ccompare :: RRGroupRefNum -> RRGroupRefNum -> Ordering
$cp1Ord :: Eq RRGroupRefNum
Ord, Int -> RRGroupRefNum -> ShowS
[RRGroupRefNum] -> ShowS
RRGroupRefNum -> String
(Int -> RRGroupRefNum -> ShowS)
-> (RRGroupRefNum -> String)
-> ([RRGroupRefNum] -> ShowS)
-> Show RRGroupRefNum
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RRGroupRefNum] -> ShowS
$cshowList :: [RRGroupRefNum] -> ShowS
show :: RRGroupRefNum -> String
$cshow :: RRGroupRefNum -> String
showsPrec :: Int -> RRGroupRefNum -> ShowS
$cshowsPrec :: Int -> RRGroupRefNum -> ShowS
Show)
instance Bounded RRGroupRefNum where
minBound :: RRGroupRefNum
minBound = Int -> RRGroupRefNum
RRGroupRefNum Int
1
maxBound :: RRGroupRefNum
maxBound = Int -> RRGroupRefNum
RRGroupRefNum Int
9
mkRRGroupRefNum :: Int -> Maybe RRGroupRefNum
mkRRGroupRefNum :: Int -> Maybe RRGroupRefNum
mkRRGroupRefNum Int
i
| Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= RRGroupRefNum -> Int
rrGroupRefNum RRGroupRefNum
forall a. Bounded a => a
minBound
Bool -> Bool -> Bool
&& Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= RRGroupRefNum -> Int
rrGroupRefNum RRGroupRefNum
forall a. Bounded a => a
maxBound =
RRGroupRefNum -> Maybe RRGroupRefNum
forall a. a -> Maybe a
Just (RRGroupRefNum -> Maybe RRGroupRefNum)
-> RRGroupRefNum -> Maybe RRGroupRefNum
forall a b. (a -> b) -> a -> b
$ Int -> RRGroupRefNum
RRGroupRefNum Int
i
| Bool
otherwise = Maybe RRGroupRefNum
forall a. Maybe a
Nothing
defaultSnapshotRestoreSettings :: SnapshotRestoreSettings
defaultSnapshotRestoreSettings :: SnapshotRestoreSettings
defaultSnapshotRestoreSettings = SnapshotRestoreSettings :: Bool
-> Maybe IndexSelection
-> Bool
-> Bool
-> Maybe RestoreRenamePattern
-> Maybe (NonEmpty RestoreRenameToken)
-> Bool
-> Bool
-> Maybe RestoreIndexSettings
-> Maybe (NonEmpty Text)
-> SnapshotRestoreSettings
SnapshotRestoreSettings {
snapRestoreWaitForCompletion :: Bool
snapRestoreWaitForCompletion = Bool
False
, snapRestoreIndices :: Maybe IndexSelection
snapRestoreIndices = Maybe IndexSelection
forall a. Maybe a
Nothing
, snapRestoreIgnoreUnavailable :: Bool
snapRestoreIgnoreUnavailable = Bool
False
, snapRestoreIncludeGlobalState :: Bool
snapRestoreIncludeGlobalState = Bool
True
, snapRestoreRenamePattern :: Maybe RestoreRenamePattern
snapRestoreRenamePattern = Maybe RestoreRenamePattern
forall a. Maybe a
Nothing
, snapRestoreRenameReplacement :: Maybe (NonEmpty RestoreRenameToken)
snapRestoreRenameReplacement = Maybe (NonEmpty RestoreRenameToken)
forall a. Maybe a
Nothing
, snapRestorePartial :: Bool
snapRestorePartial = Bool
False
, snapRestoreIncludeAliases :: Bool
snapRestoreIncludeAliases = Bool
True
, snapRestoreIndexSettingsOverrides :: Maybe RestoreIndexSettings
snapRestoreIndexSettingsOverrides = Maybe RestoreIndexSettings
forall a. Maybe a
Nothing
, snapRestoreIgnoreIndexSettings :: Maybe (NonEmpty Text)
snapRestoreIgnoreIndexSettings = Maybe (NonEmpty Text)
forall a. Maybe a
Nothing
}
newtype RestoreIndexSettings = RestoreIndexSettings
{ RestoreIndexSettings -> Maybe ReplicaCount
restoreOverrideReplicas :: Maybe ReplicaCount
} deriving (RestoreIndexSettings -> RestoreIndexSettings -> Bool
(RestoreIndexSettings -> RestoreIndexSettings -> Bool)
-> (RestoreIndexSettings -> RestoreIndexSettings -> Bool)
-> Eq RestoreIndexSettings
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RestoreIndexSettings -> RestoreIndexSettings -> Bool
$c/= :: RestoreIndexSettings -> RestoreIndexSettings -> Bool
== :: RestoreIndexSettings -> RestoreIndexSettings -> Bool
$c== :: RestoreIndexSettings -> RestoreIndexSettings -> Bool
Eq, Int -> RestoreIndexSettings -> ShowS
[RestoreIndexSettings] -> ShowS
RestoreIndexSettings -> String
(Int -> RestoreIndexSettings -> ShowS)
-> (RestoreIndexSettings -> String)
-> ([RestoreIndexSettings] -> ShowS)
-> Show RestoreIndexSettings
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RestoreIndexSettings] -> ShowS
$cshowList :: [RestoreIndexSettings] -> ShowS
show :: RestoreIndexSettings -> String
$cshow :: RestoreIndexSettings -> String
showsPrec :: Int -> RestoreIndexSettings -> ShowS
$cshowsPrec :: Int -> RestoreIndexSettings -> ShowS
Show)
instance ToJSON RestoreIndexSettings where
toJSON :: RestoreIndexSettings -> Value
toJSON RestoreIndexSettings {Maybe ReplicaCount
restoreOverrideReplicas :: Maybe ReplicaCount
restoreOverrideReplicas :: RestoreIndexSettings -> Maybe ReplicaCount
..} = [Pair] -> Value
object [Pair]
prs
where
prs :: [Pair]
prs = [Maybe Pair] -> [Pair]
forall a. [Maybe a] -> [a]
catMaybes [(Key
"index.number_of_replicas" Key -> ReplicaCount -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.=) (ReplicaCount -> Pair) -> Maybe ReplicaCount -> Maybe Pair
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe ReplicaCount
restoreOverrideReplicas]
instance FromJSON NodesInfo where
parseJSON :: Value -> Parser NodesInfo
parseJSON = String -> (Object -> Parser NodesInfo) -> Value -> Parser NodesInfo
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"NodesInfo" Object -> Parser NodesInfo
parse
where
parse :: Object -> Parser NodesInfo
parse Object
o = do
HashMap Text Value
nodes <- Object
o Object -> Key -> Parser (HashMap Text Value)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"nodes"
[NodeInfo]
infos <- [(Text, Value)]
-> ((Text, Value) -> Parser NodeInfo) -> Parser [NodeInfo]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM (HashMap Text Value -> [(Text, Value)]
forall k v. HashMap k v -> [(k, v)]
HM.toList HashMap Text Value
nodes) (((Text, Value) -> Parser NodeInfo) -> Parser [NodeInfo])
-> ((Text, Value) -> Parser NodeInfo) -> Parser [NodeInfo]
forall a b. (a -> b) -> a -> b
$ \(Text
fullNID, Value
v) -> do
Object
node <- Value -> Parser Object
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v
FullNodeId -> Object -> Parser NodeInfo
parseNodeInfo (Text -> FullNodeId
FullNodeId Text
fullNID) Object
node
ClusterName
cn <- Object
o Object -> Key -> Parser ClusterName
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"cluster_name"
NodesInfo -> Parser NodesInfo
forall (m :: * -> *) a. Monad m => a -> m a
return ([NodeInfo] -> ClusterName -> NodesInfo
NodesInfo [NodeInfo]
infos ClusterName
cn)
instance FromJSON NodesStats where
parseJSON :: Value -> Parser NodesStats
parseJSON = String
-> (Object -> Parser NodesStats) -> Value -> Parser NodesStats
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"NodesStats" Object -> Parser NodesStats
parse
where
parse :: Object -> Parser NodesStats
parse Object
o = do
HashMap Text Value
nodes <- Object
o Object -> Key -> Parser (HashMap Text Value)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"nodes"
[NodeStats]
stats <- [(Text, Value)]
-> ((Text, Value) -> Parser NodeStats) -> Parser [NodeStats]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM (HashMap Text Value -> [(Text, Value)]
forall k v. HashMap k v -> [(k, v)]
HM.toList HashMap Text Value
nodes) (((Text, Value) -> Parser NodeStats) -> Parser [NodeStats])
-> ((Text, Value) -> Parser NodeStats) -> Parser [NodeStats]
forall a b. (a -> b) -> a -> b
$ \(Text
fullNID, Value
v) -> do
Object
node <- Value -> Parser Object
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v
FullNodeId -> Object -> Parser NodeStats
parseNodeStats (Text -> FullNodeId
FullNodeId Text
fullNID) Object
node
ClusterName
cn <- Object
o Object -> Key -> Parser ClusterName
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"cluster_name"
NodesStats -> Parser NodesStats
forall (m :: * -> *) a. Monad m => a -> m a
return ([NodeStats] -> ClusterName -> NodesStats
NodesStats [NodeStats]
stats ClusterName
cn)
instance FromJSON NodeBreakerStats where
parseJSON :: Value -> Parser NodeBreakerStats
parseJSON = String
-> (Object -> Parser NodeBreakerStats)
-> Value
-> Parser NodeBreakerStats
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"NodeBreakerStats" Object -> Parser NodeBreakerStats
parse
where
parse :: Object -> Parser NodeBreakerStats
parse Object
o = Int -> Double -> Bytes -> Bytes -> NodeBreakerStats
NodeBreakerStats (Int -> Double -> Bytes -> Bytes -> NodeBreakerStats)
-> Parser Int
-> Parser (Double -> Bytes -> Bytes -> NodeBreakerStats)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"tripped"
Parser (Double -> Bytes -> Bytes -> NodeBreakerStats)
-> Parser Double -> Parser (Bytes -> Bytes -> NodeBreakerStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Double
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"overhead"
Parser (Bytes -> Bytes -> NodeBreakerStats)
-> Parser Bytes -> Parser (Bytes -> NodeBreakerStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Bytes
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"estimated_size_in_bytes"
Parser (Bytes -> NodeBreakerStats)
-> Parser Bytes -> Parser NodeBreakerStats
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Bytes
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"limit_size_in_bytes"
instance FromJSON NodeHTTPStats where
parseJSON :: Value -> Parser NodeHTTPStats
parseJSON = String
-> (Object -> Parser NodeHTTPStats)
-> Value
-> Parser NodeHTTPStats
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"NodeHTTPStats" Object -> Parser NodeHTTPStats
parse
where
parse :: Object -> Parser NodeHTTPStats
parse Object
o = Int -> Int -> NodeHTTPStats
NodeHTTPStats (Int -> Int -> NodeHTTPStats)
-> Parser Int -> Parser (Int -> NodeHTTPStats)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"total_opened"
Parser (Int -> NodeHTTPStats) -> Parser Int -> Parser NodeHTTPStats
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"current_open"
instance FromJSON NodeTransportStats where
parseJSON :: Value -> Parser NodeTransportStats
parseJSON = String
-> (Object -> Parser NodeTransportStats)
-> Value
-> Parser NodeTransportStats
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"NodeTransportStats" Object -> Parser NodeTransportStats
parse
where
parse :: Object -> Parser NodeTransportStats
parse Object
o = Bytes -> Int -> Bytes -> Int -> Int -> NodeTransportStats
NodeTransportStats (Bytes -> Int -> Bytes -> Int -> Int -> NodeTransportStats)
-> Parser Bytes
-> Parser (Int -> Bytes -> Int -> Int -> NodeTransportStats)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser Bytes
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"tx_size_in_bytes"
Parser (Int -> Bytes -> Int -> Int -> NodeTransportStats)
-> Parser Int -> Parser (Bytes -> Int -> Int -> NodeTransportStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"tx_count"
Parser (Bytes -> Int -> Int -> NodeTransportStats)
-> Parser Bytes -> Parser (Int -> Int -> NodeTransportStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Bytes
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"rx_size_in_bytes"
Parser (Int -> Int -> NodeTransportStats)
-> Parser Int -> Parser (Int -> NodeTransportStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"rx_count"
Parser (Int -> NodeTransportStats)
-> Parser Int -> Parser NodeTransportStats
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"server_open"
instance FromJSON NodeFSStats where
parseJSON :: Value -> Parser NodeFSStats
parseJSON = String
-> (Object -> Parser NodeFSStats) -> Value -> Parser NodeFSStats
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"NodeFSStats" Object -> Parser NodeFSStats
parse
where
parse :: Object -> Parser NodeFSStats
parse Object
o = [NodeDataPathStats] -> NodeFSTotalStats -> UTCTime -> NodeFSStats
NodeFSStats ([NodeDataPathStats] -> NodeFSTotalStats -> UTCTime -> NodeFSStats)
-> Parser [NodeDataPathStats]
-> Parser (NodeFSTotalStats -> UTCTime -> NodeFSStats)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser [NodeDataPathStats]
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"data"
Parser (NodeFSTotalStats -> UTCTime -> NodeFSStats)
-> Parser NodeFSTotalStats -> Parser (UTCTime -> NodeFSStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser NodeFSTotalStats
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"total"
Parser (UTCTime -> NodeFSStats)
-> Parser UTCTime -> Parser NodeFSStats
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (POSIXMS -> UTCTime
posixMS (POSIXMS -> UTCTime) -> Parser POSIXMS -> Parser UTCTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser POSIXMS
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"timestamp")
instance FromJSON NodeDataPathStats where
parseJSON :: Value -> Parser NodeDataPathStats
parseJSON = String
-> (Object -> Parser NodeDataPathStats)
-> Value
-> Parser NodeDataPathStats
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"NodeDataPathStats" Object -> Parser NodeDataPathStats
parse
where
parse :: Object -> Parser NodeDataPathStats
parse Object
o =
Maybe Double
-> Maybe Double
-> Maybe Bytes
-> Maybe Bytes
-> Maybe Bytes
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Bytes
-> Bytes
-> Bytes
-> Maybe Text
-> Maybe Text
-> Text
-> Text
-> NodeDataPathStats
NodeDataPathStats (Maybe Double
-> Maybe Double
-> Maybe Bytes
-> Maybe Bytes
-> Maybe Bytes
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Bytes
-> Bytes
-> Bytes
-> Maybe Text
-> Maybe Text
-> Text
-> Text
-> NodeDataPathStats)
-> Parser (Maybe Double)
-> Parser
(Maybe Double
-> Maybe Bytes
-> Maybe Bytes
-> Maybe Bytes
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Bytes
-> Bytes
-> Bytes
-> Maybe Text
-> Maybe Text
-> Text
-> Text
-> NodeDataPathStats)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((StringlyTypedDouble -> Double)
-> Maybe StringlyTypedDouble -> Maybe Double
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap StringlyTypedDouble -> Double
unStringlyTypedDouble (Maybe StringlyTypedDouble -> Maybe Double)
-> Parser (Maybe StringlyTypedDouble) -> Parser (Maybe Double)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser (Maybe StringlyTypedDouble)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"disk_service_time")
Parser
(Maybe Double
-> Maybe Bytes
-> Maybe Bytes
-> Maybe Bytes
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Bytes
-> Bytes
-> Bytes
-> Maybe Text
-> Maybe Text
-> Text
-> Text
-> NodeDataPathStats)
-> Parser (Maybe Double)
-> Parser
(Maybe Bytes
-> Maybe Bytes
-> Maybe Bytes
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Bytes
-> Bytes
-> Bytes
-> Maybe Text
-> Maybe Text
-> Text
-> Text
-> NodeDataPathStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ((StringlyTypedDouble -> Double)
-> Maybe StringlyTypedDouble -> Maybe Double
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap StringlyTypedDouble -> Double
unStringlyTypedDouble (Maybe StringlyTypedDouble -> Maybe Double)
-> Parser (Maybe StringlyTypedDouble) -> Parser (Maybe Double)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser (Maybe StringlyTypedDouble)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"disk_queue")
Parser
(Maybe Bytes
-> Maybe Bytes
-> Maybe Bytes
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Bytes
-> Bytes
-> Bytes
-> Maybe Text
-> Maybe Text
-> Text
-> Text
-> NodeDataPathStats)
-> Parser (Maybe Bytes)
-> Parser
(Maybe Bytes
-> Maybe Bytes
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Bytes
-> Bytes
-> Bytes
-> Maybe Text
-> Maybe Text
-> Text
-> Text
-> NodeDataPathStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Bytes)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"disk_io_size_in_bytes"
Parser
(Maybe Bytes
-> Maybe Bytes
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Bytes
-> Bytes
-> Bytes
-> Maybe Text
-> Maybe Text
-> Text
-> Text
-> NodeDataPathStats)
-> Parser (Maybe Bytes)
-> Parser
(Maybe Bytes
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Bytes
-> Bytes
-> Bytes
-> Maybe Text
-> Maybe Text
-> Text
-> Text
-> NodeDataPathStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Bytes)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"disk_write_size_in_bytes"
Parser
(Maybe Bytes
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Bytes
-> Bytes
-> Bytes
-> Maybe Text
-> Maybe Text
-> Text
-> Text
-> NodeDataPathStats)
-> Parser (Maybe Bytes)
-> Parser
(Maybe Int
-> Maybe Int
-> Maybe Int
-> Bytes
-> Bytes
-> Bytes
-> Maybe Text
-> Maybe Text
-> Text
-> Text
-> NodeDataPathStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Bytes)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"disk_read_size_in_bytes"
Parser
(Maybe Int
-> Maybe Int
-> Maybe Int
-> Bytes
-> Bytes
-> Bytes
-> Maybe Text
-> Maybe Text
-> Text
-> Text
-> NodeDataPathStats)
-> Parser (Maybe Int)
-> Parser
(Maybe Int
-> Maybe Int
-> Bytes
-> Bytes
-> Bytes
-> Maybe Text
-> Maybe Text
-> Text
-> Text
-> NodeDataPathStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"disk_io_op"
Parser
(Maybe Int
-> Maybe Int
-> Bytes
-> Bytes
-> Bytes
-> Maybe Text
-> Maybe Text
-> Text
-> Text
-> NodeDataPathStats)
-> Parser (Maybe Int)
-> Parser
(Maybe Int
-> Bytes
-> Bytes
-> Bytes
-> Maybe Text
-> Maybe Text
-> Text
-> Text
-> NodeDataPathStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"disk_writes"
Parser
(Maybe Int
-> Bytes
-> Bytes
-> Bytes
-> Maybe Text
-> Maybe Text
-> Text
-> Text
-> NodeDataPathStats)
-> Parser (Maybe Int)
-> Parser
(Bytes
-> Bytes
-> Bytes
-> Maybe Text
-> Maybe Text
-> Text
-> Text
-> NodeDataPathStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"disk_reads"
Parser
(Bytes
-> Bytes
-> Bytes
-> Maybe Text
-> Maybe Text
-> Text
-> Text
-> NodeDataPathStats)
-> Parser Bytes
-> Parser
(Bytes
-> Bytes
-> Maybe Text
-> Maybe Text
-> Text
-> Text
-> NodeDataPathStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Bytes
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"available_in_bytes"
Parser
(Bytes
-> Bytes
-> Maybe Text
-> Maybe Text
-> Text
-> Text
-> NodeDataPathStats)
-> Parser Bytes
-> Parser
(Bytes
-> Maybe Text -> Maybe Text -> Text -> Text -> NodeDataPathStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Bytes
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"free_in_bytes"
Parser
(Bytes
-> Maybe Text -> Maybe Text -> Text -> Text -> NodeDataPathStats)
-> Parser Bytes
-> Parser
(Maybe Text -> Maybe Text -> Text -> Text -> NodeDataPathStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Bytes
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"total_in_bytes"
Parser
(Maybe Text -> Maybe Text -> Text -> Text -> NodeDataPathStats)
-> Parser (Maybe Text)
-> Parser (Maybe Text -> Text -> Text -> NodeDataPathStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"type"
Parser (Maybe Text -> Text -> Text -> NodeDataPathStats)
-> Parser (Maybe Text)
-> Parser (Text -> Text -> NodeDataPathStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"dev"
Parser (Text -> Text -> NodeDataPathStats)
-> Parser Text -> Parser (Text -> NodeDataPathStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"mount"
Parser (Text -> NodeDataPathStats)
-> Parser Text -> Parser NodeDataPathStats
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"path"
instance FromJSON NodeFSTotalStats where
parseJSON :: Value -> Parser NodeFSTotalStats
parseJSON = String
-> (Object -> Parser NodeFSTotalStats)
-> Value
-> Parser NodeFSTotalStats
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"NodeFSTotalStats" Object -> Parser NodeFSTotalStats
parse
where
parse :: Object -> Parser NodeFSTotalStats
parse Object
o = Maybe Double
-> Maybe Double
-> Maybe Bytes
-> Maybe Bytes
-> Maybe Bytes
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Bytes
-> Bytes
-> Bytes
-> NodeFSTotalStats
NodeFSTotalStats (Maybe Double
-> Maybe Double
-> Maybe Bytes
-> Maybe Bytes
-> Maybe Bytes
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Bytes
-> Bytes
-> Bytes
-> NodeFSTotalStats)
-> Parser (Maybe Double)
-> Parser
(Maybe Double
-> Maybe Bytes
-> Maybe Bytes
-> Maybe Bytes
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Bytes
-> Bytes
-> Bytes
-> NodeFSTotalStats)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((StringlyTypedDouble -> Double)
-> Maybe StringlyTypedDouble -> Maybe Double
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap StringlyTypedDouble -> Double
unStringlyTypedDouble (Maybe StringlyTypedDouble -> Maybe Double)
-> Parser (Maybe StringlyTypedDouble) -> Parser (Maybe Double)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser (Maybe StringlyTypedDouble)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"disk_service_time")
Parser
(Maybe Double
-> Maybe Bytes
-> Maybe Bytes
-> Maybe Bytes
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Bytes
-> Bytes
-> Bytes
-> NodeFSTotalStats)
-> Parser (Maybe Double)
-> Parser
(Maybe Bytes
-> Maybe Bytes
-> Maybe Bytes
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Bytes
-> Bytes
-> Bytes
-> NodeFSTotalStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ((StringlyTypedDouble -> Double)
-> Maybe StringlyTypedDouble -> Maybe Double
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap StringlyTypedDouble -> Double
unStringlyTypedDouble (Maybe StringlyTypedDouble -> Maybe Double)
-> Parser (Maybe StringlyTypedDouble) -> Parser (Maybe Double)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser (Maybe StringlyTypedDouble)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"disk_queue")
Parser
(Maybe Bytes
-> Maybe Bytes
-> Maybe Bytes
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Bytes
-> Bytes
-> Bytes
-> NodeFSTotalStats)
-> Parser (Maybe Bytes)
-> Parser
(Maybe Bytes
-> Maybe Bytes
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Bytes
-> Bytes
-> Bytes
-> NodeFSTotalStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Bytes)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"disk_io_size_in_bytes"
Parser
(Maybe Bytes
-> Maybe Bytes
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Bytes
-> Bytes
-> Bytes
-> NodeFSTotalStats)
-> Parser (Maybe Bytes)
-> Parser
(Maybe Bytes
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Bytes
-> Bytes
-> Bytes
-> NodeFSTotalStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Bytes)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"disk_write_size_in_bytes"
Parser
(Maybe Bytes
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Bytes
-> Bytes
-> Bytes
-> NodeFSTotalStats)
-> Parser (Maybe Bytes)
-> Parser
(Maybe Int
-> Maybe Int
-> Maybe Int
-> Bytes
-> Bytes
-> Bytes
-> NodeFSTotalStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Bytes)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"disk_read_size_in_bytes"
Parser
(Maybe Int
-> Maybe Int
-> Maybe Int
-> Bytes
-> Bytes
-> Bytes
-> NodeFSTotalStats)
-> Parser (Maybe Int)
-> Parser
(Maybe Int
-> Maybe Int -> Bytes -> Bytes -> Bytes -> NodeFSTotalStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"disk_io_op"
Parser
(Maybe Int
-> Maybe Int -> Bytes -> Bytes -> Bytes -> NodeFSTotalStats)
-> Parser (Maybe Int)
-> Parser
(Maybe Int -> Bytes -> Bytes -> Bytes -> NodeFSTotalStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"disk_writes"
Parser (Maybe Int -> Bytes -> Bytes -> Bytes -> NodeFSTotalStats)
-> Parser (Maybe Int)
-> Parser (Bytes -> Bytes -> Bytes -> NodeFSTotalStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"disk_reads"
Parser (Bytes -> Bytes -> Bytes -> NodeFSTotalStats)
-> Parser Bytes -> Parser (Bytes -> Bytes -> NodeFSTotalStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Bytes
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"available_in_bytes"
Parser (Bytes -> Bytes -> NodeFSTotalStats)
-> Parser Bytes -> Parser (Bytes -> NodeFSTotalStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Bytes
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"free_in_bytes"
Parser (Bytes -> NodeFSTotalStats)
-> Parser Bytes -> Parser NodeFSTotalStats
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Bytes
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"total_in_bytes"
instance FromJSON NodeNetworkStats where
parseJSON :: Value -> Parser NodeNetworkStats
parseJSON = String
-> (Object -> Parser NodeNetworkStats)
-> Value
-> Parser NodeNetworkStats
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"NodeNetworkStats" Object -> Parser NodeNetworkStats
parse
where
parse :: Object -> Parser NodeNetworkStats
parse Object
o = do
Object
tcp <- Object
o Object -> Key -> Parser Object
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"tcp"
Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> NodeNetworkStats
NodeNetworkStats (Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> NodeNetworkStats)
-> Parser Int
-> Parser
(Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> NodeNetworkStats)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
tcp Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"out_rsts"
Parser
(Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> NodeNetworkStats)
-> Parser Int
-> Parser
(Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> NodeNetworkStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
tcp Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"in_errs"
Parser
(Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> NodeNetworkStats)
-> Parser Int
-> Parser
(Int -> Int -> Int -> Int -> Int -> Int -> Int -> NodeNetworkStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
tcp Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"attempt_fails"
Parser
(Int -> Int -> Int -> Int -> Int -> Int -> Int -> NodeNetworkStats)
-> Parser Int
-> Parser
(Int -> Int -> Int -> Int -> Int -> Int -> NodeNetworkStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
tcp Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"estab_resets"
Parser (Int -> Int -> Int -> Int -> Int -> Int -> NodeNetworkStats)
-> Parser Int
-> Parser (Int -> Int -> Int -> Int -> Int -> NodeNetworkStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
tcp Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"retrans_segs"
Parser (Int -> Int -> Int -> Int -> Int -> NodeNetworkStats)
-> Parser Int
-> Parser (Int -> Int -> Int -> Int -> NodeNetworkStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
tcp Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"out_segs"
Parser (Int -> Int -> Int -> Int -> NodeNetworkStats)
-> Parser Int -> Parser (Int -> Int -> Int -> NodeNetworkStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
tcp Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"in_segs"
Parser (Int -> Int -> Int -> NodeNetworkStats)
-> Parser Int -> Parser (Int -> Int -> NodeNetworkStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
tcp Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"curr_estab"
Parser (Int -> Int -> NodeNetworkStats)
-> Parser Int -> Parser (Int -> NodeNetworkStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
tcp Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"passive_opens"
Parser (Int -> NodeNetworkStats)
-> Parser Int -> Parser NodeNetworkStats
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
tcp Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"active_opens"
instance FromJSON NodeThreadPoolStats where
parseJSON :: Value -> Parser NodeThreadPoolStats
parseJSON = String
-> (Object -> Parser NodeThreadPoolStats)
-> Value
-> Parser NodeThreadPoolStats
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"NodeThreadPoolStats" Object -> Parser NodeThreadPoolStats
parse
where
parse :: Object -> Parser NodeThreadPoolStats
parse Object
o = Int -> Int -> Int -> Int -> Int -> Int -> NodeThreadPoolStats
NodeThreadPoolStats (Int -> Int -> Int -> Int -> Int -> Int -> NodeThreadPoolStats)
-> Parser Int
-> Parser (Int -> Int -> Int -> Int -> Int -> NodeThreadPoolStats)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"completed"
Parser (Int -> Int -> Int -> Int -> Int -> NodeThreadPoolStats)
-> Parser Int
-> Parser (Int -> Int -> Int -> Int -> NodeThreadPoolStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"largest"
Parser (Int -> Int -> Int -> Int -> NodeThreadPoolStats)
-> Parser Int -> Parser (Int -> Int -> Int -> NodeThreadPoolStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"rejected"
Parser (Int -> Int -> Int -> NodeThreadPoolStats)
-> Parser Int -> Parser (Int -> Int -> NodeThreadPoolStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"active"
Parser (Int -> Int -> NodeThreadPoolStats)
-> Parser Int -> Parser (Int -> NodeThreadPoolStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"queue"
Parser (Int -> NodeThreadPoolStats)
-> Parser Int -> Parser NodeThreadPoolStats
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"threads"
instance FromJSON NodeJVMStats where
parseJSON :: Value -> Parser NodeJVMStats
parseJSON = String
-> (Object -> Parser NodeJVMStats) -> Value -> Parser NodeJVMStats
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"NodeJVMStats" Object -> Parser NodeJVMStats
parse
where
parse :: Object -> Parser NodeJVMStats
parse Object
o = do
Object
bufferPools <- Object
o Object -> Key -> Parser Object
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"buffer_pools"
JVMBufferPoolStats
mapped <- Object
bufferPools Object -> Key -> Parser JVMBufferPoolStats
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"mapped"
JVMBufferPoolStats
direct <- Object
bufferPools Object -> Key -> Parser JVMBufferPoolStats
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"direct"
Object
gc <- Object
o Object -> Key -> Parser Object
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"gc"
Object
collectors <- Object
gc Object -> Key -> Parser Object
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"collectors"
JVMGCStats
oldC <- Object
collectors Object -> Key -> Parser JVMGCStats
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"old"
JVMGCStats
youngC <- Object
collectors Object -> Key -> Parser JVMGCStats
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"young"
Object
threads <- Object
o Object -> Key -> Parser Object
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"threads"
Object
mem <- Object
o Object -> Key -> Parser Object
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"mem"
Object
pools <- Object
mem Object -> Key -> Parser Object
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"pools"
JVMPoolStats
oldM <- Object
pools Object -> Key -> Parser JVMPoolStats
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"old"
JVMPoolStats
survivorM <- Object
pools Object -> Key -> Parser JVMPoolStats
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"survivor"
JVMPoolStats
youngM <- Object
pools Object -> Key -> Parser JVMPoolStats
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"young"
JVMBufferPoolStats
-> JVMBufferPoolStats
-> JVMGCStats
-> JVMGCStats
-> Int
-> Int
-> JVMPoolStats
-> JVMPoolStats
-> JVMPoolStats
-> Bytes
-> Bytes
-> Bytes
-> Bytes
-> Int
-> Bytes
-> NominalDiffTime
-> UTCTime
-> NodeJVMStats
NodeJVMStats (JVMBufferPoolStats
-> JVMBufferPoolStats
-> JVMGCStats
-> JVMGCStats
-> Int
-> Int
-> JVMPoolStats
-> JVMPoolStats
-> JVMPoolStats
-> Bytes
-> Bytes
-> Bytes
-> Bytes
-> Int
-> Bytes
-> NominalDiffTime
-> UTCTime
-> NodeJVMStats)
-> Parser JVMBufferPoolStats
-> Parser
(JVMBufferPoolStats
-> JVMGCStats
-> JVMGCStats
-> Int
-> Int
-> JVMPoolStats
-> JVMPoolStats
-> JVMPoolStats
-> Bytes
-> Bytes
-> Bytes
-> Bytes
-> Int
-> Bytes
-> NominalDiffTime
-> UTCTime
-> NodeJVMStats)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JVMBufferPoolStats -> Parser JVMBufferPoolStats
forall (f :: * -> *) a. Applicative f => a -> f a
pure JVMBufferPoolStats
mapped
Parser
(JVMBufferPoolStats
-> JVMGCStats
-> JVMGCStats
-> Int
-> Int
-> JVMPoolStats
-> JVMPoolStats
-> JVMPoolStats
-> Bytes
-> Bytes
-> Bytes
-> Bytes
-> Int
-> Bytes
-> NominalDiffTime
-> UTCTime
-> NodeJVMStats)
-> Parser JVMBufferPoolStats
-> Parser
(JVMGCStats
-> JVMGCStats
-> Int
-> Int
-> JVMPoolStats
-> JVMPoolStats
-> JVMPoolStats
-> Bytes
-> Bytes
-> Bytes
-> Bytes
-> Int
-> Bytes
-> NominalDiffTime
-> UTCTime
-> NodeJVMStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> JVMBufferPoolStats -> Parser JVMBufferPoolStats
forall (f :: * -> *) a. Applicative f => a -> f a
pure JVMBufferPoolStats
direct
Parser
(JVMGCStats
-> JVMGCStats
-> Int
-> Int
-> JVMPoolStats
-> JVMPoolStats
-> JVMPoolStats
-> Bytes
-> Bytes
-> Bytes
-> Bytes
-> Int
-> Bytes
-> NominalDiffTime
-> UTCTime
-> NodeJVMStats)
-> Parser JVMGCStats
-> Parser
(JVMGCStats
-> Int
-> Int
-> JVMPoolStats
-> JVMPoolStats
-> JVMPoolStats
-> Bytes
-> Bytes
-> Bytes
-> Bytes
-> Int
-> Bytes
-> NominalDiffTime
-> UTCTime
-> NodeJVMStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> JVMGCStats -> Parser JVMGCStats
forall (f :: * -> *) a. Applicative f => a -> f a
pure JVMGCStats
oldC
Parser
(JVMGCStats
-> Int
-> Int
-> JVMPoolStats
-> JVMPoolStats
-> JVMPoolStats
-> Bytes
-> Bytes
-> Bytes
-> Bytes
-> Int
-> Bytes
-> NominalDiffTime
-> UTCTime
-> NodeJVMStats)
-> Parser JVMGCStats
-> Parser
(Int
-> Int
-> JVMPoolStats
-> JVMPoolStats
-> JVMPoolStats
-> Bytes
-> Bytes
-> Bytes
-> Bytes
-> Int
-> Bytes
-> NominalDiffTime
-> UTCTime
-> NodeJVMStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> JVMGCStats -> Parser JVMGCStats
forall (f :: * -> *) a. Applicative f => a -> f a
pure JVMGCStats
youngC
Parser
(Int
-> Int
-> JVMPoolStats
-> JVMPoolStats
-> JVMPoolStats
-> Bytes
-> Bytes
-> Bytes
-> Bytes
-> Int
-> Bytes
-> NominalDiffTime
-> UTCTime
-> NodeJVMStats)
-> Parser Int
-> Parser
(Int
-> JVMPoolStats
-> JVMPoolStats
-> JVMPoolStats
-> Bytes
-> Bytes
-> Bytes
-> Bytes
-> Int
-> Bytes
-> NominalDiffTime
-> UTCTime
-> NodeJVMStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
threads Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"peak_count"
Parser
(Int
-> JVMPoolStats
-> JVMPoolStats
-> JVMPoolStats
-> Bytes
-> Bytes
-> Bytes
-> Bytes
-> Int
-> Bytes
-> NominalDiffTime
-> UTCTime
-> NodeJVMStats)
-> Parser Int
-> Parser
(JVMPoolStats
-> JVMPoolStats
-> JVMPoolStats
-> Bytes
-> Bytes
-> Bytes
-> Bytes
-> Int
-> Bytes
-> NominalDiffTime
-> UTCTime
-> NodeJVMStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
threads Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"count"
Parser
(JVMPoolStats
-> JVMPoolStats
-> JVMPoolStats
-> Bytes
-> Bytes
-> Bytes
-> Bytes
-> Int
-> Bytes
-> NominalDiffTime
-> UTCTime
-> NodeJVMStats)
-> Parser JVMPoolStats
-> Parser
(JVMPoolStats
-> JVMPoolStats
-> Bytes
-> Bytes
-> Bytes
-> Bytes
-> Int
-> Bytes
-> NominalDiffTime
-> UTCTime
-> NodeJVMStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> JVMPoolStats -> Parser JVMPoolStats
forall (f :: * -> *) a. Applicative f => a -> f a
pure JVMPoolStats
oldM
Parser
(JVMPoolStats
-> JVMPoolStats
-> Bytes
-> Bytes
-> Bytes
-> Bytes
-> Int
-> Bytes
-> NominalDiffTime
-> UTCTime
-> NodeJVMStats)
-> Parser JVMPoolStats
-> Parser
(JVMPoolStats
-> Bytes
-> Bytes
-> Bytes
-> Bytes
-> Int
-> Bytes
-> NominalDiffTime
-> UTCTime
-> NodeJVMStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> JVMPoolStats -> Parser JVMPoolStats
forall (f :: * -> *) a. Applicative f => a -> f a
pure JVMPoolStats
survivorM
Parser
(JVMPoolStats
-> Bytes
-> Bytes
-> Bytes
-> Bytes
-> Int
-> Bytes
-> NominalDiffTime
-> UTCTime
-> NodeJVMStats)
-> Parser JVMPoolStats
-> Parser
(Bytes
-> Bytes
-> Bytes
-> Bytes
-> Int
-> Bytes
-> NominalDiffTime
-> UTCTime
-> NodeJVMStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> JVMPoolStats -> Parser JVMPoolStats
forall (f :: * -> *) a. Applicative f => a -> f a
pure JVMPoolStats
youngM
Parser
(Bytes
-> Bytes
-> Bytes
-> Bytes
-> Int
-> Bytes
-> NominalDiffTime
-> UTCTime
-> NodeJVMStats)
-> Parser Bytes
-> Parser
(Bytes
-> Bytes
-> Bytes
-> Int
-> Bytes
-> NominalDiffTime
-> UTCTime
-> NodeJVMStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
mem Object -> Key -> Parser Bytes
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"non_heap_committed_in_bytes"
Parser
(Bytes
-> Bytes
-> Bytes
-> Int
-> Bytes
-> NominalDiffTime
-> UTCTime
-> NodeJVMStats)
-> Parser Bytes
-> Parser
(Bytes
-> Bytes
-> Int
-> Bytes
-> NominalDiffTime
-> UTCTime
-> NodeJVMStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
mem Object -> Key -> Parser Bytes
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"non_heap_used_in_bytes"
Parser
(Bytes
-> Bytes
-> Int
-> Bytes
-> NominalDiffTime
-> UTCTime
-> NodeJVMStats)
-> Parser Bytes
-> Parser
(Bytes
-> Int -> Bytes -> NominalDiffTime -> UTCTime -> NodeJVMStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
mem Object -> Key -> Parser Bytes
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"heap_max_in_bytes"
Parser
(Bytes
-> Int -> Bytes -> NominalDiffTime -> UTCTime -> NodeJVMStats)
-> Parser Bytes
-> Parser
(Int -> Bytes -> NominalDiffTime -> UTCTime -> NodeJVMStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
mem Object -> Key -> Parser Bytes
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"heap_committed_in_bytes"
Parser (Int -> Bytes -> NominalDiffTime -> UTCTime -> NodeJVMStats)
-> Parser Int
-> Parser (Bytes -> NominalDiffTime -> UTCTime -> NodeJVMStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
mem Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"heap_used_percent"
Parser (Bytes -> NominalDiffTime -> UTCTime -> NodeJVMStats)
-> Parser Bytes
-> Parser (NominalDiffTime -> UTCTime -> NodeJVMStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
mem Object -> Key -> Parser Bytes
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"heap_used_in_bytes"
Parser (NominalDiffTime -> UTCTime -> NodeJVMStats)
-> Parser NominalDiffTime -> Parser (UTCTime -> NodeJVMStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (MS -> NominalDiffTime
unMS (MS -> NominalDiffTime) -> Parser MS -> Parser NominalDiffTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser MS
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"uptime_in_millis")
Parser (UTCTime -> NodeJVMStats)
-> Parser UTCTime -> Parser NodeJVMStats
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (POSIXMS -> UTCTime
posixMS (POSIXMS -> UTCTime) -> Parser POSIXMS -> Parser UTCTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser POSIXMS
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"timestamp")
instance FromJSON JVMBufferPoolStats where
parseJSON :: Value -> Parser JVMBufferPoolStats
parseJSON = String
-> (Object -> Parser JVMBufferPoolStats)
-> Value
-> Parser JVMBufferPoolStats
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"JVMBufferPoolStats" Object -> Parser JVMBufferPoolStats
parse
where
parse :: Object -> Parser JVMBufferPoolStats
parse Object
o = Bytes -> Bytes -> Int -> JVMBufferPoolStats
JVMBufferPoolStats (Bytes -> Bytes -> Int -> JVMBufferPoolStats)
-> Parser Bytes -> Parser (Bytes -> Int -> JVMBufferPoolStats)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser Bytes
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"total_capacity_in_bytes"
Parser (Bytes -> Int -> JVMBufferPoolStats)
-> Parser Bytes -> Parser (Int -> JVMBufferPoolStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Bytes
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"used_in_bytes"
Parser (Int -> JVMBufferPoolStats)
-> Parser Int -> Parser JVMBufferPoolStats
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"count"
instance FromJSON JVMGCStats where
parseJSON :: Value -> Parser JVMGCStats
parseJSON = String
-> (Object -> Parser JVMGCStats) -> Value -> Parser JVMGCStats
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"JVMGCStats" Object -> Parser JVMGCStats
parse
where
parse :: Object -> Parser JVMGCStats
parse Object
o = NominalDiffTime -> Int -> JVMGCStats
JVMGCStats (NominalDiffTime -> Int -> JVMGCStats)
-> Parser NominalDiffTime -> Parser (Int -> JVMGCStats)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (MS -> NominalDiffTime
unMS (MS -> NominalDiffTime) -> Parser MS -> Parser NominalDiffTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser MS
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"collection_time_in_millis")
Parser (Int -> JVMGCStats) -> Parser Int -> Parser JVMGCStats
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"collection_count"
instance FromJSON JVMPoolStats where
parseJSON :: Value -> Parser JVMPoolStats
parseJSON = String
-> (Object -> Parser JVMPoolStats) -> Value -> Parser JVMPoolStats
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"JVMPoolStats" Object -> Parser JVMPoolStats
parse
where
parse :: Object -> Parser JVMPoolStats
parse Object
o = Bytes -> Bytes -> Bytes -> Bytes -> JVMPoolStats
JVMPoolStats (Bytes -> Bytes -> Bytes -> Bytes -> JVMPoolStats)
-> Parser Bytes -> Parser (Bytes -> Bytes -> Bytes -> JVMPoolStats)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser Bytes
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"peak_max_in_bytes"
Parser (Bytes -> Bytes -> Bytes -> JVMPoolStats)
-> Parser Bytes -> Parser (Bytes -> Bytes -> JVMPoolStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Bytes
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"peak_used_in_bytes"
Parser (Bytes -> Bytes -> JVMPoolStats)
-> Parser Bytes -> Parser (Bytes -> JVMPoolStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Bytes
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"max_in_bytes"
Parser (Bytes -> JVMPoolStats)
-> Parser Bytes -> Parser JVMPoolStats
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Bytes
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"used_in_bytes"
instance FromJSON NodeProcessStats where
parseJSON :: Value -> Parser NodeProcessStats
parseJSON = String
-> (Object -> Parser NodeProcessStats)
-> Value
-> Parser NodeProcessStats
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"NodeProcessStats" Object -> Parser NodeProcessStats
parse
where
parse :: Object -> Parser NodeProcessStats
parse Object
o = do
Object
mem <- Object
o Object -> Key -> Parser Object
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"mem"
Object
cpu <- Object
o Object -> Key -> Parser Object
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"cpu"
UTCTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Bytes
-> NodeProcessStats
NodeProcessStats (UTCTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Bytes
-> NodeProcessStats)
-> Parser UTCTime
-> Parser
(Int -> Int -> Int -> NominalDiffTime -> Bytes -> NodeProcessStats)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (POSIXMS -> UTCTime
posixMS (POSIXMS -> UTCTime) -> Parser POSIXMS -> Parser UTCTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser POSIXMS
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"timestamp")
Parser
(Int -> Int -> Int -> NominalDiffTime -> Bytes -> NodeProcessStats)
-> Parser Int
-> Parser
(Int -> Int -> NominalDiffTime -> Bytes -> NodeProcessStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"open_file_descriptors"
Parser (Int -> Int -> NominalDiffTime -> Bytes -> NodeProcessStats)
-> Parser Int
-> Parser (Int -> NominalDiffTime -> Bytes -> NodeProcessStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"max_file_descriptors"
Parser (Int -> NominalDiffTime -> Bytes -> NodeProcessStats)
-> Parser Int
-> Parser (NominalDiffTime -> Bytes -> NodeProcessStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
cpu Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"percent"
Parser (NominalDiffTime -> Bytes -> NodeProcessStats)
-> Parser NominalDiffTime -> Parser (Bytes -> NodeProcessStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (MS -> NominalDiffTime
unMS (MS -> NominalDiffTime) -> Parser MS -> Parser NominalDiffTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
cpu Object -> Key -> Parser MS
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"total_in_millis")
Parser (Bytes -> NodeProcessStats)
-> Parser Bytes -> Parser NodeProcessStats
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
mem Object -> Key -> Parser Bytes
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"total_virtual_in_bytes"
instance FromJSON NodeOSStats where
parseJSON :: Value -> Parser NodeOSStats
parseJSON = String
-> (Object -> Parser NodeOSStats) -> Value -> Parser NodeOSStats
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"NodeOSStats" Object -> Parser NodeOSStats
parse
where
parse :: Object -> Parser NodeOSStats
parse Object
o = do
Object
swap <- Object
o Object -> Key -> Parser Object
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"swap"
Object
mem <- Object
o Object -> Key -> Parser Object
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"mem"
Object
cpu <- Object
o Object -> Key -> Parser Object
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"cpu"
Maybe LoadAvgs
load <- Object
o Object -> Key -> Parser (Maybe LoadAvgs)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"load_average"
UTCTime
-> Int
-> Maybe LoadAvgs
-> Bytes
-> Bytes
-> Int
-> Bytes
-> Int
-> Bytes
-> Bytes
-> Bytes
-> NodeOSStats
NodeOSStats (UTCTime
-> Int
-> Maybe LoadAvgs
-> Bytes
-> Bytes
-> Int
-> Bytes
-> Int
-> Bytes
-> Bytes
-> Bytes
-> NodeOSStats)
-> Parser UTCTime
-> Parser
(Int
-> Maybe LoadAvgs
-> Bytes
-> Bytes
-> Int
-> Bytes
-> Int
-> Bytes
-> Bytes
-> Bytes
-> NodeOSStats)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (POSIXMS -> UTCTime
posixMS (POSIXMS -> UTCTime) -> Parser POSIXMS -> Parser UTCTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser POSIXMS
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"timestamp")
Parser
(Int
-> Maybe LoadAvgs
-> Bytes
-> Bytes
-> Int
-> Bytes
-> Int
-> Bytes
-> Bytes
-> Bytes
-> NodeOSStats)
-> Parser Int
-> Parser
(Maybe LoadAvgs
-> Bytes
-> Bytes
-> Int
-> Bytes
-> Int
-> Bytes
-> Bytes
-> Bytes
-> NodeOSStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
cpu Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"percent"
Parser
(Maybe LoadAvgs
-> Bytes
-> Bytes
-> Int
-> Bytes
-> Int
-> Bytes
-> Bytes
-> Bytes
-> NodeOSStats)
-> Parser (Maybe LoadAvgs)
-> Parser
(Bytes
-> Bytes
-> Int
-> Bytes
-> Int
-> Bytes
-> Bytes
-> Bytes
-> NodeOSStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe LoadAvgs -> Parser (Maybe LoadAvgs)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe LoadAvgs
load
Parser
(Bytes
-> Bytes
-> Int
-> Bytes
-> Int
-> Bytes
-> Bytes
-> Bytes
-> NodeOSStats)
-> Parser Bytes
-> Parser
(Bytes
-> Int -> Bytes -> Int -> Bytes -> Bytes -> Bytes -> NodeOSStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
mem Object -> Key -> Parser Bytes
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"total_in_bytes"
Parser
(Bytes
-> Int -> Bytes -> Int -> Bytes -> Bytes -> Bytes -> NodeOSStats)
-> Parser Bytes
-> Parser
(Int -> Bytes -> Int -> Bytes -> Bytes -> Bytes -> NodeOSStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
mem Object -> Key -> Parser Bytes
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"free_in_bytes"
Parser
(Int -> Bytes -> Int -> Bytes -> Bytes -> Bytes -> NodeOSStats)
-> Parser Int
-> Parser (Bytes -> Int -> Bytes -> Bytes -> Bytes -> NodeOSStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
mem Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"free_percent"
Parser (Bytes -> Int -> Bytes -> Bytes -> Bytes -> NodeOSStats)
-> Parser Bytes
-> Parser (Int -> Bytes -> Bytes -> Bytes -> NodeOSStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
mem Object -> Key -> Parser Bytes
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"used_in_bytes"
Parser (Int -> Bytes -> Bytes -> Bytes -> NodeOSStats)
-> Parser Int -> Parser (Bytes -> Bytes -> Bytes -> NodeOSStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
mem Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"used_percent"
Parser (Bytes -> Bytes -> Bytes -> NodeOSStats)
-> Parser Bytes -> Parser (Bytes -> Bytes -> NodeOSStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
swap Object -> Key -> Parser Bytes
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"total_in_bytes"
Parser (Bytes -> Bytes -> NodeOSStats)
-> Parser Bytes -> Parser (Bytes -> NodeOSStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
swap Object -> Key -> Parser Bytes
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"free_in_bytes"
Parser (Bytes -> NodeOSStats) -> Parser Bytes -> Parser NodeOSStats
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
swap Object -> Key -> Parser Bytes
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"used_in_bytes"
instance FromJSON LoadAvgs where
parseJSON :: Value -> Parser LoadAvgs
parseJSON = String -> (Array -> Parser LoadAvgs) -> Value -> Parser LoadAvgs
forall a. String -> (Array -> Parser a) -> Value -> Parser a
withArray String
"LoadAvgs" Array -> Parser LoadAvgs
parse
where
parse :: Array -> Parser LoadAvgs
parse Array
v = case Array -> [Value]
forall a. Vector a -> [a]
V.toList Array
v of
[Value
one, Value
five, Value
fifteen] -> Double -> Double -> Double -> LoadAvgs
LoadAvgs (Double -> Double -> Double -> LoadAvgs)
-> Parser Double -> Parser (Double -> Double -> LoadAvgs)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser Double
forall a. FromJSON a => Value -> Parser a
parseJSON Value
one
Parser (Double -> Double -> LoadAvgs)
-> Parser Double -> Parser (Double -> LoadAvgs)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Value -> Parser Double
forall a. FromJSON a => Value -> Parser a
parseJSON Value
five
Parser (Double -> LoadAvgs) -> Parser Double -> Parser LoadAvgs
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Value -> Parser Double
forall a. FromJSON a => Value -> Parser a
parseJSON Value
fifteen
[Value]
_ -> String -> Parser LoadAvgs
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Expecting a triple of Doubles"
instance FromJSON NodeIndicesStats where
parseJSON :: Value -> Parser NodeIndicesStats
parseJSON = String
-> (Object -> Parser NodeIndicesStats)
-> Value
-> Parser NodeIndicesStats
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"NodeIndicesStats" Object -> Parser NodeIndicesStats
parse
where
parse :: Object -> Parser NodeIndicesStats
parse Object
o = do
let .:: :: Maybe Object -> Key -> Parser (Maybe a)
(.::) Maybe Object
mv Key
k = case Maybe Object
mv of
Just Object
v -> a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> Parser a -> Parser (Maybe a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Key -> Parser a
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
k
Maybe Object
Nothing -> Maybe a -> Parser (Maybe a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe a
forall a. Maybe a
Nothing
Maybe Object
mRecovery <- Object
o Object -> Key -> Parser (Maybe Object)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"recovery"
Maybe Object
mQueryCache <- Object
o Object -> Key -> Parser (Maybe Object)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"query_cache"
Maybe Object
mSuggest <- Object
o Object -> Key -> Parser (Maybe Object)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"suggest"
Object
translog <- Object
o Object -> Key -> Parser Object
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"translog"
Object
segments <- Object
o Object -> Key -> Parser Object
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"segments"
Object
completion <- Object
o Object -> Key -> Parser Object
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"completion"
Maybe Object
mPercolate <- Object
o Object -> Key -> Parser (Maybe Object)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"percolate"
Object
fielddata <- Object
o Object -> Key -> Parser Object
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"fielddata"
Object
warmer <- Object
o Object -> Key -> Parser Object
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"warmer"
Object
flush <- Object
o Object -> Key -> Parser Object
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"flush"
Object
refresh <- Object
o Object -> Key -> Parser Object
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"refresh"
Object
merges <- Object
o Object -> Key -> Parser Object
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"merges"
Object
search <- Object
o Object -> Key -> Parser Object
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"search"
Object
getStats <- Object
o Object -> Key -> Parser Object
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"get"
Object
indexing <- Object
o Object -> Key -> Parser Object
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"indexing"
Object
store <- Object
o Object -> Key -> Parser Object
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"store"
Object
docs <- Object
o Object -> Key -> Parser Object
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"docs"
Maybe NominalDiffTime
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe Bytes
-> Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Bytes
-> Int
-> Maybe Bytes
-> Bytes
-> Maybe Bytes
-> Bytes
-> Bytes
-> Int
-> Bytes
-> Maybe Int
-> Maybe Bytes
-> Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Int
-> Bytes
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats
NodeIndicesStats (Maybe NominalDiffTime
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe Bytes
-> Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Bytes
-> Int
-> Maybe Bytes
-> Bytes
-> Maybe Bytes
-> Bytes
-> Bytes
-> Int
-> Bytes
-> Maybe Int
-> Maybe Bytes
-> Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Int
-> Bytes
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser (Maybe NominalDiffTime)
-> Parser
(Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe Bytes
-> Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Bytes
-> Int
-> Maybe Bytes
-> Bytes
-> Maybe Bytes
-> Bytes
-> Bytes
-> Int
-> Bytes
-> Maybe Int
-> Maybe Bytes
-> Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Int
-> Bytes
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((MS -> NominalDiffTime) -> Maybe MS -> Maybe NominalDiffTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap MS -> NominalDiffTime
unMS (Maybe MS -> Maybe NominalDiffTime)
-> Parser (Maybe MS) -> Parser (Maybe NominalDiffTime)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Object
mRecovery Maybe Object -> Key -> Parser (Maybe MS)
forall a. FromJSON a => Maybe Object -> Key -> Parser (Maybe a)
.:: Key
"throttle_time_in_millis")
Parser
(Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe Bytes
-> Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Bytes
-> Int
-> Maybe Bytes
-> Bytes
-> Maybe Bytes
-> Bytes
-> Bytes
-> Int
-> Bytes
-> Maybe Int
-> Maybe Bytes
-> Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Int
-> Bytes
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser (Maybe Int)
-> Parser
(Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe Bytes
-> Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Bytes
-> Int
-> Maybe Bytes
-> Bytes
-> Maybe Bytes
-> Bytes
-> Bytes
-> Int
-> Bytes
-> Maybe Int
-> Maybe Bytes
-> Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Int
-> Bytes
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe Object
mRecovery Maybe Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Maybe Object -> Key -> Parser (Maybe a)
.:: Key
"current_as_target"
Parser
(Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe Bytes
-> Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Bytes
-> Int
-> Maybe Bytes
-> Bytes
-> Maybe Bytes
-> Bytes
-> Bytes
-> Int
-> Bytes
-> Maybe Int
-> Maybe Bytes
-> Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Int
-> Bytes
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser (Maybe Int)
-> Parser
(Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe Bytes
-> Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Bytes
-> Int
-> Maybe Bytes
-> Bytes
-> Maybe Bytes
-> Bytes
-> Bytes
-> Int
-> Bytes
-> Maybe Int
-> Maybe Bytes
-> Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Int
-> Bytes
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe Object
mRecovery Maybe Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Maybe Object -> Key -> Parser (Maybe a)
.:: Key
"current_as_source"
Parser
(Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe Bytes
-> Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Bytes
-> Int
-> Maybe Bytes
-> Bytes
-> Maybe Bytes
-> Bytes
-> Bytes
-> Int
-> Bytes
-> Maybe Int
-> Maybe Bytes
-> Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Int
-> Bytes
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser (Maybe Int)
-> Parser
(Maybe Int
-> Maybe Int
-> Maybe Bytes
-> Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Bytes
-> Int
-> Maybe Bytes
-> Bytes
-> Maybe Bytes
-> Bytes
-> Bytes
-> Int
-> Bytes
-> Maybe Int
-> Maybe Bytes
-> Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Int
-> Bytes
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe Object
mQueryCache Maybe Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Maybe Object -> Key -> Parser (Maybe a)
.:: Key
"miss_count"
Parser
(Maybe Int
-> Maybe Int
-> Maybe Bytes
-> Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Bytes
-> Int
-> Maybe Bytes
-> Bytes
-> Maybe Bytes
-> Bytes
-> Bytes
-> Int
-> Bytes
-> Maybe Int
-> Maybe Bytes
-> Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Int
-> Bytes
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser (Maybe Int)
-> Parser
(Maybe Int
-> Maybe Bytes
-> Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Bytes
-> Int
-> Maybe Bytes
-> Bytes
-> Maybe Bytes
-> Bytes
-> Bytes
-> Int
-> Bytes
-> Maybe Int
-> Maybe Bytes
-> Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Int
-> Bytes
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe Object
mQueryCache Maybe Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Maybe Object -> Key -> Parser (Maybe a)
.:: Key
"hit_count"
Parser
(Maybe Int
-> Maybe Bytes
-> Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Bytes
-> Int
-> Maybe Bytes
-> Bytes
-> Maybe Bytes
-> Bytes
-> Bytes
-> Int
-> Bytes
-> Maybe Int
-> Maybe Bytes
-> Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Int
-> Bytes
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser (Maybe Int)
-> Parser
(Maybe Bytes
-> Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Bytes
-> Int
-> Maybe Bytes
-> Bytes
-> Maybe Bytes
-> Bytes
-> Bytes
-> Int
-> Bytes
-> Maybe Int
-> Maybe Bytes
-> Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Int
-> Bytes
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe Object
mQueryCache Maybe Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Maybe Object -> Key -> Parser (Maybe a)
.:: Key
"evictions"
Parser
(Maybe Bytes
-> Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Bytes
-> Int
-> Maybe Bytes
-> Bytes
-> Maybe Bytes
-> Bytes
-> Bytes
-> Int
-> Bytes
-> Maybe Int
-> Maybe Bytes
-> Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Int
-> Bytes
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser (Maybe Bytes)
-> Parser
(Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Bytes
-> Int
-> Maybe Bytes
-> Bytes
-> Maybe Bytes
-> Bytes
-> Bytes
-> Int
-> Bytes
-> Maybe Int
-> Maybe Bytes
-> Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Int
-> Bytes
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe Object
mQueryCache Maybe Object -> Key -> Parser (Maybe Bytes)
forall a. FromJSON a => Maybe Object -> Key -> Parser (Maybe a)
.:: Key
"memory_size_in_bytes"
Parser
(Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Bytes
-> Int
-> Maybe Bytes
-> Bytes
-> Maybe Bytes
-> Bytes
-> Bytes
-> Int
-> Bytes
-> Maybe Int
-> Maybe Bytes
-> Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Int
-> Bytes
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser (Maybe Int)
-> Parser
(Maybe NominalDiffTime
-> Maybe Int
-> Bytes
-> Int
-> Maybe Bytes
-> Bytes
-> Maybe Bytes
-> Bytes
-> Bytes
-> Int
-> Bytes
-> Maybe Int
-> Maybe Bytes
-> Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Int
-> Bytes
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe Object
mSuggest Maybe Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Maybe Object -> Key -> Parser (Maybe a)
.:: Key
"current"
Parser
(Maybe NominalDiffTime
-> Maybe Int
-> Bytes
-> Int
-> Maybe Bytes
-> Bytes
-> Maybe Bytes
-> Bytes
-> Bytes
-> Int
-> Bytes
-> Maybe Int
-> Maybe Bytes
-> Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Int
-> Bytes
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser (Maybe NominalDiffTime)
-> Parser
(Maybe Int
-> Bytes
-> Int
-> Maybe Bytes
-> Bytes
-> Maybe Bytes
-> Bytes
-> Bytes
-> Int
-> Bytes
-> Maybe Int
-> Maybe Bytes
-> Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Int
-> Bytes
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ((MS -> NominalDiffTime) -> Maybe MS -> Maybe NominalDiffTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap MS -> NominalDiffTime
unMS (Maybe MS -> Maybe NominalDiffTime)
-> Parser (Maybe MS) -> Parser (Maybe NominalDiffTime)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Object
mSuggest Maybe Object -> Key -> Parser (Maybe MS)
forall a. FromJSON a => Maybe Object -> Key -> Parser (Maybe a)
.:: Key
"time_in_millis")
Parser
(Maybe Int
-> Bytes
-> Int
-> Maybe Bytes
-> Bytes
-> Maybe Bytes
-> Bytes
-> Bytes
-> Int
-> Bytes
-> Maybe Int
-> Maybe Bytes
-> Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Int
-> Bytes
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser (Maybe Int)
-> Parser
(Bytes
-> Int
-> Maybe Bytes
-> Bytes
-> Maybe Bytes
-> Bytes
-> Bytes
-> Int
-> Bytes
-> Maybe Int
-> Maybe Bytes
-> Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Int
-> Bytes
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe Object
mSuggest Maybe Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Maybe Object -> Key -> Parser (Maybe a)
.:: Key
"total"
Parser
(Bytes
-> Int
-> Maybe Bytes
-> Bytes
-> Maybe Bytes
-> Bytes
-> Bytes
-> Int
-> Bytes
-> Maybe Int
-> Maybe Bytes
-> Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Int
-> Bytes
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser Bytes
-> Parser
(Int
-> Maybe Bytes
-> Bytes
-> Maybe Bytes
-> Bytes
-> Bytes
-> Int
-> Bytes
-> Maybe Int
-> Maybe Bytes
-> Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Int
-> Bytes
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
translog Object -> Key -> Parser Bytes
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"size_in_bytes"
Parser
(Int
-> Maybe Bytes
-> Bytes
-> Maybe Bytes
-> Bytes
-> Bytes
-> Int
-> Bytes
-> Maybe Int
-> Maybe Bytes
-> Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Int
-> Bytes
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser Int
-> Parser
(Maybe Bytes
-> Bytes
-> Maybe Bytes
-> Bytes
-> Bytes
-> Int
-> Bytes
-> Maybe Int
-> Maybe Bytes
-> Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Int
-> Bytes
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
translog Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"operations"
Parser
(Maybe Bytes
-> Bytes
-> Maybe Bytes
-> Bytes
-> Bytes
-> Int
-> Bytes
-> Maybe Int
-> Maybe Bytes
-> Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Int
-> Bytes
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser (Maybe Bytes)
-> Parser
(Bytes
-> Maybe Bytes
-> Bytes
-> Bytes
-> Int
-> Bytes
-> Maybe Int
-> Maybe Bytes
-> Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Int
-> Bytes
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
segments Object -> Key -> Parser (Maybe Bytes)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"fixed_bit_set_memory_in_bytes"
Parser
(Bytes
-> Maybe Bytes
-> Bytes
-> Bytes
-> Int
-> Bytes
-> Maybe Int
-> Maybe Bytes
-> Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Int
-> Bytes
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser Bytes
-> Parser
(Maybe Bytes
-> Bytes
-> Bytes
-> Int
-> Bytes
-> Maybe Int
-> Maybe Bytes
-> Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Int
-> Bytes
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
segments Object -> Key -> Parser Bytes
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"version_map_memory_in_bytes"
Parser
(Maybe Bytes
-> Bytes
-> Bytes
-> Int
-> Bytes
-> Maybe Int
-> Maybe Bytes
-> Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Int
-> Bytes
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser (Maybe Bytes)
-> Parser
(Bytes
-> Bytes
-> Int
-> Bytes
-> Maybe Int
-> Maybe Bytes
-> Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Int
-> Bytes
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
segments Object -> Key -> Parser (Maybe Bytes)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"index_writer_max_memory_in_bytes"
Parser
(Bytes
-> Bytes
-> Int
-> Bytes
-> Maybe Int
-> Maybe Bytes
-> Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Int
-> Bytes
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser Bytes
-> Parser
(Bytes
-> Int
-> Bytes
-> Maybe Int
-> Maybe Bytes
-> Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Int
-> Bytes
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
segments Object -> Key -> Parser Bytes
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"index_writer_memory_in_bytes"
Parser
(Bytes
-> Int
-> Bytes
-> Maybe Int
-> Maybe Bytes
-> Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Int
-> Bytes
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser Bytes
-> Parser
(Int
-> Bytes
-> Maybe Int
-> Maybe Bytes
-> Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Int
-> Bytes
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
segments Object -> Key -> Parser Bytes
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"memory_in_bytes"
Parser
(Int
-> Bytes
-> Maybe Int
-> Maybe Bytes
-> Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Int
-> Bytes
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser Int
-> Parser
(Bytes
-> Maybe Int
-> Maybe Bytes
-> Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Int
-> Bytes
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
segments Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"count"
Parser
(Bytes
-> Maybe Int
-> Maybe Bytes
-> Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Int
-> Bytes
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser Bytes
-> Parser
(Maybe Int
-> Maybe Bytes
-> Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Int
-> Bytes
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
completion Object -> Key -> Parser Bytes
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"size_in_bytes"
Parser
(Maybe Int
-> Maybe Bytes
-> Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Int
-> Bytes
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser (Maybe Int)
-> Parser
(Maybe Bytes
-> Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Int
-> Bytes
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe Object
mPercolate Maybe Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Maybe Object -> Key -> Parser (Maybe a)
.:: Key
"queries"
Parser
(Maybe Bytes
-> Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Int
-> Bytes
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser (Maybe Bytes)
-> Parser
(Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Int
-> Bytes
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe Object
mPercolate Maybe Object -> Key -> Parser (Maybe Bytes)
forall a. FromJSON a => Maybe Object -> Key -> Parser (Maybe a)
.:: Key
"memory_size_in_bytes"
Parser
(Maybe Int
-> Maybe NominalDiffTime
-> Maybe Int
-> Int
-> Bytes
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser (Maybe Int)
-> Parser
(Maybe NominalDiffTime
-> Maybe Int
-> Int
-> Bytes
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe Object
mPercolate Maybe Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Maybe Object -> Key -> Parser (Maybe a)
.:: Key
"current"
Parser
(Maybe NominalDiffTime
-> Maybe Int
-> Int
-> Bytes
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser (Maybe NominalDiffTime)
-> Parser
(Maybe Int
-> Int
-> Bytes
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ((MS -> NominalDiffTime) -> Maybe MS -> Maybe NominalDiffTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap MS -> NominalDiffTime
unMS (Maybe MS -> Maybe NominalDiffTime)
-> Parser (Maybe MS) -> Parser (Maybe NominalDiffTime)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Object
mPercolate Maybe Object -> Key -> Parser (Maybe MS)
forall a. FromJSON a => Maybe Object -> Key -> Parser (Maybe a)
.:: Key
"time_in_millis")
Parser
(Maybe Int
-> Int
-> Bytes
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser (Maybe Int)
-> Parser
(Int
-> Bytes
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe Object
mPercolate Maybe Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Maybe Object -> Key -> Parser (Maybe a)
.:: Key
"total"
Parser
(Int
-> Bytes
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser Int
-> Parser
(Bytes
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
fielddata Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"evictions"
Parser
(Bytes
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser Bytes
-> Parser
(NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
fielddata Object -> Key -> Parser Bytes
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"memory_size_in_bytes"
Parser
(NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser NominalDiffTime
-> Parser
(Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (MS -> NominalDiffTime
unMS (MS -> NominalDiffTime) -> Parser MS -> Parser NominalDiffTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
warmer Object -> Key -> Parser MS
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"total_time_in_millis")
Parser
(Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser Int
-> Parser
(Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
warmer Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"total"
Parser
(Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser Int
-> Parser
(NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
warmer Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"current"
Parser
(NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser NominalDiffTime
-> Parser
(Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (MS -> NominalDiffTime
unMS (MS -> NominalDiffTime) -> Parser MS -> Parser NominalDiffTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
flush Object -> Key -> Parser MS
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"total_time_in_millis")
Parser
(Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser Int
-> Parser
(NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
flush Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"total"
Parser
(NominalDiffTime
-> Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser NominalDiffTime
-> Parser
(Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (MS -> NominalDiffTime
unMS (MS -> NominalDiffTime) -> Parser MS -> Parser NominalDiffTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
refresh Object -> Key -> Parser MS
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"total_time_in_millis")
Parser
(Int
-> Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser Int
-> Parser
(Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
refresh Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"total"
Parser
(Bytes
-> Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser Bytes
-> Parser
(Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
merges Object -> Key -> Parser Bytes
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"total_size_in_bytes"
Parser
(Int
-> NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser Int
-> Parser
(NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
merges Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"total_docs"
Parser
(NominalDiffTime
-> Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser NominalDiffTime
-> Parser
(Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (MS -> NominalDiffTime
unMS (MS -> NominalDiffTime) -> Parser MS -> Parser NominalDiffTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
merges Object -> Key -> Parser MS
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"total_time_in_millis")
Parser
(Int
-> Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser Int
-> Parser
(Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
merges Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"total"
Parser
(Bytes
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser Bytes
-> Parser
(Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
merges Object -> Key -> Parser Bytes
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"current_size_in_bytes"
Parser
(Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser Int
-> Parser
(Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
merges Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"current_docs"
Parser
(Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser Int
-> Parser
(Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
merges Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"current"
Parser
(Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser Int
-> Parser
(NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
search Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"fetch_current"
Parser
(NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser NominalDiffTime
-> Parser
(Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (MS -> NominalDiffTime
unMS (MS -> NominalDiffTime) -> Parser MS -> Parser NominalDiffTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
search Object -> Key -> Parser MS
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"fetch_time_in_millis")
Parser
(Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser Int
-> Parser
(Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
search Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"fetch_total"
Parser
(Int
-> NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser Int
-> Parser
(NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
search Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"query_current"
Parser
(NominalDiffTime
-> Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser NominalDiffTime
-> Parser
(Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (MS -> NominalDiffTime
unMS (MS -> NominalDiffTime) -> Parser MS -> Parser NominalDiffTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
search Object -> Key -> Parser MS
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"query_time_in_millis")
Parser
(Int
-> Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser Int
-> Parser
(Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
search Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"query_total"
Parser
(Int
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser Int
-> Parser
(Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
search Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"open_contexts"
Parser
(Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser Int
-> Parser
(NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
getStats Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"current"
Parser
(NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser NominalDiffTime
-> Parser
(Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (MS -> NominalDiffTime
unMS (MS -> NominalDiffTime) -> Parser MS -> Parser NominalDiffTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
getStats Object -> Key -> Parser MS
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"missing_time_in_millis")
Parser
(Int
-> NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser Int
-> Parser
(NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
getStats Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"missing_total"
Parser
(NominalDiffTime
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser NominalDiffTime
-> Parser
(Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (MS -> NominalDiffTime
unMS (MS -> NominalDiffTime) -> Parser MS -> Parser NominalDiffTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
getStats Object -> Key -> Parser MS
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"exists_time_in_millis")
Parser
(Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser Int
-> Parser
(NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
getStats Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"exists_total"
Parser
(NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser NominalDiffTime
-> Parser
(Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (MS -> NominalDiffTime
unMS (MS -> NominalDiffTime) -> Parser MS -> Parser NominalDiffTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
getStats Object -> Key -> Parser MS
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"time_in_millis")
Parser
(Int
-> Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser Int
-> Parser
(Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
getStats Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"total"
Parser
(Maybe NominalDiffTime
-> Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser (Maybe NominalDiffTime)
-> Parser
(Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ((MS -> NominalDiffTime) -> Maybe MS -> Maybe NominalDiffTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap MS -> NominalDiffTime
unMS (Maybe MS -> Maybe NominalDiffTime)
-> Parser (Maybe MS) -> Parser (Maybe NominalDiffTime)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
indexing Object -> Key -> Parser (Maybe MS)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"throttle_time_in_millis")
Parser
(Maybe Bool
-> Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser (Maybe Bool)
-> Parser
(Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
indexing Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"is_throttled"
Parser
(Maybe Int
-> Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser (Maybe Int)
-> Parser
(Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
indexing Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"noop_update_total"
Parser
(Int
-> NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser Int
-> Parser
(NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
indexing Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"delete_current"
Parser
(NominalDiffTime
-> Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser NominalDiffTime
-> Parser
(Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (MS -> NominalDiffTime
unMS (MS -> NominalDiffTime) -> Parser MS -> Parser NominalDiffTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
indexing Object -> Key -> Parser MS
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"delete_time_in_millis")
Parser
(Int
-> Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser Int
-> Parser
(Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
indexing Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"delete_total"
Parser
(Int
-> NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser Int
-> Parser
(NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
indexing Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"index_current"
Parser
(NominalDiffTime
-> Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser NominalDiffTime
-> Parser
(Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (MS -> NominalDiffTime
unMS (MS -> NominalDiffTime) -> Parser MS -> Parser NominalDiffTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
indexing Object -> Key -> Parser MS
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"index_time_in_millis")
Parser
(Int
-> Maybe NominalDiffTime
-> Bytes
-> Int
-> Int
-> NodeIndicesStats)
-> Parser Int
-> Parser
(Maybe NominalDiffTime -> Bytes -> Int -> Int -> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
indexing Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"index_total"
Parser
(Maybe NominalDiffTime -> Bytes -> Int -> Int -> NodeIndicesStats)
-> Parser (Maybe NominalDiffTime)
-> Parser (Bytes -> Int -> Int -> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ((MS -> NominalDiffTime) -> Maybe MS -> Maybe NominalDiffTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap MS -> NominalDiffTime
unMS (Maybe MS -> Maybe NominalDiffTime)
-> Parser (Maybe MS) -> Parser (Maybe NominalDiffTime)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
store Object -> Key -> Parser (Maybe MS)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"throttle_time_in_millis")
Parser (Bytes -> Int -> Int -> NodeIndicesStats)
-> Parser Bytes -> Parser (Int -> Int -> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
store Object -> Key -> Parser Bytes
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"size_in_bytes"
Parser (Int -> Int -> NodeIndicesStats)
-> Parser Int -> Parser (Int -> NodeIndicesStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
docs Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"deleted"
Parser (Int -> NodeIndicesStats)
-> Parser Int -> Parser NodeIndicesStats
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
docs Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"count"
instance FromJSON NodeBreakersStats where
parseJSON :: Value -> Parser NodeBreakersStats
parseJSON = String
-> (Object -> Parser NodeBreakersStats)
-> Value
-> Parser NodeBreakersStats
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"NodeBreakersStats" Object -> Parser NodeBreakersStats
parse
where
parse :: Object -> Parser NodeBreakersStats
parse Object
o = NodeBreakerStats
-> NodeBreakerStats -> NodeBreakerStats -> NodeBreakersStats
NodeBreakersStats (NodeBreakerStats
-> NodeBreakerStats -> NodeBreakerStats -> NodeBreakersStats)
-> Parser NodeBreakerStats
-> Parser
(NodeBreakerStats -> NodeBreakerStats -> NodeBreakersStats)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser NodeBreakerStats
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"parent"
Parser (NodeBreakerStats -> NodeBreakerStats -> NodeBreakersStats)
-> Parser NodeBreakerStats
-> Parser (NodeBreakerStats -> NodeBreakersStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser NodeBreakerStats
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"request"
Parser (NodeBreakerStats -> NodeBreakersStats)
-> Parser NodeBreakerStats -> Parser NodeBreakersStats
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser NodeBreakerStats
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"fielddata"
parseNodeStats :: FullNodeId -> Object -> Parser NodeStats
parseNodeStats :: FullNodeId -> Object -> Parser NodeStats
parseNodeStats FullNodeId
fnid Object
o =
NodeName
-> FullNodeId
-> Maybe NodeBreakersStats
-> NodeHTTPStats
-> NodeTransportStats
-> NodeFSStats
-> Maybe NodeNetworkStats
-> Map Text NodeThreadPoolStats
-> NodeJVMStats
-> NodeProcessStats
-> NodeOSStats
-> NodeIndicesStats
-> NodeStats
NodeStats (NodeName
-> FullNodeId
-> Maybe NodeBreakersStats
-> NodeHTTPStats
-> NodeTransportStats
-> NodeFSStats
-> Maybe NodeNetworkStats
-> Map Text NodeThreadPoolStats
-> NodeJVMStats
-> NodeProcessStats
-> NodeOSStats
-> NodeIndicesStats
-> NodeStats)
-> Parser NodeName
-> Parser
(FullNodeId
-> Maybe NodeBreakersStats
-> NodeHTTPStats
-> NodeTransportStats
-> NodeFSStats
-> Maybe NodeNetworkStats
-> Map Text NodeThreadPoolStats
-> NodeJVMStats
-> NodeProcessStats
-> NodeOSStats
-> NodeIndicesStats
-> NodeStats)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser NodeName
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"name"
Parser
(FullNodeId
-> Maybe NodeBreakersStats
-> NodeHTTPStats
-> NodeTransportStats
-> NodeFSStats
-> Maybe NodeNetworkStats
-> Map Text NodeThreadPoolStats
-> NodeJVMStats
-> NodeProcessStats
-> NodeOSStats
-> NodeIndicesStats
-> NodeStats)
-> Parser FullNodeId
-> Parser
(Maybe NodeBreakersStats
-> NodeHTTPStats
-> NodeTransportStats
-> NodeFSStats
-> Maybe NodeNetworkStats
-> Map Text NodeThreadPoolStats
-> NodeJVMStats
-> NodeProcessStats
-> NodeOSStats
-> NodeIndicesStats
-> NodeStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FullNodeId -> Parser FullNodeId
forall (f :: * -> *) a. Applicative f => a -> f a
pure FullNodeId
fnid
Parser
(Maybe NodeBreakersStats
-> NodeHTTPStats
-> NodeTransportStats
-> NodeFSStats
-> Maybe NodeNetworkStats
-> Map Text NodeThreadPoolStats
-> NodeJVMStats
-> NodeProcessStats
-> NodeOSStats
-> NodeIndicesStats
-> NodeStats)
-> Parser (Maybe NodeBreakersStats)
-> Parser
(NodeHTTPStats
-> NodeTransportStats
-> NodeFSStats
-> Maybe NodeNetworkStats
-> Map Text NodeThreadPoolStats
-> NodeJVMStats
-> NodeProcessStats
-> NodeOSStats
-> NodeIndicesStats
-> NodeStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe NodeBreakersStats)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"breakers"
Parser
(NodeHTTPStats
-> NodeTransportStats
-> NodeFSStats
-> Maybe NodeNetworkStats
-> Map Text NodeThreadPoolStats
-> NodeJVMStats
-> NodeProcessStats
-> NodeOSStats
-> NodeIndicesStats
-> NodeStats)
-> Parser NodeHTTPStats
-> Parser
(NodeTransportStats
-> NodeFSStats
-> Maybe NodeNetworkStats
-> Map Text NodeThreadPoolStats
-> NodeJVMStats
-> NodeProcessStats
-> NodeOSStats
-> NodeIndicesStats
-> NodeStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser NodeHTTPStats
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"http"
Parser
(NodeTransportStats
-> NodeFSStats
-> Maybe NodeNetworkStats
-> Map Text NodeThreadPoolStats
-> NodeJVMStats
-> NodeProcessStats
-> NodeOSStats
-> NodeIndicesStats
-> NodeStats)
-> Parser NodeTransportStats
-> Parser
(NodeFSStats
-> Maybe NodeNetworkStats
-> Map Text NodeThreadPoolStats
-> NodeJVMStats
-> NodeProcessStats
-> NodeOSStats
-> NodeIndicesStats
-> NodeStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser NodeTransportStats
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"transport"
Parser
(NodeFSStats
-> Maybe NodeNetworkStats
-> Map Text NodeThreadPoolStats
-> NodeJVMStats
-> NodeProcessStats
-> NodeOSStats
-> NodeIndicesStats
-> NodeStats)
-> Parser NodeFSStats
-> Parser
(Maybe NodeNetworkStats
-> Map Text NodeThreadPoolStats
-> NodeJVMStats
-> NodeProcessStats
-> NodeOSStats
-> NodeIndicesStats
-> NodeStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser NodeFSStats
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"fs"
Parser
(Maybe NodeNetworkStats
-> Map Text NodeThreadPoolStats
-> NodeJVMStats
-> NodeProcessStats
-> NodeOSStats
-> NodeIndicesStats
-> NodeStats)
-> Parser (Maybe NodeNetworkStats)
-> Parser
(Map Text NodeThreadPoolStats
-> NodeJVMStats
-> NodeProcessStats
-> NodeOSStats
-> NodeIndicesStats
-> NodeStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe NodeNetworkStats)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"network"
Parser
(Map Text NodeThreadPoolStats
-> NodeJVMStats
-> NodeProcessStats
-> NodeOSStats
-> NodeIndicesStats
-> NodeStats)
-> Parser (Map Text NodeThreadPoolStats)
-> Parser
(NodeJVMStats
-> NodeProcessStats
-> NodeOSStats
-> NodeIndicesStats
-> NodeStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Map Text NodeThreadPoolStats)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"thread_pool"
Parser
(NodeJVMStats
-> NodeProcessStats
-> NodeOSStats
-> NodeIndicesStats
-> NodeStats)
-> Parser NodeJVMStats
-> Parser
(NodeProcessStats -> NodeOSStats -> NodeIndicesStats -> NodeStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser NodeJVMStats
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"jvm"
Parser
(NodeProcessStats -> NodeOSStats -> NodeIndicesStats -> NodeStats)
-> Parser NodeProcessStats
-> Parser (NodeOSStats -> NodeIndicesStats -> NodeStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser NodeProcessStats
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"process"
Parser (NodeOSStats -> NodeIndicesStats -> NodeStats)
-> Parser NodeOSStats -> Parser (NodeIndicesStats -> NodeStats)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser NodeOSStats
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"os"
Parser (NodeIndicesStats -> NodeStats)
-> Parser NodeIndicesStats -> Parser NodeStats
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser NodeIndicesStats
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"indices"
parseNodeInfo :: FullNodeId -> Object -> Parser NodeInfo
parseNodeInfo :: FullNodeId -> Object -> Parser NodeInfo
parseNodeInfo FullNodeId
nid Object
o =
Maybe EsAddress
-> BuildHash
-> VersionNumber
-> Server
-> Server
-> EsAddress
-> NodeName
-> FullNodeId
-> [NodePluginInfo]
-> NodeHTTPInfo
-> NodeTransportInfo
-> Maybe NodeNetworkInfo
-> Map Text NodeThreadPoolInfo
-> NodeJVMInfo
-> NodeProcessInfo
-> NodeOSInfo
-> Object
-> NodeInfo
NodeInfo (Maybe EsAddress
-> BuildHash
-> VersionNumber
-> Server
-> Server
-> EsAddress
-> NodeName
-> FullNodeId
-> [NodePluginInfo]
-> NodeHTTPInfo
-> NodeTransportInfo
-> Maybe NodeNetworkInfo
-> Map Text NodeThreadPoolInfo
-> NodeJVMInfo
-> NodeProcessInfo
-> NodeOSInfo
-> Object
-> NodeInfo)
-> Parser (Maybe EsAddress)
-> Parser
(BuildHash
-> VersionNumber
-> Server
-> Server
-> EsAddress
-> NodeName
-> FullNodeId
-> [NodePluginInfo]
-> NodeHTTPInfo
-> NodeTransportInfo
-> Maybe NodeNetworkInfo
-> Map Text NodeThreadPoolInfo
-> NodeJVMInfo
-> NodeProcessInfo
-> NodeOSInfo
-> Object
-> NodeInfo)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser (Maybe EsAddress)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"http_address"
Parser
(BuildHash
-> VersionNumber
-> Server
-> Server
-> EsAddress
-> NodeName
-> FullNodeId
-> [NodePluginInfo]
-> NodeHTTPInfo
-> NodeTransportInfo
-> Maybe NodeNetworkInfo
-> Map Text NodeThreadPoolInfo
-> NodeJVMInfo
-> NodeProcessInfo
-> NodeOSInfo
-> Object
-> NodeInfo)
-> Parser BuildHash
-> Parser
(VersionNumber
-> Server
-> Server
-> EsAddress
-> NodeName
-> FullNodeId
-> [NodePluginInfo]
-> NodeHTTPInfo
-> NodeTransportInfo
-> Maybe NodeNetworkInfo
-> Map Text NodeThreadPoolInfo
-> NodeJVMInfo
-> NodeProcessInfo
-> NodeOSInfo
-> Object
-> NodeInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser BuildHash
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"build_hash"
Parser
(VersionNumber
-> Server
-> Server
-> EsAddress
-> NodeName
-> FullNodeId
-> [NodePluginInfo]
-> NodeHTTPInfo
-> NodeTransportInfo
-> Maybe NodeNetworkInfo
-> Map Text NodeThreadPoolInfo
-> NodeJVMInfo
-> NodeProcessInfo
-> NodeOSInfo
-> Object
-> NodeInfo)
-> Parser VersionNumber
-> Parser
(Server
-> Server
-> EsAddress
-> NodeName
-> FullNodeId
-> [NodePluginInfo]
-> NodeHTTPInfo
-> NodeTransportInfo
-> Maybe NodeNetworkInfo
-> Map Text NodeThreadPoolInfo
-> NodeJVMInfo
-> NodeProcessInfo
-> NodeOSInfo
-> Object
-> NodeInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser VersionNumber
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"version"
Parser
(Server
-> Server
-> EsAddress
-> NodeName
-> FullNodeId
-> [NodePluginInfo]
-> NodeHTTPInfo
-> NodeTransportInfo
-> Maybe NodeNetworkInfo
-> Map Text NodeThreadPoolInfo
-> NodeJVMInfo
-> NodeProcessInfo
-> NodeOSInfo
-> Object
-> NodeInfo)
-> Parser Server
-> Parser
(Server
-> EsAddress
-> NodeName
-> FullNodeId
-> [NodePluginInfo]
-> NodeHTTPInfo
-> NodeTransportInfo
-> Maybe NodeNetworkInfo
-> Map Text NodeThreadPoolInfo
-> NodeJVMInfo
-> NodeProcessInfo
-> NodeOSInfo
-> Object
-> NodeInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Server
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"ip"
Parser
(Server
-> EsAddress
-> NodeName
-> FullNodeId
-> [NodePluginInfo]
-> NodeHTTPInfo
-> NodeTransportInfo
-> Maybe NodeNetworkInfo
-> Map Text NodeThreadPoolInfo
-> NodeJVMInfo
-> NodeProcessInfo
-> NodeOSInfo
-> Object
-> NodeInfo)
-> Parser Server
-> Parser
(EsAddress
-> NodeName
-> FullNodeId
-> [NodePluginInfo]
-> NodeHTTPInfo
-> NodeTransportInfo
-> Maybe NodeNetworkInfo
-> Map Text NodeThreadPoolInfo
-> NodeJVMInfo
-> NodeProcessInfo
-> NodeOSInfo
-> Object
-> NodeInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Server
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"host"
Parser
(EsAddress
-> NodeName
-> FullNodeId
-> [NodePluginInfo]
-> NodeHTTPInfo
-> NodeTransportInfo
-> Maybe NodeNetworkInfo
-> Map Text NodeThreadPoolInfo
-> NodeJVMInfo
-> NodeProcessInfo
-> NodeOSInfo
-> Object
-> NodeInfo)
-> Parser EsAddress
-> Parser
(NodeName
-> FullNodeId
-> [NodePluginInfo]
-> NodeHTTPInfo
-> NodeTransportInfo
-> Maybe NodeNetworkInfo
-> Map Text NodeThreadPoolInfo
-> NodeJVMInfo
-> NodeProcessInfo
-> NodeOSInfo
-> Object
-> NodeInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser EsAddress
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"transport_address"
Parser
(NodeName
-> FullNodeId
-> [NodePluginInfo]
-> NodeHTTPInfo
-> NodeTransportInfo
-> Maybe NodeNetworkInfo
-> Map Text NodeThreadPoolInfo
-> NodeJVMInfo
-> NodeProcessInfo
-> NodeOSInfo
-> Object
-> NodeInfo)
-> Parser NodeName
-> Parser
(FullNodeId
-> [NodePluginInfo]
-> NodeHTTPInfo
-> NodeTransportInfo
-> Maybe NodeNetworkInfo
-> Map Text NodeThreadPoolInfo
-> NodeJVMInfo
-> NodeProcessInfo
-> NodeOSInfo
-> Object
-> NodeInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser NodeName
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"name"
Parser
(FullNodeId
-> [NodePluginInfo]
-> NodeHTTPInfo
-> NodeTransportInfo
-> Maybe NodeNetworkInfo
-> Map Text NodeThreadPoolInfo
-> NodeJVMInfo
-> NodeProcessInfo
-> NodeOSInfo
-> Object
-> NodeInfo)
-> Parser FullNodeId
-> Parser
([NodePluginInfo]
-> NodeHTTPInfo
-> NodeTransportInfo
-> Maybe NodeNetworkInfo
-> Map Text NodeThreadPoolInfo
-> NodeJVMInfo
-> NodeProcessInfo
-> NodeOSInfo
-> Object
-> NodeInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FullNodeId -> Parser FullNodeId
forall (f :: * -> *) a. Applicative f => a -> f a
pure FullNodeId
nid
Parser
([NodePluginInfo]
-> NodeHTTPInfo
-> NodeTransportInfo
-> Maybe NodeNetworkInfo
-> Map Text NodeThreadPoolInfo
-> NodeJVMInfo
-> NodeProcessInfo
-> NodeOSInfo
-> Object
-> NodeInfo)
-> Parser [NodePluginInfo]
-> Parser
(NodeHTTPInfo
-> NodeTransportInfo
-> Maybe NodeNetworkInfo
-> Map Text NodeThreadPoolInfo
-> NodeJVMInfo
-> NodeProcessInfo
-> NodeOSInfo
-> Object
-> NodeInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser [NodePluginInfo]
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"plugins"
Parser
(NodeHTTPInfo
-> NodeTransportInfo
-> Maybe NodeNetworkInfo
-> Map Text NodeThreadPoolInfo
-> NodeJVMInfo
-> NodeProcessInfo
-> NodeOSInfo
-> Object
-> NodeInfo)
-> Parser NodeHTTPInfo
-> Parser
(NodeTransportInfo
-> Maybe NodeNetworkInfo
-> Map Text NodeThreadPoolInfo
-> NodeJVMInfo
-> NodeProcessInfo
-> NodeOSInfo
-> Object
-> NodeInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser NodeHTTPInfo
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"http"
Parser
(NodeTransportInfo
-> Maybe NodeNetworkInfo
-> Map Text NodeThreadPoolInfo
-> NodeJVMInfo
-> NodeProcessInfo
-> NodeOSInfo
-> Object
-> NodeInfo)
-> Parser NodeTransportInfo
-> Parser
(Maybe NodeNetworkInfo
-> Map Text NodeThreadPoolInfo
-> NodeJVMInfo
-> NodeProcessInfo
-> NodeOSInfo
-> Object
-> NodeInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser NodeTransportInfo
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"transport"
Parser
(Maybe NodeNetworkInfo
-> Map Text NodeThreadPoolInfo
-> NodeJVMInfo
-> NodeProcessInfo
-> NodeOSInfo
-> Object
-> NodeInfo)
-> Parser (Maybe NodeNetworkInfo)
-> Parser
(Map Text NodeThreadPoolInfo
-> NodeJVMInfo
-> NodeProcessInfo
-> NodeOSInfo
-> Object
-> NodeInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe NodeNetworkInfo)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"network"
Parser
(Map Text NodeThreadPoolInfo
-> NodeJVMInfo
-> NodeProcessInfo
-> NodeOSInfo
-> Object
-> NodeInfo)
-> Parser (Map Text NodeThreadPoolInfo)
-> Parser
(NodeJVMInfo
-> NodeProcessInfo -> NodeOSInfo -> Object -> NodeInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Map Text NodeThreadPoolInfo)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"thread_pool"
Parser
(NodeJVMInfo
-> NodeProcessInfo -> NodeOSInfo -> Object -> NodeInfo)
-> Parser NodeJVMInfo
-> Parser (NodeProcessInfo -> NodeOSInfo -> Object -> NodeInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser NodeJVMInfo
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"jvm"
Parser (NodeProcessInfo -> NodeOSInfo -> Object -> NodeInfo)
-> Parser NodeProcessInfo
-> Parser (NodeOSInfo -> Object -> NodeInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser NodeProcessInfo
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"process"
Parser (NodeOSInfo -> Object -> NodeInfo)
-> Parser NodeOSInfo -> Parser (Object -> NodeInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser NodeOSInfo
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"os"
Parser (Object -> NodeInfo) -> Parser Object -> Parser NodeInfo
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Object
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"settings"
instance FromJSON NodePluginInfo where
parseJSON :: Value -> Parser NodePluginInfo
parseJSON = String
-> (Object -> Parser NodePluginInfo)
-> Value
-> Parser NodePluginInfo
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"NodePluginInfo" Object -> Parser NodePluginInfo
parse
where
parse :: Object -> Parser NodePluginInfo
parse Object
o = Maybe Bool
-> Maybe Bool
-> Text
-> MaybeNA VersionNumber
-> PluginName
-> NodePluginInfo
NodePluginInfo (Maybe Bool
-> Maybe Bool
-> Text
-> MaybeNA VersionNumber
-> PluginName
-> NodePluginInfo)
-> Parser (Maybe Bool)
-> Parser
(Maybe Bool
-> Text -> MaybeNA VersionNumber -> PluginName -> NodePluginInfo)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"site"
Parser
(Maybe Bool
-> Text -> MaybeNA VersionNumber -> PluginName -> NodePluginInfo)
-> Parser (Maybe Bool)
-> Parser
(Text -> MaybeNA VersionNumber -> PluginName -> NodePluginInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"jvm"
Parser
(Text -> MaybeNA VersionNumber -> PluginName -> NodePluginInfo)
-> Parser Text
-> Parser (MaybeNA VersionNumber -> PluginName -> NodePluginInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"description"
Parser (MaybeNA VersionNumber -> PluginName -> NodePluginInfo)
-> Parser (MaybeNA VersionNumber)
-> Parser (PluginName -> NodePluginInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (MaybeNA VersionNumber)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"version"
Parser (PluginName -> NodePluginInfo)
-> Parser PluginName -> Parser NodePluginInfo
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser PluginName
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"name"
instance FromJSON NodeHTTPInfo where
parseJSON :: Value -> Parser NodeHTTPInfo
parseJSON = String
-> (Object -> Parser NodeHTTPInfo) -> Value -> Parser NodeHTTPInfo
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"NodeHTTPInfo" Object -> Parser NodeHTTPInfo
parse
where
parse :: Object -> Parser NodeHTTPInfo
parse Object
o = Bytes -> EsAddress -> [EsAddress] -> NodeHTTPInfo
NodeHTTPInfo (Bytes -> EsAddress -> [EsAddress] -> NodeHTTPInfo)
-> Parser Bytes
-> Parser (EsAddress -> [EsAddress] -> NodeHTTPInfo)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser Bytes
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"max_content_length_in_bytes"
Parser (EsAddress -> [EsAddress] -> NodeHTTPInfo)
-> Parser EsAddress -> Parser ([EsAddress] -> NodeHTTPInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser EsAddress
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"publish_address"
Parser ([EsAddress] -> NodeHTTPInfo)
-> Parser [EsAddress] -> Parser NodeHTTPInfo
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser [EsAddress]
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"bound_address"
instance FromJSON BoundTransportAddress where
parseJSON :: Value -> Parser BoundTransportAddress
parseJSON = String
-> (Object -> Parser BoundTransportAddress)
-> Value
-> Parser BoundTransportAddress
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"BoundTransportAddress" Object -> Parser BoundTransportAddress
parse
where
parse :: Object -> Parser BoundTransportAddress
parse Object
o = EsAddress -> [EsAddress] -> BoundTransportAddress
BoundTransportAddress (EsAddress -> [EsAddress] -> BoundTransportAddress)
-> Parser EsAddress
-> Parser ([EsAddress] -> BoundTransportAddress)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser EsAddress
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"publish_address"
Parser ([EsAddress] -> BoundTransportAddress)
-> Parser [EsAddress] -> Parser BoundTransportAddress
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser [EsAddress]
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"bound_address"
instance FromJSON NodeOSInfo where
parseJSON :: Value -> Parser NodeOSInfo
parseJSON = String
-> (Object -> Parser NodeOSInfo) -> Value -> Parser NodeOSInfo
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"NodeOSInfo" Object -> Parser NodeOSInfo
parse
where
parse :: Object -> Parser NodeOSInfo
parse Object
o =
NominalDiffTime -> Text -> Text -> Text -> Int -> Int -> NodeOSInfo
NodeOSInfo (NominalDiffTime
-> Text -> Text -> Text -> Int -> Int -> NodeOSInfo)
-> Parser NominalDiffTime
-> Parser (Text -> Text -> Text -> Int -> Int -> NodeOSInfo)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (MS -> NominalDiffTime
unMS (MS -> NominalDiffTime) -> Parser MS -> Parser NominalDiffTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser MS
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"refresh_interval_in_millis")
Parser (Text -> Text -> Text -> Int -> Int -> NodeOSInfo)
-> Parser Text -> Parser (Text -> Text -> Int -> Int -> NodeOSInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"name"
Parser (Text -> Text -> Int -> Int -> NodeOSInfo)
-> Parser Text -> Parser (Text -> Int -> Int -> NodeOSInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"arch"
Parser (Text -> Int -> Int -> NodeOSInfo)
-> Parser Text -> Parser (Int -> Int -> NodeOSInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"version"
Parser (Int -> Int -> NodeOSInfo)
-> Parser Int -> Parser (Int -> NodeOSInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"available_processors"
Parser (Int -> NodeOSInfo) -> Parser Int -> Parser NodeOSInfo
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"allocated_processors"
instance FromJSON CPUInfo where
parseJSON :: Value -> Parser CPUInfo
parseJSON = String -> (Object -> Parser CPUInfo) -> Value -> Parser CPUInfo
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"CPUInfo" Object -> Parser CPUInfo
parse
where
parse :: Object -> Parser CPUInfo
parse Object
o = Bytes -> Int -> Int -> Int -> Int -> Text -> Text -> CPUInfo
CPUInfo (Bytes -> Int -> Int -> Int -> Int -> Text -> Text -> CPUInfo)
-> Parser Bytes
-> Parser (Int -> Int -> Int -> Int -> Text -> Text -> CPUInfo)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser Bytes
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"cache_size_in_bytes"
Parser (Int -> Int -> Int -> Int -> Text -> Text -> CPUInfo)
-> Parser Int
-> Parser (Int -> Int -> Int -> Text -> Text -> CPUInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"cores_per_socket"
Parser (Int -> Int -> Int -> Text -> Text -> CPUInfo)
-> Parser Int -> Parser (Int -> Int -> Text -> Text -> CPUInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"total_sockets"
Parser (Int -> Int -> Text -> Text -> CPUInfo)
-> Parser Int -> Parser (Int -> Text -> Text -> CPUInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"total_cores"
Parser (Int -> Text -> Text -> CPUInfo)
-> Parser Int -> Parser (Text -> Text -> CPUInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"mhz"
Parser (Text -> Text -> CPUInfo)
-> Parser Text -> Parser (Text -> CPUInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"model"
Parser (Text -> CPUInfo) -> Parser Text -> Parser CPUInfo
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"vendor"
instance FromJSON NodeProcessInfo where
parseJSON :: Value -> Parser NodeProcessInfo
parseJSON = String
-> (Object -> Parser NodeProcessInfo)
-> Value
-> Parser NodeProcessInfo
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"NodeProcessInfo" Object -> Parser NodeProcessInfo
parse
where
parse :: Object -> Parser NodeProcessInfo
parse Object
o = Bool -> Maybe Int -> PID -> NominalDiffTime -> NodeProcessInfo
NodeProcessInfo (Bool -> Maybe Int -> PID -> NominalDiffTime -> NodeProcessInfo)
-> Parser Bool
-> Parser (Maybe Int -> PID -> NominalDiffTime -> NodeProcessInfo)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser Bool
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"mlockall"
Parser (Maybe Int -> PID -> NominalDiffTime -> NodeProcessInfo)
-> Parser (Maybe Int)
-> Parser (PID -> NominalDiffTime -> NodeProcessInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"max_file_descriptors"
Parser (PID -> NominalDiffTime -> NodeProcessInfo)
-> Parser PID -> Parser (NominalDiffTime -> NodeProcessInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser PID
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"id"
Parser (NominalDiffTime -> NodeProcessInfo)
-> Parser NominalDiffTime -> Parser NodeProcessInfo
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (MS -> NominalDiffTime
unMS (MS -> NominalDiffTime) -> Parser MS -> Parser NominalDiffTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser MS
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"refresh_interval_in_millis")
instance FromJSON NodeJVMInfo where
parseJSON :: Value -> Parser NodeJVMInfo
parseJSON = String
-> (Object -> Parser NodeJVMInfo) -> Value -> Parser NodeJVMInfo
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"NodeJVMInfo" Object -> Parser NodeJVMInfo
parse
where
parse :: Object -> Parser NodeJVMInfo
parse Object
o = [JVMMemoryPool]
-> [JVMGCCollector]
-> JVMMemoryInfo
-> UTCTime
-> Text
-> VMVersion
-> Text
-> JVMVersion
-> PID
-> NodeJVMInfo
NodeJVMInfo ([JVMMemoryPool]
-> [JVMGCCollector]
-> JVMMemoryInfo
-> UTCTime
-> Text
-> VMVersion
-> Text
-> JVMVersion
-> PID
-> NodeJVMInfo)
-> Parser [JVMMemoryPool]
-> Parser
([JVMGCCollector]
-> JVMMemoryInfo
-> UTCTime
-> Text
-> VMVersion
-> Text
-> JVMVersion
-> PID
-> NodeJVMInfo)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser [JVMMemoryPool]
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"memory_pools"
Parser
([JVMGCCollector]
-> JVMMemoryInfo
-> UTCTime
-> Text
-> VMVersion
-> Text
-> JVMVersion
-> PID
-> NodeJVMInfo)
-> Parser [JVMGCCollector]
-> Parser
(JVMMemoryInfo
-> UTCTime
-> Text
-> VMVersion
-> Text
-> JVMVersion
-> PID
-> NodeJVMInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser [JVMGCCollector]
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"gc_collectors"
Parser
(JVMMemoryInfo
-> UTCTime
-> Text
-> VMVersion
-> Text
-> JVMVersion
-> PID
-> NodeJVMInfo)
-> Parser JVMMemoryInfo
-> Parser
(UTCTime
-> Text -> VMVersion -> Text -> JVMVersion -> PID -> NodeJVMInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser JVMMemoryInfo
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"mem"
Parser
(UTCTime
-> Text -> VMVersion -> Text -> JVMVersion -> PID -> NodeJVMInfo)
-> Parser UTCTime
-> Parser
(Text -> VMVersion -> Text -> JVMVersion -> PID -> NodeJVMInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (POSIXMS -> UTCTime
posixMS (POSIXMS -> UTCTime) -> Parser POSIXMS -> Parser UTCTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser POSIXMS
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"start_time_in_millis")
Parser
(Text -> VMVersion -> Text -> JVMVersion -> PID -> NodeJVMInfo)
-> Parser Text
-> Parser (VMVersion -> Text -> JVMVersion -> PID -> NodeJVMInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"vm_vendor"
Parser (VMVersion -> Text -> JVMVersion -> PID -> NodeJVMInfo)
-> Parser VMVersion
-> Parser (Text -> JVMVersion -> PID -> NodeJVMInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser VMVersion
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"vm_version"
Parser (Text -> JVMVersion -> PID -> NodeJVMInfo)
-> Parser Text -> Parser (JVMVersion -> PID -> NodeJVMInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"vm_name"
Parser (JVMVersion -> PID -> NodeJVMInfo)
-> Parser JVMVersion -> Parser (PID -> NodeJVMInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser JVMVersion
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"version"
Parser (PID -> NodeJVMInfo) -> Parser PID -> Parser NodeJVMInfo
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser PID
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"pid"
instance FromJSON JVMMemoryInfo where
parseJSON :: Value -> Parser JVMMemoryInfo
parseJSON = String
-> (Object -> Parser JVMMemoryInfo)
-> Value
-> Parser JVMMemoryInfo
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"JVMMemoryInfo" Object -> Parser JVMMemoryInfo
parse
where
parse :: Object -> Parser JVMMemoryInfo
parse Object
o = Bytes -> Bytes -> Bytes -> Bytes -> Bytes -> JVMMemoryInfo
JVMMemoryInfo (Bytes -> Bytes -> Bytes -> Bytes -> Bytes -> JVMMemoryInfo)
-> Parser Bytes
-> Parser (Bytes -> Bytes -> Bytes -> Bytes -> JVMMemoryInfo)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser Bytes
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"direct_max_in_bytes"
Parser (Bytes -> Bytes -> Bytes -> Bytes -> JVMMemoryInfo)
-> Parser Bytes
-> Parser (Bytes -> Bytes -> Bytes -> JVMMemoryInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Bytes
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"non_heap_max_in_bytes"
Parser (Bytes -> Bytes -> Bytes -> JVMMemoryInfo)
-> Parser Bytes -> Parser (Bytes -> Bytes -> JVMMemoryInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Bytes
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"non_heap_init_in_bytes"
Parser (Bytes -> Bytes -> JVMMemoryInfo)
-> Parser Bytes -> Parser (Bytes -> JVMMemoryInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Bytes
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"heap_max_in_bytes"
Parser (Bytes -> JVMMemoryInfo)
-> Parser Bytes -> Parser JVMMemoryInfo
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Bytes
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"heap_init_in_bytes"
instance FromJSON NodeThreadPoolInfo where
parseJSON :: Value -> Parser NodeThreadPoolInfo
parseJSON = String
-> (Object -> Parser NodeThreadPoolInfo)
-> Value
-> Parser NodeThreadPoolInfo
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"NodeThreadPoolInfo" Object -> Parser NodeThreadPoolInfo
parse
where
parse :: Object -> Parser NodeThreadPoolInfo
parse Object
o = do
Maybe NominalDiffTime
ka <- Parser (Maybe NominalDiffTime)
-> (String -> Parser (Maybe NominalDiffTime))
-> Maybe String
-> Parser (Maybe NominalDiffTime)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Maybe NominalDiffTime -> Parser (Maybe NominalDiffTime)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe NominalDiffTime
forall a. Maybe a
Nothing) ((NominalDiffTime -> Maybe NominalDiffTime)
-> Parser NominalDiffTime -> Parser (Maybe NominalDiffTime)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap NominalDiffTime -> Maybe NominalDiffTime
forall a. a -> Maybe a
Just (Parser NominalDiffTime -> Parser (Maybe NominalDiffTime))
-> (String -> Parser NominalDiffTime)
-> String
-> Parser (Maybe NominalDiffTime)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Parser NominalDiffTime
forall (m :: * -> *).
(Monad m, MonadFail m) =>
String -> m NominalDiffTime
parseStringInterval) (Maybe String -> Parser (Maybe NominalDiffTime))
-> Parser (Maybe String) -> Parser (Maybe NominalDiffTime)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Object
o Object -> Key -> Parser (Maybe String)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"keep_alive"
ThreadPoolSize
-> Maybe NominalDiffTime
-> Maybe Int
-> Maybe Int
-> ThreadPoolType
-> NodeThreadPoolInfo
NodeThreadPoolInfo (ThreadPoolSize
-> Maybe NominalDiffTime
-> Maybe Int
-> Maybe Int
-> ThreadPoolType
-> NodeThreadPoolInfo)
-> Parser ThreadPoolSize
-> Parser
(Maybe NominalDiffTime
-> Maybe Int -> Maybe Int -> ThreadPoolType -> NodeThreadPoolInfo)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Value -> Parser ThreadPoolSize
forall a. FromJSON a => Value -> Parser a
parseJSON (Value -> Parser ThreadPoolSize)
-> (Value -> Value) -> Value -> Parser ThreadPoolSize
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> Value
unStringlyTypeJSON (Value -> Parser ThreadPoolSize)
-> Parser Value -> Parser ThreadPoolSize
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Object
o Object -> Key -> Parser Value
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"queue_size")
Parser
(Maybe NominalDiffTime
-> Maybe Int -> Maybe Int -> ThreadPoolType -> NodeThreadPoolInfo)
-> Parser (Maybe NominalDiffTime)
-> Parser
(Maybe Int -> Maybe Int -> ThreadPoolType -> NodeThreadPoolInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe NominalDiffTime -> Parser (Maybe NominalDiffTime)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe NominalDiffTime
ka
Parser
(Maybe Int -> Maybe Int -> ThreadPoolType -> NodeThreadPoolInfo)
-> Parser (Maybe Int)
-> Parser (Maybe Int -> ThreadPoolType -> NodeThreadPoolInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"min"
Parser (Maybe Int -> ThreadPoolType -> NodeThreadPoolInfo)
-> Parser (Maybe Int)
-> Parser (ThreadPoolType -> NodeThreadPoolInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"max"
Parser (ThreadPoolType -> NodeThreadPoolInfo)
-> Parser ThreadPoolType -> Parser NodeThreadPoolInfo
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser ThreadPoolType
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"type"
data TimeInterval = Weeks
| Days
| Hours
| Minutes
| Seconds deriving TimeInterval -> TimeInterval -> Bool
(TimeInterval -> TimeInterval -> Bool)
-> (TimeInterval -> TimeInterval -> Bool) -> Eq TimeInterval
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TimeInterval -> TimeInterval -> Bool
$c/= :: TimeInterval -> TimeInterval -> Bool
== :: TimeInterval -> TimeInterval -> Bool
$c== :: TimeInterval -> TimeInterval -> Bool
Eq
instance Show TimeInterval where
show :: TimeInterval -> String
show TimeInterval
Weeks = String
"w"
show TimeInterval
Days = String
"d"
show TimeInterval
Hours = String
"h"
show TimeInterval
Minutes = String
"m"
show TimeInterval
Seconds = String
"s"
instance Read TimeInterval where
readPrec :: ReadPrec TimeInterval
readPrec = Char -> ReadPrec TimeInterval
forall (m :: * -> *). MonadFail m => Char -> m TimeInterval
f (Char -> ReadPrec TimeInterval)
-> ReadPrec Char -> ReadPrec TimeInterval
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< ReadPrec Char
TR.get
where
f :: Char -> m TimeInterval
f Char
'w' = TimeInterval -> m TimeInterval
forall (m :: * -> *) a. Monad m => a -> m a
return TimeInterval
Weeks
f Char
'd' = TimeInterval -> m TimeInterval
forall (m :: * -> *) a. Monad m => a -> m a
return TimeInterval
Days
f Char
'h' = TimeInterval -> m TimeInterval
forall (m :: * -> *) a. Monad m => a -> m a
return TimeInterval
Hours
f Char
'm' = TimeInterval -> m TimeInterval
forall (m :: * -> *) a. Monad m => a -> m a
return TimeInterval
Minutes
f Char
's' = TimeInterval -> m TimeInterval
forall (m :: * -> *) a. Monad m => a -> m a
return TimeInterval
Seconds
f Char
_ = String -> m TimeInterval
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"TimeInterval expected one of w, d, h, m, s"
data Interval = Year
| Quarter
| Month
| Week
| Day
| Hour
| Minute
| Second deriving (Interval -> Interval -> Bool
(Interval -> Interval -> Bool)
-> (Interval -> Interval -> Bool) -> Eq Interval
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Interval -> Interval -> Bool
$c/= :: Interval -> Interval -> Bool
== :: Interval -> Interval -> Bool
$c== :: Interval -> Interval -> Bool
Eq, Int -> Interval -> ShowS
[Interval] -> ShowS
Interval -> String
(Int -> Interval -> ShowS)
-> (Interval -> String) -> ([Interval] -> ShowS) -> Show Interval
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Interval] -> ShowS
$cshowList :: [Interval] -> ShowS
show :: Interval -> String
$cshow :: Interval -> String
showsPrec :: Int -> Interval -> ShowS
$cshowsPrec :: Int -> Interval -> ShowS
Show)
instance ToJSON Interval where
toJSON :: Interval -> Value
toJSON Interval
Year = Value
"year"
toJSON Interval
Quarter = Value
"quarter"
toJSON Interval
Month = Value
"month"
toJSON Interval
Week = Value
"week"
toJSON Interval
Day = Value
"day"
toJSON Interval
Hour = Value
"hour"
toJSON Interval
Minute = Value
"minute"
toJSON Interval
Second = Value
"second"
parseStringInterval :: (Monad m, MonadFail m) => String -> m NominalDiffTime
parseStringInterval :: String -> m NominalDiffTime
parseStringInterval String
s = case (Char -> Bool) -> String -> (String, String)
forall a. (a -> Bool) -> [a] -> ([a], [a])
span Char -> Bool
isNumber String
s of
(String
"", String
_) -> String -> m NominalDiffTime
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Invalid interval"
(String
nS, String
unitS) -> case (String -> Maybe Integer
forall a. Read a => String -> Maybe a
readMay String
nS, String -> Maybe TimeInterval
forall a. Read a => String -> Maybe a
readMay String
unitS) of
(Just Integer
n, Just TimeInterval
unit) -> NominalDiffTime -> m NominalDiffTime
forall (m :: * -> *) a. Monad m => a -> m a
return (Integer -> NominalDiffTime
forall a. Num a => Integer -> a
fromInteger (Integer
n Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* TimeInterval -> Integer
forall p. Num p => TimeInterval -> p
unitNDT TimeInterval
unit))
(Maybe Integer
Nothing, Maybe TimeInterval
_) -> String -> m NominalDiffTime
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Invalid interval number"
(Maybe Integer
_, Maybe TimeInterval
Nothing) -> String -> m NominalDiffTime
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Invalid interval unit"
where
unitNDT :: TimeInterval -> p
unitNDT TimeInterval
Seconds = p
1
unitNDT TimeInterval
Minutes = p
60
unitNDT TimeInterval
Hours = p
60 p -> p -> p
forall a. Num a => a -> a -> a
* p
60
unitNDT TimeInterval
Days = p
24 p -> p -> p
forall a. Num a => a -> a -> a
* p
60 p -> p -> p
forall a. Num a => a -> a -> a
* p
60
unitNDT TimeInterval
Weeks = p
7 p -> p -> p
forall a. Num a => a -> a -> a
* p
24 p -> p -> p
forall a. Num a => a -> a -> a
* p
60 p -> p -> p
forall a. Num a => a -> a -> a
* p
60
instance FromJSON ThreadPoolSize where
parseJSON :: Value -> Parser ThreadPoolSize
parseJSON Value
v = Value -> Parser ThreadPoolSize
parseAsNumber Value
v Parser ThreadPoolSize
-> Parser ThreadPoolSize -> Parser ThreadPoolSize
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Value -> Parser ThreadPoolSize
parseAsString Value
v
where
parseAsNumber :: Value -> Parser ThreadPoolSize
parseAsNumber = Int -> Parser ThreadPoolSize
forall (m :: * -> *). MonadFail m => Int -> m ThreadPoolSize
parseAsInt (Int -> Parser ThreadPoolSize)
-> (Value -> Parser Int) -> Value -> Parser ThreadPoolSize
forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< Value -> Parser Int
forall a. FromJSON a => Value -> Parser a
parseJSON
parseAsInt :: Int -> m ThreadPoolSize
parseAsInt (-1) = ThreadPoolSize -> m ThreadPoolSize
forall (m :: * -> *) a. Monad m => a -> m a
return ThreadPoolSize
ThreadPoolUnbounded
parseAsInt Int
n
| Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
0 = ThreadPoolSize -> m ThreadPoolSize
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> ThreadPoolSize
ThreadPoolBounded Int
n)
| Bool
otherwise = String -> m ThreadPoolSize
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Thread pool size must be >= -1."
parseAsString :: Value -> Parser ThreadPoolSize
parseAsString = String
-> (Text -> Parser ThreadPoolSize)
-> Value
-> Parser ThreadPoolSize
forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"ThreadPoolSize" ((Text -> Parser ThreadPoolSize) -> Value -> Parser ThreadPoolSize)
-> (Text -> Parser ThreadPoolSize)
-> Value
-> Parser ThreadPoolSize
forall a b. (a -> b) -> a -> b
$ \Text
t ->
case (Text -> Maybe Int) -> (Text, Text) -> (Maybe Int, Text)
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first (String -> Maybe Int
forall a. Read a => String -> Maybe a
readMay (String -> Maybe Int) -> (Text -> String) -> Text -> Maybe Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
T.unpack) ((Char -> Bool) -> Text -> (Text, Text)
T.span Char -> Bool
isNumber Text
t) of
(Just Int
n, Text
"k") -> ThreadPoolSize -> Parser ThreadPoolSize
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> ThreadPoolSize
ThreadPoolBounded (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
1000))
(Just Int
n, Text
"") -> ThreadPoolSize -> Parser ThreadPoolSize
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> ThreadPoolSize
ThreadPoolBounded Int
n)
(Maybe Int, Text)
_ -> String -> Parser ThreadPoolSize
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String
"Invalid thread pool size " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Text -> String
T.unpack Text
t)
instance FromJSON ThreadPoolType where
parseJSON :: Value -> Parser ThreadPoolType
parseJSON = String
-> (Text -> Parser ThreadPoolType)
-> Value
-> Parser ThreadPoolType
forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"ThreadPoolType" Text -> Parser ThreadPoolType
forall (m :: * -> *). MonadFail m => Text -> m ThreadPoolType
parse
where
parse :: Text -> m ThreadPoolType
parse Text
"scaling" = ThreadPoolType -> m ThreadPoolType
forall (m :: * -> *) a. Monad m => a -> m a
return ThreadPoolType
ThreadPoolScaling
parse Text
"fixed" = ThreadPoolType -> m ThreadPoolType
forall (m :: * -> *) a. Monad m => a -> m a
return ThreadPoolType
ThreadPoolFixed
parse Text
"cached" = ThreadPoolType -> m ThreadPoolType
forall (m :: * -> *) a. Monad m => a -> m a
return ThreadPoolType
ThreadPoolCached
parse Text
"fixed_auto_queue_size" = ThreadPoolType -> m ThreadPoolType
forall (m :: * -> *) a. Monad m => a -> m a
return ThreadPoolType
ThreadPoolFixedAutoQueueSize
parse Text
e = String -> m ThreadPoolType
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String
"Unexpected thread pool type" String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Text -> String
T.unpack Text
e)
instance FromJSON NodeTransportInfo where
parseJSON :: Value -> Parser NodeTransportInfo
parseJSON = String
-> (Object -> Parser NodeTransportInfo)
-> Value
-> Parser NodeTransportInfo
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"NodeTransportInfo" Object -> Parser NodeTransportInfo
parse
where
parse :: Object -> Parser NodeTransportInfo
parse Object
o = [BoundTransportAddress]
-> EsAddress -> [EsAddress] -> NodeTransportInfo
NodeTransportInfo ([BoundTransportAddress]
-> EsAddress -> [EsAddress] -> NodeTransportInfo)
-> Parser [BoundTransportAddress]
-> Parser (EsAddress -> [EsAddress] -> NodeTransportInfo)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Parser [BoundTransportAddress]
-> (Value -> Parser [BoundTransportAddress])
-> Maybe Value
-> Parser [BoundTransportAddress]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe ([BoundTransportAddress] -> Parser [BoundTransportAddress]
forall (m :: * -> *) a. Monad m => a -> m a
return [BoundTransportAddress]
forall a. Monoid a => a
mempty) Value -> Parser [BoundTransportAddress]
forall a. FromJSON a => Value -> Parser [a]
parseProfiles (Maybe Value -> Parser [BoundTransportAddress])
-> Parser (Maybe Value) -> Parser [BoundTransportAddress]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Object
o Object -> Key -> Parser (Maybe Value)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"profiles")
Parser (EsAddress -> [EsAddress] -> NodeTransportInfo)
-> Parser EsAddress -> Parser ([EsAddress] -> NodeTransportInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser EsAddress
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"publish_address"
Parser ([EsAddress] -> NodeTransportInfo)
-> Parser [EsAddress] -> Parser NodeTransportInfo
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser [EsAddress]
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"bound_address"
parseProfiles :: Value -> Parser [a]
parseProfiles (Object Object
o) | Object -> Bool
forall v. KeyMap v -> Bool
X.null Object
o = [a] -> Parser [a]
forall (m :: * -> *) a. Monad m => a -> m a
return []
parseProfiles v :: Value
v@(Array Array
_) = Value -> Parser [a]
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v
parseProfiles Value
Null = [a] -> Parser [a]
forall (m :: * -> *) a. Monad m => a -> m a
return []
parseProfiles Value
_ = String -> Parser [a]
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Could not parse profiles"
instance FromJSON NodeNetworkInfo where
parseJSON :: Value -> Parser NodeNetworkInfo
parseJSON = String
-> (Object -> Parser NodeNetworkInfo)
-> Value
-> Parser NodeNetworkInfo
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"NodeNetworkInfo" Object -> Parser NodeNetworkInfo
parse
where
parse :: Object -> Parser NodeNetworkInfo
parse Object
o = NodeNetworkInterface -> NominalDiffTime -> NodeNetworkInfo
NodeNetworkInfo (NodeNetworkInterface -> NominalDiffTime -> NodeNetworkInfo)
-> Parser NodeNetworkInterface
-> Parser (NominalDiffTime -> NodeNetworkInfo)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser NodeNetworkInterface
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"primary_interface"
Parser (NominalDiffTime -> NodeNetworkInfo)
-> Parser NominalDiffTime -> Parser NodeNetworkInfo
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (MS -> NominalDiffTime
unMS (MS -> NominalDiffTime) -> Parser MS -> Parser NominalDiffTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser MS
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"refresh_interval_in_millis")
instance FromJSON NodeNetworkInterface where
parseJSON :: Value -> Parser NodeNetworkInterface
parseJSON = String
-> (Object -> Parser NodeNetworkInterface)
-> Value
-> Parser NodeNetworkInterface
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"NodeNetworkInterface" Object -> Parser NodeNetworkInterface
parse
where
parse :: Object -> Parser NodeNetworkInterface
parse Object
o = MacAddress
-> NetworkInterfaceName -> Server -> NodeNetworkInterface
NodeNetworkInterface (MacAddress
-> NetworkInterfaceName -> Server -> NodeNetworkInterface)
-> Parser MacAddress
-> Parser (NetworkInterfaceName -> Server -> NodeNetworkInterface)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser MacAddress
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"mac_address"
Parser (NetworkInterfaceName -> Server -> NodeNetworkInterface)
-> Parser NetworkInterfaceName
-> Parser (Server -> NodeNetworkInterface)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser NetworkInterfaceName
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"name"
Parser (Server -> NodeNetworkInterface)
-> Parser Server -> Parser NodeNetworkInterface
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Server
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"address"
instance ToJSON Version where
toJSON :: Version -> Value
toJSON Version {Bool
UTCTime
BuildHash
VersionNumber
lucene_version :: VersionNumber
build_snapshot :: Bool
build_date :: UTCTime
build_hash :: BuildHash
number :: VersionNumber
lucene_version :: Version -> VersionNumber
build_snapshot :: Version -> Bool
build_date :: Version -> UTCTime
build_hash :: Version -> BuildHash
number :: Version -> VersionNumber
..} = [Pair] -> Value
object [Key
"number" Key -> VersionNumber -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= VersionNumber
number
,Key
"build_hash" Key -> BuildHash -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= BuildHash
build_hash
,Key
"build_date" Key -> UTCTime -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= UTCTime
build_date
,Key
"build_snapshot" Key -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Bool
build_snapshot
,Key
"lucene_version" Key -> VersionNumber -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= VersionNumber
lucene_version]
instance FromJSON Version where
parseJSON :: Value -> Parser Version
parseJSON = String -> (Object -> Parser Version) -> Value -> Parser Version
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Version" Object -> Parser Version
parse
where parse :: Object -> Parser Version
parse Object
o = VersionNumber
-> BuildHash -> UTCTime -> Bool -> VersionNumber -> Version
Version
(VersionNumber
-> BuildHash -> UTCTime -> Bool -> VersionNumber -> Version)
-> Parser VersionNumber
-> Parser
(BuildHash -> UTCTime -> Bool -> VersionNumber -> Version)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser VersionNumber
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"number"
Parser (BuildHash -> UTCTime -> Bool -> VersionNumber -> Version)
-> Parser BuildHash
-> Parser (UTCTime -> Bool -> VersionNumber -> Version)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser BuildHash
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"build_hash"
Parser (UTCTime -> Bool -> VersionNumber -> Version)
-> Parser UTCTime -> Parser (Bool -> VersionNumber -> Version)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser UTCTime
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"build_date"
Parser (Bool -> VersionNumber -> Version)
-> Parser Bool -> Parser (VersionNumber -> Version)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Bool
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"build_snapshot"
Parser (VersionNumber -> Version)
-> Parser VersionNumber -> Parser Version
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser VersionNumber
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"lucene_version"
instance ToJSON VersionNumber where
toJSON :: VersionNumber -> Value
toJSON = Text -> Value
forall a. ToJSON a => a -> Value
toJSON (Text -> Value)
-> (VersionNumber -> Text) -> VersionNumber -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Version -> Text
SemVer.toText (Version -> Text)
-> (VersionNumber -> Version) -> VersionNumber -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VersionNumber -> Version
versionNumber
instance FromJSON VersionNumber where
parseJSON :: Value -> Parser VersionNumber
parseJSON = String
-> (Text -> Parser VersionNumber) -> Value -> Parser VersionNumber
forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"VersionNumber" Text -> Parser VersionNumber
forall (m :: * -> *). MonadFail m => Text -> m VersionNumber
parse
where
parse :: Text -> m VersionNumber
parse Text
t =
case Text -> Either String Version
SemVer.fromText Text
t of
(Left String
err) -> String -> m VersionNumber
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
err
(Right Version
v) -> VersionNumber -> m VersionNumber
forall (m :: * -> *) a. Monad m => a -> m a
return (Version -> VersionNumber
VersionNumber Version
v)