{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
module Database.Bloodhound.Internal.Versions.Common.Types.Nodes
( BoundTransportAddress (..),
BuildHash (..),
CPUInfo (..),
ClusterName (..),
DeletedDocuments (..),
DeletedDocumentsRetries (..),
EsAddress (..),
EsPassword (..),
EsUsername (..),
FullNodeId (..),
HealthStatus (..),
IndexedDocument (..),
InitialShardCount (..),
JVMBufferPoolStats (..),
JVMGCCollector (..),
JVMGCStats (..),
JVMMemoryInfo (..),
JVMMemoryPool (..),
JVMPoolStats (..),
JVMVersion (..),
LoadAvgs (..),
MacAddress (..),
NetworkInterfaceName (..),
NodeAttrFilter (..),
NodeAttrName (..),
NodeBreakerStats (..),
NodeBreakersStats (..),
NodeDataPathStats (..),
NodeFSStats (..),
NodeFSTotalStats (..),
NodeHTTPInfo (..),
NodeHTTPStats (..),
NodeIndicesStats (..),
NodeInfo (..),
NodeJVMInfo (..),
NodeJVMStats (..),
NodeName (..),
NodeNetworkInfo (..),
NodeNetworkInterface (..),
NodeNetworkStats (..),
NodeOSInfo (..),
NodeOSStats (..),
NodePluginInfo (..),
NodeProcessInfo (..),
NodeProcessStats (..),
NodeSelection (..),
NodeSelector (..),
NodeStats (..),
NodeThreadPoolInfo (..),
NodeThreadPoolStats (..),
NodeTransportInfo (..),
NodeTransportStats (..),
NodesInfo (..),
NodesStats (..),
PID (..),
PluginName (..),
ShardResult (..),
ShardsResult (..),
ThreadPool (..),
ThreadPoolSize (..),
ThreadPoolType (..),
Version (..),
VersionNumber (..),
nodeAttrFilterNameLens,
nodeAttrFilterValuesLens,
nodeSelectionNodeListPrism,
nodeSelectorNodeByNamePrism,
nodeSelectorNodeByFullNodeIdPrism,
nodeSelectorNodeByHostPrism,
nodeSelectorNodeByAttributePrism,
nodesInfoListLens,
nodesClusterNameLens,
nodesStatsListLens,
nodesStatsClusterNameLens,
nodeStatsNameLens,
nodeStatsFullIdLens,
nodeStatsBreakersStatsLens,
nodeStatsHTTPLens,
nodeStatsTransportLens,
nodeStatsFSLens,
nodeStatsNetworkLens,
nodeStatsThreadPoolLens,
nodeStatsJVMLens,
nodeStatsProcessLens,
nodeStatsOSLens,
nodeStatsIndicesLens,
nodeStatsParentBreakerLens,
nodeStatsRequestBreakerLens,
nodeStatsFieldDataBreakerLens,
nodeBreakersStatsTrippedLens,
nodeBreakersStatsOverheadLens,
nodeBreakersStatsEstSizeLens,
nodeBreakersStatsLimitSizeLens,
nodeHTTPTotalStatsOpenedLens,
nodeHTTPStatsCurrentOpenLens,
nodeTransportStatsTXSizeLens,
nodeTransportStatsCountLens,
nodeTransportStatsRXSizeLens,
nodeTransportStatsRXCountLens,
nodeTransportStatsServerOpenLens,
nodeFSStatsDataPathsLens,
nodeFSStatsTotalLens,
nodeFSStatsTimestampLens,
nodeDataPathStatsDiskServiceTimeLens,
nodeDataPathStatsDiskQueueLens,
nodeDataPathStatsIOSizeLens,
nodeDataPathStatsWriteSizeLens,
nodeDataPathStatsReadSizeLens,
nodeDataPathStatsIOOpsLens,
nodeDataPathStatsWritesLens,
nodeDataPathStatsReadsLens,
nodeDataPathStatsAvailableLens,
nodeDataPathStatsFreeLens,
nodeDataPathStatsTotalLens,
nodeDataPathStatsTypeLens,
nodeDataPathStatsDeviceLens,
nodeDataPathStatsMountLens,
nodeDataPathStatsPathLens,
nodeFSTotalStatsDiskServiceTimeLens,
nodeFSTotalStatsDiskQueueLens,
nodeFSTotalStatsIOSizeLens,
nodeFSTotalStatsWriteSizeLens,
nodeFSTotalStatsReadSizeLens,
nodeFSTotalStatsIOOpsLens,
nodeFSTotalStatsWritesLens,
nodeFSTotalStatsReadsLens,
nodeFSTotalStatsAvailableLens,
nodeFSTotalStatsFreeLens,
nodeFSTotalStatsTotalLens,
nodeNetworkStatsTCPOutRSTsLens,
nodeNetworkStatsTCPInErrsLens,
nodeNetworkStatsTCPAttemptFailsLens,
nodeNetworkStatsTCPEstabResetsLens,
nodeNetworkStatsTCPRetransSegsLens,
nodeNetworkStatsTCPOutSegsLens,
nodeNetworkStatsTCPInSegsLens,
nodeNetworkStatsTCPCurrEstabLens,
nodeNetworkStatsTCPPassiveOpensLens,
nodeNetworkStatsTCPActiveOpensLens,
nodeThreadPoolStatsCompletedLens,
nodeThreadPoolStatsLargestLens,
nodeThreadPoolStatsRejectedLens,
nodeThreadPoolStatsActiveLens,
nodeThreadPoolStatsQueueLens,
nodeThreadPoolStatsThreadsLens,
nodeJVMStatsMappedBufferPoolLens,
nodeJVMStatsDirectBufferPoolLens,
nodeJVMStatsGCOldCollectorLens,
nodeJVMStatsGCYoungCollectorLens,
nodeJVMStatsPeakThreadsCountLens,
nodeJVMStatsThreadsCountLens,
nodeJVMStatsOldPoolLens,
nodeJVMStatsSurvivorPoolLens,
nodeJVMStatsYoungPoolLens,
nodeJVMStatsNonHeapCommittedLens,
nodeJVMStatsNonHeapUsedLens,
nodeJVMStatsHeapMaxLens,
nodeJVMStatsHeapCommittedLens,
nodeJVMStatsHeapUsedPercentLens,
nodeJVMStatsHeapUsedLens,
nodeJVMStatsUptimeLens,
nodeJVMStatsTimestampLens,
jvmBufferPoolStatsTotalCapacityLens,
jvmBufferPoolStatsUsedLens,
jvmBufferPoolStatsCountLens,
jvmGCStatsCollectionTimeLens,
jvmGCStatsCollectionCountLens,
jvmPoolStatsPeakMaxLens,
jvmPoolStatsPeakUsedLens,
jvmPoolStatsMaxLens,
jvmPoolStatsUsedLens,
nodeProcessStatsTimestampLens,
nodeProcessStatsOpenFDsLens,
nodeProcessStatsMaxFDsLens,
nodeProcessStatsCPUPercentLens,
nodeProcessStatsCPUTotalLens,
nodeProcessStatsMemTotalVirtualLens,
nodeOSStatsTimestampLens,
nodeOSStatsCPUPercentLens,
nodeOSStatsLoadLens,
nodeOSStatsMemTotalLens,
nodeOSStatsMemFreeLens,
nodeOSStatsMemFreePercentLens,
nodeOSStatsMemUsedLens,
nodeOSStatsMemUsedPercentLens,
nodeOSStatsSwapTotalLens,
nodeOSStatsSwapFreeLens,
nodeOSStatsSwapUsedLens,
loadAvgs1MinLens,
loadAvgs5MinLens,
loadAvgs15MinLens,
nodeIndicesStatsRecoveryThrottleTimeLens,
nodeIndicesStatsRecoveryCurrentAsTargetLens,
nodeIndicesStatsRecoveryCurrentAsSourceLens,
nodeIndicesStatsQueryCacheMissesLens,
nodeIndicesStatsQueryCacheHitsLens,
nodeIndicesStatsQueryCacheEvictionsLens,
nodeIndicesStatsQueryCacheSizeLens,
nodeIndicesStatsSuggestCurrentLens,
nodeIndicesStatsSuggestTimeLens,
nodeIndicesStatsSuggestTotalLens,
nodeIndicesStatsTranslogSizeLens,
nodeIndicesStatsTranslogOpsLens,
nodeIndicesStatsSegFixedBitSetMemoryLens,
nodeIndicesStatsSegVersionMapMemoryLens,
nodeIndicesStatsSegIndexWriterMaxMemoryLens,
nodeIndicesStatsSegIndexWriterMemoryLens,
nodeIndicesStatsSegMemoryLens,
nodeIndicesStatsSegCountLens,
nodeIndicesStatsCompletionSizeLens,
nodeIndicesStatsPercolateQueriesLens,
nodeIndicesStatsPercolateMemoryLens,
nodeIndicesStatsPercolateCurrentLens,
nodeIndicesStatsPercolateTimeLens,
nodeIndicesStatsPercolateTotalLens,
nodeIndicesStatsFieldDataEvictionsLens,
nodeIndicesStatsFieldDataMemoryLens,
nodeIndicesStatsWarmerTotalTimeLens,
nodeIndicesStatsWarmerTotalLens,
nodeIndicesStatsWarmerCurrentLens,
nodeIndicesStatsFlushTotalTimeLens,
nodeIndicesStatsFlushTotalLens,
nodeIndicesStatsRefreshTotalTimeLens,
nodeIndicesStatsRefreshTotalLens,
nodeIndicesStatsMergesTotalSizeLens,
nodeIndicesStatsMergesTotalDocsLens,
nodeIndicesStatsMergesTotalTimeLens,
nodeIndicesStatsMergesTotalLens,
nodeIndicesStatsMergesCurrentSizeLens,
nodeIndicesStatsMergesCurrentDocsLens,
nodeIndicesStatsMergesCurrentLens,
nodeIndicesStatsSearchFetchCurrentLens,
nodeIndicesStatsSearchFetchTimeLens,
nodeIndicesStatsSearchFetchTotalLens,
nodeIndicesStatsSearchQueryCurrentLens,
nodeIndicesStatsSearchQueryTimeLens,
nodeIndicesStatsSearchQueryTotalLens,
nodeIndicesStatsSearchOpenContextsLens,
nodeIndicesStatsGetCurrentLens,
nodeIndicesStatsGetMissingTimeLens,
nodeIndicesStatsGetMissingTotalLens,
nodeIndicesStatsGetExistsTimeLens,
nodeIndicesStatsGetExistsTotalLens,
nodeIndicesStatsGetTimeLens,
nodeIndicesStatsGetTotalLens,
nodeIndicesStatsIndexingThrottleTimeLens,
nodeIndicesStatsIndexingIsThrottledLens,
nodeIndicesStatsIndexingNoopUpdateTotalLens,
nodeIndicesStatsIndexingDeleteCurrentLens,
nodeIndicesStatsIndexingDeleteTimeLens,
nodeIndicesStatsIndexingDeleteTotalLens,
nodeIndicesStatsIndexingIndexCurrentLens,
nodeIndicesStatsIndexingIndexTimeLens,
nodeIndicesStatsIndexingTotalLens,
nodeIndicesStatsStoreThrottleTimeLens,
nodeIndicesStatsStoreSizeLens,
nodeIndicesStatsDocsDeletedLens,
nodeIndicesStatsDocsCountLens,
nodeInfoHTTPAddressLens,
nodeInfoBuildLens,
nodeInfoESVersionLens,
nodeInfoIPLens,
nodeInfoHostLens,
nodeInfoTransportAddressLens,
nodeInfoNameLens,
nodeInfoFullIdLens,
nodeInfoPluginsLens,
nodeInfoHTTPLens,
nodeInfoTransportLens,
nodeInfoNetworkLens,
nodeInfoThreadPoolLens,
nodeInfoJVMLens,
nodeInfoProcessLens,
nodeInfoOSLens,
nodeInfoSettingsLens,
nodePluginSiteLens,
nodePluginInfoJVMLens,
nodePluginInfoDescriptionLens,
nodePluginInfoVersionLens,
nodePluginInfoNameLens,
nodeHTTPInfoMaxContentLengthLens,
nodeHTTPInfopublishAddressLens,
nodeHTTPInfoBoundAddressesLens,
nodeTransportInfoProfilesLens,
nodeTransportInfoPublishAddressLens,
nodeTransportInfoBoundAddressLens,
boundTransportAddressPublishAddressLens,
boundTransportAddressBoundAddressesLens,
nodeNetworkInfoPrimaryInterfaceLens,
nodeNetworkInfoRefreshIntervalLens,
nodeNetworkInterfaceMacAddressLens,
nodeNetworkInterfaceNameLens,
nodeNetworkInterfaceAddressLens,
threadPoolNodeThreadPoolNameLens,
threadPoolNodeThreadPoolInfoLens,
nodeThreadPoolInfoQueueSizeLens,
nodeThreadPoolInfoKeepaliveLens,
nodeThreadPoolInfoMinLens,
nodeThreadPoolInfoMaxLens,
nodeThreadPoolInfoTypeLens,
threadPoolSizeBoundedPrism,
nodeJVMInfoMemoryPoolsLens,
nodeJVMInfoMemoryPoolsGCCollectorsLens,
nodeJVMInfoMemoryInfoLens,
nodeJVMInfoStartTimeLens,
nodeJVMInfoVMVendorLens,
nodeJVMInfoVMVersionLens,
nodeJVMInfoVMNameLens,
nodeJVMInfoVersionLens,
nodeJVMInfoPIDLens,
jvmMemoryInfoDirectMaxLens,
jvmMemoryInfoNonHeapMaxLens,
jvmMemoryInfoNonHeapInitLens,
jvmMemoryInfoHeapMaxLens,
jvmMemoryInfoHeapInitLens,
nodeOSInfoRefreshIntervalLens,
nodeOSInfoNameLens,
nodeOSInfoArchLens,
nodeOSInfoVersionLens,
nodeOSInfoAvailableProcessorsLens,
nodeOSInfoAllocatedProcessorsLens,
cpuInfoCacheSizeLens,
cpuInfoCoresPerSocketLens,
cpuInfoTotalSocketsLens,
cpuInfoTotalCoresLens,
cpuInfoMHZLens,
cpuInfoModelLens,
cpuInfoVendorLens,
nodeProcessInfoMLockAllLens,
nodeProcessInfoMaxFileDescriptorsLens,
nodeProcessInfoIdLens,
nodeProcessInfoRefreshIntervalLens,
initialShardCountExplicitShardsPrism,
shardsResultShardsLens,
shardResultTotalLens,
shardsResultSuccessfulLens,
shardsResultResultSkippedLens,
shardsResultFailedLens,
versionNumberLens,
versionBuildHashLens,
versionBuildDateLens,
versionBuildSnapshotLens,
versionLuceneVersionLens,
healthStatusClusterNameLens,
healthStatusStatusLens,
healthStatusTimedOutLens,
healthStatusNumberOfNodesLens,
healthStatusNumberOfDataNodesLens,
healthStatusActivePrimaryShardsLens,
healthStatusActiveShardsLens,
healthStatusRelocatingShardsLens,
healthStatusInitializingShardsLens,
healthStatusUnassignedShardsLens,
healthStatusDelayedUnassignedShardsLens,
healthStatusNumberOfPendingTasksLens,
healthStatusNumberOfInFlightFetchLens,
healthStatusTaskMaxWaitingInQueueMillisLens,
healthStatusActiveShardsPercentAsNumberLens,
indexedDocumentIndexLens,
indexedDocumentTypeLens,
indexedDocumentIdLens,
indexedDocumentVersionLens,
indexedDocumentResultLens,
indexedDocumentShardsLens,
indexedDocumentSeqNoLens,
indexedDocumentPrimaryTermLens,
deletedDocumentsTookLens,
deletedDocumentsTimedOutLens,
deletedDocumentsTotalLens,
deletedDocumentsDeletedLens,
deletedDocumentsBatchesLens,
deletedDocumentsVersionConflictsLens,
deletedDocumentsNoopsLens,
deletedDocumentsRetriesLens,
deletedDocumentsThrottledMillisLens,
deletedDocumentsRequestsPerSecondLens,
deletedDocumentsThrottledUntilMillisLens,
deletedDocumentsFailuresLens,
deletedDocumentsRetriesBulkLens,
deletedDocumentsRetriesSearchLens,
)
where
import qualified Data.Aeson.KeyMap as X
import qualified Data.HashMap.Strict as HM
import Data.Map.Strict (Map)
import qualified Data.Text as T
import qualified Data.Vector as V
import qualified Data.Versions as Versions
import Database.Bloodhound.Internal.Client.BHRequest
import Database.Bloodhound.Internal.Utils.Imports
import Database.Bloodhound.Internal.Utils.StringlyTyped
import Database.Bloodhound.Internal.Versions.Common.Types.Newtypes
import Database.Bloodhound.Internal.Versions.Common.Types.Units
import GHC.Generics
data NodeAttrFilter = NodeAttrFilter
{ NodeAttrFilter -> NodeAttrName
nodeAttrFilterName :: NodeAttrName,
NodeAttrFilter -> NonEmpty Text
nodeAttrFilterValues :: NonEmpty Text
}
deriving stock (NodeAttrFilter -> NodeAttrFilter -> Bool
(NodeAttrFilter -> NodeAttrFilter -> Bool)
-> (NodeAttrFilter -> NodeAttrFilter -> Bool) -> Eq NodeAttrFilter
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NodeAttrFilter -> NodeAttrFilter -> Bool
== :: NodeAttrFilter -> NodeAttrFilter -> Bool
$c/= :: NodeAttrFilter -> NodeAttrFilter -> Bool
/= :: 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
$ccompare :: NodeAttrFilter -> NodeAttrFilter -> Ordering
compare :: NodeAttrFilter -> NodeAttrFilter -> Ordering
$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
>= :: NodeAttrFilter -> NodeAttrFilter -> Bool
$cmax :: NodeAttrFilter -> NodeAttrFilter -> NodeAttrFilter
max :: NodeAttrFilter -> NodeAttrFilter -> NodeAttrFilter
$cmin :: NodeAttrFilter -> NodeAttrFilter -> NodeAttrFilter
min :: NodeAttrFilter -> NodeAttrFilter -> 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
$cshowsPrec :: Int -> NodeAttrFilter -> ShowS
showsPrec :: Int -> NodeAttrFilter -> ShowS
$cshow :: NodeAttrFilter -> String
show :: NodeAttrFilter -> String
$cshowList :: [NodeAttrFilter] -> ShowS
showList :: [NodeAttrFilter] -> ShowS
Show)
nodeAttrFilterNameLens :: Lens' NodeAttrFilter NodeAttrName
nodeAttrFilterNameLens :: Lens' NodeAttrFilter NodeAttrName
nodeAttrFilterNameLens = (NodeAttrFilter -> NodeAttrName)
-> (NodeAttrFilter -> NodeAttrName -> NodeAttrFilter)
-> Lens' NodeAttrFilter NodeAttrName
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeAttrFilter -> NodeAttrName
nodeAttrFilterName (\NodeAttrFilter
x NodeAttrName
y -> NodeAttrFilter
x {nodeAttrFilterName = y})
nodeAttrFilterValuesLens :: Lens' NodeAttrFilter (NonEmpty Text)
nodeAttrFilterValuesLens :: Lens' NodeAttrFilter (NonEmpty Text)
nodeAttrFilterValuesLens = (NodeAttrFilter -> NonEmpty Text)
-> (NodeAttrFilter -> NonEmpty Text -> NodeAttrFilter)
-> Lens' NodeAttrFilter (NonEmpty Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeAttrFilter -> NonEmpty Text
nodeAttrFilterValues (\NodeAttrFilter
x NonEmpty Text
y -> NodeAttrFilter
x {nodeAttrFilterValues = y})
newtype NodeAttrName = NodeAttrName Text deriving stock (NodeAttrName -> NodeAttrName -> Bool
(NodeAttrName -> NodeAttrName -> Bool)
-> (NodeAttrName -> NodeAttrName -> Bool) -> Eq NodeAttrName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NodeAttrName -> NodeAttrName -> Bool
== :: NodeAttrName -> NodeAttrName -> Bool
$c/= :: NodeAttrName -> NodeAttrName -> Bool
/= :: 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
$ccompare :: NodeAttrName -> NodeAttrName -> Ordering
compare :: NodeAttrName -> NodeAttrName -> Ordering
$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
>= :: NodeAttrName -> NodeAttrName -> Bool
$cmax :: NodeAttrName -> NodeAttrName -> NodeAttrName
max :: NodeAttrName -> NodeAttrName -> NodeAttrName
$cmin :: NodeAttrName -> NodeAttrName -> NodeAttrName
min :: NodeAttrName -> NodeAttrName -> 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
$cshowsPrec :: Int -> NodeAttrName -> ShowS
showsPrec :: Int -> NodeAttrName -> ShowS
$cshow :: NodeAttrName -> String
show :: NodeAttrName -> String
$cshowList :: [NodeAttrName] -> ShowS
showList :: [NodeAttrName] -> ShowS
Show)
data NodeSelection
=
LocalNode
| NodeList (NonEmpty NodeSelector)
| AllNodes
deriving stock (NodeSelection -> NodeSelection -> Bool
(NodeSelection -> NodeSelection -> Bool)
-> (NodeSelection -> NodeSelection -> Bool) -> Eq NodeSelection
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NodeSelection -> NodeSelection -> Bool
== :: NodeSelection -> NodeSelection -> Bool
$c/= :: NodeSelection -> NodeSelection -> Bool
/= :: 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
$cshowsPrec :: Int -> NodeSelection -> ShowS
showsPrec :: Int -> NodeSelection -> ShowS
$cshow :: NodeSelection -> String
show :: NodeSelection -> String
$cshowList :: [NodeSelection] -> ShowS
showList :: [NodeSelection] -> ShowS
Show)
nodeSelectionNodeListPrism :: Prism' NodeSelection (NonEmpty NodeSelector)
nodeSelectionNodeListPrism :: Prism' NodeSelection (NonEmpty NodeSelector)
nodeSelectionNodeListPrism = (NonEmpty NodeSelector -> NodeSelection)
-> (NodeSelection -> Either NodeSelection (NonEmpty NodeSelector))
-> Prism' NodeSelection (NonEmpty NodeSelector)
forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b
prism NonEmpty NodeSelector -> NodeSelection
NodeList NodeSelection -> Either NodeSelection (NonEmpty NodeSelector)
extract
where
extract :: NodeSelection -> Either NodeSelection (NonEmpty NodeSelector)
extract NodeSelection
s =
case NodeSelection
s of
NodeList NonEmpty NodeSelector
x -> NonEmpty NodeSelector
-> Either NodeSelection (NonEmpty NodeSelector)
forall a b. b -> Either a b
Right NonEmpty NodeSelector
x
NodeSelection
_ -> NodeSelection -> Either NodeSelection (NonEmpty NodeSelector)
forall a b. a -> Either a b
Left NodeSelection
s
data NodeSelector
= NodeByName NodeName
| NodeByFullNodeId FullNodeId
|
NodeByHost Server
|
NodeByAttribute NodeAttrName Text
deriving stock (NodeSelector -> NodeSelector -> Bool
(NodeSelector -> NodeSelector -> Bool)
-> (NodeSelector -> NodeSelector -> Bool) -> Eq NodeSelector
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NodeSelector -> NodeSelector -> Bool
== :: NodeSelector -> NodeSelector -> Bool
$c/= :: NodeSelector -> NodeSelector -> Bool
/= :: 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
$cshowsPrec :: Int -> NodeSelector -> ShowS
showsPrec :: Int -> NodeSelector -> ShowS
$cshow :: NodeSelector -> String
show :: NodeSelector -> String
$cshowList :: [NodeSelector] -> ShowS
showList :: [NodeSelector] -> ShowS
Show)
nodeSelectorNodeByNamePrism :: Prism' NodeSelector NodeName
nodeSelectorNodeByNamePrism :: Prism' NodeSelector NodeName
nodeSelectorNodeByNamePrism = (NodeName -> NodeSelector)
-> (NodeSelector -> Either NodeSelector NodeName)
-> Prism' NodeSelector NodeName
forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b
prism NodeName -> NodeSelector
NodeByName NodeSelector -> Either NodeSelector NodeName
extract
where
extract :: NodeSelector -> Either NodeSelector NodeName
extract NodeSelector
s =
case NodeSelector
s of
NodeByName NodeName
x -> NodeName -> Either NodeSelector NodeName
forall a b. b -> Either a b
Right NodeName
x
NodeSelector
_ -> NodeSelector -> Either NodeSelector NodeName
forall a b. a -> Either a b
Left NodeSelector
s
nodeSelectorNodeByFullNodeIdPrism :: Prism' NodeSelector FullNodeId
nodeSelectorNodeByFullNodeIdPrism :: Prism' NodeSelector FullNodeId
nodeSelectorNodeByFullNodeIdPrism = (FullNodeId -> NodeSelector)
-> (NodeSelector -> Either NodeSelector FullNodeId)
-> Prism' NodeSelector FullNodeId
forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b
prism FullNodeId -> NodeSelector
NodeByFullNodeId NodeSelector -> Either NodeSelector FullNodeId
extract
where
extract :: NodeSelector -> Either NodeSelector FullNodeId
extract NodeSelector
s =
case NodeSelector
s of
NodeByFullNodeId FullNodeId
x -> FullNodeId -> Either NodeSelector FullNodeId
forall a b. b -> Either a b
Right FullNodeId
x
NodeSelector
_ -> NodeSelector -> Either NodeSelector FullNodeId
forall a b. a -> Either a b
Left NodeSelector
s
nodeSelectorNodeByHostPrism :: Prism' NodeSelector Server
nodeSelectorNodeByHostPrism :: Prism' NodeSelector Server
nodeSelectorNodeByHostPrism = (Server -> NodeSelector)
-> (NodeSelector -> Either NodeSelector Server)
-> Prism' NodeSelector Server
forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b
prism Server -> NodeSelector
NodeByHost NodeSelector -> Either NodeSelector Server
extract
where
extract :: NodeSelector -> Either NodeSelector Server
extract NodeSelector
s =
case NodeSelector
s of
NodeByHost Server
x -> Server -> Either NodeSelector Server
forall a b. b -> Either a b
Right Server
x
NodeSelector
_ -> NodeSelector -> Either NodeSelector Server
forall a b. a -> Either a b
Left NodeSelector
s
nodeSelectorNodeByAttributePrism :: Prism' NodeSelector (NodeAttrName, Text)
nodeSelectorNodeByAttributePrism :: Prism' NodeSelector (NodeAttrName, Text)
nodeSelectorNodeByAttributePrism = ((NodeAttrName, Text) -> NodeSelector)
-> (NodeSelector -> Either NodeSelector (NodeAttrName, Text))
-> Prism' NodeSelector (NodeAttrName, Text)
forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b
prism ((NodeAttrName -> Text -> NodeSelector)
-> (NodeAttrName, Text) -> NodeSelector
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry NodeAttrName -> Text -> NodeSelector
NodeByAttribute) NodeSelector -> Either NodeSelector (NodeAttrName, Text)
extract
where
extract :: NodeSelector -> Either NodeSelector (NodeAttrName, Text)
extract NodeSelector
s =
case NodeSelector
s of
NodeByAttribute NodeAttrName
x Text
y -> (NodeAttrName, Text) -> Either NodeSelector (NodeAttrName, Text)
forall a b. b -> Either a b
Right (NodeAttrName
x, Text
y)
NodeSelector
_ -> NodeSelector -> Either NodeSelector (NodeAttrName, Text)
forall a b. a -> Either a b
Left NodeSelector
s
newtype FullNodeId = FullNodeId {FullNodeId -> Text
fullNodeId :: Text}
deriving newtype (FullNodeId -> FullNodeId -> Bool
(FullNodeId -> FullNodeId -> Bool)
-> (FullNodeId -> FullNodeId -> Bool) -> Eq FullNodeId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FullNodeId -> FullNodeId -> Bool
== :: FullNodeId -> FullNodeId -> Bool
$c/= :: FullNodeId -> FullNodeId -> Bool
/= :: 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
$ccompare :: FullNodeId -> FullNodeId -> Ordering
compare :: FullNodeId -> FullNodeId -> Ordering
$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
>= :: FullNodeId -> FullNodeId -> Bool
$cmax :: FullNodeId -> FullNodeId -> FullNodeId
max :: FullNodeId -> FullNodeId -> FullNodeId
$cmin :: FullNodeId -> FullNodeId -> FullNodeId
min :: FullNodeId -> FullNodeId -> 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
$cshowsPrec :: Int -> FullNodeId -> ShowS
showsPrec :: Int -> FullNodeId -> ShowS
$cshow :: FullNodeId -> String
show :: FullNodeId -> String
$cshowList :: [FullNodeId] -> ShowS
showList :: [FullNodeId] -> ShowS
Show, Maybe FullNodeId
Value -> Parser [FullNodeId]
Value -> Parser FullNodeId
(Value -> Parser FullNodeId)
-> (Value -> Parser [FullNodeId])
-> Maybe FullNodeId
-> FromJSON FullNodeId
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser FullNodeId
parseJSON :: Value -> Parser FullNodeId
$cparseJSONList :: Value -> Parser [FullNodeId]
parseJSONList :: Value -> Parser [FullNodeId]
$comittedField :: Maybe FullNodeId
omittedField :: Maybe FullNodeId
FromJSON)
newtype NodeName = NodeName {NodeName -> Text
nodeName :: Text}
deriving newtype (NodeName -> NodeName -> Bool
(NodeName -> NodeName -> Bool)
-> (NodeName -> NodeName -> Bool) -> Eq NodeName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NodeName -> NodeName -> Bool
== :: NodeName -> NodeName -> Bool
$c/= :: NodeName -> NodeName -> Bool
/= :: 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
$ccompare :: NodeName -> NodeName -> Ordering
compare :: NodeName -> NodeName -> Ordering
$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
>= :: NodeName -> NodeName -> Bool
$cmax :: NodeName -> NodeName -> NodeName
max :: NodeName -> NodeName -> NodeName
$cmin :: NodeName -> NodeName -> NodeName
min :: NodeName -> NodeName -> 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
$cshowsPrec :: Int -> NodeName -> ShowS
showsPrec :: Int -> NodeName -> ShowS
$cshow :: NodeName -> String
show :: NodeName -> String
$cshowList :: [NodeName] -> ShowS
showList :: [NodeName] -> ShowS
Show, Maybe NodeName
Value -> Parser [NodeName]
Value -> Parser NodeName
(Value -> Parser NodeName)
-> (Value -> Parser [NodeName])
-> Maybe NodeName
-> FromJSON NodeName
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser NodeName
parseJSON :: Value -> Parser NodeName
$cparseJSONList :: Value -> Parser [NodeName]
parseJSONList :: Value -> Parser [NodeName]
$comittedField :: Maybe NodeName
omittedField :: Maybe NodeName
FromJSON)
newtype ClusterName = ClusterName {ClusterName -> Text
clusterName :: Text}
deriving newtype (ClusterName -> ClusterName -> Bool
(ClusterName -> ClusterName -> Bool)
-> (ClusterName -> ClusterName -> Bool) -> Eq ClusterName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ClusterName -> ClusterName -> Bool
== :: ClusterName -> ClusterName -> Bool
$c/= :: ClusterName -> ClusterName -> Bool
/= :: 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
$ccompare :: ClusterName -> ClusterName -> Ordering
compare :: ClusterName -> ClusterName -> Ordering
$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
>= :: ClusterName -> ClusterName -> Bool
$cmax :: ClusterName -> ClusterName -> ClusterName
max :: ClusterName -> ClusterName -> ClusterName
$cmin :: ClusterName -> ClusterName -> ClusterName
min :: ClusterName -> ClusterName -> 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
$cshowsPrec :: Int -> ClusterName -> ShowS
showsPrec :: Int -> ClusterName -> ShowS
$cshow :: ClusterName -> String
show :: ClusterName -> String
$cshowList :: [ClusterName] -> ShowS
showList :: [ClusterName] -> ShowS
Show, Maybe ClusterName
Value -> Parser [ClusterName]
Value -> Parser ClusterName
(Value -> Parser ClusterName)
-> (Value -> Parser [ClusterName])
-> Maybe ClusterName
-> FromJSON ClusterName
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser ClusterName
parseJSON :: Value -> Parser ClusterName
$cparseJSONList :: Value -> Parser [ClusterName]
parseJSONList :: Value -> Parser [ClusterName]
$comittedField :: Maybe ClusterName
omittedField :: Maybe ClusterName
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
$creadsPrec :: Int -> ReadS EsUsername
readsPrec :: Int -> ReadS EsUsername
$creadList :: ReadS [EsUsername]
readList :: ReadS [EsUsername]
$creadPrec :: ReadPrec EsUsername
readPrec :: ReadPrec EsUsername
$creadListPrec :: ReadPrec [EsUsername]
readListPrec :: ReadPrec [EsUsername]
Read, EsUsername -> EsUsername -> Bool
(EsUsername -> EsUsername -> Bool)
-> (EsUsername -> EsUsername -> Bool) -> Eq EsUsername
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EsUsername -> EsUsername -> Bool
== :: EsUsername -> EsUsername -> Bool
$c/= :: EsUsername -> EsUsername -> Bool
/= :: EsUsername -> EsUsername -> Bool
Eq, 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
$cshowsPrec :: Int -> EsUsername -> ShowS
showsPrec :: Int -> EsUsername -> ShowS
$cshow :: EsUsername -> String
show :: EsUsername -> String
$cshowList :: [EsUsername] -> ShowS
showList :: [EsUsername] -> ShowS
Show)
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
$creadsPrec :: Int -> ReadS EsPassword
readsPrec :: Int -> ReadS EsPassword
$creadList :: ReadS [EsPassword]
readList :: ReadS [EsPassword]
$creadPrec :: ReadPrec EsPassword
readPrec :: ReadPrec EsPassword
$creadListPrec :: ReadPrec [EsPassword]
readListPrec :: ReadPrec [EsPassword]
Read, EsPassword -> EsPassword -> Bool
(EsPassword -> EsPassword -> Bool)
-> (EsPassword -> EsPassword -> Bool) -> Eq EsPassword
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EsPassword -> EsPassword -> Bool
== :: EsPassword -> EsPassword -> Bool
$c/= :: EsPassword -> EsPassword -> Bool
/= :: EsPassword -> EsPassword -> Bool
Eq, 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
$cshowsPrec :: Int -> EsPassword -> ShowS
showsPrec :: Int -> EsPassword -> ShowS
$cshow :: EsPassword -> String
show :: EsPassword -> String
$cshowList :: [EsPassword] -> ShowS
showList :: [EsPassword] -> ShowS
Show)
data NodesInfo = NodesInfo
{ NodesInfo -> [NodeInfo]
nodesInfo :: [NodeInfo],
NodesInfo -> ClusterName
nodesClusterName :: ClusterName
}
deriving stock (NodesInfo -> NodesInfo -> Bool
(NodesInfo -> NodesInfo -> Bool)
-> (NodesInfo -> NodesInfo -> Bool) -> Eq NodesInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NodesInfo -> NodesInfo -> Bool
== :: NodesInfo -> NodesInfo -> Bool
$c/= :: NodesInfo -> NodesInfo -> Bool
/= :: 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
$cshowsPrec :: Int -> NodesInfo -> ShowS
showsPrec :: Int -> NodesInfo -> ShowS
$cshow :: NodesInfo -> String
show :: NodesInfo -> String
$cshowList :: [NodesInfo] -> ShowS
showList :: [NodesInfo] -> ShowS
Show)
nodesInfoListLens :: Lens' NodesInfo [NodeInfo]
nodesInfoListLens :: Lens' NodesInfo [NodeInfo]
nodesInfoListLens = (NodesInfo -> [NodeInfo])
-> (NodesInfo -> [NodeInfo] -> NodesInfo)
-> Lens' NodesInfo [NodeInfo]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodesInfo -> [NodeInfo]
nodesInfo (\NodesInfo
x [NodeInfo]
y -> NodesInfo
x {nodesInfo = y})
nodesClusterNameLens :: Lens' NodesInfo ClusterName
nodesClusterNameLens :: Lens' NodesInfo ClusterName
nodesClusterNameLens = (NodesInfo -> ClusterName)
-> (NodesInfo -> ClusterName -> NodesInfo)
-> Lens' NodesInfo ClusterName
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodesInfo -> ClusterName
nodesClusterName (\NodesInfo
x ClusterName
y -> NodesInfo
x {nodesClusterName = y})
data NodesStats = NodesStats
{ NodesStats -> [NodeStats]
nodesStats :: [NodeStats],
NodesStats -> ClusterName
nodesStatsClusterName :: ClusterName
}
deriving stock (NodesStats -> NodesStats -> Bool
(NodesStats -> NodesStats -> Bool)
-> (NodesStats -> NodesStats -> Bool) -> Eq NodesStats
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NodesStats -> NodesStats -> Bool
== :: NodesStats -> NodesStats -> Bool
$c/= :: NodesStats -> NodesStats -> Bool
/= :: 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
$cshowsPrec :: Int -> NodesStats -> ShowS
showsPrec :: Int -> NodesStats -> ShowS
$cshow :: NodesStats -> String
show :: NodesStats -> String
$cshowList :: [NodesStats] -> ShowS
showList :: [NodesStats] -> ShowS
Show)
nodesStatsListLens :: Lens' NodesStats [NodeStats]
nodesStatsListLens :: Lens' NodesStats [NodeStats]
nodesStatsListLens = (NodesStats -> [NodeStats])
-> (NodesStats -> [NodeStats] -> NodesStats)
-> Lens' NodesStats [NodeStats]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodesStats -> [NodeStats]
nodesStats (\NodesStats
x [NodeStats]
y -> NodesStats
x {nodesStats = y})
nodesStatsClusterNameLens :: Lens' NodesStats ClusterName
nodesStatsClusterNameLens :: Lens' NodesStats ClusterName
nodesStatsClusterNameLens = (NodesStats -> ClusterName)
-> (NodesStats -> ClusterName -> NodesStats)
-> Lens' NodesStats ClusterName
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodesStats -> ClusterName
nodesStatsClusterName (\NodesStats
x ClusterName
y -> NodesStats
x {nodesStatsClusterName = y})
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 stock (NodeStats -> NodeStats -> Bool
(NodeStats -> NodeStats -> Bool)
-> (NodeStats -> NodeStats -> Bool) -> Eq NodeStats
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NodeStats -> NodeStats -> Bool
== :: NodeStats -> NodeStats -> Bool
$c/= :: NodeStats -> NodeStats -> Bool
/= :: 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
$cshowsPrec :: Int -> NodeStats -> ShowS
showsPrec :: Int -> NodeStats -> ShowS
$cshow :: NodeStats -> String
show :: NodeStats -> String
$cshowList :: [NodeStats] -> ShowS
showList :: [NodeStats] -> ShowS
Show)
nodeStatsNameLens :: Lens' NodeStats NodeName
nodeStatsNameLens :: Lens' NodeStats NodeName
nodeStatsNameLens = (NodeStats -> NodeName)
-> (NodeStats -> NodeName -> NodeStats) -> Lens' NodeStats NodeName
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeStats -> NodeName
nodeStatsName (\NodeStats
x NodeName
y -> NodeStats
x {nodeStatsName = y})
nodeStatsFullIdLens :: Lens' NodeStats FullNodeId
nodeStatsFullIdLens :: Lens' NodeStats FullNodeId
nodeStatsFullIdLens = (NodeStats -> FullNodeId)
-> (NodeStats -> FullNodeId -> NodeStats)
-> Lens' NodeStats FullNodeId
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeStats -> FullNodeId
nodeStatsFullId (\NodeStats
x FullNodeId
y -> NodeStats
x {nodeStatsFullId = y})
nodeStatsBreakersStatsLens :: Lens' NodeStats (Maybe NodeBreakersStats)
= (NodeStats -> Maybe NodeBreakersStats)
-> (NodeStats -> Maybe NodeBreakersStats -> NodeStats)
-> Lens' NodeStats (Maybe NodeBreakersStats)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeStats -> Maybe NodeBreakersStats
nodeStatsBreakersStats (\NodeStats
x Maybe NodeBreakersStats
y -> NodeStats
x {nodeStatsBreakersStats = y})
nodeStatsHTTPLens :: Lens' NodeStats NodeHTTPStats
nodeStatsHTTPLens :: Lens' NodeStats NodeHTTPStats
nodeStatsHTTPLens = (NodeStats -> NodeHTTPStats)
-> (NodeStats -> NodeHTTPStats -> NodeStats)
-> Lens' NodeStats NodeHTTPStats
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeStats -> NodeHTTPStats
nodeStatsHTTP (\NodeStats
x NodeHTTPStats
y -> NodeStats
x {nodeStatsHTTP = y})
nodeStatsTransportLens :: Lens' NodeStats NodeTransportStats
nodeStatsTransportLens :: Lens' NodeStats NodeTransportStats
nodeStatsTransportLens = (NodeStats -> NodeTransportStats)
-> (NodeStats -> NodeTransportStats -> NodeStats)
-> Lens' NodeStats NodeTransportStats
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeStats -> NodeTransportStats
nodeStatsTransport (\NodeStats
x NodeTransportStats
y -> NodeStats
x {nodeStatsTransport = y})
nodeStatsFSLens :: Lens' NodeStats NodeFSStats
nodeStatsFSLens :: Lens' NodeStats NodeFSStats
nodeStatsFSLens = (NodeStats -> NodeFSStats)
-> (NodeStats -> NodeFSStats -> NodeStats)
-> Lens' NodeStats NodeFSStats
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeStats -> NodeFSStats
nodeStatsFS (\NodeStats
x NodeFSStats
y -> NodeStats
x {nodeStatsFS = y})
nodeStatsNetworkLens :: Lens' NodeStats (Maybe NodeNetworkStats)
nodeStatsNetworkLens :: Lens' NodeStats (Maybe NodeNetworkStats)
nodeStatsNetworkLens = (NodeStats -> Maybe NodeNetworkStats)
-> (NodeStats -> Maybe NodeNetworkStats -> NodeStats)
-> Lens' NodeStats (Maybe NodeNetworkStats)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeStats -> Maybe NodeNetworkStats
nodeStatsNetwork (\NodeStats
x Maybe NodeNetworkStats
y -> NodeStats
x {nodeStatsNetwork = y})
nodeStatsThreadPoolLens :: Lens' NodeStats (Map Text NodeThreadPoolStats)
nodeStatsThreadPoolLens :: Lens' NodeStats (Map Text NodeThreadPoolStats)
nodeStatsThreadPoolLens = (NodeStats -> Map Text NodeThreadPoolStats)
-> (NodeStats -> Map Text NodeThreadPoolStats -> NodeStats)
-> Lens' NodeStats (Map Text NodeThreadPoolStats)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeStats -> Map Text NodeThreadPoolStats
nodeStatsThreadPool (\NodeStats
x Map Text NodeThreadPoolStats
y -> NodeStats
x {nodeStatsThreadPool = y})
nodeStatsJVMLens :: Lens' NodeStats NodeJVMStats
nodeStatsJVMLens :: Lens' NodeStats NodeJVMStats
nodeStatsJVMLens = (NodeStats -> NodeJVMStats)
-> (NodeStats -> NodeJVMStats -> NodeStats)
-> Lens' NodeStats NodeJVMStats
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeStats -> NodeJVMStats
nodeStatsJVM (\NodeStats
x NodeJVMStats
y -> NodeStats
x {nodeStatsJVM = y})
nodeStatsProcessLens :: Lens' NodeStats NodeProcessStats
nodeStatsProcessLens :: Lens' NodeStats NodeProcessStats
nodeStatsProcessLens = (NodeStats -> NodeProcessStats)
-> (NodeStats -> NodeProcessStats -> NodeStats)
-> Lens' NodeStats NodeProcessStats
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeStats -> NodeProcessStats
nodeStatsProcess (\NodeStats
x NodeProcessStats
y -> NodeStats
x {nodeStatsProcess = y})
nodeStatsOSLens :: Lens' NodeStats NodeOSStats
nodeStatsOSLens :: Lens' NodeStats NodeOSStats
nodeStatsOSLens = (NodeStats -> NodeOSStats)
-> (NodeStats -> NodeOSStats -> NodeStats)
-> Lens' NodeStats NodeOSStats
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeStats -> NodeOSStats
nodeStatsOS (\NodeStats
x NodeOSStats
y -> NodeStats
x {nodeStatsOS = y})
nodeStatsIndicesLens :: Lens' NodeStats NodeIndicesStats
nodeStatsIndicesLens :: Lens' NodeStats NodeIndicesStats
nodeStatsIndicesLens = (NodeStats -> NodeIndicesStats)
-> (NodeStats -> NodeIndicesStats -> NodeStats)
-> Lens' NodeStats NodeIndicesStats
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeStats -> NodeIndicesStats
nodeStatsIndices (\NodeStats
x NodeIndicesStats
y -> NodeStats
x {nodeStatsIndices = y})
data =
{ NodeBreakersStats -> NodeBreakerStats
nodeStatsParentBreaker :: NodeBreakerStats,
NodeBreakersStats -> NodeBreakerStats
nodeStatsRequestBreaker :: NodeBreakerStats,
NodeBreakersStats -> NodeBreakerStats
nodeStatsFieldDataBreaker :: NodeBreakerStats
}
deriving stock (NodeBreakersStats -> NodeBreakersStats -> Bool
(NodeBreakersStats -> NodeBreakersStats -> Bool)
-> (NodeBreakersStats -> NodeBreakersStats -> Bool)
-> Eq NodeBreakersStats
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NodeBreakersStats -> NodeBreakersStats -> Bool
== :: NodeBreakersStats -> NodeBreakersStats -> Bool
$c/= :: NodeBreakersStats -> NodeBreakersStats -> Bool
/= :: 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
$cshowsPrec :: Int -> NodeBreakersStats -> ShowS
showsPrec :: Int -> NodeBreakersStats -> ShowS
$cshow :: NodeBreakersStats -> String
show :: NodeBreakersStats -> String
$cshowList :: [NodeBreakersStats] -> ShowS
showList :: [NodeBreakersStats] -> ShowS
Show)
nodeStatsParentBreakerLens :: Lens' NodeBreakersStats NodeBreakerStats
nodeStatsParentBreakerLens :: Lens' NodeBreakersStats NodeBreakerStats
nodeStatsParentBreakerLens = (NodeBreakersStats -> NodeBreakerStats)
-> (NodeBreakersStats -> NodeBreakerStats -> NodeBreakersStats)
-> Lens' NodeBreakersStats NodeBreakerStats
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeBreakersStats -> NodeBreakerStats
nodeStatsParentBreaker (\NodeBreakersStats
x NodeBreakerStats
y -> NodeBreakersStats
x {nodeStatsParentBreaker = y})
nodeStatsRequestBreakerLens :: Lens' NodeBreakersStats NodeBreakerStats
nodeStatsRequestBreakerLens :: Lens' NodeBreakersStats NodeBreakerStats
nodeStatsRequestBreakerLens = (NodeBreakersStats -> NodeBreakerStats)
-> (NodeBreakersStats -> NodeBreakerStats -> NodeBreakersStats)
-> Lens' NodeBreakersStats NodeBreakerStats
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeBreakersStats -> NodeBreakerStats
nodeStatsRequestBreaker (\NodeBreakersStats
x NodeBreakerStats
y -> NodeBreakersStats
x {nodeStatsRequestBreaker = y})
nodeStatsFieldDataBreakerLens :: Lens' NodeBreakersStats NodeBreakerStats
nodeStatsFieldDataBreakerLens :: Lens' NodeBreakersStats NodeBreakerStats
nodeStatsFieldDataBreakerLens = (NodeBreakersStats -> NodeBreakerStats)
-> (NodeBreakersStats -> NodeBreakerStats -> NodeBreakersStats)
-> Lens' NodeBreakersStats NodeBreakerStats
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeBreakersStats -> NodeBreakerStats
nodeStatsFieldDataBreaker (\NodeBreakersStats
x NodeBreakerStats
y -> NodeBreakersStats
x {nodeStatsFieldDataBreaker = y})
data NodeBreakerStats = NodeBreakerStats
{ NodeBreakerStats -> Int
nodeBreakersTripped :: Int,
NodeBreakerStats -> Double
nodeBreakersOverhead :: Double,
NodeBreakerStats -> Bytes
nodeBreakersEstSize :: Bytes,
NodeBreakerStats -> Bytes
nodeBreakersLimitSize :: Bytes
}
deriving stock (NodeBreakerStats -> NodeBreakerStats -> Bool
(NodeBreakerStats -> NodeBreakerStats -> Bool)
-> (NodeBreakerStats -> NodeBreakerStats -> Bool)
-> Eq NodeBreakerStats
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NodeBreakerStats -> NodeBreakerStats -> Bool
== :: NodeBreakerStats -> NodeBreakerStats -> Bool
$c/= :: NodeBreakerStats -> NodeBreakerStats -> Bool
/= :: 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
$cshowsPrec :: Int -> NodeBreakerStats -> ShowS
showsPrec :: Int -> NodeBreakerStats -> ShowS
$cshow :: NodeBreakerStats -> String
show :: NodeBreakerStats -> String
$cshowList :: [NodeBreakerStats] -> ShowS
showList :: [NodeBreakerStats] -> ShowS
Show)
nodeBreakersStatsTrippedLens :: Lens' NodeBreakerStats Int
= (NodeBreakerStats -> Int)
-> (NodeBreakerStats -> Int -> NodeBreakerStats)
-> Lens' NodeBreakerStats Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeBreakerStats -> Int
nodeBreakersTripped (\NodeBreakerStats
x Int
y -> NodeBreakerStats
x {nodeBreakersTripped = y})
nodeBreakersStatsOverheadLens :: Lens' NodeBreakerStats Double
= (NodeBreakerStats -> Double)
-> (NodeBreakerStats -> Double -> NodeBreakerStats)
-> Lens' NodeBreakerStats Double
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeBreakerStats -> Double
nodeBreakersOverhead (\NodeBreakerStats
x Double
y -> NodeBreakerStats
x {nodeBreakersOverhead = y})
nodeBreakersStatsEstSizeLens :: Lens' NodeBreakerStats Bytes
= (NodeBreakerStats -> Bytes)
-> (NodeBreakerStats -> Bytes -> NodeBreakerStats)
-> Lens' NodeBreakerStats Bytes
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeBreakerStats -> Bytes
nodeBreakersEstSize (\NodeBreakerStats
x Bytes
y -> NodeBreakerStats
x {nodeBreakersEstSize = y})
nodeBreakersStatsLimitSizeLens :: Lens' NodeBreakerStats Bytes
= (NodeBreakerStats -> Bytes)
-> (NodeBreakerStats -> Bytes -> NodeBreakerStats)
-> Lens' NodeBreakerStats Bytes
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeBreakerStats -> Bytes
nodeBreakersLimitSize (\NodeBreakerStats
x Bytes
y -> NodeBreakerStats
x {nodeBreakersLimitSize = y})
data NodeHTTPStats = NodeHTTPStats
{ NodeHTTPStats -> Int
nodeHTTPTotalOpened :: Int,
NodeHTTPStats -> Int
nodeHTTPCurrentOpen :: Int
}
deriving stock (NodeHTTPStats -> NodeHTTPStats -> Bool
(NodeHTTPStats -> NodeHTTPStats -> Bool)
-> (NodeHTTPStats -> NodeHTTPStats -> Bool) -> Eq NodeHTTPStats
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NodeHTTPStats -> NodeHTTPStats -> Bool
== :: NodeHTTPStats -> NodeHTTPStats -> Bool
$c/= :: NodeHTTPStats -> NodeHTTPStats -> Bool
/= :: 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
$cshowsPrec :: Int -> NodeHTTPStats -> ShowS
showsPrec :: Int -> NodeHTTPStats -> ShowS
$cshow :: NodeHTTPStats -> String
show :: NodeHTTPStats -> String
$cshowList :: [NodeHTTPStats] -> ShowS
showList :: [NodeHTTPStats] -> ShowS
Show)
nodeHTTPTotalStatsOpenedLens :: Lens' NodeHTTPStats Int
nodeHTTPTotalStatsOpenedLens :: Lens' NodeHTTPStats Int
nodeHTTPTotalStatsOpenedLens = (NodeHTTPStats -> Int)
-> (NodeHTTPStats -> Int -> NodeHTTPStats)
-> Lens' NodeHTTPStats Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeHTTPStats -> Int
nodeHTTPTotalOpened (\NodeHTTPStats
x Int
y -> NodeHTTPStats
x {nodeHTTPTotalOpened = y})
nodeHTTPStatsCurrentOpenLens :: Lens' NodeHTTPStats Int
nodeHTTPStatsCurrentOpenLens :: Lens' NodeHTTPStats Int
nodeHTTPStatsCurrentOpenLens = (NodeHTTPStats -> Int)
-> (NodeHTTPStats -> Int -> NodeHTTPStats)
-> Lens' NodeHTTPStats Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeHTTPStats -> Int
nodeHTTPCurrentOpen (\NodeHTTPStats
x Int
y -> NodeHTTPStats
x {nodeHTTPCurrentOpen = y})
data NodeTransportStats = NodeTransportStats
{ NodeTransportStats -> Bytes
nodeTransportTXSize :: Bytes,
NodeTransportStats -> Int
nodeTransportCount :: Int,
NodeTransportStats -> Bytes
nodeTransportRXSize :: Bytes,
NodeTransportStats -> Int
nodeTransportRXCount :: Int,
NodeTransportStats -> Int
nodeTransportServerOpen :: Int
}
deriving stock (NodeTransportStats -> NodeTransportStats -> Bool
(NodeTransportStats -> NodeTransportStats -> Bool)
-> (NodeTransportStats -> NodeTransportStats -> Bool)
-> Eq NodeTransportStats
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NodeTransportStats -> NodeTransportStats -> Bool
== :: NodeTransportStats -> NodeTransportStats -> Bool
$c/= :: NodeTransportStats -> NodeTransportStats -> Bool
/= :: 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
$cshowsPrec :: Int -> NodeTransportStats -> ShowS
showsPrec :: Int -> NodeTransportStats -> ShowS
$cshow :: NodeTransportStats -> String
show :: NodeTransportStats -> String
$cshowList :: [NodeTransportStats] -> ShowS
showList :: [NodeTransportStats] -> ShowS
Show)
nodeTransportStatsTXSizeLens :: Lens' NodeTransportStats Bytes
nodeTransportStatsTXSizeLens :: Lens' NodeTransportStats Bytes
nodeTransportStatsTXSizeLens = (NodeTransportStats -> Bytes)
-> (NodeTransportStats -> Bytes -> NodeTransportStats)
-> Lens' NodeTransportStats Bytes
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeTransportStats -> Bytes
nodeTransportTXSize (\NodeTransportStats
x Bytes
y -> NodeTransportStats
x {nodeTransportTXSize = y})
nodeTransportStatsCountLens :: Lens' NodeTransportStats Int
nodeTransportStatsCountLens :: Lens' NodeTransportStats Int
nodeTransportStatsCountLens = (NodeTransportStats -> Int)
-> (NodeTransportStats -> Int -> NodeTransportStats)
-> Lens' NodeTransportStats Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeTransportStats -> Int
nodeTransportCount (\NodeTransportStats
x Int
y -> NodeTransportStats
x {nodeTransportCount = y})
nodeTransportStatsRXSizeLens :: Lens' NodeTransportStats Bytes
nodeTransportStatsRXSizeLens :: Lens' NodeTransportStats Bytes
nodeTransportStatsRXSizeLens = (NodeTransportStats -> Bytes)
-> (NodeTransportStats -> Bytes -> NodeTransportStats)
-> Lens' NodeTransportStats Bytes
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeTransportStats -> Bytes
nodeTransportRXSize (\NodeTransportStats
x Bytes
y -> NodeTransportStats
x {nodeTransportRXSize = y})
nodeTransportStatsRXCountLens :: Lens' NodeTransportStats Int
nodeTransportStatsRXCountLens :: Lens' NodeTransportStats Int
nodeTransportStatsRXCountLens = (NodeTransportStats -> Int)
-> (NodeTransportStats -> Int -> NodeTransportStats)
-> Lens' NodeTransportStats Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeTransportStats -> Int
nodeTransportRXCount (\NodeTransportStats
x Int
y -> NodeTransportStats
x {nodeTransportRXCount = y})
nodeTransportStatsServerOpenLens :: Lens' NodeTransportStats Int
nodeTransportStatsServerOpenLens :: Lens' NodeTransportStats Int
nodeTransportStatsServerOpenLens = (NodeTransportStats -> Int)
-> (NodeTransportStats -> Int -> NodeTransportStats)
-> Lens' NodeTransportStats Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeTransportStats -> Int
nodeTransportServerOpen (\NodeTransportStats
x Int
y -> NodeTransportStats
x {nodeTransportServerOpen = y})
data NodeFSStats = NodeFSStats
{ NodeFSStats -> [NodeDataPathStats]
nodeFSDataPaths :: [NodeDataPathStats],
NodeFSStats -> NodeFSTotalStats
nodeFSTotal :: NodeFSTotalStats,
NodeFSStats -> UTCTime
nodeFSTimestamp :: UTCTime
}
deriving stock (NodeFSStats -> NodeFSStats -> Bool
(NodeFSStats -> NodeFSStats -> Bool)
-> (NodeFSStats -> NodeFSStats -> Bool) -> Eq NodeFSStats
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NodeFSStats -> NodeFSStats -> Bool
== :: NodeFSStats -> NodeFSStats -> Bool
$c/= :: NodeFSStats -> NodeFSStats -> Bool
/= :: 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
$cshowsPrec :: Int -> NodeFSStats -> ShowS
showsPrec :: Int -> NodeFSStats -> ShowS
$cshow :: NodeFSStats -> String
show :: NodeFSStats -> String
$cshowList :: [NodeFSStats] -> ShowS
showList :: [NodeFSStats] -> ShowS
Show)
nodeFSStatsDataPathsLens :: Lens' NodeFSStats [NodeDataPathStats]
nodeFSStatsDataPathsLens :: Lens' NodeFSStats [NodeDataPathStats]
nodeFSStatsDataPathsLens = (NodeFSStats -> [NodeDataPathStats])
-> (NodeFSStats -> [NodeDataPathStats] -> NodeFSStats)
-> Lens' NodeFSStats [NodeDataPathStats]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeFSStats -> [NodeDataPathStats]
nodeFSDataPaths (\NodeFSStats
x [NodeDataPathStats]
y -> NodeFSStats
x {nodeFSDataPaths = y})
nodeFSStatsTotalLens :: Lens' NodeFSStats NodeFSTotalStats
nodeFSStatsTotalLens :: Lens' NodeFSStats NodeFSTotalStats
nodeFSStatsTotalLens = (NodeFSStats -> NodeFSTotalStats)
-> (NodeFSStats -> NodeFSTotalStats -> NodeFSStats)
-> Lens' NodeFSStats NodeFSTotalStats
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeFSStats -> NodeFSTotalStats
nodeFSTotal (\NodeFSStats
x NodeFSTotalStats
y -> NodeFSStats
x {nodeFSTotal = y})
nodeFSStatsTimestampLens :: Lens' NodeFSStats UTCTime
nodeFSStatsTimestampLens :: Lens' NodeFSStats UTCTime
nodeFSStatsTimestampLens = (NodeFSStats -> UTCTime)
-> (NodeFSStats -> UTCTime -> NodeFSStats)
-> Lens' NodeFSStats UTCTime
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeFSStats -> UTCTime
nodeFSTimestamp (\NodeFSStats
x UTCTime
y -> NodeFSStats
x {nodeFSTimestamp = y})
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 stock (NodeDataPathStats -> NodeDataPathStats -> Bool
(NodeDataPathStats -> NodeDataPathStats -> Bool)
-> (NodeDataPathStats -> NodeDataPathStats -> Bool)
-> Eq NodeDataPathStats
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NodeDataPathStats -> NodeDataPathStats -> Bool
== :: NodeDataPathStats -> NodeDataPathStats -> Bool
$c/= :: NodeDataPathStats -> NodeDataPathStats -> Bool
/= :: 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
$cshowsPrec :: Int -> NodeDataPathStats -> ShowS
showsPrec :: Int -> NodeDataPathStats -> ShowS
$cshow :: NodeDataPathStats -> String
show :: NodeDataPathStats -> String
$cshowList :: [NodeDataPathStats] -> ShowS
showList :: [NodeDataPathStats] -> ShowS
Show)
nodeDataPathStatsDiskServiceTimeLens :: Lens' NodeDataPathStats (Maybe Double)
nodeDataPathStatsDiskServiceTimeLens :: Lens' NodeDataPathStats (Maybe Double)
nodeDataPathStatsDiskServiceTimeLens = (NodeDataPathStats -> Maybe Double)
-> (NodeDataPathStats -> Maybe Double -> NodeDataPathStats)
-> Lens' NodeDataPathStats (Maybe Double)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeDataPathStats -> Maybe Double
nodeDataPathDiskServiceTime (\NodeDataPathStats
x Maybe Double
y -> NodeDataPathStats
x {nodeDataPathDiskServiceTime = y})
nodeDataPathStatsDiskQueueLens :: Lens' NodeDataPathStats (Maybe Double)
nodeDataPathStatsDiskQueueLens :: Lens' NodeDataPathStats (Maybe Double)
nodeDataPathStatsDiskQueueLens = (NodeDataPathStats -> Maybe Double)
-> (NodeDataPathStats -> Maybe Double -> NodeDataPathStats)
-> Lens' NodeDataPathStats (Maybe Double)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeDataPathStats -> Maybe Double
nodeDataPathDiskQueue (\NodeDataPathStats
x Maybe Double
y -> NodeDataPathStats
x {nodeDataPathDiskQueue = y})
nodeDataPathStatsIOSizeLens :: Lens' NodeDataPathStats (Maybe Bytes)
nodeDataPathStatsIOSizeLens :: Lens' NodeDataPathStats (Maybe Bytes)
nodeDataPathStatsIOSizeLens = (NodeDataPathStats -> Maybe Bytes)
-> (NodeDataPathStats -> Maybe Bytes -> NodeDataPathStats)
-> Lens' NodeDataPathStats (Maybe Bytes)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeDataPathStats -> Maybe Bytes
nodeDataPathIOSize (\NodeDataPathStats
x Maybe Bytes
y -> NodeDataPathStats
x {nodeDataPathIOSize = y})
nodeDataPathStatsWriteSizeLens :: Lens' NodeDataPathStats (Maybe Bytes)
nodeDataPathStatsWriteSizeLens :: Lens' NodeDataPathStats (Maybe Bytes)
nodeDataPathStatsWriteSizeLens = (NodeDataPathStats -> Maybe Bytes)
-> (NodeDataPathStats -> Maybe Bytes -> NodeDataPathStats)
-> Lens' NodeDataPathStats (Maybe Bytes)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeDataPathStats -> Maybe Bytes
nodeDataPathWriteSize (\NodeDataPathStats
x Maybe Bytes
y -> NodeDataPathStats
x {nodeDataPathWriteSize = y})
nodeDataPathStatsReadSizeLens :: Lens' NodeDataPathStats (Maybe Bytes)
nodeDataPathStatsReadSizeLens :: Lens' NodeDataPathStats (Maybe Bytes)
nodeDataPathStatsReadSizeLens = (NodeDataPathStats -> Maybe Bytes)
-> (NodeDataPathStats -> Maybe Bytes -> NodeDataPathStats)
-> Lens' NodeDataPathStats (Maybe Bytes)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeDataPathStats -> Maybe Bytes
nodeDataPathReadSize (\NodeDataPathStats
x Maybe Bytes
y -> NodeDataPathStats
x {nodeDataPathReadSize = y})
nodeDataPathStatsIOOpsLens :: Lens' NodeDataPathStats (Maybe Int)
nodeDataPathStatsIOOpsLens :: Lens' NodeDataPathStats (Maybe Int)
nodeDataPathStatsIOOpsLens = (NodeDataPathStats -> Maybe Int)
-> (NodeDataPathStats -> Maybe Int -> NodeDataPathStats)
-> Lens' NodeDataPathStats (Maybe Int)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeDataPathStats -> Maybe Int
nodeDataPathIOOps (\NodeDataPathStats
x Maybe Int
y -> NodeDataPathStats
x {nodeDataPathIOOps = y})
nodeDataPathStatsWritesLens :: Lens' NodeDataPathStats (Maybe Int)
nodeDataPathStatsWritesLens :: Lens' NodeDataPathStats (Maybe Int)
nodeDataPathStatsWritesLens = (NodeDataPathStats -> Maybe Int)
-> (NodeDataPathStats -> Maybe Int -> NodeDataPathStats)
-> Lens' NodeDataPathStats (Maybe Int)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeDataPathStats -> Maybe Int
nodeDataPathWrites (\NodeDataPathStats
x Maybe Int
y -> NodeDataPathStats
x {nodeDataPathWrites = y})
nodeDataPathStatsReadsLens :: Lens' NodeDataPathStats (Maybe Int)
nodeDataPathStatsReadsLens :: Lens' NodeDataPathStats (Maybe Int)
nodeDataPathStatsReadsLens = (NodeDataPathStats -> Maybe Int)
-> (NodeDataPathStats -> Maybe Int -> NodeDataPathStats)
-> Lens' NodeDataPathStats (Maybe Int)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeDataPathStats -> Maybe Int
nodeDataPathReads (\NodeDataPathStats
x Maybe Int
y -> NodeDataPathStats
x {nodeDataPathReads = y})
nodeDataPathStatsAvailableLens :: Lens' NodeDataPathStats Bytes
nodeDataPathStatsAvailableLens :: Lens' NodeDataPathStats Bytes
nodeDataPathStatsAvailableLens = (NodeDataPathStats -> Bytes)
-> (NodeDataPathStats -> Bytes -> NodeDataPathStats)
-> Lens' NodeDataPathStats Bytes
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeDataPathStats -> Bytes
nodeDataPathAvailable (\NodeDataPathStats
x Bytes
y -> NodeDataPathStats
x {nodeDataPathAvailable = y})
nodeDataPathStatsFreeLens :: Lens' NodeDataPathStats Bytes
nodeDataPathStatsFreeLens :: Lens' NodeDataPathStats Bytes
nodeDataPathStatsFreeLens = (NodeDataPathStats -> Bytes)
-> (NodeDataPathStats -> Bytes -> NodeDataPathStats)
-> Lens' NodeDataPathStats Bytes
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeDataPathStats -> Bytes
nodeDataPathFree (\NodeDataPathStats
x Bytes
y -> NodeDataPathStats
x {nodeDataPathFree = y})
nodeDataPathStatsTotalLens :: Lens' NodeDataPathStats Bytes
nodeDataPathStatsTotalLens :: Lens' NodeDataPathStats Bytes
nodeDataPathStatsTotalLens = (NodeDataPathStats -> Bytes)
-> (NodeDataPathStats -> Bytes -> NodeDataPathStats)
-> Lens' NodeDataPathStats Bytes
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeDataPathStats -> Bytes
nodeDataPathTotal (\NodeDataPathStats
x Bytes
y -> NodeDataPathStats
x {nodeDataPathTotal = y})
nodeDataPathStatsTypeLens :: Lens' NodeDataPathStats (Maybe Text)
nodeDataPathStatsTypeLens :: Lens' NodeDataPathStats (Maybe Text)
nodeDataPathStatsTypeLens = (NodeDataPathStats -> Maybe Text)
-> (NodeDataPathStats -> Maybe Text -> NodeDataPathStats)
-> Lens' NodeDataPathStats (Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeDataPathStats -> Maybe Text
nodeDataPathType (\NodeDataPathStats
x Maybe Text
y -> NodeDataPathStats
x {nodeDataPathType = y})
nodeDataPathStatsDeviceLens :: Lens' NodeDataPathStats (Maybe Text)
nodeDataPathStatsDeviceLens :: Lens' NodeDataPathStats (Maybe Text)
nodeDataPathStatsDeviceLens = (NodeDataPathStats -> Maybe Text)
-> (NodeDataPathStats -> Maybe Text -> NodeDataPathStats)
-> Lens' NodeDataPathStats (Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeDataPathStats -> Maybe Text
nodeDataPathDevice (\NodeDataPathStats
x Maybe Text
y -> NodeDataPathStats
x {nodeDataPathDevice = y})
nodeDataPathStatsMountLens :: Lens' NodeDataPathStats Text
nodeDataPathStatsMountLens :: Lens' NodeDataPathStats Text
nodeDataPathStatsMountLens = (NodeDataPathStats -> Text)
-> (NodeDataPathStats -> Text -> NodeDataPathStats)
-> Lens' NodeDataPathStats Text
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeDataPathStats -> Text
nodeDataPathMount (\NodeDataPathStats
x Text
y -> NodeDataPathStats
x {nodeDataPathMount = y})
nodeDataPathStatsPathLens :: Lens' NodeDataPathStats Text
nodeDataPathStatsPathLens :: Lens' NodeDataPathStats Text
nodeDataPathStatsPathLens = (NodeDataPathStats -> Text)
-> (NodeDataPathStats -> Text -> NodeDataPathStats)
-> Lens' NodeDataPathStats Text
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeDataPathStats -> Text
nodeDataPathPath (\NodeDataPathStats
x Text
y -> NodeDataPathStats
x {nodeDataPathPath = y})
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 stock (NodeFSTotalStats -> NodeFSTotalStats -> Bool
(NodeFSTotalStats -> NodeFSTotalStats -> Bool)
-> (NodeFSTotalStats -> NodeFSTotalStats -> Bool)
-> Eq NodeFSTotalStats
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NodeFSTotalStats -> NodeFSTotalStats -> Bool
== :: NodeFSTotalStats -> NodeFSTotalStats -> Bool
$c/= :: NodeFSTotalStats -> NodeFSTotalStats -> Bool
/= :: 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
$cshowsPrec :: Int -> NodeFSTotalStats -> ShowS
showsPrec :: Int -> NodeFSTotalStats -> ShowS
$cshow :: NodeFSTotalStats -> String
show :: NodeFSTotalStats -> String
$cshowList :: [NodeFSTotalStats] -> ShowS
showList :: [NodeFSTotalStats] -> ShowS
Show)
nodeFSTotalStatsDiskServiceTimeLens :: Lens' NodeFSTotalStats (Maybe Double)
nodeFSTotalStatsDiskServiceTimeLens :: Lens' NodeFSTotalStats (Maybe Double)
nodeFSTotalStatsDiskServiceTimeLens = (NodeFSTotalStats -> Maybe Double)
-> (NodeFSTotalStats -> Maybe Double -> NodeFSTotalStats)
-> Lens' NodeFSTotalStats (Maybe Double)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeFSTotalStats -> Maybe Double
nodeFSTotalDiskServiceTime (\NodeFSTotalStats
x Maybe Double
y -> NodeFSTotalStats
x {nodeFSTotalDiskServiceTime = y})
nodeFSTotalStatsDiskQueueLens :: Lens' NodeFSTotalStats (Maybe Double)
nodeFSTotalStatsDiskQueueLens :: Lens' NodeFSTotalStats (Maybe Double)
nodeFSTotalStatsDiskQueueLens = (NodeFSTotalStats -> Maybe Double)
-> (NodeFSTotalStats -> Maybe Double -> NodeFSTotalStats)
-> Lens' NodeFSTotalStats (Maybe Double)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeFSTotalStats -> Maybe Double
nodeFSTotalDiskQueue (\NodeFSTotalStats
x Maybe Double
y -> NodeFSTotalStats
x {nodeFSTotalDiskQueue = y})
nodeFSTotalStatsIOSizeLens :: Lens' NodeFSTotalStats (Maybe Bytes)
nodeFSTotalStatsIOSizeLens :: Lens' NodeFSTotalStats (Maybe Bytes)
nodeFSTotalStatsIOSizeLens = (NodeFSTotalStats -> Maybe Bytes)
-> (NodeFSTotalStats -> Maybe Bytes -> NodeFSTotalStats)
-> Lens' NodeFSTotalStats (Maybe Bytes)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeFSTotalStats -> Maybe Bytes
nodeFSTotalIOSize (\NodeFSTotalStats
x Maybe Bytes
y -> NodeFSTotalStats
x {nodeFSTotalIOSize = y})
nodeFSTotalStatsWriteSizeLens :: Lens' NodeFSTotalStats (Maybe Bytes)
nodeFSTotalStatsWriteSizeLens :: Lens' NodeFSTotalStats (Maybe Bytes)
nodeFSTotalStatsWriteSizeLens = (NodeFSTotalStats -> Maybe Bytes)
-> (NodeFSTotalStats -> Maybe Bytes -> NodeFSTotalStats)
-> Lens' NodeFSTotalStats (Maybe Bytes)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeFSTotalStats -> Maybe Bytes
nodeFSTotalWriteSize (\NodeFSTotalStats
x Maybe Bytes
y -> NodeFSTotalStats
x {nodeFSTotalWriteSize = y})
nodeFSTotalStatsReadSizeLens :: Lens' NodeFSTotalStats (Maybe Bytes)
nodeFSTotalStatsReadSizeLens :: Lens' NodeFSTotalStats (Maybe Bytes)
nodeFSTotalStatsReadSizeLens = (NodeFSTotalStats -> Maybe Bytes)
-> (NodeFSTotalStats -> Maybe Bytes -> NodeFSTotalStats)
-> Lens' NodeFSTotalStats (Maybe Bytes)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeFSTotalStats -> Maybe Bytes
nodeFSTotalReadSize (\NodeFSTotalStats
x Maybe Bytes
y -> NodeFSTotalStats
x {nodeFSTotalReadSize = y})
nodeFSTotalStatsIOOpsLens :: Lens' NodeFSTotalStats (Maybe Int)
nodeFSTotalStatsIOOpsLens :: Lens' NodeFSTotalStats (Maybe Int)
nodeFSTotalStatsIOOpsLens = (NodeFSTotalStats -> Maybe Int)
-> (NodeFSTotalStats -> Maybe Int -> NodeFSTotalStats)
-> Lens' NodeFSTotalStats (Maybe Int)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeFSTotalStats -> Maybe Int
nodeFSTotalIOOps (\NodeFSTotalStats
x Maybe Int
y -> NodeFSTotalStats
x {nodeFSTotalIOOps = y})
nodeFSTotalStatsWritesLens :: Lens' NodeFSTotalStats (Maybe Int)
nodeFSTotalStatsWritesLens :: Lens' NodeFSTotalStats (Maybe Int)
nodeFSTotalStatsWritesLens = (NodeFSTotalStats -> Maybe Int)
-> (NodeFSTotalStats -> Maybe Int -> NodeFSTotalStats)
-> Lens' NodeFSTotalStats (Maybe Int)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeFSTotalStats -> Maybe Int
nodeFSTotalWrites (\NodeFSTotalStats
x Maybe Int
y -> NodeFSTotalStats
x {nodeFSTotalWrites = y})
nodeFSTotalStatsReadsLens :: Lens' NodeFSTotalStats (Maybe Int)
nodeFSTotalStatsReadsLens :: Lens' NodeFSTotalStats (Maybe Int)
nodeFSTotalStatsReadsLens = (NodeFSTotalStats -> Maybe Int)
-> (NodeFSTotalStats -> Maybe Int -> NodeFSTotalStats)
-> Lens' NodeFSTotalStats (Maybe Int)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeFSTotalStats -> Maybe Int
nodeFSTotalReads (\NodeFSTotalStats
x Maybe Int
y -> NodeFSTotalStats
x {nodeFSTotalReads = y})
nodeFSTotalStatsAvailableLens :: Lens' NodeFSTotalStats Bytes
nodeFSTotalStatsAvailableLens :: Lens' NodeFSTotalStats Bytes
nodeFSTotalStatsAvailableLens = (NodeFSTotalStats -> Bytes)
-> (NodeFSTotalStats -> Bytes -> NodeFSTotalStats)
-> Lens' NodeFSTotalStats Bytes
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeFSTotalStats -> Bytes
nodeFSTotalAvailable (\NodeFSTotalStats
x Bytes
y -> NodeFSTotalStats
x {nodeFSTotalAvailable = y})
nodeFSTotalStatsFreeLens :: Lens' NodeFSTotalStats Bytes
nodeFSTotalStatsFreeLens :: Lens' NodeFSTotalStats Bytes
nodeFSTotalStatsFreeLens = (NodeFSTotalStats -> Bytes)
-> (NodeFSTotalStats -> Bytes -> NodeFSTotalStats)
-> Lens' NodeFSTotalStats Bytes
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeFSTotalStats -> Bytes
nodeFSTotalFree (\NodeFSTotalStats
x Bytes
y -> NodeFSTotalStats
x {nodeFSTotalFree = y})
nodeFSTotalStatsTotalLens :: Lens' NodeFSTotalStats Bytes
nodeFSTotalStatsTotalLens :: Lens' NodeFSTotalStats Bytes
nodeFSTotalStatsTotalLens = (NodeFSTotalStats -> Bytes)
-> (NodeFSTotalStats -> Bytes -> NodeFSTotalStats)
-> Lens' NodeFSTotalStats Bytes
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeFSTotalStats -> Bytes
nodeFSTotalTotal (\NodeFSTotalStats
x Bytes
y -> NodeFSTotalStats
x {nodeFSTotalTotal = y})
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 stock (NodeNetworkStats -> NodeNetworkStats -> Bool
(NodeNetworkStats -> NodeNetworkStats -> Bool)
-> (NodeNetworkStats -> NodeNetworkStats -> Bool)
-> Eq NodeNetworkStats
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NodeNetworkStats -> NodeNetworkStats -> Bool
== :: NodeNetworkStats -> NodeNetworkStats -> Bool
$c/= :: NodeNetworkStats -> NodeNetworkStats -> Bool
/= :: 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
$cshowsPrec :: Int -> NodeNetworkStats -> ShowS
showsPrec :: Int -> NodeNetworkStats -> ShowS
$cshow :: NodeNetworkStats -> String
show :: NodeNetworkStats -> String
$cshowList :: [NodeNetworkStats] -> ShowS
showList :: [NodeNetworkStats] -> ShowS
Show)
nodeNetworkStatsTCPOutRSTsLens :: Lens' NodeNetworkStats Int
nodeNetworkStatsTCPOutRSTsLens :: Lens' NodeNetworkStats Int
nodeNetworkStatsTCPOutRSTsLens = (NodeNetworkStats -> Int)
-> (NodeNetworkStats -> Int -> NodeNetworkStats)
-> Lens' NodeNetworkStats Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeNetworkStats -> Int
nodeNetTCPOutRSTs (\NodeNetworkStats
x Int
y -> NodeNetworkStats
x {nodeNetTCPOutRSTs = y})
nodeNetworkStatsTCPInErrsLens :: Lens' NodeNetworkStats Int
nodeNetworkStatsTCPInErrsLens :: Lens' NodeNetworkStats Int
nodeNetworkStatsTCPInErrsLens = (NodeNetworkStats -> Int)
-> (NodeNetworkStats -> Int -> NodeNetworkStats)
-> Lens' NodeNetworkStats Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeNetworkStats -> Int
nodeNetTCPInErrs (\NodeNetworkStats
x Int
y -> NodeNetworkStats
x {nodeNetTCPInErrs = y})
nodeNetworkStatsTCPAttemptFailsLens :: Lens' NodeNetworkStats Int
nodeNetworkStatsTCPAttemptFailsLens :: Lens' NodeNetworkStats Int
nodeNetworkStatsTCPAttemptFailsLens = (NodeNetworkStats -> Int)
-> (NodeNetworkStats -> Int -> NodeNetworkStats)
-> Lens' NodeNetworkStats Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeNetworkStats -> Int
nodeNetTCPAttemptFails (\NodeNetworkStats
x Int
y -> NodeNetworkStats
x {nodeNetTCPAttemptFails = y})
nodeNetworkStatsTCPEstabResetsLens :: Lens' NodeNetworkStats Int
nodeNetworkStatsTCPEstabResetsLens :: Lens' NodeNetworkStats Int
nodeNetworkStatsTCPEstabResetsLens = (NodeNetworkStats -> Int)
-> (NodeNetworkStats -> Int -> NodeNetworkStats)
-> Lens' NodeNetworkStats Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeNetworkStats -> Int
nodeNetTCPEstabResets (\NodeNetworkStats
x Int
y -> NodeNetworkStats
x {nodeNetTCPEstabResets = y})
nodeNetworkStatsTCPRetransSegsLens :: Lens' NodeNetworkStats Int
nodeNetworkStatsTCPRetransSegsLens :: Lens' NodeNetworkStats Int
nodeNetworkStatsTCPRetransSegsLens = (NodeNetworkStats -> Int)
-> (NodeNetworkStats -> Int -> NodeNetworkStats)
-> Lens' NodeNetworkStats Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeNetworkStats -> Int
nodeNetTCPRetransSegs (\NodeNetworkStats
x Int
y -> NodeNetworkStats
x {nodeNetTCPRetransSegs = y})
nodeNetworkStatsTCPOutSegsLens :: Lens' NodeNetworkStats Int
nodeNetworkStatsTCPOutSegsLens :: Lens' NodeNetworkStats Int
nodeNetworkStatsTCPOutSegsLens = (NodeNetworkStats -> Int)
-> (NodeNetworkStats -> Int -> NodeNetworkStats)
-> Lens' NodeNetworkStats Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeNetworkStats -> Int
nodeNetTCPOutSegs (\NodeNetworkStats
x Int
y -> NodeNetworkStats
x {nodeNetTCPOutSegs = y})
nodeNetworkStatsTCPInSegsLens :: Lens' NodeNetworkStats Int
nodeNetworkStatsTCPInSegsLens :: Lens' NodeNetworkStats Int
nodeNetworkStatsTCPInSegsLens = (NodeNetworkStats -> Int)
-> (NodeNetworkStats -> Int -> NodeNetworkStats)
-> Lens' NodeNetworkStats Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeNetworkStats -> Int
nodeNetTCPInSegs (\NodeNetworkStats
x Int
y -> NodeNetworkStats
x {nodeNetTCPInSegs = y})
nodeNetworkStatsTCPCurrEstabLens :: Lens' NodeNetworkStats Int
nodeNetworkStatsTCPCurrEstabLens :: Lens' NodeNetworkStats Int
nodeNetworkStatsTCPCurrEstabLens = (NodeNetworkStats -> Int)
-> (NodeNetworkStats -> Int -> NodeNetworkStats)
-> Lens' NodeNetworkStats Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeNetworkStats -> Int
nodeNetTCPCurrEstab (\NodeNetworkStats
x Int
y -> NodeNetworkStats
x {nodeNetTCPCurrEstab = y})
nodeNetworkStatsTCPPassiveOpensLens :: Lens' NodeNetworkStats Int
nodeNetworkStatsTCPPassiveOpensLens :: Lens' NodeNetworkStats Int
nodeNetworkStatsTCPPassiveOpensLens = (NodeNetworkStats -> Int)
-> (NodeNetworkStats -> Int -> NodeNetworkStats)
-> Lens' NodeNetworkStats Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeNetworkStats -> Int
nodeNetTCPPassiveOpens (\NodeNetworkStats
x Int
y -> NodeNetworkStats
x {nodeNetTCPPassiveOpens = y})
nodeNetworkStatsTCPActiveOpensLens :: Lens' NodeNetworkStats Int
nodeNetworkStatsTCPActiveOpensLens :: Lens' NodeNetworkStats Int
nodeNetworkStatsTCPActiveOpensLens = (NodeNetworkStats -> Int)
-> (NodeNetworkStats -> Int -> NodeNetworkStats)
-> Lens' NodeNetworkStats Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeNetworkStats -> Int
nodeNetTCPActiveOpens (\NodeNetworkStats
x Int
y -> NodeNetworkStats
x {nodeNetTCPActiveOpens = y})
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 stock (NodeThreadPoolStats -> NodeThreadPoolStats -> Bool
(NodeThreadPoolStats -> NodeThreadPoolStats -> Bool)
-> (NodeThreadPoolStats -> NodeThreadPoolStats -> Bool)
-> Eq NodeThreadPoolStats
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NodeThreadPoolStats -> NodeThreadPoolStats -> Bool
== :: NodeThreadPoolStats -> NodeThreadPoolStats -> Bool
$c/= :: NodeThreadPoolStats -> NodeThreadPoolStats -> Bool
/= :: 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
$cshowsPrec :: Int -> NodeThreadPoolStats -> ShowS
showsPrec :: Int -> NodeThreadPoolStats -> ShowS
$cshow :: NodeThreadPoolStats -> String
show :: NodeThreadPoolStats -> String
$cshowList :: [NodeThreadPoolStats] -> ShowS
showList :: [NodeThreadPoolStats] -> ShowS
Show)
nodeThreadPoolStatsCompletedLens :: Lens' NodeThreadPoolStats Int
nodeThreadPoolStatsCompletedLens :: Lens' NodeThreadPoolStats Int
nodeThreadPoolStatsCompletedLens = (NodeThreadPoolStats -> Int)
-> (NodeThreadPoolStats -> Int -> NodeThreadPoolStats)
-> Lens' NodeThreadPoolStats Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeThreadPoolStats -> Int
nodeThreadPoolCompleted (\NodeThreadPoolStats
x Int
y -> NodeThreadPoolStats
x {nodeThreadPoolCompleted = y})
nodeThreadPoolStatsLargestLens :: Lens' NodeThreadPoolStats Int
nodeThreadPoolStatsLargestLens :: Lens' NodeThreadPoolStats Int
nodeThreadPoolStatsLargestLens = (NodeThreadPoolStats -> Int)
-> (NodeThreadPoolStats -> Int -> NodeThreadPoolStats)
-> Lens' NodeThreadPoolStats Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeThreadPoolStats -> Int
nodeThreadPoolLargest (\NodeThreadPoolStats
x Int
y -> NodeThreadPoolStats
x {nodeThreadPoolLargest = y})
nodeThreadPoolStatsRejectedLens :: Lens' NodeThreadPoolStats Int
nodeThreadPoolStatsRejectedLens :: Lens' NodeThreadPoolStats Int
nodeThreadPoolStatsRejectedLens = (NodeThreadPoolStats -> Int)
-> (NodeThreadPoolStats -> Int -> NodeThreadPoolStats)
-> Lens' NodeThreadPoolStats Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeThreadPoolStats -> Int
nodeThreadPoolRejected (\NodeThreadPoolStats
x Int
y -> NodeThreadPoolStats
x {nodeThreadPoolRejected = y})
nodeThreadPoolStatsActiveLens :: Lens' NodeThreadPoolStats Int
nodeThreadPoolStatsActiveLens :: Lens' NodeThreadPoolStats Int
nodeThreadPoolStatsActiveLens = (NodeThreadPoolStats -> Int)
-> (NodeThreadPoolStats -> Int -> NodeThreadPoolStats)
-> Lens' NodeThreadPoolStats Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeThreadPoolStats -> Int
nodeThreadPoolActive (\NodeThreadPoolStats
x Int
y -> NodeThreadPoolStats
x {nodeThreadPoolActive = y})
nodeThreadPoolStatsQueueLens :: Lens' NodeThreadPoolStats Int
nodeThreadPoolStatsQueueLens :: Lens' NodeThreadPoolStats Int
nodeThreadPoolStatsQueueLens = (NodeThreadPoolStats -> Int)
-> (NodeThreadPoolStats -> Int -> NodeThreadPoolStats)
-> Lens' NodeThreadPoolStats Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeThreadPoolStats -> Int
nodeThreadPoolQueue (\NodeThreadPoolStats
x Int
y -> NodeThreadPoolStats
x {nodeThreadPoolQueue = y})
nodeThreadPoolStatsThreadsLens :: Lens' NodeThreadPoolStats Int
nodeThreadPoolStatsThreadsLens :: Lens' NodeThreadPoolStats Int
nodeThreadPoolStatsThreadsLens = (NodeThreadPoolStats -> Int)
-> (NodeThreadPoolStats -> Int -> NodeThreadPoolStats)
-> Lens' NodeThreadPoolStats Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeThreadPoolStats -> Int
nodeThreadPoolThreads (\NodeThreadPoolStats
x Int
y -> NodeThreadPoolStats
x {nodeThreadPoolThreads = y})
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 stock (NodeJVMStats -> NodeJVMStats -> Bool
(NodeJVMStats -> NodeJVMStats -> Bool)
-> (NodeJVMStats -> NodeJVMStats -> Bool) -> Eq NodeJVMStats
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NodeJVMStats -> NodeJVMStats -> Bool
== :: NodeJVMStats -> NodeJVMStats -> Bool
$c/= :: NodeJVMStats -> NodeJVMStats -> Bool
/= :: 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
$cshowsPrec :: Int -> NodeJVMStats -> ShowS
showsPrec :: Int -> NodeJVMStats -> ShowS
$cshow :: NodeJVMStats -> String
show :: NodeJVMStats -> String
$cshowList :: [NodeJVMStats] -> ShowS
showList :: [NodeJVMStats] -> ShowS
Show)
nodeJVMStatsMappedBufferPoolLens :: Lens' NodeJVMStats JVMBufferPoolStats
nodeJVMStatsMappedBufferPoolLens :: Lens' NodeJVMStats JVMBufferPoolStats
nodeJVMStatsMappedBufferPoolLens = (NodeJVMStats -> JVMBufferPoolStats)
-> (NodeJVMStats -> JVMBufferPoolStats -> NodeJVMStats)
-> Lens' NodeJVMStats JVMBufferPoolStats
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeJVMStats -> JVMBufferPoolStats
nodeJVMStatsMappedBufferPool (\NodeJVMStats
x JVMBufferPoolStats
y -> NodeJVMStats
x {nodeJVMStatsMappedBufferPool = y})
nodeJVMStatsDirectBufferPoolLens :: Lens' NodeJVMStats JVMBufferPoolStats
nodeJVMStatsDirectBufferPoolLens :: Lens' NodeJVMStats JVMBufferPoolStats
nodeJVMStatsDirectBufferPoolLens = (NodeJVMStats -> JVMBufferPoolStats)
-> (NodeJVMStats -> JVMBufferPoolStats -> NodeJVMStats)
-> Lens' NodeJVMStats JVMBufferPoolStats
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeJVMStats -> JVMBufferPoolStats
nodeJVMStatsDirectBufferPool (\NodeJVMStats
x JVMBufferPoolStats
y -> NodeJVMStats
x {nodeJVMStatsDirectBufferPool = y})
nodeJVMStatsGCOldCollectorLens :: Lens' NodeJVMStats JVMGCStats
nodeJVMStatsGCOldCollectorLens :: Lens' NodeJVMStats JVMGCStats
nodeJVMStatsGCOldCollectorLens = (NodeJVMStats -> JVMGCStats)
-> (NodeJVMStats -> JVMGCStats -> NodeJVMStats)
-> Lens' NodeJVMStats JVMGCStats
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeJVMStats -> JVMGCStats
nodeJVMStatsGCOldCollector (\NodeJVMStats
x JVMGCStats
y -> NodeJVMStats
x {nodeJVMStatsGCOldCollector = y})
nodeJVMStatsGCYoungCollectorLens :: Lens' NodeJVMStats JVMGCStats
nodeJVMStatsGCYoungCollectorLens :: Lens' NodeJVMStats JVMGCStats
nodeJVMStatsGCYoungCollectorLens = (NodeJVMStats -> JVMGCStats)
-> (NodeJVMStats -> JVMGCStats -> NodeJVMStats)
-> Lens' NodeJVMStats JVMGCStats
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeJVMStats -> JVMGCStats
nodeJVMStatsGCYoungCollector (\NodeJVMStats
x JVMGCStats
y -> NodeJVMStats
x {nodeJVMStatsGCYoungCollector = y})
nodeJVMStatsPeakThreadsCountLens :: Lens' NodeJVMStats Int
nodeJVMStatsPeakThreadsCountLens :: Lens' NodeJVMStats Int
nodeJVMStatsPeakThreadsCountLens = (NodeJVMStats -> Int)
-> (NodeJVMStats -> Int -> NodeJVMStats) -> Lens' NodeJVMStats Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeJVMStats -> Int
nodeJVMStatsPeakThreadsCount (\NodeJVMStats
x Int
y -> NodeJVMStats
x {nodeJVMStatsPeakThreadsCount = y})
nodeJVMStatsThreadsCountLens :: Lens' NodeJVMStats Int
nodeJVMStatsThreadsCountLens :: Lens' NodeJVMStats Int
nodeJVMStatsThreadsCountLens = (NodeJVMStats -> Int)
-> (NodeJVMStats -> Int -> NodeJVMStats) -> Lens' NodeJVMStats Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeJVMStats -> Int
nodeJVMStatsThreadsCount (\NodeJVMStats
x Int
y -> NodeJVMStats
x {nodeJVMStatsThreadsCount = y})
nodeJVMStatsOldPoolLens :: Lens' NodeJVMStats JVMPoolStats
nodeJVMStatsOldPoolLens :: Lens' NodeJVMStats JVMPoolStats
nodeJVMStatsOldPoolLens = (NodeJVMStats -> JVMPoolStats)
-> (NodeJVMStats -> JVMPoolStats -> NodeJVMStats)
-> Lens' NodeJVMStats JVMPoolStats
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeJVMStats -> JVMPoolStats
nodeJVMStatsOldPool (\NodeJVMStats
x JVMPoolStats
y -> NodeJVMStats
x {nodeJVMStatsOldPool = y})
nodeJVMStatsSurvivorPoolLens :: Lens' NodeJVMStats JVMPoolStats
nodeJVMStatsSurvivorPoolLens :: Lens' NodeJVMStats JVMPoolStats
nodeJVMStatsSurvivorPoolLens = (NodeJVMStats -> JVMPoolStats)
-> (NodeJVMStats -> JVMPoolStats -> NodeJVMStats)
-> Lens' NodeJVMStats JVMPoolStats
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeJVMStats -> JVMPoolStats
nodeJVMStatsSurvivorPool (\NodeJVMStats
x JVMPoolStats
y -> NodeJVMStats
x {nodeJVMStatsSurvivorPool = y})
nodeJVMStatsYoungPoolLens :: Lens' NodeJVMStats JVMPoolStats
nodeJVMStatsYoungPoolLens :: Lens' NodeJVMStats JVMPoolStats
nodeJVMStatsYoungPoolLens = (NodeJVMStats -> JVMPoolStats)
-> (NodeJVMStats -> JVMPoolStats -> NodeJVMStats)
-> Lens' NodeJVMStats JVMPoolStats
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeJVMStats -> JVMPoolStats
nodeJVMStatsYoungPool (\NodeJVMStats
x JVMPoolStats
y -> NodeJVMStats
x {nodeJVMStatsYoungPool = y})
nodeJVMStatsNonHeapCommittedLens :: Lens' NodeJVMStats Bytes
nodeJVMStatsNonHeapCommittedLens :: Lens' NodeJVMStats Bytes
nodeJVMStatsNonHeapCommittedLens = (NodeJVMStats -> Bytes)
-> (NodeJVMStats -> Bytes -> NodeJVMStats)
-> Lens' NodeJVMStats Bytes
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeJVMStats -> Bytes
nodeJVMStatsNonHeapCommitted (\NodeJVMStats
x Bytes
y -> NodeJVMStats
x {nodeJVMStatsNonHeapCommitted = y})
nodeJVMStatsNonHeapUsedLens :: Lens' NodeJVMStats Bytes
nodeJVMStatsNonHeapUsedLens :: Lens' NodeJVMStats Bytes
nodeJVMStatsNonHeapUsedLens = (NodeJVMStats -> Bytes)
-> (NodeJVMStats -> Bytes -> NodeJVMStats)
-> Lens' NodeJVMStats Bytes
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeJVMStats -> Bytes
nodeJVMStatsNonHeapUsed (\NodeJVMStats
x Bytes
y -> NodeJVMStats
x {nodeJVMStatsNonHeapUsed = y})
nodeJVMStatsHeapMaxLens :: Lens' NodeJVMStats Bytes
nodeJVMStatsHeapMaxLens :: Lens' NodeJVMStats Bytes
nodeJVMStatsHeapMaxLens = (NodeJVMStats -> Bytes)
-> (NodeJVMStats -> Bytes -> NodeJVMStats)
-> Lens' NodeJVMStats Bytes
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeJVMStats -> Bytes
nodeJVMStatsHeapMax (\NodeJVMStats
x Bytes
y -> NodeJVMStats
x {nodeJVMStatsHeapMax = y})
nodeJVMStatsHeapCommittedLens :: Lens' NodeJVMStats Bytes
nodeJVMStatsHeapCommittedLens :: Lens' NodeJVMStats Bytes
nodeJVMStatsHeapCommittedLens = (NodeJVMStats -> Bytes)
-> (NodeJVMStats -> Bytes -> NodeJVMStats)
-> Lens' NodeJVMStats Bytes
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeJVMStats -> Bytes
nodeJVMStatsHeapCommitted (\NodeJVMStats
x Bytes
y -> NodeJVMStats
x {nodeJVMStatsHeapCommitted = y})
nodeJVMStatsHeapUsedPercentLens :: Lens' NodeJVMStats Int
nodeJVMStatsHeapUsedPercentLens :: Lens' NodeJVMStats Int
nodeJVMStatsHeapUsedPercentLens = (NodeJVMStats -> Int)
-> (NodeJVMStats -> Int -> NodeJVMStats) -> Lens' NodeJVMStats Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeJVMStats -> Int
nodeJVMStatsHeapUsedPercent (\NodeJVMStats
x Int
y -> NodeJVMStats
x {nodeJVMStatsHeapUsedPercent = y})
nodeJVMStatsHeapUsedLens :: Lens' NodeJVMStats Bytes
nodeJVMStatsHeapUsedLens :: Lens' NodeJVMStats Bytes
nodeJVMStatsHeapUsedLens = (NodeJVMStats -> Bytes)
-> (NodeJVMStats -> Bytes -> NodeJVMStats)
-> Lens' NodeJVMStats Bytes
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeJVMStats -> Bytes
nodeJVMStatsHeapUsed (\NodeJVMStats
x Bytes
y -> NodeJVMStats
x {nodeJVMStatsHeapUsed = y})
nodeJVMStatsUptimeLens :: Lens' NodeJVMStats NominalDiffTime
nodeJVMStatsUptimeLens :: Lens' NodeJVMStats NominalDiffTime
nodeJVMStatsUptimeLens = (NodeJVMStats -> NominalDiffTime)
-> (NodeJVMStats -> NominalDiffTime -> NodeJVMStats)
-> Lens' NodeJVMStats NominalDiffTime
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeJVMStats -> NominalDiffTime
nodeJVMStatsUptime (\NodeJVMStats
x NominalDiffTime
y -> NodeJVMStats
x {nodeJVMStatsUptime = y})
nodeJVMStatsTimestampLens :: Lens' NodeJVMStats UTCTime
nodeJVMStatsTimestampLens :: Lens' NodeJVMStats UTCTime
nodeJVMStatsTimestampLens = (NodeJVMStats -> UTCTime)
-> (NodeJVMStats -> UTCTime -> NodeJVMStats)
-> Lens' NodeJVMStats UTCTime
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeJVMStats -> UTCTime
nodeJVMStatsTimestamp (\NodeJVMStats
x UTCTime
y -> NodeJVMStats
x {nodeJVMStatsTimestamp = y})
data JVMBufferPoolStats = JVMBufferPoolStats
{ JVMBufferPoolStats -> Bytes
jvmBufferPoolStatsTotalCapacity :: Bytes,
JVMBufferPoolStats -> Bytes
jvmBufferPoolStatsUsed :: Bytes,
JVMBufferPoolStats -> Int
jvmBufferPoolStatsCount :: Int
}
deriving stock (JVMBufferPoolStats -> JVMBufferPoolStats -> Bool
(JVMBufferPoolStats -> JVMBufferPoolStats -> Bool)
-> (JVMBufferPoolStats -> JVMBufferPoolStats -> Bool)
-> Eq JVMBufferPoolStats
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: JVMBufferPoolStats -> JVMBufferPoolStats -> Bool
== :: JVMBufferPoolStats -> JVMBufferPoolStats -> Bool
$c/= :: JVMBufferPoolStats -> JVMBufferPoolStats -> Bool
/= :: 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
$cshowsPrec :: Int -> JVMBufferPoolStats -> ShowS
showsPrec :: Int -> JVMBufferPoolStats -> ShowS
$cshow :: JVMBufferPoolStats -> String
show :: JVMBufferPoolStats -> String
$cshowList :: [JVMBufferPoolStats] -> ShowS
showList :: [JVMBufferPoolStats] -> ShowS
Show)
jvmBufferPoolStatsTotalCapacityLens :: Lens' JVMBufferPoolStats Bytes
jvmBufferPoolStatsTotalCapacityLens :: Lens' JVMBufferPoolStats Bytes
jvmBufferPoolStatsTotalCapacityLens = (JVMBufferPoolStats -> Bytes)
-> (JVMBufferPoolStats -> Bytes -> JVMBufferPoolStats)
-> Lens' JVMBufferPoolStats Bytes
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens JVMBufferPoolStats -> Bytes
jvmBufferPoolStatsTotalCapacity (\JVMBufferPoolStats
x Bytes
y -> JVMBufferPoolStats
x {jvmBufferPoolStatsTotalCapacity = y})
jvmBufferPoolStatsUsedLens :: Lens' JVMBufferPoolStats Bytes
jvmBufferPoolStatsUsedLens :: Lens' JVMBufferPoolStats Bytes
jvmBufferPoolStatsUsedLens = (JVMBufferPoolStats -> Bytes)
-> (JVMBufferPoolStats -> Bytes -> JVMBufferPoolStats)
-> Lens' JVMBufferPoolStats Bytes
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens JVMBufferPoolStats -> Bytes
jvmBufferPoolStatsUsed (\JVMBufferPoolStats
x Bytes
y -> JVMBufferPoolStats
x {jvmBufferPoolStatsUsed = y})
jvmBufferPoolStatsCountLens :: Lens' JVMBufferPoolStats Int
jvmBufferPoolStatsCountLens :: Lens' JVMBufferPoolStats Int
jvmBufferPoolStatsCountLens = (JVMBufferPoolStats -> Int)
-> (JVMBufferPoolStats -> Int -> JVMBufferPoolStats)
-> Lens' JVMBufferPoolStats Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens JVMBufferPoolStats -> Int
jvmBufferPoolStatsCount (\JVMBufferPoolStats
x Int
y -> JVMBufferPoolStats
x {jvmBufferPoolStatsCount = y})
data JVMGCStats = JVMGCStats
{ JVMGCStats -> NominalDiffTime
jvmGCStatsCollectionTime :: NominalDiffTime,
JVMGCStats -> Int
jvmGCStatsCollectionCount :: Int
}
deriving stock (JVMGCStats -> JVMGCStats -> Bool
(JVMGCStats -> JVMGCStats -> Bool)
-> (JVMGCStats -> JVMGCStats -> Bool) -> Eq JVMGCStats
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: JVMGCStats -> JVMGCStats -> Bool
== :: JVMGCStats -> JVMGCStats -> Bool
$c/= :: JVMGCStats -> JVMGCStats -> Bool
/= :: 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
$cshowsPrec :: Int -> JVMGCStats -> ShowS
showsPrec :: Int -> JVMGCStats -> ShowS
$cshow :: JVMGCStats -> String
show :: JVMGCStats -> String
$cshowList :: [JVMGCStats] -> ShowS
showList :: [JVMGCStats] -> ShowS
Show)
jvmGCStatsCollectionTimeLens :: Lens' JVMGCStats NominalDiffTime
jvmGCStatsCollectionTimeLens :: Lens' JVMGCStats NominalDiffTime
jvmGCStatsCollectionTimeLens = (JVMGCStats -> NominalDiffTime)
-> (JVMGCStats -> NominalDiffTime -> JVMGCStats)
-> Lens' JVMGCStats NominalDiffTime
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens JVMGCStats -> NominalDiffTime
jvmGCStatsCollectionTime (\JVMGCStats
x NominalDiffTime
y -> JVMGCStats
x {jvmGCStatsCollectionTime = y})
jvmGCStatsCollectionCountLens :: Lens' JVMGCStats Int
jvmGCStatsCollectionCountLens :: Lens' JVMGCStats Int
jvmGCStatsCollectionCountLens = (JVMGCStats -> Int)
-> (JVMGCStats -> Int -> JVMGCStats) -> Lens' JVMGCStats Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens JVMGCStats -> Int
jvmGCStatsCollectionCount (\JVMGCStats
x Int
y -> JVMGCStats
x {jvmGCStatsCollectionCount = y})
data JVMPoolStats = JVMPoolStats
{ JVMPoolStats -> Bytes
jvmPoolStatsPeakMax :: Bytes,
JVMPoolStats -> Bytes
jvmPoolStatsPeakUsed :: Bytes,
JVMPoolStats -> Bytes
jvmPoolStatsMax :: Bytes,
JVMPoolStats -> Bytes
jvmPoolStatsUsed :: Bytes
}
deriving stock (JVMPoolStats -> JVMPoolStats -> Bool
(JVMPoolStats -> JVMPoolStats -> Bool)
-> (JVMPoolStats -> JVMPoolStats -> Bool) -> Eq JVMPoolStats
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: JVMPoolStats -> JVMPoolStats -> Bool
== :: JVMPoolStats -> JVMPoolStats -> Bool
$c/= :: JVMPoolStats -> JVMPoolStats -> Bool
/= :: 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
$cshowsPrec :: Int -> JVMPoolStats -> ShowS
showsPrec :: Int -> JVMPoolStats -> ShowS
$cshow :: JVMPoolStats -> String
show :: JVMPoolStats -> String
$cshowList :: [JVMPoolStats] -> ShowS
showList :: [JVMPoolStats] -> ShowS
Show)
jvmPoolStatsPeakMaxLens :: Lens' JVMPoolStats Bytes
jvmPoolStatsPeakMaxLens :: Lens' JVMPoolStats Bytes
jvmPoolStatsPeakMaxLens = (JVMPoolStats -> Bytes)
-> (JVMPoolStats -> Bytes -> JVMPoolStats)
-> Lens' JVMPoolStats Bytes
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens JVMPoolStats -> Bytes
jvmPoolStatsPeakMax (\JVMPoolStats
x Bytes
y -> JVMPoolStats
x {jvmPoolStatsPeakMax = y})
jvmPoolStatsPeakUsedLens :: Lens' JVMPoolStats Bytes
jvmPoolStatsPeakUsedLens :: Lens' JVMPoolStats Bytes
jvmPoolStatsPeakUsedLens = (JVMPoolStats -> Bytes)
-> (JVMPoolStats -> Bytes -> JVMPoolStats)
-> Lens' JVMPoolStats Bytes
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens JVMPoolStats -> Bytes
jvmPoolStatsPeakUsed (\JVMPoolStats
x Bytes
y -> JVMPoolStats
x {jvmPoolStatsPeakUsed = y})
jvmPoolStatsMaxLens :: Lens' JVMPoolStats Bytes
jvmPoolStatsMaxLens :: Lens' JVMPoolStats Bytes
jvmPoolStatsMaxLens = (JVMPoolStats -> Bytes)
-> (JVMPoolStats -> Bytes -> JVMPoolStats)
-> Lens' JVMPoolStats Bytes
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens JVMPoolStats -> Bytes
jvmPoolStatsMax (\JVMPoolStats
x Bytes
y -> JVMPoolStats
x {jvmPoolStatsMax = y})
jvmPoolStatsUsedLens :: Lens' JVMPoolStats Bytes
jvmPoolStatsUsedLens :: Lens' JVMPoolStats Bytes
jvmPoolStatsUsedLens = (JVMPoolStats -> Bytes)
-> (JVMPoolStats -> Bytes -> JVMPoolStats)
-> Lens' JVMPoolStats Bytes
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens JVMPoolStats -> Bytes
jvmPoolStatsUsed (\JVMPoolStats
x Bytes
y -> JVMPoolStats
x {jvmPoolStatsUsed = y})
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 stock (NodeProcessStats -> NodeProcessStats -> Bool
(NodeProcessStats -> NodeProcessStats -> Bool)
-> (NodeProcessStats -> NodeProcessStats -> Bool)
-> Eq NodeProcessStats
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NodeProcessStats -> NodeProcessStats -> Bool
== :: NodeProcessStats -> NodeProcessStats -> Bool
$c/= :: NodeProcessStats -> NodeProcessStats -> Bool
/= :: 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
$cshowsPrec :: Int -> NodeProcessStats -> ShowS
showsPrec :: Int -> NodeProcessStats -> ShowS
$cshow :: NodeProcessStats -> String
show :: NodeProcessStats -> String
$cshowList :: [NodeProcessStats] -> ShowS
showList :: [NodeProcessStats] -> ShowS
Show)
nodeProcessStatsTimestampLens :: Lens' NodeProcessStats UTCTime
nodeProcessStatsTimestampLens :: Lens' NodeProcessStats UTCTime
nodeProcessStatsTimestampLens = (NodeProcessStats -> UTCTime)
-> (NodeProcessStats -> UTCTime -> NodeProcessStats)
-> Lens' NodeProcessStats UTCTime
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeProcessStats -> UTCTime
nodeProcessTimestamp (\NodeProcessStats
x UTCTime
y -> NodeProcessStats
x {nodeProcessTimestamp = y})
nodeProcessStatsOpenFDsLens :: Lens' NodeProcessStats Int
nodeProcessStatsOpenFDsLens :: Lens' NodeProcessStats Int
nodeProcessStatsOpenFDsLens = (NodeProcessStats -> Int)
-> (NodeProcessStats -> Int -> NodeProcessStats)
-> Lens' NodeProcessStats Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeProcessStats -> Int
nodeProcessOpenFDs (\NodeProcessStats
x Int
y -> NodeProcessStats
x {nodeProcessOpenFDs = y})
nodeProcessStatsMaxFDsLens :: Lens' NodeProcessStats Int
nodeProcessStatsMaxFDsLens :: Lens' NodeProcessStats Int
nodeProcessStatsMaxFDsLens = (NodeProcessStats -> Int)
-> (NodeProcessStats -> Int -> NodeProcessStats)
-> Lens' NodeProcessStats Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeProcessStats -> Int
nodeProcessMaxFDs (\NodeProcessStats
x Int
y -> NodeProcessStats
x {nodeProcessMaxFDs = y})
nodeProcessStatsCPUPercentLens :: Lens' NodeProcessStats Int
nodeProcessStatsCPUPercentLens :: Lens' NodeProcessStats Int
nodeProcessStatsCPUPercentLens = (NodeProcessStats -> Int)
-> (NodeProcessStats -> Int -> NodeProcessStats)
-> Lens' NodeProcessStats Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeProcessStats -> Int
nodeProcessCPUPercent (\NodeProcessStats
x Int
y -> NodeProcessStats
x {nodeProcessCPUPercent = y})
nodeProcessStatsCPUTotalLens :: Lens' NodeProcessStats NominalDiffTime
nodeProcessStatsCPUTotalLens :: Lens' NodeProcessStats NominalDiffTime
nodeProcessStatsCPUTotalLens = (NodeProcessStats -> NominalDiffTime)
-> (NodeProcessStats -> NominalDiffTime -> NodeProcessStats)
-> Lens' NodeProcessStats NominalDiffTime
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeProcessStats -> NominalDiffTime
nodeProcessCPUTotal (\NodeProcessStats
x NominalDiffTime
y -> NodeProcessStats
x {nodeProcessCPUTotal = y})
nodeProcessStatsMemTotalVirtualLens :: Lens' NodeProcessStats Bytes
nodeProcessStatsMemTotalVirtualLens :: Lens' NodeProcessStats Bytes
nodeProcessStatsMemTotalVirtualLens = (NodeProcessStats -> Bytes)
-> (NodeProcessStats -> Bytes -> NodeProcessStats)
-> Lens' NodeProcessStats Bytes
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeProcessStats -> Bytes
nodeProcessMemTotalVirtual (\NodeProcessStats
x Bytes
y -> NodeProcessStats
x {nodeProcessMemTotalVirtual = y})
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 stock (NodeOSStats -> NodeOSStats -> Bool
(NodeOSStats -> NodeOSStats -> Bool)
-> (NodeOSStats -> NodeOSStats -> Bool) -> Eq NodeOSStats
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NodeOSStats -> NodeOSStats -> Bool
== :: NodeOSStats -> NodeOSStats -> Bool
$c/= :: NodeOSStats -> NodeOSStats -> Bool
/= :: 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
$cshowsPrec :: Int -> NodeOSStats -> ShowS
showsPrec :: Int -> NodeOSStats -> ShowS
$cshow :: NodeOSStats -> String
show :: NodeOSStats -> String
$cshowList :: [NodeOSStats] -> ShowS
showList :: [NodeOSStats] -> ShowS
Show)
nodeOSStatsTimestampLens :: Lens' NodeOSStats UTCTime
nodeOSStatsTimestampLens :: Lens' NodeOSStats UTCTime
nodeOSStatsTimestampLens = (NodeOSStats -> UTCTime)
-> (NodeOSStats -> UTCTime -> NodeOSStats)
-> Lens' NodeOSStats UTCTime
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeOSStats -> UTCTime
nodeOSTimestamp (\NodeOSStats
x UTCTime
y -> NodeOSStats
x {nodeOSTimestamp = y})
nodeOSStatsCPUPercentLens :: Lens' NodeOSStats Int
nodeOSStatsCPUPercentLens :: Lens' NodeOSStats Int
nodeOSStatsCPUPercentLens = (NodeOSStats -> Int)
-> (NodeOSStats -> Int -> NodeOSStats) -> Lens' NodeOSStats Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeOSStats -> Int
nodeOSCPUPercent (\NodeOSStats
x Int
y -> NodeOSStats
x {nodeOSCPUPercent = y})
nodeOSStatsLoadLens :: Lens' NodeOSStats (Maybe LoadAvgs)
nodeOSStatsLoadLens :: Lens' NodeOSStats (Maybe LoadAvgs)
nodeOSStatsLoadLens = (NodeOSStats -> Maybe LoadAvgs)
-> (NodeOSStats -> Maybe LoadAvgs -> NodeOSStats)
-> Lens' NodeOSStats (Maybe LoadAvgs)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeOSStats -> Maybe LoadAvgs
nodeOSLoad (\NodeOSStats
x Maybe LoadAvgs
y -> NodeOSStats
x {nodeOSLoad = y})
nodeOSStatsMemTotalLens :: Lens' NodeOSStats Bytes
nodeOSStatsMemTotalLens :: Lens' NodeOSStats Bytes
nodeOSStatsMemTotalLens = (NodeOSStats -> Bytes)
-> (NodeOSStats -> Bytes -> NodeOSStats) -> Lens' NodeOSStats Bytes
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeOSStats -> Bytes
nodeOSMemTotal (\NodeOSStats
x Bytes
y -> NodeOSStats
x {nodeOSMemTotal = y})
nodeOSStatsMemFreeLens :: Lens' NodeOSStats Bytes
nodeOSStatsMemFreeLens :: Lens' NodeOSStats Bytes
nodeOSStatsMemFreeLens = (NodeOSStats -> Bytes)
-> (NodeOSStats -> Bytes -> NodeOSStats) -> Lens' NodeOSStats Bytes
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeOSStats -> Bytes
nodeOSMemFree (\NodeOSStats
x Bytes
y -> NodeOSStats
x {nodeOSMemFree = y})
nodeOSStatsMemFreePercentLens :: Lens' NodeOSStats Int
nodeOSStatsMemFreePercentLens :: Lens' NodeOSStats Int
nodeOSStatsMemFreePercentLens = (NodeOSStats -> Int)
-> (NodeOSStats -> Int -> NodeOSStats) -> Lens' NodeOSStats Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeOSStats -> Int
nodeOSMemFreePercent (\NodeOSStats
x Int
y -> NodeOSStats
x {nodeOSMemFreePercent = y})
nodeOSStatsMemUsedLens :: Lens' NodeOSStats Bytes
nodeOSStatsMemUsedLens :: Lens' NodeOSStats Bytes
nodeOSStatsMemUsedLens = (NodeOSStats -> Bytes)
-> (NodeOSStats -> Bytes -> NodeOSStats) -> Lens' NodeOSStats Bytes
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeOSStats -> Bytes
nodeOSMemUsed (\NodeOSStats
x Bytes
y -> NodeOSStats
x {nodeOSMemUsed = y})
nodeOSStatsMemUsedPercentLens :: Lens' NodeOSStats Int
nodeOSStatsMemUsedPercentLens :: Lens' NodeOSStats Int
nodeOSStatsMemUsedPercentLens = (NodeOSStats -> Int)
-> (NodeOSStats -> Int -> NodeOSStats) -> Lens' NodeOSStats Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeOSStats -> Int
nodeOSMemUsedPercent (\NodeOSStats
x Int
y -> NodeOSStats
x {nodeOSMemUsedPercent = y})
nodeOSStatsSwapTotalLens :: Lens' NodeOSStats Bytes
nodeOSStatsSwapTotalLens :: Lens' NodeOSStats Bytes
nodeOSStatsSwapTotalLens = (NodeOSStats -> Bytes)
-> (NodeOSStats -> Bytes -> NodeOSStats) -> Lens' NodeOSStats Bytes
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeOSStats -> Bytes
nodeOSSwapTotal (\NodeOSStats
x Bytes
y -> NodeOSStats
x {nodeOSSwapTotal = y})
nodeOSStatsSwapFreeLens :: Lens' NodeOSStats Bytes
nodeOSStatsSwapFreeLens :: Lens' NodeOSStats Bytes
nodeOSStatsSwapFreeLens = (NodeOSStats -> Bytes)
-> (NodeOSStats -> Bytes -> NodeOSStats) -> Lens' NodeOSStats Bytes
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeOSStats -> Bytes
nodeOSSwapFree (\NodeOSStats
x Bytes
y -> NodeOSStats
x {nodeOSSwapFree = y})
nodeOSStatsSwapUsedLens :: Lens' NodeOSStats Bytes
nodeOSStatsSwapUsedLens :: Lens' NodeOSStats Bytes
nodeOSStatsSwapUsedLens = (NodeOSStats -> Bytes)
-> (NodeOSStats -> Bytes -> NodeOSStats) -> Lens' NodeOSStats Bytes
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeOSStats -> Bytes
nodeOSSwapUsed (\NodeOSStats
x Bytes
y -> NodeOSStats
x {nodeOSSwapUsed = y})
data LoadAvgs = LoadAvgs
{ LoadAvgs -> Double
loadAvg1Min :: Double,
LoadAvgs -> Double
loadAvg5Min :: Double,
LoadAvgs -> Double
loadAvg15Min :: Double
}
deriving stock (LoadAvgs -> LoadAvgs -> Bool
(LoadAvgs -> LoadAvgs -> Bool)
-> (LoadAvgs -> LoadAvgs -> Bool) -> Eq LoadAvgs
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LoadAvgs -> LoadAvgs -> Bool
== :: LoadAvgs -> LoadAvgs -> Bool
$c/= :: LoadAvgs -> LoadAvgs -> Bool
/= :: 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
$cshowsPrec :: Int -> LoadAvgs -> ShowS
showsPrec :: Int -> LoadAvgs -> ShowS
$cshow :: LoadAvgs -> String
show :: LoadAvgs -> String
$cshowList :: [LoadAvgs] -> ShowS
showList :: [LoadAvgs] -> ShowS
Show)
loadAvgs1MinLens :: Lens' LoadAvgs Double
loadAvgs1MinLens :: Lens' LoadAvgs Double
loadAvgs1MinLens = (LoadAvgs -> Double)
-> (LoadAvgs -> Double -> LoadAvgs) -> Lens' LoadAvgs Double
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens LoadAvgs -> Double
loadAvg1Min (\LoadAvgs
x Double
y -> LoadAvgs
x {loadAvg1Min = y})
loadAvgs5MinLens :: Lens' LoadAvgs Double
loadAvgs5MinLens :: Lens' LoadAvgs Double
loadAvgs5MinLens = (LoadAvgs -> Double)
-> (LoadAvgs -> Double -> LoadAvgs) -> Lens' LoadAvgs Double
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens LoadAvgs -> Double
loadAvg5Min (\LoadAvgs
x Double
y -> LoadAvgs
x {loadAvg5Min = y})
loadAvgs15MinLens :: Lens' LoadAvgs Double
loadAvgs15MinLens :: Lens' LoadAvgs Double
loadAvgs15MinLens = (LoadAvgs -> Double)
-> (LoadAvgs -> Double -> LoadAvgs) -> Lens' LoadAvgs Double
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens LoadAvgs -> Double
loadAvg15Min (\LoadAvgs
x Double
y -> LoadAvgs
x {loadAvg15Min = y})
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 stock (NodeIndicesStats -> NodeIndicesStats -> Bool
(NodeIndicesStats -> NodeIndicesStats -> Bool)
-> (NodeIndicesStats -> NodeIndicesStats -> Bool)
-> Eq NodeIndicesStats
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NodeIndicesStats -> NodeIndicesStats -> Bool
== :: NodeIndicesStats -> NodeIndicesStats -> Bool
$c/= :: NodeIndicesStats -> NodeIndicesStats -> Bool
/= :: 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
$cshowsPrec :: Int -> NodeIndicesStats -> ShowS
showsPrec :: Int -> NodeIndicesStats -> ShowS
$cshow :: NodeIndicesStats -> String
show :: NodeIndicesStats -> String
$cshowList :: [NodeIndicesStats] -> ShowS
showList :: [NodeIndicesStats] -> ShowS
Show)
nodeIndicesStatsRecoveryThrottleTimeLens :: Lens' NodeIndicesStats (Maybe NominalDiffTime)
nodeIndicesStatsRecoveryThrottleTimeLens :: Lens' NodeIndicesStats (Maybe NominalDiffTime)
nodeIndicesStatsRecoveryThrottleTimeLens = (NodeIndicesStats -> Maybe NominalDiffTime)
-> (NodeIndicesStats -> Maybe NominalDiffTime -> NodeIndicesStats)
-> Lens' NodeIndicesStats (Maybe NominalDiffTime)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> Maybe NominalDiffTime
nodeIndicesStatsRecoveryThrottleTime (\NodeIndicesStats
x Maybe NominalDiffTime
y -> NodeIndicesStats
x {nodeIndicesStatsRecoveryThrottleTime = y})
nodeIndicesStatsRecoveryCurrentAsTargetLens :: Lens' NodeIndicesStats (Maybe Int)
nodeIndicesStatsRecoveryCurrentAsTargetLens :: Lens' NodeIndicesStats (Maybe Int)
nodeIndicesStatsRecoveryCurrentAsTargetLens = (NodeIndicesStats -> Maybe Int)
-> (NodeIndicesStats -> Maybe Int -> NodeIndicesStats)
-> Lens' NodeIndicesStats (Maybe Int)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> Maybe Int
nodeIndicesStatsRecoveryCurrentAsTarget (\NodeIndicesStats
x Maybe Int
y -> NodeIndicesStats
x {nodeIndicesStatsRecoveryCurrentAsTarget = y})
nodeIndicesStatsRecoveryCurrentAsSourceLens :: Lens' NodeIndicesStats (Maybe Int)
nodeIndicesStatsRecoveryCurrentAsSourceLens :: Lens' NodeIndicesStats (Maybe Int)
nodeIndicesStatsRecoveryCurrentAsSourceLens = (NodeIndicesStats -> Maybe Int)
-> (NodeIndicesStats -> Maybe Int -> NodeIndicesStats)
-> Lens' NodeIndicesStats (Maybe Int)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> Maybe Int
nodeIndicesStatsRecoveryCurrentAsSource (\NodeIndicesStats
x Maybe Int
y -> NodeIndicesStats
x {nodeIndicesStatsRecoveryCurrentAsSource = y})
nodeIndicesStatsQueryCacheMissesLens :: Lens' NodeIndicesStats (Maybe Int)
nodeIndicesStatsQueryCacheMissesLens :: Lens' NodeIndicesStats (Maybe Int)
nodeIndicesStatsQueryCacheMissesLens = (NodeIndicesStats -> Maybe Int)
-> (NodeIndicesStats -> Maybe Int -> NodeIndicesStats)
-> Lens' NodeIndicesStats (Maybe Int)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> Maybe Int
nodeIndicesStatsQueryCacheMisses (\NodeIndicesStats
x Maybe Int
y -> NodeIndicesStats
x {nodeIndicesStatsQueryCacheMisses = y})
nodeIndicesStatsQueryCacheHitsLens :: Lens' NodeIndicesStats (Maybe Int)
nodeIndicesStatsQueryCacheHitsLens :: Lens' NodeIndicesStats (Maybe Int)
nodeIndicesStatsQueryCacheHitsLens = (NodeIndicesStats -> Maybe Int)
-> (NodeIndicesStats -> Maybe Int -> NodeIndicesStats)
-> Lens' NodeIndicesStats (Maybe Int)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> Maybe Int
nodeIndicesStatsQueryCacheHits (\NodeIndicesStats
x Maybe Int
y -> NodeIndicesStats
x {nodeIndicesStatsQueryCacheHits = y})
nodeIndicesStatsQueryCacheEvictionsLens :: Lens' NodeIndicesStats (Maybe Int)
nodeIndicesStatsQueryCacheEvictionsLens :: Lens' NodeIndicesStats (Maybe Int)
nodeIndicesStatsQueryCacheEvictionsLens = (NodeIndicesStats -> Maybe Int)
-> (NodeIndicesStats -> Maybe Int -> NodeIndicesStats)
-> Lens' NodeIndicesStats (Maybe Int)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> Maybe Int
nodeIndicesStatsQueryCacheEvictions (\NodeIndicesStats
x Maybe Int
y -> NodeIndicesStats
x {nodeIndicesStatsQueryCacheEvictions = y})
nodeIndicesStatsQueryCacheSizeLens :: Lens' NodeIndicesStats (Maybe Bytes)
nodeIndicesStatsQueryCacheSizeLens :: Lens' NodeIndicesStats (Maybe Bytes)
nodeIndicesStatsQueryCacheSizeLens = (NodeIndicesStats -> Maybe Bytes)
-> (NodeIndicesStats -> Maybe Bytes -> NodeIndicesStats)
-> Lens' NodeIndicesStats (Maybe Bytes)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> Maybe Bytes
nodeIndicesStatsQueryCacheSize (\NodeIndicesStats
x Maybe Bytes
y -> NodeIndicesStats
x {nodeIndicesStatsQueryCacheSize = y})
nodeIndicesStatsSuggestCurrentLens :: Lens' NodeIndicesStats (Maybe Int)
nodeIndicesStatsSuggestCurrentLens :: Lens' NodeIndicesStats (Maybe Int)
nodeIndicesStatsSuggestCurrentLens = (NodeIndicesStats -> Maybe Int)
-> (NodeIndicesStats -> Maybe Int -> NodeIndicesStats)
-> Lens' NodeIndicesStats (Maybe Int)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> Maybe Int
nodeIndicesStatsSuggestCurrent (\NodeIndicesStats
x Maybe Int
y -> NodeIndicesStats
x {nodeIndicesStatsSuggestCurrent = y})
nodeIndicesStatsSuggestTimeLens :: Lens' NodeIndicesStats (Maybe NominalDiffTime)
nodeIndicesStatsSuggestTimeLens :: Lens' NodeIndicesStats (Maybe NominalDiffTime)
nodeIndicesStatsSuggestTimeLens = (NodeIndicesStats -> Maybe NominalDiffTime)
-> (NodeIndicesStats -> Maybe NominalDiffTime -> NodeIndicesStats)
-> Lens' NodeIndicesStats (Maybe NominalDiffTime)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> Maybe NominalDiffTime
nodeIndicesStatsSuggestTime (\NodeIndicesStats
x Maybe NominalDiffTime
y -> NodeIndicesStats
x {nodeIndicesStatsSuggestTime = y})
nodeIndicesStatsSuggestTotalLens :: Lens' NodeIndicesStats (Maybe Int)
nodeIndicesStatsSuggestTotalLens :: Lens' NodeIndicesStats (Maybe Int)
nodeIndicesStatsSuggestTotalLens = (NodeIndicesStats -> Maybe Int)
-> (NodeIndicesStats -> Maybe Int -> NodeIndicesStats)
-> Lens' NodeIndicesStats (Maybe Int)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> Maybe Int
nodeIndicesStatsSuggestTotal (\NodeIndicesStats
x Maybe Int
y -> NodeIndicesStats
x {nodeIndicesStatsSuggestTotal = y})
nodeIndicesStatsTranslogSizeLens :: Lens' NodeIndicesStats Bytes
nodeIndicesStatsTranslogSizeLens :: Lens' NodeIndicesStats Bytes
nodeIndicesStatsTranslogSizeLens = (NodeIndicesStats -> Bytes)
-> (NodeIndicesStats -> Bytes -> NodeIndicesStats)
-> Lens' NodeIndicesStats Bytes
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> Bytes
nodeIndicesStatsTranslogSize (\NodeIndicesStats
x Bytes
y -> NodeIndicesStats
x {nodeIndicesStatsTranslogSize = y})
nodeIndicesStatsTranslogOpsLens :: Lens' NodeIndicesStats Int
nodeIndicesStatsTranslogOpsLens :: Lens' NodeIndicesStats Int
nodeIndicesStatsTranslogOpsLens = (NodeIndicesStats -> Int)
-> (NodeIndicesStats -> Int -> NodeIndicesStats)
-> Lens' NodeIndicesStats Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> Int
nodeIndicesStatsTranslogOps (\NodeIndicesStats
x Int
y -> NodeIndicesStats
x {nodeIndicesStatsTranslogOps = y})
nodeIndicesStatsSegFixedBitSetMemoryLens :: Lens' NodeIndicesStats (Maybe Bytes)
nodeIndicesStatsSegFixedBitSetMemoryLens :: Lens' NodeIndicesStats (Maybe Bytes)
nodeIndicesStatsSegFixedBitSetMemoryLens = (NodeIndicesStats -> Maybe Bytes)
-> (NodeIndicesStats -> Maybe Bytes -> NodeIndicesStats)
-> Lens' NodeIndicesStats (Maybe Bytes)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> Maybe Bytes
nodeIndicesStatsSegFixedBitSetMemory (\NodeIndicesStats
x Maybe Bytes
y -> NodeIndicesStats
x {nodeIndicesStatsSegFixedBitSetMemory = y})
nodeIndicesStatsSegVersionMapMemoryLens :: Lens' NodeIndicesStats Bytes
nodeIndicesStatsSegVersionMapMemoryLens :: Lens' NodeIndicesStats Bytes
nodeIndicesStatsSegVersionMapMemoryLens = (NodeIndicesStats -> Bytes)
-> (NodeIndicesStats -> Bytes -> NodeIndicesStats)
-> Lens' NodeIndicesStats Bytes
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> Bytes
nodeIndicesStatsSegVersionMapMemory (\NodeIndicesStats
x Bytes
y -> NodeIndicesStats
x {nodeIndicesStatsSegVersionMapMemory = y})
nodeIndicesStatsSegIndexWriterMaxMemoryLens :: Lens' NodeIndicesStats (Maybe Bytes)
nodeIndicesStatsSegIndexWriterMaxMemoryLens :: Lens' NodeIndicesStats (Maybe Bytes)
nodeIndicesStatsSegIndexWriterMaxMemoryLens = (NodeIndicesStats -> Maybe Bytes)
-> (NodeIndicesStats -> Maybe Bytes -> NodeIndicesStats)
-> Lens' NodeIndicesStats (Maybe Bytes)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> Maybe Bytes
nodeIndicesStatsSegIndexWriterMaxMemory (\NodeIndicesStats
x Maybe Bytes
y -> NodeIndicesStats
x {nodeIndicesStatsSegIndexWriterMaxMemory = y})
nodeIndicesStatsSegIndexWriterMemoryLens :: Lens' NodeIndicesStats Bytes
nodeIndicesStatsSegIndexWriterMemoryLens :: Lens' NodeIndicesStats Bytes
nodeIndicesStatsSegIndexWriterMemoryLens = (NodeIndicesStats -> Bytes)
-> (NodeIndicesStats -> Bytes -> NodeIndicesStats)
-> Lens' NodeIndicesStats Bytes
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> Bytes
nodeIndicesStatsSegIndexWriterMemory (\NodeIndicesStats
x Bytes
y -> NodeIndicesStats
x {nodeIndicesStatsSegIndexWriterMemory = y})
nodeIndicesStatsSegMemoryLens :: Lens' NodeIndicesStats Bytes
nodeIndicesStatsSegMemoryLens :: Lens' NodeIndicesStats Bytes
nodeIndicesStatsSegMemoryLens = (NodeIndicesStats -> Bytes)
-> (NodeIndicesStats -> Bytes -> NodeIndicesStats)
-> Lens' NodeIndicesStats Bytes
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> Bytes
nodeIndicesStatsSegMemory (\NodeIndicesStats
x Bytes
y -> NodeIndicesStats
x {nodeIndicesStatsSegMemory = y})
nodeIndicesStatsSegCountLens :: Lens' NodeIndicesStats Int
nodeIndicesStatsSegCountLens :: Lens' NodeIndicesStats Int
nodeIndicesStatsSegCountLens = (NodeIndicesStats -> Int)
-> (NodeIndicesStats -> Int -> NodeIndicesStats)
-> Lens' NodeIndicesStats Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> Int
nodeIndicesStatsSegCount (\NodeIndicesStats
x Int
y -> NodeIndicesStats
x {nodeIndicesStatsSegCount = y})
nodeIndicesStatsCompletionSizeLens :: Lens' NodeIndicesStats Bytes
nodeIndicesStatsCompletionSizeLens :: Lens' NodeIndicesStats Bytes
nodeIndicesStatsCompletionSizeLens = (NodeIndicesStats -> Bytes)
-> (NodeIndicesStats -> Bytes -> NodeIndicesStats)
-> Lens' NodeIndicesStats Bytes
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> Bytes
nodeIndicesStatsCompletionSize (\NodeIndicesStats
x Bytes
y -> NodeIndicesStats
x {nodeIndicesStatsCompletionSize = y})
nodeIndicesStatsPercolateQueriesLens :: Lens' NodeIndicesStats (Maybe Int)
nodeIndicesStatsPercolateQueriesLens :: Lens' NodeIndicesStats (Maybe Int)
nodeIndicesStatsPercolateQueriesLens = (NodeIndicesStats -> Maybe Int)
-> (NodeIndicesStats -> Maybe Int -> NodeIndicesStats)
-> Lens' NodeIndicesStats (Maybe Int)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> Maybe Int
nodeIndicesStatsPercolateQueries (\NodeIndicesStats
x Maybe Int
y -> NodeIndicesStats
x {nodeIndicesStatsPercolateQueries = y})
nodeIndicesStatsPercolateMemoryLens :: Lens' NodeIndicesStats (Maybe Bytes)
nodeIndicesStatsPercolateMemoryLens :: Lens' NodeIndicesStats (Maybe Bytes)
nodeIndicesStatsPercolateMemoryLens = (NodeIndicesStats -> Maybe Bytes)
-> (NodeIndicesStats -> Maybe Bytes -> NodeIndicesStats)
-> Lens' NodeIndicesStats (Maybe Bytes)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> Maybe Bytes
nodeIndicesStatsPercolateMemory (\NodeIndicesStats
x Maybe Bytes
y -> NodeIndicesStats
x {nodeIndicesStatsPercolateMemory = y})
nodeIndicesStatsPercolateCurrentLens :: Lens' NodeIndicesStats (Maybe Int)
nodeIndicesStatsPercolateCurrentLens :: Lens' NodeIndicesStats (Maybe Int)
nodeIndicesStatsPercolateCurrentLens = (NodeIndicesStats -> Maybe Int)
-> (NodeIndicesStats -> Maybe Int -> NodeIndicesStats)
-> Lens' NodeIndicesStats (Maybe Int)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> Maybe Int
nodeIndicesStatsPercolateCurrent (\NodeIndicesStats
x Maybe Int
y -> NodeIndicesStats
x {nodeIndicesStatsPercolateCurrent = y})
nodeIndicesStatsPercolateTimeLens :: Lens' NodeIndicesStats (Maybe NominalDiffTime)
nodeIndicesStatsPercolateTimeLens :: Lens' NodeIndicesStats (Maybe NominalDiffTime)
nodeIndicesStatsPercolateTimeLens = (NodeIndicesStats -> Maybe NominalDiffTime)
-> (NodeIndicesStats -> Maybe NominalDiffTime -> NodeIndicesStats)
-> Lens' NodeIndicesStats (Maybe NominalDiffTime)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> Maybe NominalDiffTime
nodeIndicesStatsPercolateTime (\NodeIndicesStats
x Maybe NominalDiffTime
y -> NodeIndicesStats
x {nodeIndicesStatsPercolateTime = y})
nodeIndicesStatsPercolateTotalLens :: Lens' NodeIndicesStats (Maybe Int)
nodeIndicesStatsPercolateTotalLens :: Lens' NodeIndicesStats (Maybe Int)
nodeIndicesStatsPercolateTotalLens = (NodeIndicesStats -> Maybe Int)
-> (NodeIndicesStats -> Maybe Int -> NodeIndicesStats)
-> Lens' NodeIndicesStats (Maybe Int)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> Maybe Int
nodeIndicesStatsPercolateTotal (\NodeIndicesStats
x Maybe Int
y -> NodeIndicesStats
x {nodeIndicesStatsPercolateTotal = y})
nodeIndicesStatsFieldDataEvictionsLens :: Lens' NodeIndicesStats Int
nodeIndicesStatsFieldDataEvictionsLens :: Lens' NodeIndicesStats Int
nodeIndicesStatsFieldDataEvictionsLens = (NodeIndicesStats -> Int)
-> (NodeIndicesStats -> Int -> NodeIndicesStats)
-> Lens' NodeIndicesStats Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> Int
nodeIndicesStatsFieldDataEvictions (\NodeIndicesStats
x Int
y -> NodeIndicesStats
x {nodeIndicesStatsFieldDataEvictions = y})
nodeIndicesStatsFieldDataMemoryLens :: Lens' NodeIndicesStats Bytes
nodeIndicesStatsFieldDataMemoryLens :: Lens' NodeIndicesStats Bytes
nodeIndicesStatsFieldDataMemoryLens = (NodeIndicesStats -> Bytes)
-> (NodeIndicesStats -> Bytes -> NodeIndicesStats)
-> Lens' NodeIndicesStats Bytes
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> Bytes
nodeIndicesStatsFieldDataMemory (\NodeIndicesStats
x Bytes
y -> NodeIndicesStats
x {nodeIndicesStatsFieldDataMemory = y})
nodeIndicesStatsWarmerTotalTimeLens :: Lens' NodeIndicesStats NominalDiffTime
nodeIndicesStatsWarmerTotalTimeLens :: Lens' NodeIndicesStats NominalDiffTime
nodeIndicesStatsWarmerTotalTimeLens = (NodeIndicesStats -> NominalDiffTime)
-> (NodeIndicesStats -> NominalDiffTime -> NodeIndicesStats)
-> Lens' NodeIndicesStats NominalDiffTime
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> NominalDiffTime
nodeIndicesStatsWarmerTotalTime (\NodeIndicesStats
x NominalDiffTime
y -> NodeIndicesStats
x {nodeIndicesStatsWarmerTotalTime = y})
nodeIndicesStatsWarmerTotalLens :: Lens' NodeIndicesStats Int
nodeIndicesStatsWarmerTotalLens :: Lens' NodeIndicesStats Int
nodeIndicesStatsWarmerTotalLens = (NodeIndicesStats -> Int)
-> (NodeIndicesStats -> Int -> NodeIndicesStats)
-> Lens' NodeIndicesStats Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> Int
nodeIndicesStatsWarmerTotal (\NodeIndicesStats
x Int
y -> NodeIndicesStats
x {nodeIndicesStatsWarmerTotal = y})
nodeIndicesStatsWarmerCurrentLens :: Lens' NodeIndicesStats Int
nodeIndicesStatsWarmerCurrentLens :: Lens' NodeIndicesStats Int
nodeIndicesStatsWarmerCurrentLens = (NodeIndicesStats -> Int)
-> (NodeIndicesStats -> Int -> NodeIndicesStats)
-> Lens' NodeIndicesStats Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> Int
nodeIndicesStatsWarmerCurrent (\NodeIndicesStats
x Int
y -> NodeIndicesStats
x {nodeIndicesStatsWarmerCurrent = y})
nodeIndicesStatsFlushTotalTimeLens :: Lens' NodeIndicesStats NominalDiffTime
nodeIndicesStatsFlushTotalTimeLens :: Lens' NodeIndicesStats NominalDiffTime
nodeIndicesStatsFlushTotalTimeLens = (NodeIndicesStats -> NominalDiffTime)
-> (NodeIndicesStats -> NominalDiffTime -> NodeIndicesStats)
-> Lens' NodeIndicesStats NominalDiffTime
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> NominalDiffTime
nodeIndicesStatsFlushTotalTime (\NodeIndicesStats
x NominalDiffTime
y -> NodeIndicesStats
x {nodeIndicesStatsFlushTotalTime = y})
nodeIndicesStatsFlushTotalLens :: Lens' NodeIndicesStats Int
nodeIndicesStatsFlushTotalLens :: Lens' NodeIndicesStats Int
nodeIndicesStatsFlushTotalLens = (NodeIndicesStats -> Int)
-> (NodeIndicesStats -> Int -> NodeIndicesStats)
-> Lens' NodeIndicesStats Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> Int
nodeIndicesStatsFlushTotal (\NodeIndicesStats
x Int
y -> NodeIndicesStats
x {nodeIndicesStatsFlushTotal = y})
nodeIndicesStatsRefreshTotalTimeLens :: Lens' NodeIndicesStats NominalDiffTime
nodeIndicesStatsRefreshTotalTimeLens :: Lens' NodeIndicesStats NominalDiffTime
nodeIndicesStatsRefreshTotalTimeLens = (NodeIndicesStats -> NominalDiffTime)
-> (NodeIndicesStats -> NominalDiffTime -> NodeIndicesStats)
-> Lens' NodeIndicesStats NominalDiffTime
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> NominalDiffTime
nodeIndicesStatsRefreshTotalTime (\NodeIndicesStats
x NominalDiffTime
y -> NodeIndicesStats
x {nodeIndicesStatsRefreshTotalTime = y})
nodeIndicesStatsRefreshTotalLens :: Lens' NodeIndicesStats Int
nodeIndicesStatsRefreshTotalLens :: Lens' NodeIndicesStats Int
nodeIndicesStatsRefreshTotalLens = (NodeIndicesStats -> Int)
-> (NodeIndicesStats -> Int -> NodeIndicesStats)
-> Lens' NodeIndicesStats Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> Int
nodeIndicesStatsRefreshTotal (\NodeIndicesStats
x Int
y -> NodeIndicesStats
x {nodeIndicesStatsRefreshTotal = y})
nodeIndicesStatsMergesTotalSizeLens :: Lens' NodeIndicesStats Bytes
nodeIndicesStatsMergesTotalSizeLens :: Lens' NodeIndicesStats Bytes
nodeIndicesStatsMergesTotalSizeLens = (NodeIndicesStats -> Bytes)
-> (NodeIndicesStats -> Bytes -> NodeIndicesStats)
-> Lens' NodeIndicesStats Bytes
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> Bytes
nodeIndicesStatsMergesTotalSize (\NodeIndicesStats
x Bytes
y -> NodeIndicesStats
x {nodeIndicesStatsMergesTotalSize = y})
nodeIndicesStatsMergesTotalDocsLens :: Lens' NodeIndicesStats Int
nodeIndicesStatsMergesTotalDocsLens :: Lens' NodeIndicesStats Int
nodeIndicesStatsMergesTotalDocsLens = (NodeIndicesStats -> Int)
-> (NodeIndicesStats -> Int -> NodeIndicesStats)
-> Lens' NodeIndicesStats Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> Int
nodeIndicesStatsMergesTotalDocs (\NodeIndicesStats
x Int
y -> NodeIndicesStats
x {nodeIndicesStatsMergesTotalDocs = y})
nodeIndicesStatsMergesTotalTimeLens :: Lens' NodeIndicesStats NominalDiffTime
nodeIndicesStatsMergesTotalTimeLens :: Lens' NodeIndicesStats NominalDiffTime
nodeIndicesStatsMergesTotalTimeLens = (NodeIndicesStats -> NominalDiffTime)
-> (NodeIndicesStats -> NominalDiffTime -> NodeIndicesStats)
-> Lens' NodeIndicesStats NominalDiffTime
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> NominalDiffTime
nodeIndicesStatsMergesTotalTime (\NodeIndicesStats
x NominalDiffTime
y -> NodeIndicesStats
x {nodeIndicesStatsMergesTotalTime = y})
nodeIndicesStatsMergesTotalLens :: Lens' NodeIndicesStats Int
nodeIndicesStatsMergesTotalLens :: Lens' NodeIndicesStats Int
nodeIndicesStatsMergesTotalLens = (NodeIndicesStats -> Int)
-> (NodeIndicesStats -> Int -> NodeIndicesStats)
-> Lens' NodeIndicesStats Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> Int
nodeIndicesStatsMergesTotal (\NodeIndicesStats
x Int
y -> NodeIndicesStats
x {nodeIndicesStatsMergesTotal = y})
nodeIndicesStatsMergesCurrentSizeLens :: Lens' NodeIndicesStats Bytes
nodeIndicesStatsMergesCurrentSizeLens :: Lens' NodeIndicesStats Bytes
nodeIndicesStatsMergesCurrentSizeLens = (NodeIndicesStats -> Bytes)
-> (NodeIndicesStats -> Bytes -> NodeIndicesStats)
-> Lens' NodeIndicesStats Bytes
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> Bytes
nodeIndicesStatsMergesCurrentSize (\NodeIndicesStats
x Bytes
y -> NodeIndicesStats
x {nodeIndicesStatsMergesCurrentSize = y})
nodeIndicesStatsMergesCurrentDocsLens :: Lens' NodeIndicesStats Int
nodeIndicesStatsMergesCurrentDocsLens :: Lens' NodeIndicesStats Int
nodeIndicesStatsMergesCurrentDocsLens = (NodeIndicesStats -> Int)
-> (NodeIndicesStats -> Int -> NodeIndicesStats)
-> Lens' NodeIndicesStats Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> Int
nodeIndicesStatsMergesCurrentDocs (\NodeIndicesStats
x Int
y -> NodeIndicesStats
x {nodeIndicesStatsMergesCurrentDocs = y})
nodeIndicesStatsMergesCurrentLens :: Lens' NodeIndicesStats Int
nodeIndicesStatsMergesCurrentLens :: Lens' NodeIndicesStats Int
nodeIndicesStatsMergesCurrentLens = (NodeIndicesStats -> Int)
-> (NodeIndicesStats -> Int -> NodeIndicesStats)
-> Lens' NodeIndicesStats Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> Int
nodeIndicesStatsMergesCurrent (\NodeIndicesStats
x Int
y -> NodeIndicesStats
x {nodeIndicesStatsMergesCurrent = y})
nodeIndicesStatsSearchFetchCurrentLens :: Lens' NodeIndicesStats Int
nodeIndicesStatsSearchFetchCurrentLens :: Lens' NodeIndicesStats Int
nodeIndicesStatsSearchFetchCurrentLens = (NodeIndicesStats -> Int)
-> (NodeIndicesStats -> Int -> NodeIndicesStats)
-> Lens' NodeIndicesStats Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> Int
nodeIndicesStatsSearchFetchCurrent (\NodeIndicesStats
x Int
y -> NodeIndicesStats
x {nodeIndicesStatsSearchFetchCurrent = y})
nodeIndicesStatsSearchFetchTimeLens :: Lens' NodeIndicesStats NominalDiffTime
nodeIndicesStatsSearchFetchTimeLens :: Lens' NodeIndicesStats NominalDiffTime
nodeIndicesStatsSearchFetchTimeLens = (NodeIndicesStats -> NominalDiffTime)
-> (NodeIndicesStats -> NominalDiffTime -> NodeIndicesStats)
-> Lens' NodeIndicesStats NominalDiffTime
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> NominalDiffTime
nodeIndicesStatsSearchFetchTime (\NodeIndicesStats
x NominalDiffTime
y -> NodeIndicesStats
x {nodeIndicesStatsSearchFetchTime = y})
nodeIndicesStatsSearchFetchTotalLens :: Lens' NodeIndicesStats Int
nodeIndicesStatsSearchFetchTotalLens :: Lens' NodeIndicesStats Int
nodeIndicesStatsSearchFetchTotalLens = (NodeIndicesStats -> Int)
-> (NodeIndicesStats -> Int -> NodeIndicesStats)
-> Lens' NodeIndicesStats Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> Int
nodeIndicesStatsSearchFetchTotal (\NodeIndicesStats
x Int
y -> NodeIndicesStats
x {nodeIndicesStatsSearchFetchTotal = y})
nodeIndicesStatsSearchQueryCurrentLens :: Lens' NodeIndicesStats Int
nodeIndicesStatsSearchQueryCurrentLens :: Lens' NodeIndicesStats Int
nodeIndicesStatsSearchQueryCurrentLens = (NodeIndicesStats -> Int)
-> (NodeIndicesStats -> Int -> NodeIndicesStats)
-> Lens' NodeIndicesStats Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> Int
nodeIndicesStatsSearchQueryCurrent (\NodeIndicesStats
x Int
y -> NodeIndicesStats
x {nodeIndicesStatsSearchQueryCurrent = y})
nodeIndicesStatsSearchQueryTimeLens :: Lens' NodeIndicesStats NominalDiffTime
nodeIndicesStatsSearchQueryTimeLens :: Lens' NodeIndicesStats NominalDiffTime
nodeIndicesStatsSearchQueryTimeLens = (NodeIndicesStats -> NominalDiffTime)
-> (NodeIndicesStats -> NominalDiffTime -> NodeIndicesStats)
-> Lens' NodeIndicesStats NominalDiffTime
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> NominalDiffTime
nodeIndicesStatsSearchQueryTime (\NodeIndicesStats
x NominalDiffTime
y -> NodeIndicesStats
x {nodeIndicesStatsSearchQueryTime = y})
nodeIndicesStatsSearchQueryTotalLens :: Lens' NodeIndicesStats Int
nodeIndicesStatsSearchQueryTotalLens :: Lens' NodeIndicesStats Int
nodeIndicesStatsSearchQueryTotalLens = (NodeIndicesStats -> Int)
-> (NodeIndicesStats -> Int -> NodeIndicesStats)
-> Lens' NodeIndicesStats Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> Int
nodeIndicesStatsSearchQueryTotal (\NodeIndicesStats
x Int
y -> NodeIndicesStats
x {nodeIndicesStatsSearchQueryTotal = y})
nodeIndicesStatsSearchOpenContextsLens :: Lens' NodeIndicesStats Int
nodeIndicesStatsSearchOpenContextsLens :: Lens' NodeIndicesStats Int
nodeIndicesStatsSearchOpenContextsLens = (NodeIndicesStats -> Int)
-> (NodeIndicesStats -> Int -> NodeIndicesStats)
-> Lens' NodeIndicesStats Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> Int
nodeIndicesStatsSearchOpenContexts (\NodeIndicesStats
x Int
y -> NodeIndicesStats
x {nodeIndicesStatsSearchOpenContexts = y})
nodeIndicesStatsGetCurrentLens :: Lens' NodeIndicesStats Int
nodeIndicesStatsGetCurrentLens :: Lens' NodeIndicesStats Int
nodeIndicesStatsGetCurrentLens = (NodeIndicesStats -> Int)
-> (NodeIndicesStats -> Int -> NodeIndicesStats)
-> Lens' NodeIndicesStats Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> Int
nodeIndicesStatsGetCurrent (\NodeIndicesStats
x Int
y -> NodeIndicesStats
x {nodeIndicesStatsGetCurrent = y})
nodeIndicesStatsGetMissingTimeLens :: Lens' NodeIndicesStats NominalDiffTime
nodeIndicesStatsGetMissingTimeLens :: Lens' NodeIndicesStats NominalDiffTime
nodeIndicesStatsGetMissingTimeLens = (NodeIndicesStats -> NominalDiffTime)
-> (NodeIndicesStats -> NominalDiffTime -> NodeIndicesStats)
-> Lens' NodeIndicesStats NominalDiffTime
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> NominalDiffTime
nodeIndicesStatsGetMissingTime (\NodeIndicesStats
x NominalDiffTime
y -> NodeIndicesStats
x {nodeIndicesStatsGetMissingTime = y})
nodeIndicesStatsGetMissingTotalLens :: Lens' NodeIndicesStats Int
nodeIndicesStatsGetMissingTotalLens :: Lens' NodeIndicesStats Int
nodeIndicesStatsGetMissingTotalLens = (NodeIndicesStats -> Int)
-> (NodeIndicesStats -> Int -> NodeIndicesStats)
-> Lens' NodeIndicesStats Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> Int
nodeIndicesStatsGetMissingTotal (\NodeIndicesStats
x Int
y -> NodeIndicesStats
x {nodeIndicesStatsGetMissingTotal = y})
nodeIndicesStatsGetExistsTimeLens :: Lens' NodeIndicesStats NominalDiffTime
nodeIndicesStatsGetExistsTimeLens :: Lens' NodeIndicesStats NominalDiffTime
nodeIndicesStatsGetExistsTimeLens = (NodeIndicesStats -> NominalDiffTime)
-> (NodeIndicesStats -> NominalDiffTime -> NodeIndicesStats)
-> Lens' NodeIndicesStats NominalDiffTime
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> NominalDiffTime
nodeIndicesStatsGetExistsTime (\NodeIndicesStats
x NominalDiffTime
y -> NodeIndicesStats
x {nodeIndicesStatsGetExistsTime = y})
nodeIndicesStatsGetExistsTotalLens :: Lens' NodeIndicesStats Int
nodeIndicesStatsGetExistsTotalLens :: Lens' NodeIndicesStats Int
nodeIndicesStatsGetExistsTotalLens = (NodeIndicesStats -> Int)
-> (NodeIndicesStats -> Int -> NodeIndicesStats)
-> Lens' NodeIndicesStats Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> Int
nodeIndicesStatsGetExistsTotal (\NodeIndicesStats
x Int
y -> NodeIndicesStats
x {nodeIndicesStatsGetExistsTotal = y})
nodeIndicesStatsGetTimeLens :: Lens' NodeIndicesStats NominalDiffTime
nodeIndicesStatsGetTimeLens :: Lens' NodeIndicesStats NominalDiffTime
nodeIndicesStatsGetTimeLens = (NodeIndicesStats -> NominalDiffTime)
-> (NodeIndicesStats -> NominalDiffTime -> NodeIndicesStats)
-> Lens' NodeIndicesStats NominalDiffTime
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> NominalDiffTime
nodeIndicesStatsGetTime (\NodeIndicesStats
x NominalDiffTime
y -> NodeIndicesStats
x {nodeIndicesStatsGetTime = y})
nodeIndicesStatsGetTotalLens :: Lens' NodeIndicesStats Int
nodeIndicesStatsGetTotalLens :: Lens' NodeIndicesStats Int
nodeIndicesStatsGetTotalLens = (NodeIndicesStats -> Int)
-> (NodeIndicesStats -> Int -> NodeIndicesStats)
-> Lens' NodeIndicesStats Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> Int
nodeIndicesStatsGetTotal (\NodeIndicesStats
x Int
y -> NodeIndicesStats
x {nodeIndicesStatsGetTotal = y})
nodeIndicesStatsIndexingThrottleTimeLens :: Lens' NodeIndicesStats (Maybe NominalDiffTime)
nodeIndicesStatsIndexingThrottleTimeLens :: Lens' NodeIndicesStats (Maybe NominalDiffTime)
nodeIndicesStatsIndexingThrottleTimeLens = (NodeIndicesStats -> Maybe NominalDiffTime)
-> (NodeIndicesStats -> Maybe NominalDiffTime -> NodeIndicesStats)
-> Lens' NodeIndicesStats (Maybe NominalDiffTime)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> Maybe NominalDiffTime
nodeIndicesStatsIndexingThrottleTime (\NodeIndicesStats
x Maybe NominalDiffTime
y -> NodeIndicesStats
x {nodeIndicesStatsIndexingThrottleTime = y})
nodeIndicesStatsIndexingIsThrottledLens :: Lens' NodeIndicesStats (Maybe Bool)
nodeIndicesStatsIndexingIsThrottledLens :: Lens' NodeIndicesStats (Maybe Bool)
nodeIndicesStatsIndexingIsThrottledLens = (NodeIndicesStats -> Maybe Bool)
-> (NodeIndicesStats -> Maybe Bool -> NodeIndicesStats)
-> Lens' NodeIndicesStats (Maybe Bool)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> Maybe Bool
nodeIndicesStatsIndexingIsThrottled (\NodeIndicesStats
x Maybe Bool
y -> NodeIndicesStats
x {nodeIndicesStatsIndexingIsThrottled = y})
nodeIndicesStatsIndexingNoopUpdateTotalLens :: Lens' NodeIndicesStats (Maybe Int)
nodeIndicesStatsIndexingNoopUpdateTotalLens :: Lens' NodeIndicesStats (Maybe Int)
nodeIndicesStatsIndexingNoopUpdateTotalLens = (NodeIndicesStats -> Maybe Int)
-> (NodeIndicesStats -> Maybe Int -> NodeIndicesStats)
-> Lens' NodeIndicesStats (Maybe Int)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> Maybe Int
nodeIndicesStatsIndexingNoopUpdateTotal (\NodeIndicesStats
x Maybe Int
y -> NodeIndicesStats
x {nodeIndicesStatsIndexingNoopUpdateTotal = y})
nodeIndicesStatsIndexingDeleteCurrentLens :: Lens' NodeIndicesStats Int
nodeIndicesStatsIndexingDeleteCurrentLens :: Lens' NodeIndicesStats Int
nodeIndicesStatsIndexingDeleteCurrentLens = (NodeIndicesStats -> Int)
-> (NodeIndicesStats -> Int -> NodeIndicesStats)
-> Lens' NodeIndicesStats Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> Int
nodeIndicesStatsIndexingDeleteCurrent (\NodeIndicesStats
x Int
y -> NodeIndicesStats
x {nodeIndicesStatsIndexingDeleteCurrent = y})
nodeIndicesStatsIndexingDeleteTimeLens :: Lens' NodeIndicesStats NominalDiffTime
nodeIndicesStatsIndexingDeleteTimeLens :: Lens' NodeIndicesStats NominalDiffTime
nodeIndicesStatsIndexingDeleteTimeLens = (NodeIndicesStats -> NominalDiffTime)
-> (NodeIndicesStats -> NominalDiffTime -> NodeIndicesStats)
-> Lens' NodeIndicesStats NominalDiffTime
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> NominalDiffTime
nodeIndicesStatsIndexingDeleteTime (\NodeIndicesStats
x NominalDiffTime
y -> NodeIndicesStats
x {nodeIndicesStatsIndexingDeleteTime = y})
nodeIndicesStatsIndexingDeleteTotalLens :: Lens' NodeIndicesStats Int
nodeIndicesStatsIndexingDeleteTotalLens :: Lens' NodeIndicesStats Int
nodeIndicesStatsIndexingDeleteTotalLens = (NodeIndicesStats -> Int)
-> (NodeIndicesStats -> Int -> NodeIndicesStats)
-> Lens' NodeIndicesStats Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> Int
nodeIndicesStatsIndexingDeleteTotal (\NodeIndicesStats
x Int
y -> NodeIndicesStats
x {nodeIndicesStatsIndexingDeleteTotal = y})
nodeIndicesStatsIndexingIndexCurrentLens :: Lens' NodeIndicesStats Int
nodeIndicesStatsIndexingIndexCurrentLens :: Lens' NodeIndicesStats Int
nodeIndicesStatsIndexingIndexCurrentLens = (NodeIndicesStats -> Int)
-> (NodeIndicesStats -> Int -> NodeIndicesStats)
-> Lens' NodeIndicesStats Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> Int
nodeIndicesStatsIndexingIndexCurrent (\NodeIndicesStats
x Int
y -> NodeIndicesStats
x {nodeIndicesStatsIndexingIndexCurrent = y})
nodeIndicesStatsIndexingIndexTimeLens :: Lens' NodeIndicesStats NominalDiffTime
nodeIndicesStatsIndexingIndexTimeLens :: Lens' NodeIndicesStats NominalDiffTime
nodeIndicesStatsIndexingIndexTimeLens = (NodeIndicesStats -> NominalDiffTime)
-> (NodeIndicesStats -> NominalDiffTime -> NodeIndicesStats)
-> Lens' NodeIndicesStats NominalDiffTime
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> NominalDiffTime
nodeIndicesStatsIndexingIndexTime (\NodeIndicesStats
x NominalDiffTime
y -> NodeIndicesStats
x {nodeIndicesStatsIndexingIndexTime = y})
nodeIndicesStatsIndexingTotalLens :: Lens' NodeIndicesStats Int
nodeIndicesStatsIndexingTotalLens :: Lens' NodeIndicesStats Int
nodeIndicesStatsIndexingTotalLens = (NodeIndicesStats -> Int)
-> (NodeIndicesStats -> Int -> NodeIndicesStats)
-> Lens' NodeIndicesStats Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> Int
nodeIndicesStatsIndexingTotal (\NodeIndicesStats
x Int
y -> NodeIndicesStats
x {nodeIndicesStatsIndexingTotal = y})
nodeIndicesStatsStoreThrottleTimeLens :: Lens' NodeIndicesStats (Maybe NominalDiffTime)
nodeIndicesStatsStoreThrottleTimeLens :: Lens' NodeIndicesStats (Maybe NominalDiffTime)
nodeIndicesStatsStoreThrottleTimeLens = (NodeIndicesStats -> Maybe NominalDiffTime)
-> (NodeIndicesStats -> Maybe NominalDiffTime -> NodeIndicesStats)
-> Lens' NodeIndicesStats (Maybe NominalDiffTime)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> Maybe NominalDiffTime
nodeIndicesStatsStoreThrottleTime (\NodeIndicesStats
x Maybe NominalDiffTime
y -> NodeIndicesStats
x {nodeIndicesStatsStoreThrottleTime = y})
nodeIndicesStatsStoreSizeLens :: Lens' NodeIndicesStats Bytes
nodeIndicesStatsStoreSizeLens :: Lens' NodeIndicesStats Bytes
nodeIndicesStatsStoreSizeLens = (NodeIndicesStats -> Bytes)
-> (NodeIndicesStats -> Bytes -> NodeIndicesStats)
-> Lens' NodeIndicesStats Bytes
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> Bytes
nodeIndicesStatsStoreSize (\NodeIndicesStats
x Bytes
y -> NodeIndicesStats
x {nodeIndicesStatsStoreSize = y})
nodeIndicesStatsDocsDeletedLens :: Lens' NodeIndicesStats Int
nodeIndicesStatsDocsDeletedLens :: Lens' NodeIndicesStats Int
nodeIndicesStatsDocsDeletedLens = (NodeIndicesStats -> Int)
-> (NodeIndicesStats -> Int -> NodeIndicesStats)
-> Lens' NodeIndicesStats Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> Int
nodeIndicesStatsDocsDeleted (\NodeIndicesStats
x Int
y -> NodeIndicesStats
x {nodeIndicesStatsDocsDeleted = y})
nodeIndicesStatsDocsCountLens :: Lens' NodeIndicesStats Int
nodeIndicesStatsDocsCountLens :: Lens' NodeIndicesStats Int
nodeIndicesStatsDocsCountLens = (NodeIndicesStats -> Int)
-> (NodeIndicesStats -> Int -> NodeIndicesStats)
-> Lens' NodeIndicesStats Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeIndicesStats -> Int
nodeIndicesStatsDocsCount (\NodeIndicesStats
x Int
y -> NodeIndicesStats
x {nodeIndicesStatsDocsCount = y})
newtype EsAddress = EsAddress {EsAddress -> Text
esAddress :: Text}
deriving newtype (EsAddress -> EsAddress -> Bool
(EsAddress -> EsAddress -> Bool)
-> (EsAddress -> EsAddress -> Bool) -> Eq EsAddress
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EsAddress -> EsAddress -> Bool
== :: EsAddress -> EsAddress -> Bool
$c/= :: EsAddress -> EsAddress -> Bool
/= :: 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
$ccompare :: EsAddress -> EsAddress -> Ordering
compare :: EsAddress -> EsAddress -> Ordering
$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
>= :: EsAddress -> EsAddress -> Bool
$cmax :: EsAddress -> EsAddress -> EsAddress
max :: EsAddress -> EsAddress -> EsAddress
$cmin :: EsAddress -> EsAddress -> EsAddress
min :: EsAddress -> EsAddress -> 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
$cshowsPrec :: Int -> EsAddress -> ShowS
showsPrec :: Int -> EsAddress -> ShowS
$cshow :: EsAddress -> String
show :: EsAddress -> String
$cshowList :: [EsAddress] -> ShowS
showList :: [EsAddress] -> ShowS
Show, Maybe EsAddress
Value -> Parser [EsAddress]
Value -> Parser EsAddress
(Value -> Parser EsAddress)
-> (Value -> Parser [EsAddress])
-> Maybe EsAddress
-> FromJSON EsAddress
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser EsAddress
parseJSON :: Value -> Parser EsAddress
$cparseJSONList :: Value -> Parser [EsAddress]
parseJSONList :: Value -> Parser [EsAddress]
$comittedField :: Maybe EsAddress
omittedField :: Maybe EsAddress
FromJSON)
newtype BuildHash = BuildHash {BuildHash -> Text
buildHash :: Text}
deriving newtype (BuildHash -> BuildHash -> Bool
(BuildHash -> BuildHash -> Bool)
-> (BuildHash -> BuildHash -> Bool) -> Eq BuildHash
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BuildHash -> BuildHash -> Bool
== :: BuildHash -> BuildHash -> Bool
$c/= :: BuildHash -> BuildHash -> Bool
/= :: 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
$ccompare :: BuildHash -> BuildHash -> Ordering
compare :: BuildHash -> BuildHash -> Ordering
$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
>= :: BuildHash -> BuildHash -> Bool
$cmax :: BuildHash -> BuildHash -> BuildHash
max :: BuildHash -> BuildHash -> BuildHash
$cmin :: BuildHash -> BuildHash -> BuildHash
min :: BuildHash -> BuildHash -> 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
$cshowsPrec :: Int -> BuildHash -> ShowS
showsPrec :: Int -> BuildHash -> ShowS
$cshow :: BuildHash -> String
show :: BuildHash -> String
$cshowList :: [BuildHash] -> ShowS
showList :: [BuildHash] -> ShowS
Show, Maybe BuildHash
Value -> Parser [BuildHash]
Value -> Parser BuildHash
(Value -> Parser BuildHash)
-> (Value -> Parser [BuildHash])
-> Maybe BuildHash
-> FromJSON BuildHash
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser BuildHash
parseJSON :: Value -> Parser BuildHash
$cparseJSONList :: Value -> Parser [BuildHash]
parseJSONList :: Value -> Parser [BuildHash]
$comittedField :: Maybe BuildHash
omittedField :: Maybe BuildHash
FromJSON, [BuildHash] -> Value
[BuildHash] -> Encoding
BuildHash -> Bool
BuildHash -> Value
BuildHash -> Encoding
(BuildHash -> Value)
-> (BuildHash -> Encoding)
-> ([BuildHash] -> Value)
-> ([BuildHash] -> Encoding)
-> (BuildHash -> Bool)
-> ToJSON BuildHash
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: BuildHash -> Value
toJSON :: BuildHash -> Value
$ctoEncoding :: BuildHash -> Encoding
toEncoding :: BuildHash -> Encoding
$ctoJSONList :: [BuildHash] -> Value
toJSONList :: [BuildHash] -> Value
$ctoEncodingList :: [BuildHash] -> Encoding
toEncodingList :: [BuildHash] -> Encoding
$comitField :: BuildHash -> Bool
omitField :: BuildHash -> Bool
ToJSON)
newtype PluginName = PluginName {PluginName -> Text
pluginName :: Text}
deriving newtype (PluginName -> PluginName -> Bool
(PluginName -> PluginName -> Bool)
-> (PluginName -> PluginName -> Bool) -> Eq PluginName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PluginName -> PluginName -> Bool
== :: PluginName -> PluginName -> Bool
$c/= :: PluginName -> PluginName -> Bool
/= :: 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
$ccompare :: PluginName -> PluginName -> Ordering
compare :: PluginName -> PluginName -> Ordering
$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
>= :: PluginName -> PluginName -> Bool
$cmax :: PluginName -> PluginName -> PluginName
max :: PluginName -> PluginName -> PluginName
$cmin :: PluginName -> PluginName -> PluginName
min :: PluginName -> PluginName -> 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
$cshowsPrec :: Int -> PluginName -> ShowS
showsPrec :: Int -> PluginName -> ShowS
$cshow :: PluginName -> String
show :: PluginName -> String
$cshowList :: [PluginName] -> ShowS
showList :: [PluginName] -> ShowS
Show, Maybe PluginName
Value -> Parser [PluginName]
Value -> Parser PluginName
(Value -> Parser PluginName)
-> (Value -> Parser [PluginName])
-> Maybe PluginName
-> FromJSON PluginName
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser PluginName
parseJSON :: Value -> Parser PluginName
$cparseJSONList :: Value -> Parser [PluginName]
parseJSONList :: Value -> Parser [PluginName]
$comittedField :: Maybe PluginName
omittedField :: Maybe 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 stock (NodeInfo -> NodeInfo -> Bool
(NodeInfo -> NodeInfo -> Bool)
-> (NodeInfo -> NodeInfo -> Bool) -> Eq NodeInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NodeInfo -> NodeInfo -> Bool
== :: NodeInfo -> NodeInfo -> Bool
$c/= :: NodeInfo -> NodeInfo -> Bool
/= :: 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
$cshowsPrec :: Int -> NodeInfo -> ShowS
showsPrec :: Int -> NodeInfo -> ShowS
$cshow :: NodeInfo -> String
show :: NodeInfo -> String
$cshowList :: [NodeInfo] -> ShowS
showList :: [NodeInfo] -> ShowS
Show)
nodeInfoHTTPAddressLens :: Lens' NodeInfo (Maybe EsAddress)
nodeInfoHTTPAddressLens :: Lens' NodeInfo (Maybe EsAddress)
nodeInfoHTTPAddressLens = (NodeInfo -> Maybe EsAddress)
-> (NodeInfo -> Maybe EsAddress -> NodeInfo)
-> Lens' NodeInfo (Maybe EsAddress)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeInfo -> Maybe EsAddress
nodeInfoHTTPAddress (\NodeInfo
x Maybe EsAddress
y -> NodeInfo
x {nodeInfoHTTPAddress = y})
nodeInfoBuildLens :: Lens' NodeInfo BuildHash
nodeInfoBuildLens :: Lens' NodeInfo BuildHash
nodeInfoBuildLens = (NodeInfo -> BuildHash)
-> (NodeInfo -> BuildHash -> NodeInfo) -> Lens' NodeInfo BuildHash
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeInfo -> BuildHash
nodeInfoBuild (\NodeInfo
x BuildHash
y -> NodeInfo
x {nodeInfoBuild = y})
nodeInfoESVersionLens :: Lens' NodeInfo VersionNumber
nodeInfoESVersionLens :: Lens' NodeInfo VersionNumber
nodeInfoESVersionLens = (NodeInfo -> VersionNumber)
-> (NodeInfo -> VersionNumber -> NodeInfo)
-> Lens' NodeInfo VersionNumber
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeInfo -> VersionNumber
nodeInfoESVersion (\NodeInfo
x VersionNumber
y -> NodeInfo
x {nodeInfoESVersion = y})
nodeInfoIPLens :: Lens' NodeInfo Server
nodeInfoIPLens :: Lens' NodeInfo Server
nodeInfoIPLens = (NodeInfo -> Server)
-> (NodeInfo -> Server -> NodeInfo) -> Lens' NodeInfo Server
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeInfo -> Server
nodeInfoIP (\NodeInfo
x Server
y -> NodeInfo
x {nodeInfoIP = y})
nodeInfoHostLens :: Lens' NodeInfo Server
nodeInfoHostLens :: Lens' NodeInfo Server
nodeInfoHostLens = (NodeInfo -> Server)
-> (NodeInfo -> Server -> NodeInfo) -> Lens' NodeInfo Server
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeInfo -> Server
nodeInfoHost (\NodeInfo
x Server
y -> NodeInfo
x {nodeInfoHost = y})
nodeInfoTransportAddressLens :: Lens' NodeInfo EsAddress
nodeInfoTransportAddressLens :: Lens' NodeInfo EsAddress
nodeInfoTransportAddressLens = (NodeInfo -> EsAddress)
-> (NodeInfo -> EsAddress -> NodeInfo) -> Lens' NodeInfo EsAddress
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeInfo -> EsAddress
nodeInfoTransportAddress (\NodeInfo
x EsAddress
y -> NodeInfo
x {nodeInfoTransportAddress = y})
nodeInfoNameLens :: Lens' NodeInfo NodeName
nodeInfoNameLens :: Lens' NodeInfo NodeName
nodeInfoNameLens = (NodeInfo -> NodeName)
-> (NodeInfo -> NodeName -> NodeInfo) -> Lens' NodeInfo NodeName
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeInfo -> NodeName
nodeInfoName (\NodeInfo
x NodeName
y -> NodeInfo
x {nodeInfoName = y})
nodeInfoFullIdLens :: Lens' NodeInfo FullNodeId
nodeInfoFullIdLens :: Lens' NodeInfo FullNodeId
nodeInfoFullIdLens = (NodeInfo -> FullNodeId)
-> (NodeInfo -> FullNodeId -> NodeInfo)
-> Lens' NodeInfo FullNodeId
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeInfo -> FullNodeId
nodeInfoFullId (\NodeInfo
x FullNodeId
y -> NodeInfo
x {nodeInfoFullId = y})
nodeInfoPluginsLens :: Lens' NodeInfo [NodePluginInfo]
nodeInfoPluginsLens :: Lens' NodeInfo [NodePluginInfo]
nodeInfoPluginsLens = (NodeInfo -> [NodePluginInfo])
-> (NodeInfo -> [NodePluginInfo] -> NodeInfo)
-> Lens' NodeInfo [NodePluginInfo]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeInfo -> [NodePluginInfo]
nodeInfoPlugins (\NodeInfo
x [NodePluginInfo]
y -> NodeInfo
x {nodeInfoPlugins = y})
nodeInfoHTTPLens :: Lens' NodeInfo NodeHTTPInfo
nodeInfoHTTPLens :: Lens' NodeInfo NodeHTTPInfo
nodeInfoHTTPLens = (NodeInfo -> NodeHTTPInfo)
-> (NodeInfo -> NodeHTTPInfo -> NodeInfo)
-> Lens' NodeInfo NodeHTTPInfo
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeInfo -> NodeHTTPInfo
nodeInfoHTTP (\NodeInfo
x NodeHTTPInfo
y -> NodeInfo
x {nodeInfoHTTP = y})
nodeInfoTransportLens :: Lens' NodeInfo NodeTransportInfo
nodeInfoTransportLens :: Lens' NodeInfo NodeTransportInfo
nodeInfoTransportLens = (NodeInfo -> NodeTransportInfo)
-> (NodeInfo -> NodeTransportInfo -> NodeInfo)
-> Lens' NodeInfo NodeTransportInfo
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeInfo -> NodeTransportInfo
nodeInfoTransport (\NodeInfo
x NodeTransportInfo
y -> NodeInfo
x {nodeInfoTransport = y})
nodeInfoNetworkLens :: Lens' NodeInfo (Maybe NodeNetworkInfo)
nodeInfoNetworkLens :: Lens' NodeInfo (Maybe NodeNetworkInfo)
nodeInfoNetworkLens = (NodeInfo -> Maybe NodeNetworkInfo)
-> (NodeInfo -> Maybe NodeNetworkInfo -> NodeInfo)
-> Lens' NodeInfo (Maybe NodeNetworkInfo)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeInfo -> Maybe NodeNetworkInfo
nodeInfoNetwork (\NodeInfo
x Maybe NodeNetworkInfo
y -> NodeInfo
x {nodeInfoNetwork = y})
nodeInfoThreadPoolLens :: Lens' NodeInfo (Map Text NodeThreadPoolInfo)
nodeInfoThreadPoolLens :: Lens' NodeInfo (Map Text NodeThreadPoolInfo)
nodeInfoThreadPoolLens = (NodeInfo -> Map Text NodeThreadPoolInfo)
-> (NodeInfo -> Map Text NodeThreadPoolInfo -> NodeInfo)
-> Lens' NodeInfo (Map Text NodeThreadPoolInfo)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeInfo -> Map Text NodeThreadPoolInfo
nodeInfoThreadPool (\NodeInfo
x Map Text NodeThreadPoolInfo
y -> NodeInfo
x {nodeInfoThreadPool = y})
nodeInfoJVMLens :: Lens' NodeInfo NodeJVMInfo
nodeInfoJVMLens :: Lens' NodeInfo NodeJVMInfo
nodeInfoJVMLens = (NodeInfo -> NodeJVMInfo)
-> (NodeInfo -> NodeJVMInfo -> NodeInfo)
-> Lens' NodeInfo NodeJVMInfo
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeInfo -> NodeJVMInfo
nodeInfoJVM (\NodeInfo
x NodeJVMInfo
y -> NodeInfo
x {nodeInfoJVM = y})
nodeInfoProcessLens :: Lens' NodeInfo NodeProcessInfo
nodeInfoProcessLens :: Lens' NodeInfo NodeProcessInfo
nodeInfoProcessLens = (NodeInfo -> NodeProcessInfo)
-> (NodeInfo -> NodeProcessInfo -> NodeInfo)
-> Lens' NodeInfo NodeProcessInfo
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeInfo -> NodeProcessInfo
nodeInfoProcess (\NodeInfo
x NodeProcessInfo
y -> NodeInfo
x {nodeInfoProcess = y})
nodeInfoOSLens :: Lens' NodeInfo NodeOSInfo
nodeInfoOSLens :: Lens' NodeInfo NodeOSInfo
nodeInfoOSLens = (NodeInfo -> NodeOSInfo)
-> (NodeInfo -> NodeOSInfo -> NodeInfo)
-> Lens' NodeInfo NodeOSInfo
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeInfo -> NodeOSInfo
nodeInfoOS (\NodeInfo
x NodeOSInfo
y -> NodeInfo
x {nodeInfoOS = y})
nodeInfoSettingsLens :: Lens' NodeInfo Object
nodeInfoSettingsLens :: Lens' NodeInfo Object
nodeInfoSettingsLens = (NodeInfo -> Object)
-> (NodeInfo -> Object -> NodeInfo) -> Lens' NodeInfo Object
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeInfo -> Object
nodeInfoSettings (\NodeInfo
x Object
y -> NodeInfo
x {nodeInfoSettings = y})
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 stock (NodePluginInfo -> NodePluginInfo -> Bool
(NodePluginInfo -> NodePluginInfo -> Bool)
-> (NodePluginInfo -> NodePluginInfo -> Bool) -> Eq NodePluginInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NodePluginInfo -> NodePluginInfo -> Bool
== :: NodePluginInfo -> NodePluginInfo -> Bool
$c/= :: NodePluginInfo -> NodePluginInfo -> Bool
/= :: 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
$cshowsPrec :: Int -> NodePluginInfo -> ShowS
showsPrec :: Int -> NodePluginInfo -> ShowS
$cshow :: NodePluginInfo -> String
show :: NodePluginInfo -> String
$cshowList :: [NodePluginInfo] -> ShowS
showList :: [NodePluginInfo] -> ShowS
Show)
nodePluginSiteLens :: Lens' NodePluginInfo (Maybe Bool)
nodePluginSiteLens :: Lens' NodePluginInfo (Maybe Bool)
nodePluginSiteLens = (NodePluginInfo -> Maybe Bool)
-> (NodePluginInfo -> Maybe Bool -> NodePluginInfo)
-> Lens' NodePluginInfo (Maybe Bool)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodePluginInfo -> Maybe Bool
nodePluginSite (\NodePluginInfo
x Maybe Bool
y -> NodePluginInfo
x {nodePluginSite = y})
nodePluginInfoJVMLens :: Lens' NodePluginInfo (Maybe Bool)
nodePluginInfoJVMLens :: Lens' NodePluginInfo (Maybe Bool)
nodePluginInfoJVMLens = (NodePluginInfo -> Maybe Bool)
-> (NodePluginInfo -> Maybe Bool -> NodePluginInfo)
-> Lens' NodePluginInfo (Maybe Bool)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodePluginInfo -> Maybe Bool
nodePluginJVM (\NodePluginInfo
x Maybe Bool
y -> NodePluginInfo
x {nodePluginJVM = y})
nodePluginInfoDescriptionLens :: Lens' NodePluginInfo Text
nodePluginInfoDescriptionLens :: Lens' NodePluginInfo Text
nodePluginInfoDescriptionLens = (NodePluginInfo -> Text)
-> (NodePluginInfo -> Text -> NodePluginInfo)
-> Lens' NodePluginInfo Text
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodePluginInfo -> Text
nodePluginDescription (\NodePluginInfo
x Text
y -> NodePluginInfo
x {nodePluginDescription = y})
nodePluginInfoVersionLens :: Lens' NodePluginInfo (MaybeNA VersionNumber)
nodePluginInfoVersionLens :: Lens' NodePluginInfo (MaybeNA VersionNumber)
nodePluginInfoVersionLens = (NodePluginInfo -> MaybeNA VersionNumber)
-> (NodePluginInfo -> MaybeNA VersionNumber -> NodePluginInfo)
-> Lens' NodePluginInfo (MaybeNA VersionNumber)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodePluginInfo -> MaybeNA VersionNumber
nodePluginVersion (\NodePluginInfo
x MaybeNA VersionNumber
y -> NodePluginInfo
x {nodePluginVersion = y})
nodePluginInfoNameLens :: Lens' NodePluginInfo PluginName
nodePluginInfoNameLens :: Lens' NodePluginInfo PluginName
nodePluginInfoNameLens = (NodePluginInfo -> PluginName)
-> (NodePluginInfo -> PluginName -> NodePluginInfo)
-> Lens' NodePluginInfo PluginName
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodePluginInfo -> PluginName
nodePluginName (\NodePluginInfo
x PluginName
y -> NodePluginInfo
x {nodePluginName = y})
data NodeHTTPInfo = NodeHTTPInfo
{ NodeHTTPInfo -> Bytes
nodeHTTPMaxContentLength :: Bytes,
NodeHTTPInfo -> EsAddress
nodeHTTPpublishAddress :: EsAddress,
NodeHTTPInfo -> [EsAddress]
nodeHTTPbound_address :: [EsAddress]
}
deriving stock (NodeHTTPInfo -> NodeHTTPInfo -> Bool
(NodeHTTPInfo -> NodeHTTPInfo -> Bool)
-> (NodeHTTPInfo -> NodeHTTPInfo -> Bool) -> Eq NodeHTTPInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NodeHTTPInfo -> NodeHTTPInfo -> Bool
== :: NodeHTTPInfo -> NodeHTTPInfo -> Bool
$c/= :: NodeHTTPInfo -> NodeHTTPInfo -> Bool
/= :: 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
$cshowsPrec :: Int -> NodeHTTPInfo -> ShowS
showsPrec :: Int -> NodeHTTPInfo -> ShowS
$cshow :: NodeHTTPInfo -> String
show :: NodeHTTPInfo -> String
$cshowList :: [NodeHTTPInfo] -> ShowS
showList :: [NodeHTTPInfo] -> ShowS
Show)
nodeHTTPInfoMaxContentLengthLens :: Lens' NodeHTTPInfo Bytes
nodeHTTPInfoMaxContentLengthLens :: Lens' NodeHTTPInfo Bytes
nodeHTTPInfoMaxContentLengthLens = (NodeHTTPInfo -> Bytes)
-> (NodeHTTPInfo -> Bytes -> NodeHTTPInfo)
-> Lens' NodeHTTPInfo Bytes
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeHTTPInfo -> Bytes
nodeHTTPMaxContentLength (\NodeHTTPInfo
x Bytes
y -> NodeHTTPInfo
x {nodeHTTPMaxContentLength = y})
nodeHTTPInfopublishAddressLens :: Lens' NodeHTTPInfo EsAddress
nodeHTTPInfopublishAddressLens :: Lens' NodeHTTPInfo EsAddress
nodeHTTPInfopublishAddressLens = (NodeHTTPInfo -> EsAddress)
-> (NodeHTTPInfo -> EsAddress -> NodeHTTPInfo)
-> Lens' NodeHTTPInfo EsAddress
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeHTTPInfo -> EsAddress
nodeHTTPpublishAddress (\NodeHTTPInfo
x EsAddress
y -> NodeHTTPInfo
x {nodeHTTPpublishAddress = y})
nodeHTTPInfoBoundAddressesLens :: Lens' NodeHTTPInfo [EsAddress]
nodeHTTPInfoBoundAddressesLens :: Lens' NodeHTTPInfo [EsAddress]
nodeHTTPInfoBoundAddressesLens = (NodeHTTPInfo -> [EsAddress])
-> (NodeHTTPInfo -> [EsAddress] -> NodeHTTPInfo)
-> Lens' NodeHTTPInfo [EsAddress]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeHTTPInfo -> [EsAddress]
nodeHTTPbound_address (\NodeHTTPInfo
x [EsAddress]
y -> NodeHTTPInfo
x {nodeHTTPbound_address = y})
data NodeTransportInfo = NodeTransportInfo
{ NodeTransportInfo -> [BoundTransportAddress]
nodeTransportProfiles :: [BoundTransportAddress],
NodeTransportInfo -> EsAddress
nodeTransportPublishAddress :: EsAddress,
NodeTransportInfo -> [EsAddress]
nodeTransportBoundAddress :: [EsAddress]
}
deriving stock (NodeTransportInfo -> NodeTransportInfo -> Bool
(NodeTransportInfo -> NodeTransportInfo -> Bool)
-> (NodeTransportInfo -> NodeTransportInfo -> Bool)
-> Eq NodeTransportInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NodeTransportInfo -> NodeTransportInfo -> Bool
== :: NodeTransportInfo -> NodeTransportInfo -> Bool
$c/= :: NodeTransportInfo -> NodeTransportInfo -> Bool
/= :: 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
$cshowsPrec :: Int -> NodeTransportInfo -> ShowS
showsPrec :: Int -> NodeTransportInfo -> ShowS
$cshow :: NodeTransportInfo -> String
show :: NodeTransportInfo -> String
$cshowList :: [NodeTransportInfo] -> ShowS
showList :: [NodeTransportInfo] -> ShowS
Show)
nodeTransportInfoProfilesLens :: Lens' NodeTransportInfo [BoundTransportAddress]
nodeTransportInfoProfilesLens :: Lens' NodeTransportInfo [BoundTransportAddress]
nodeTransportInfoProfilesLens = (NodeTransportInfo -> [BoundTransportAddress])
-> (NodeTransportInfo
-> [BoundTransportAddress] -> NodeTransportInfo)
-> Lens' NodeTransportInfo [BoundTransportAddress]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeTransportInfo -> [BoundTransportAddress]
nodeTransportProfiles (\NodeTransportInfo
x [BoundTransportAddress]
y -> NodeTransportInfo
x {nodeTransportProfiles = y})
nodeTransportInfoPublishAddressLens :: Lens' NodeTransportInfo EsAddress
nodeTransportInfoPublishAddressLens :: Lens' NodeTransportInfo EsAddress
nodeTransportInfoPublishAddressLens = (NodeTransportInfo -> EsAddress)
-> (NodeTransportInfo -> EsAddress -> NodeTransportInfo)
-> Lens' NodeTransportInfo EsAddress
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeTransportInfo -> EsAddress
nodeTransportPublishAddress (\NodeTransportInfo
x EsAddress
y -> NodeTransportInfo
x {nodeTransportPublishAddress = y})
nodeTransportInfoBoundAddressLens :: Lens' NodeTransportInfo [EsAddress]
nodeTransportInfoBoundAddressLens :: Lens' NodeTransportInfo [EsAddress]
nodeTransportInfoBoundAddressLens = (NodeTransportInfo -> [EsAddress])
-> (NodeTransportInfo -> [EsAddress] -> NodeTransportInfo)
-> Lens' NodeTransportInfo [EsAddress]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeTransportInfo -> [EsAddress]
nodeTransportBoundAddress (\NodeTransportInfo
x [EsAddress]
y -> NodeTransportInfo
x {nodeTransportBoundAddress = y})
data BoundTransportAddress = BoundTransportAddress
{ BoundTransportAddress -> EsAddress
publishAddress :: EsAddress,
BoundTransportAddress -> [EsAddress]
boundAddress :: [EsAddress]
}
deriving stock (BoundTransportAddress -> BoundTransportAddress -> Bool
(BoundTransportAddress -> BoundTransportAddress -> Bool)
-> (BoundTransportAddress -> BoundTransportAddress -> Bool)
-> Eq BoundTransportAddress
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BoundTransportAddress -> BoundTransportAddress -> Bool
== :: BoundTransportAddress -> BoundTransportAddress -> Bool
$c/= :: BoundTransportAddress -> BoundTransportAddress -> Bool
/= :: 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
$cshowsPrec :: Int -> BoundTransportAddress -> ShowS
showsPrec :: Int -> BoundTransportAddress -> ShowS
$cshow :: BoundTransportAddress -> String
show :: BoundTransportAddress -> String
$cshowList :: [BoundTransportAddress] -> ShowS
showList :: [BoundTransportAddress] -> ShowS
Show)
boundTransportAddressPublishAddressLens :: Lens' BoundTransportAddress EsAddress
boundTransportAddressPublishAddressLens :: Lens' BoundTransportAddress EsAddress
boundTransportAddressPublishAddressLens = (BoundTransportAddress -> EsAddress)
-> (BoundTransportAddress -> EsAddress -> BoundTransportAddress)
-> Lens' BoundTransportAddress EsAddress
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens BoundTransportAddress -> EsAddress
publishAddress (\BoundTransportAddress
x EsAddress
y -> BoundTransportAddress
x {publishAddress = y})
boundTransportAddressBoundAddressesLens :: Lens' BoundTransportAddress [EsAddress]
boundTransportAddressBoundAddressesLens :: Lens' BoundTransportAddress [EsAddress]
boundTransportAddressBoundAddressesLens = (BoundTransportAddress -> [EsAddress])
-> (BoundTransportAddress -> [EsAddress] -> BoundTransportAddress)
-> Lens' BoundTransportAddress [EsAddress]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens BoundTransportAddress -> [EsAddress]
boundAddress (\BoundTransportAddress
x [EsAddress]
y -> BoundTransportAddress
x {boundAddress = y})
data NodeNetworkInfo = NodeNetworkInfo
{ NodeNetworkInfo -> NodeNetworkInterface
nodeNetworkPrimaryInterface :: NodeNetworkInterface,
NodeNetworkInfo -> NominalDiffTime
nodeNetworkRefreshInterval :: NominalDiffTime
}
deriving stock (NodeNetworkInfo -> NodeNetworkInfo -> Bool
(NodeNetworkInfo -> NodeNetworkInfo -> Bool)
-> (NodeNetworkInfo -> NodeNetworkInfo -> Bool)
-> Eq NodeNetworkInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NodeNetworkInfo -> NodeNetworkInfo -> Bool
== :: NodeNetworkInfo -> NodeNetworkInfo -> Bool
$c/= :: NodeNetworkInfo -> NodeNetworkInfo -> Bool
/= :: 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
$cshowsPrec :: Int -> NodeNetworkInfo -> ShowS
showsPrec :: Int -> NodeNetworkInfo -> ShowS
$cshow :: NodeNetworkInfo -> String
show :: NodeNetworkInfo -> String
$cshowList :: [NodeNetworkInfo] -> ShowS
showList :: [NodeNetworkInfo] -> ShowS
Show)
nodeNetworkInfoPrimaryInterfaceLens :: Lens' NodeNetworkInfo NodeNetworkInterface
nodeNetworkInfoPrimaryInterfaceLens :: Lens' NodeNetworkInfo NodeNetworkInterface
nodeNetworkInfoPrimaryInterfaceLens = (NodeNetworkInfo -> NodeNetworkInterface)
-> (NodeNetworkInfo -> NodeNetworkInterface -> NodeNetworkInfo)
-> Lens' NodeNetworkInfo NodeNetworkInterface
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeNetworkInfo -> NodeNetworkInterface
nodeNetworkPrimaryInterface (\NodeNetworkInfo
x NodeNetworkInterface
y -> NodeNetworkInfo
x {nodeNetworkPrimaryInterface = y})
nodeNetworkInfoRefreshIntervalLens :: Lens' NodeNetworkInfo NominalDiffTime
nodeNetworkInfoRefreshIntervalLens :: Lens' NodeNetworkInfo NominalDiffTime
nodeNetworkInfoRefreshIntervalLens = (NodeNetworkInfo -> NominalDiffTime)
-> (NodeNetworkInfo -> NominalDiffTime -> NodeNetworkInfo)
-> Lens' NodeNetworkInfo NominalDiffTime
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeNetworkInfo -> NominalDiffTime
nodeNetworkRefreshInterval (\NodeNetworkInfo
x NominalDiffTime
y -> NodeNetworkInfo
x {nodeNetworkRefreshInterval = y})
newtype MacAddress = MacAddress {MacAddress -> Text
macAddress :: Text}
deriving newtype (MacAddress -> MacAddress -> Bool
(MacAddress -> MacAddress -> Bool)
-> (MacAddress -> MacAddress -> Bool) -> Eq MacAddress
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MacAddress -> MacAddress -> Bool
== :: MacAddress -> MacAddress -> Bool
$c/= :: MacAddress -> MacAddress -> Bool
/= :: 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
$ccompare :: MacAddress -> MacAddress -> Ordering
compare :: MacAddress -> MacAddress -> Ordering
$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
>= :: MacAddress -> MacAddress -> Bool
$cmax :: MacAddress -> MacAddress -> MacAddress
max :: MacAddress -> MacAddress -> MacAddress
$cmin :: MacAddress -> MacAddress -> MacAddress
min :: MacAddress -> MacAddress -> 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
$cshowsPrec :: Int -> MacAddress -> ShowS
showsPrec :: Int -> MacAddress -> ShowS
$cshow :: MacAddress -> String
show :: MacAddress -> String
$cshowList :: [MacAddress] -> ShowS
showList :: [MacAddress] -> ShowS
Show, Maybe MacAddress
Value -> Parser [MacAddress]
Value -> Parser MacAddress
(Value -> Parser MacAddress)
-> (Value -> Parser [MacAddress])
-> Maybe MacAddress
-> FromJSON MacAddress
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser MacAddress
parseJSON :: Value -> Parser MacAddress
$cparseJSONList :: Value -> Parser [MacAddress]
parseJSONList :: Value -> Parser [MacAddress]
$comittedField :: Maybe MacAddress
omittedField :: Maybe MacAddress
FromJSON)
newtype NetworkInterfaceName = NetworkInterfaceName {NetworkInterfaceName -> Text
networkInterfaceName :: Text}
deriving newtype (NetworkInterfaceName -> NetworkInterfaceName -> Bool
(NetworkInterfaceName -> NetworkInterfaceName -> Bool)
-> (NetworkInterfaceName -> NetworkInterfaceName -> Bool)
-> Eq NetworkInterfaceName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NetworkInterfaceName -> NetworkInterfaceName -> Bool
== :: NetworkInterfaceName -> NetworkInterfaceName -> Bool
$c/= :: NetworkInterfaceName -> NetworkInterfaceName -> Bool
/= :: 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
$ccompare :: NetworkInterfaceName -> NetworkInterfaceName -> Ordering
compare :: NetworkInterfaceName -> NetworkInterfaceName -> Ordering
$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
>= :: NetworkInterfaceName -> NetworkInterfaceName -> Bool
$cmax :: NetworkInterfaceName
-> NetworkInterfaceName -> NetworkInterfaceName
max :: NetworkInterfaceName
-> NetworkInterfaceName -> NetworkInterfaceName
$cmin :: NetworkInterfaceName
-> NetworkInterfaceName -> NetworkInterfaceName
min :: NetworkInterfaceName
-> NetworkInterfaceName -> 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
$cshowsPrec :: Int -> NetworkInterfaceName -> ShowS
showsPrec :: Int -> NetworkInterfaceName -> ShowS
$cshow :: NetworkInterfaceName -> String
show :: NetworkInterfaceName -> String
$cshowList :: [NetworkInterfaceName] -> ShowS
showList :: [NetworkInterfaceName] -> ShowS
Show, Maybe NetworkInterfaceName
Value -> Parser [NetworkInterfaceName]
Value -> Parser NetworkInterfaceName
(Value -> Parser NetworkInterfaceName)
-> (Value -> Parser [NetworkInterfaceName])
-> Maybe NetworkInterfaceName
-> FromJSON NetworkInterfaceName
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser NetworkInterfaceName
parseJSON :: Value -> Parser NetworkInterfaceName
$cparseJSONList :: Value -> Parser [NetworkInterfaceName]
parseJSONList :: Value -> Parser [NetworkInterfaceName]
$comittedField :: Maybe NetworkInterfaceName
omittedField :: Maybe NetworkInterfaceName
FromJSON)
data NodeNetworkInterface = NodeNetworkInterface
{ NodeNetworkInterface -> MacAddress
nodeNetIfaceMacAddress :: MacAddress,
NodeNetworkInterface -> NetworkInterfaceName
nodeNetIfaceName :: NetworkInterfaceName,
NodeNetworkInterface -> Server
nodeNetIfaceAddress :: Server
}
deriving stock (NodeNetworkInterface -> NodeNetworkInterface -> Bool
(NodeNetworkInterface -> NodeNetworkInterface -> Bool)
-> (NodeNetworkInterface -> NodeNetworkInterface -> Bool)
-> Eq NodeNetworkInterface
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NodeNetworkInterface -> NodeNetworkInterface -> Bool
== :: NodeNetworkInterface -> NodeNetworkInterface -> Bool
$c/= :: NodeNetworkInterface -> NodeNetworkInterface -> Bool
/= :: 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
$cshowsPrec :: Int -> NodeNetworkInterface -> ShowS
showsPrec :: Int -> NodeNetworkInterface -> ShowS
$cshow :: NodeNetworkInterface -> String
show :: NodeNetworkInterface -> String
$cshowList :: [NodeNetworkInterface] -> ShowS
showList :: [NodeNetworkInterface] -> ShowS
Show)
nodeNetworkInterfaceMacAddressLens :: Lens' NodeNetworkInterface MacAddress
nodeNetworkInterfaceMacAddressLens :: Lens' NodeNetworkInterface MacAddress
nodeNetworkInterfaceMacAddressLens = (NodeNetworkInterface -> MacAddress)
-> (NodeNetworkInterface -> MacAddress -> NodeNetworkInterface)
-> Lens' NodeNetworkInterface MacAddress
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeNetworkInterface -> MacAddress
nodeNetIfaceMacAddress (\NodeNetworkInterface
x MacAddress
y -> NodeNetworkInterface
x {nodeNetIfaceMacAddress = y})
nodeNetworkInterfaceNameLens :: Lens' NodeNetworkInterface NetworkInterfaceName
nodeNetworkInterfaceNameLens :: Lens' NodeNetworkInterface NetworkInterfaceName
nodeNetworkInterfaceNameLens = (NodeNetworkInterface -> NetworkInterfaceName)
-> (NodeNetworkInterface
-> NetworkInterfaceName -> NodeNetworkInterface)
-> Lens' NodeNetworkInterface NetworkInterfaceName
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeNetworkInterface -> NetworkInterfaceName
nodeNetIfaceName (\NodeNetworkInterface
x NetworkInterfaceName
y -> NodeNetworkInterface
x {nodeNetIfaceName = y})
nodeNetworkInterfaceAddressLens :: Lens' NodeNetworkInterface Server
nodeNetworkInterfaceAddressLens :: Lens' NodeNetworkInterface Server
nodeNetworkInterfaceAddressLens = (NodeNetworkInterface -> Server)
-> (NodeNetworkInterface -> Server -> NodeNetworkInterface)
-> Lens' NodeNetworkInterface Server
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeNetworkInterface -> Server
nodeNetIfaceAddress (\NodeNetworkInterface
x Server
y -> NodeNetworkInterface
x {nodeNetIfaceAddress = y})
data ThreadPool = ThreadPool
{ ThreadPool -> Text
nodeThreadPoolName :: Text,
ThreadPool -> NodeThreadPoolInfo
nodeThreadPoolInfo :: NodeThreadPoolInfo
}
deriving stock (ThreadPool -> ThreadPool -> Bool
(ThreadPool -> ThreadPool -> Bool)
-> (ThreadPool -> ThreadPool -> Bool) -> Eq ThreadPool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ThreadPool -> ThreadPool -> Bool
== :: ThreadPool -> ThreadPool -> Bool
$c/= :: ThreadPool -> ThreadPool -> Bool
/= :: 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
$cshowsPrec :: Int -> ThreadPool -> ShowS
showsPrec :: Int -> ThreadPool -> ShowS
$cshow :: ThreadPool -> String
show :: ThreadPool -> String
$cshowList :: [ThreadPool] -> ShowS
showList :: [ThreadPool] -> ShowS
Show)
threadPoolNodeThreadPoolNameLens :: Lens' ThreadPool Text
threadPoolNodeThreadPoolNameLens :: Lens' ThreadPool Text
threadPoolNodeThreadPoolNameLens = (ThreadPool -> Text)
-> (ThreadPool -> Text -> ThreadPool) -> Lens' ThreadPool Text
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens ThreadPool -> Text
nodeThreadPoolName (\ThreadPool
x Text
y -> ThreadPool
x {nodeThreadPoolName = y})
threadPoolNodeThreadPoolInfoLens :: Lens' ThreadPool NodeThreadPoolInfo
threadPoolNodeThreadPoolInfoLens :: Lens' ThreadPool NodeThreadPoolInfo
threadPoolNodeThreadPoolInfoLens = (ThreadPool -> NodeThreadPoolInfo)
-> (ThreadPool -> NodeThreadPoolInfo -> ThreadPool)
-> Lens' ThreadPool NodeThreadPoolInfo
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens ThreadPool -> NodeThreadPoolInfo
nodeThreadPoolInfo (\ThreadPool
x NodeThreadPoolInfo
y -> ThreadPool
x {nodeThreadPoolInfo = y})
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 stock (NodeThreadPoolInfo -> NodeThreadPoolInfo -> Bool
(NodeThreadPoolInfo -> NodeThreadPoolInfo -> Bool)
-> (NodeThreadPoolInfo -> NodeThreadPoolInfo -> Bool)
-> Eq NodeThreadPoolInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NodeThreadPoolInfo -> NodeThreadPoolInfo -> Bool
== :: NodeThreadPoolInfo -> NodeThreadPoolInfo -> Bool
$c/= :: NodeThreadPoolInfo -> NodeThreadPoolInfo -> Bool
/= :: 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
$cshowsPrec :: Int -> NodeThreadPoolInfo -> ShowS
showsPrec :: Int -> NodeThreadPoolInfo -> ShowS
$cshow :: NodeThreadPoolInfo -> String
show :: NodeThreadPoolInfo -> String
$cshowList :: [NodeThreadPoolInfo] -> ShowS
showList :: [NodeThreadPoolInfo] -> ShowS
Show)
nodeThreadPoolInfoQueueSizeLens :: Lens' NodeThreadPoolInfo ThreadPoolSize
nodeThreadPoolInfoQueueSizeLens :: Lens' NodeThreadPoolInfo ThreadPoolSize
nodeThreadPoolInfoQueueSizeLens = (NodeThreadPoolInfo -> ThreadPoolSize)
-> (NodeThreadPoolInfo -> ThreadPoolSize -> NodeThreadPoolInfo)
-> Lens' NodeThreadPoolInfo ThreadPoolSize
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeThreadPoolInfo -> ThreadPoolSize
nodeThreadPoolQueueSize (\NodeThreadPoolInfo
x ThreadPoolSize
y -> NodeThreadPoolInfo
x {nodeThreadPoolQueueSize = y})
nodeThreadPoolInfoKeepaliveLens :: Lens' NodeThreadPoolInfo (Maybe NominalDiffTime)
nodeThreadPoolInfoKeepaliveLens :: Lens' NodeThreadPoolInfo (Maybe NominalDiffTime)
nodeThreadPoolInfoKeepaliveLens = (NodeThreadPoolInfo -> Maybe NominalDiffTime)
-> (NodeThreadPoolInfo
-> Maybe NominalDiffTime -> NodeThreadPoolInfo)
-> Lens' NodeThreadPoolInfo (Maybe NominalDiffTime)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeThreadPoolInfo -> Maybe NominalDiffTime
nodeThreadPoolKeepalive (\NodeThreadPoolInfo
x Maybe NominalDiffTime
y -> NodeThreadPoolInfo
x {nodeThreadPoolKeepalive = y})
nodeThreadPoolInfoMinLens :: Lens' NodeThreadPoolInfo (Maybe Int)
nodeThreadPoolInfoMinLens :: Lens' NodeThreadPoolInfo (Maybe Int)
nodeThreadPoolInfoMinLens = (NodeThreadPoolInfo -> Maybe Int)
-> (NodeThreadPoolInfo -> Maybe Int -> NodeThreadPoolInfo)
-> Lens' NodeThreadPoolInfo (Maybe Int)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeThreadPoolInfo -> Maybe Int
nodeThreadPoolMin (\NodeThreadPoolInfo
x Maybe Int
y -> NodeThreadPoolInfo
x {nodeThreadPoolMin = y})
nodeThreadPoolInfoMaxLens :: Lens' NodeThreadPoolInfo (Maybe Int)
nodeThreadPoolInfoMaxLens :: Lens' NodeThreadPoolInfo (Maybe Int)
nodeThreadPoolInfoMaxLens = (NodeThreadPoolInfo -> Maybe Int)
-> (NodeThreadPoolInfo -> Maybe Int -> NodeThreadPoolInfo)
-> Lens' NodeThreadPoolInfo (Maybe Int)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeThreadPoolInfo -> Maybe Int
nodeThreadPoolMax (\NodeThreadPoolInfo
x Maybe Int
y -> NodeThreadPoolInfo
x {nodeThreadPoolMax = y})
nodeThreadPoolInfoTypeLens :: Lens' NodeThreadPoolInfo ThreadPoolType
nodeThreadPoolInfoTypeLens :: Lens' NodeThreadPoolInfo ThreadPoolType
nodeThreadPoolInfoTypeLens = (NodeThreadPoolInfo -> ThreadPoolType)
-> (NodeThreadPoolInfo -> ThreadPoolType -> NodeThreadPoolInfo)
-> Lens' NodeThreadPoolInfo ThreadPoolType
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeThreadPoolInfo -> ThreadPoolType
nodeThreadPoolType (\NodeThreadPoolInfo
x ThreadPoolType
y -> NodeThreadPoolInfo
x {nodeThreadPoolType = y})
data ThreadPoolSize
= ThreadPoolBounded Int
| ThreadPoolUnbounded
deriving stock (ThreadPoolSize -> ThreadPoolSize -> Bool
(ThreadPoolSize -> ThreadPoolSize -> Bool)
-> (ThreadPoolSize -> ThreadPoolSize -> Bool) -> Eq ThreadPoolSize
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ThreadPoolSize -> ThreadPoolSize -> Bool
== :: ThreadPoolSize -> ThreadPoolSize -> Bool
$c/= :: ThreadPoolSize -> ThreadPoolSize -> Bool
/= :: 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
$cshowsPrec :: Int -> ThreadPoolSize -> ShowS
showsPrec :: Int -> ThreadPoolSize -> ShowS
$cshow :: ThreadPoolSize -> String
show :: ThreadPoolSize -> String
$cshowList :: [ThreadPoolSize] -> ShowS
showList :: [ThreadPoolSize] -> ShowS
Show)
threadPoolSizeBoundedPrism :: Prism' ThreadPoolSize Int
threadPoolSizeBoundedPrism :: Prism' ThreadPoolSize Int
threadPoolSizeBoundedPrism = (Int -> ThreadPoolSize)
-> (ThreadPoolSize -> Either ThreadPoolSize Int)
-> Prism' ThreadPoolSize Int
forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b
prism Int -> ThreadPoolSize
ThreadPoolBounded ThreadPoolSize -> Either ThreadPoolSize Int
extract
where
extract :: ThreadPoolSize -> Either ThreadPoolSize Int
extract ThreadPoolSize
s =
case ThreadPoolSize
s of
ThreadPoolBounded Int
x -> Int -> Either ThreadPoolSize Int
forall a b. b -> Either a b
Right Int
x
ThreadPoolSize
_ -> ThreadPoolSize -> Either ThreadPoolSize Int
forall a b. a -> Either a b
Left ThreadPoolSize
s
data ThreadPoolType
= ThreadPoolScaling
| ThreadPoolFixed
| ThreadPoolCached
| ThreadPoolFixedAutoQueueSize
deriving stock (ThreadPoolType -> ThreadPoolType -> Bool
(ThreadPoolType -> ThreadPoolType -> Bool)
-> (ThreadPoolType -> ThreadPoolType -> Bool) -> Eq ThreadPoolType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ThreadPoolType -> ThreadPoolType -> Bool
== :: ThreadPoolType -> ThreadPoolType -> Bool
$c/= :: ThreadPoolType -> ThreadPoolType -> Bool
/= :: 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
$cshowsPrec :: Int -> ThreadPoolType -> ShowS
showsPrec :: Int -> ThreadPoolType -> ShowS
$cshow :: ThreadPoolType -> String
show :: ThreadPoolType -> String
$cshowList :: [ThreadPoolType] -> ShowS
showList :: [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 -> VersionNumber
nodeJVMVMVersion :: VersionNumber,
NodeJVMInfo -> Text
nodeJVMVMName :: Text,
NodeJVMInfo -> JVMVersion
nodeJVMVersion :: JVMVersion,
NodeJVMInfo -> PID
nodeJVMPID :: PID
}
deriving stock (NodeJVMInfo -> NodeJVMInfo -> Bool
(NodeJVMInfo -> NodeJVMInfo -> Bool)
-> (NodeJVMInfo -> NodeJVMInfo -> Bool) -> Eq NodeJVMInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NodeJVMInfo -> NodeJVMInfo -> Bool
== :: NodeJVMInfo -> NodeJVMInfo -> Bool
$c/= :: NodeJVMInfo -> NodeJVMInfo -> Bool
/= :: 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
$cshowsPrec :: Int -> NodeJVMInfo -> ShowS
showsPrec :: Int -> NodeJVMInfo -> ShowS
$cshow :: NodeJVMInfo -> String
show :: NodeJVMInfo -> String
$cshowList :: [NodeJVMInfo] -> ShowS
showList :: [NodeJVMInfo] -> ShowS
Show)
nodeJVMInfoMemoryPoolsLens :: Lens' NodeJVMInfo [JVMMemoryPool]
nodeJVMInfoMemoryPoolsLens :: Lens' NodeJVMInfo [JVMMemoryPool]
nodeJVMInfoMemoryPoolsLens = (NodeJVMInfo -> [JVMMemoryPool])
-> (NodeJVMInfo -> [JVMMemoryPool] -> NodeJVMInfo)
-> Lens' NodeJVMInfo [JVMMemoryPool]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeJVMInfo -> [JVMMemoryPool]
nodeJVMInfoMemoryPools (\NodeJVMInfo
x [JVMMemoryPool]
y -> NodeJVMInfo
x {nodeJVMInfoMemoryPools = y})
nodeJVMInfoMemoryPoolsGCCollectorsLens :: Lens' NodeJVMInfo [JVMGCCollector]
nodeJVMInfoMemoryPoolsGCCollectorsLens :: Lens' NodeJVMInfo [JVMGCCollector]
nodeJVMInfoMemoryPoolsGCCollectorsLens = (NodeJVMInfo -> [JVMGCCollector])
-> (NodeJVMInfo -> [JVMGCCollector] -> NodeJVMInfo)
-> Lens' NodeJVMInfo [JVMGCCollector]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeJVMInfo -> [JVMGCCollector]
nodeJVMInfoMemoryPoolsGCCollectors (\NodeJVMInfo
x [JVMGCCollector]
y -> NodeJVMInfo
x {nodeJVMInfoMemoryPoolsGCCollectors = y})
nodeJVMInfoMemoryInfoLens :: Lens' NodeJVMInfo JVMMemoryInfo
nodeJVMInfoMemoryInfoLens :: Lens' NodeJVMInfo JVMMemoryInfo
nodeJVMInfoMemoryInfoLens = (NodeJVMInfo -> JVMMemoryInfo)
-> (NodeJVMInfo -> JVMMemoryInfo -> NodeJVMInfo)
-> Lens' NodeJVMInfo JVMMemoryInfo
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeJVMInfo -> JVMMemoryInfo
nodeJVMInfoMemoryInfo (\NodeJVMInfo
x JVMMemoryInfo
y -> NodeJVMInfo
x {nodeJVMInfoMemoryInfo = y})
nodeJVMInfoStartTimeLens :: Lens' NodeJVMInfo UTCTime
nodeJVMInfoStartTimeLens :: Lens' NodeJVMInfo UTCTime
nodeJVMInfoStartTimeLens = (NodeJVMInfo -> UTCTime)
-> (NodeJVMInfo -> UTCTime -> NodeJVMInfo)
-> Lens' NodeJVMInfo UTCTime
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeJVMInfo -> UTCTime
nodeJVMInfoStartTime (\NodeJVMInfo
x UTCTime
y -> NodeJVMInfo
x {nodeJVMInfoStartTime = y})
nodeJVMInfoVMVendorLens :: Lens' NodeJVMInfo Text
nodeJVMInfoVMVendorLens :: Lens' NodeJVMInfo Text
nodeJVMInfoVMVendorLens = (NodeJVMInfo -> Text)
-> (NodeJVMInfo -> Text -> NodeJVMInfo) -> Lens' NodeJVMInfo Text
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeJVMInfo -> Text
nodeJVMInfoVMVendor (\NodeJVMInfo
x Text
y -> NodeJVMInfo
x {nodeJVMInfoVMVendor = y})
nodeJVMInfoVMVersionLens :: Lens' NodeJVMInfo VersionNumber
nodeJVMInfoVMVersionLens :: Lens' NodeJVMInfo VersionNumber
nodeJVMInfoVMVersionLens = (NodeJVMInfo -> VersionNumber)
-> (NodeJVMInfo -> VersionNumber -> NodeJVMInfo)
-> Lens' NodeJVMInfo VersionNumber
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeJVMInfo -> VersionNumber
nodeJVMVMVersion (\NodeJVMInfo
x VersionNumber
y -> NodeJVMInfo
x {nodeJVMVMVersion = y})
nodeJVMInfoVMNameLens :: Lens' NodeJVMInfo Text
nodeJVMInfoVMNameLens :: Lens' NodeJVMInfo Text
nodeJVMInfoVMNameLens = (NodeJVMInfo -> Text)
-> (NodeJVMInfo -> Text -> NodeJVMInfo) -> Lens' NodeJVMInfo Text
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeJVMInfo -> Text
nodeJVMVMName (\NodeJVMInfo
x Text
y -> NodeJVMInfo
x {nodeJVMVMName = y})
nodeJVMInfoVersionLens :: Lens' NodeJVMInfo JVMVersion
nodeJVMInfoVersionLens :: Lens' NodeJVMInfo JVMVersion
nodeJVMInfoVersionLens = (NodeJVMInfo -> JVMVersion)
-> (NodeJVMInfo -> JVMVersion -> NodeJVMInfo)
-> Lens' NodeJVMInfo JVMVersion
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeJVMInfo -> JVMVersion
nodeJVMVersion (\NodeJVMInfo
x JVMVersion
y -> NodeJVMInfo
x {nodeJVMVersion = y})
nodeJVMInfoPIDLens :: Lens' NodeJVMInfo PID
nodeJVMInfoPIDLens :: Lens' NodeJVMInfo PID
nodeJVMInfoPIDLens = (NodeJVMInfo -> PID)
-> (NodeJVMInfo -> PID -> NodeJVMInfo) -> Lens' NodeJVMInfo PID
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeJVMInfo -> PID
nodeJVMPID (\NodeJVMInfo
x PID
y -> NodeJVMInfo
x {nodeJVMPID = y})
newtype JVMVersion = JVMVersion {JVMVersion -> Text
unJVMVersion :: Text}
deriving stock (JVMVersion -> JVMVersion -> Bool
(JVMVersion -> JVMVersion -> Bool)
-> (JVMVersion -> JVMVersion -> Bool) -> Eq JVMVersion
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: JVMVersion -> JVMVersion -> Bool
== :: JVMVersion -> JVMVersion -> Bool
$c/= :: JVMVersion -> JVMVersion -> Bool
/= :: 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
$cshowsPrec :: Int -> JVMVersion -> ShowS
showsPrec :: Int -> JVMVersion -> ShowS
$cshow :: JVMVersion -> String
show :: JVMVersion -> String
$cshowList :: [JVMVersion] -> ShowS
showList :: [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 a. a -> Parser a
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 stock (JVMMemoryInfo -> JVMMemoryInfo -> Bool
(JVMMemoryInfo -> JVMMemoryInfo -> Bool)
-> (JVMMemoryInfo -> JVMMemoryInfo -> Bool) -> Eq JVMMemoryInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: JVMMemoryInfo -> JVMMemoryInfo -> Bool
== :: JVMMemoryInfo -> JVMMemoryInfo -> Bool
$c/= :: JVMMemoryInfo -> JVMMemoryInfo -> Bool
/= :: 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
$cshowsPrec :: Int -> JVMMemoryInfo -> ShowS
showsPrec :: Int -> JVMMemoryInfo -> ShowS
$cshow :: JVMMemoryInfo -> String
show :: JVMMemoryInfo -> String
$cshowList :: [JVMMemoryInfo] -> ShowS
showList :: [JVMMemoryInfo] -> ShowS
Show)
jvmMemoryInfoDirectMaxLens :: Lens' JVMMemoryInfo Bytes
jvmMemoryInfoDirectMaxLens :: Lens' JVMMemoryInfo Bytes
jvmMemoryInfoDirectMaxLens = (JVMMemoryInfo -> Bytes)
-> (JVMMemoryInfo -> Bytes -> JVMMemoryInfo)
-> Lens' JVMMemoryInfo Bytes
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens JVMMemoryInfo -> Bytes
jvmMemoryInfoDirectMax (\JVMMemoryInfo
x Bytes
y -> JVMMemoryInfo
x {jvmMemoryInfoDirectMax = y})
jvmMemoryInfoNonHeapMaxLens :: Lens' JVMMemoryInfo Bytes
jvmMemoryInfoNonHeapMaxLens :: Lens' JVMMemoryInfo Bytes
jvmMemoryInfoNonHeapMaxLens = (JVMMemoryInfo -> Bytes)
-> (JVMMemoryInfo -> Bytes -> JVMMemoryInfo)
-> Lens' JVMMemoryInfo Bytes
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens JVMMemoryInfo -> Bytes
jvmMemoryInfoNonHeapMax (\JVMMemoryInfo
x Bytes
y -> JVMMemoryInfo
x {jvmMemoryInfoNonHeapMax = y})
jvmMemoryInfoNonHeapInitLens :: Lens' JVMMemoryInfo Bytes
jvmMemoryInfoNonHeapInitLens :: Lens' JVMMemoryInfo Bytes
jvmMemoryInfoNonHeapInitLens = (JVMMemoryInfo -> Bytes)
-> (JVMMemoryInfo -> Bytes -> JVMMemoryInfo)
-> Lens' JVMMemoryInfo Bytes
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens JVMMemoryInfo -> Bytes
jvmMemoryInfoNonHeapInit (\JVMMemoryInfo
x Bytes
y -> JVMMemoryInfo
x {jvmMemoryInfoNonHeapInit = y})
jvmMemoryInfoHeapMaxLens :: Lens' JVMMemoryInfo Bytes
jvmMemoryInfoHeapMaxLens :: Lens' JVMMemoryInfo Bytes
jvmMemoryInfoHeapMaxLens = (JVMMemoryInfo -> Bytes)
-> (JVMMemoryInfo -> Bytes -> JVMMemoryInfo)
-> Lens' JVMMemoryInfo Bytes
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens JVMMemoryInfo -> Bytes
jvmMemoryInfoHeapMax (\JVMMemoryInfo
x Bytes
y -> JVMMemoryInfo
x {jvmMemoryInfoHeapMax = y})
jvmMemoryInfoHeapInitLens :: Lens' JVMMemoryInfo Bytes
jvmMemoryInfoHeapInitLens :: Lens' JVMMemoryInfo Bytes
jvmMemoryInfoHeapInitLens = (JVMMemoryInfo -> Bytes)
-> (JVMMemoryInfo -> Bytes -> JVMMemoryInfo)
-> Lens' JVMMemoryInfo Bytes
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens JVMMemoryInfo -> Bytes
jvmMemoryInfoHeapInit (\JVMMemoryInfo
x Bytes
y -> JVMMemoryInfo
x {jvmMemoryInfoHeapInit = y})
newtype JVMMemoryPool = JVMMemoryPool
{ JVMMemoryPool -> Text
jvmMemoryPool :: Text
}
deriving newtype (JVMMemoryPool -> JVMMemoryPool -> Bool
(JVMMemoryPool -> JVMMemoryPool -> Bool)
-> (JVMMemoryPool -> JVMMemoryPool -> Bool) -> Eq JVMMemoryPool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: JVMMemoryPool -> JVMMemoryPool -> Bool
== :: JVMMemoryPool -> JVMMemoryPool -> Bool
$c/= :: JVMMemoryPool -> JVMMemoryPool -> Bool
/= :: 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
$cshowsPrec :: Int -> JVMMemoryPool -> ShowS
showsPrec :: Int -> JVMMemoryPool -> ShowS
$cshow :: JVMMemoryPool -> String
show :: JVMMemoryPool -> String
$cshowList :: [JVMMemoryPool] -> ShowS
showList :: [JVMMemoryPool] -> ShowS
Show, Maybe JVMMemoryPool
Value -> Parser [JVMMemoryPool]
Value -> Parser JVMMemoryPool
(Value -> Parser JVMMemoryPool)
-> (Value -> Parser [JVMMemoryPool])
-> Maybe JVMMemoryPool
-> FromJSON JVMMemoryPool
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser JVMMemoryPool
parseJSON :: Value -> Parser JVMMemoryPool
$cparseJSONList :: Value -> Parser [JVMMemoryPool]
parseJSONList :: Value -> Parser [JVMMemoryPool]
$comittedField :: Maybe JVMMemoryPool
omittedField :: Maybe JVMMemoryPool
FromJSON)
newtype JVMGCCollector = JVMGCCollector
{ JVMGCCollector -> Text
jvmGCCollector :: Text
}
deriving newtype (JVMGCCollector -> JVMGCCollector -> Bool
(JVMGCCollector -> JVMGCCollector -> Bool)
-> (JVMGCCollector -> JVMGCCollector -> Bool) -> Eq JVMGCCollector
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: JVMGCCollector -> JVMGCCollector -> Bool
== :: JVMGCCollector -> JVMGCCollector -> Bool
$c/= :: JVMGCCollector -> JVMGCCollector -> Bool
/= :: 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
$cshowsPrec :: Int -> JVMGCCollector -> ShowS
showsPrec :: Int -> JVMGCCollector -> ShowS
$cshow :: JVMGCCollector -> String
show :: JVMGCCollector -> String
$cshowList :: [JVMGCCollector] -> ShowS
showList :: [JVMGCCollector] -> ShowS
Show, Maybe JVMGCCollector
Value -> Parser [JVMGCCollector]
Value -> Parser JVMGCCollector
(Value -> Parser JVMGCCollector)
-> (Value -> Parser [JVMGCCollector])
-> Maybe JVMGCCollector
-> FromJSON JVMGCCollector
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser JVMGCCollector
parseJSON :: Value -> Parser JVMGCCollector
$cparseJSONList :: Value -> Parser [JVMGCCollector]
parseJSONList :: Value -> Parser [JVMGCCollector]
$comittedField :: Maybe JVMGCCollector
omittedField :: Maybe JVMGCCollector
FromJSON)
newtype PID = PID
{ PID -> Int
pid :: Int
}
deriving newtype (PID -> PID -> Bool
(PID -> PID -> Bool) -> (PID -> PID -> Bool) -> Eq PID
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PID -> PID -> Bool
== :: PID -> PID -> Bool
$c/= :: PID -> PID -> Bool
/= :: 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
$cshowsPrec :: Int -> PID -> ShowS
showsPrec :: Int -> PID -> ShowS
$cshow :: PID -> String
show :: PID -> String
$cshowList :: [PID] -> ShowS
showList :: [PID] -> ShowS
Show, Maybe PID
Value -> Parser [PID]
Value -> Parser PID
(Value -> Parser PID)
-> (Value -> Parser [PID]) -> Maybe PID -> FromJSON PID
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser PID
parseJSON :: Value -> Parser PID
$cparseJSONList :: Value -> Parser [PID]
parseJSONList :: Value -> Parser [PID]
$comittedField :: Maybe PID
omittedField :: Maybe 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 stock (NodeOSInfo -> NodeOSInfo -> Bool
(NodeOSInfo -> NodeOSInfo -> Bool)
-> (NodeOSInfo -> NodeOSInfo -> Bool) -> Eq NodeOSInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NodeOSInfo -> NodeOSInfo -> Bool
== :: NodeOSInfo -> NodeOSInfo -> Bool
$c/= :: NodeOSInfo -> NodeOSInfo -> Bool
/= :: 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
$cshowsPrec :: Int -> NodeOSInfo -> ShowS
showsPrec :: Int -> NodeOSInfo -> ShowS
$cshow :: NodeOSInfo -> String
show :: NodeOSInfo -> String
$cshowList :: [NodeOSInfo] -> ShowS
showList :: [NodeOSInfo] -> ShowS
Show)
nodeOSInfoRefreshIntervalLens :: Lens' NodeOSInfo NominalDiffTime
nodeOSInfoRefreshIntervalLens :: Lens' NodeOSInfo NominalDiffTime
nodeOSInfoRefreshIntervalLens = (NodeOSInfo -> NominalDiffTime)
-> (NodeOSInfo -> NominalDiffTime -> NodeOSInfo)
-> Lens' NodeOSInfo NominalDiffTime
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeOSInfo -> NominalDiffTime
nodeOSRefreshInterval (\NodeOSInfo
x NominalDiffTime
y -> NodeOSInfo
x {nodeOSRefreshInterval = y})
nodeOSInfoNameLens :: Lens' NodeOSInfo Text
nodeOSInfoNameLens :: Lens' NodeOSInfo Text
nodeOSInfoNameLens = (NodeOSInfo -> Text)
-> (NodeOSInfo -> Text -> NodeOSInfo) -> Lens' NodeOSInfo Text
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeOSInfo -> Text
nodeOSName (\NodeOSInfo
x Text
y -> NodeOSInfo
x {nodeOSName = y})
nodeOSInfoArchLens :: Lens' NodeOSInfo Text
nodeOSInfoArchLens :: Lens' NodeOSInfo Text
nodeOSInfoArchLens = (NodeOSInfo -> Text)
-> (NodeOSInfo -> Text -> NodeOSInfo) -> Lens' NodeOSInfo Text
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeOSInfo -> Text
nodeOSArch (\NodeOSInfo
x Text
y -> NodeOSInfo
x {nodeOSArch = y})
nodeOSInfoVersionLens :: Lens' NodeOSInfo Text
nodeOSInfoVersionLens :: Lens' NodeOSInfo Text
nodeOSInfoVersionLens = (NodeOSInfo -> Text)
-> (NodeOSInfo -> Text -> NodeOSInfo) -> Lens' NodeOSInfo Text
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeOSInfo -> Text
nodeOSVersion (\NodeOSInfo
x Text
y -> NodeOSInfo
x {nodeOSVersion = y})
nodeOSInfoAvailableProcessorsLens :: Lens' NodeOSInfo Int
nodeOSInfoAvailableProcessorsLens :: Lens' NodeOSInfo Int
nodeOSInfoAvailableProcessorsLens = (NodeOSInfo -> Int)
-> (NodeOSInfo -> Int -> NodeOSInfo) -> Lens' NodeOSInfo Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeOSInfo -> Int
nodeOSAvailableProcessors (\NodeOSInfo
x Int
y -> NodeOSInfo
x {nodeOSAvailableProcessors = y})
nodeOSInfoAllocatedProcessorsLens :: Lens' NodeOSInfo Int
nodeOSInfoAllocatedProcessorsLens :: Lens' NodeOSInfo Int
nodeOSInfoAllocatedProcessorsLens = (NodeOSInfo -> Int)
-> (NodeOSInfo -> Int -> NodeOSInfo) -> Lens' NodeOSInfo Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeOSInfo -> Int
nodeOSAllocatedProcessors (\NodeOSInfo
x Int
y -> NodeOSInfo
x {nodeOSAllocatedProcessors = y})
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 stock (CPUInfo -> CPUInfo -> Bool
(CPUInfo -> CPUInfo -> Bool)
-> (CPUInfo -> CPUInfo -> Bool) -> Eq CPUInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CPUInfo -> CPUInfo -> Bool
== :: CPUInfo -> CPUInfo -> Bool
$c/= :: CPUInfo -> CPUInfo -> Bool
/= :: 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
$cshowsPrec :: Int -> CPUInfo -> ShowS
showsPrec :: Int -> CPUInfo -> ShowS
$cshow :: CPUInfo -> String
show :: CPUInfo -> String
$cshowList :: [CPUInfo] -> ShowS
showList :: [CPUInfo] -> ShowS
Show)
cpuInfoCacheSizeLens :: Lens' CPUInfo Bytes
cpuInfoCacheSizeLens :: Lens' CPUInfo Bytes
cpuInfoCacheSizeLens = (CPUInfo -> Bytes)
-> (CPUInfo -> Bytes -> CPUInfo) -> Lens' CPUInfo Bytes
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens CPUInfo -> Bytes
cpuCacheSize (\CPUInfo
x Bytes
y -> CPUInfo
x {cpuCacheSize = y})
cpuInfoCoresPerSocketLens :: Lens' CPUInfo Int
cpuInfoCoresPerSocketLens :: Lens' CPUInfo Int
cpuInfoCoresPerSocketLens = (CPUInfo -> Int)
-> (CPUInfo -> Int -> CPUInfo) -> Lens' CPUInfo Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens CPUInfo -> Int
cpuCoresPerSocket (\CPUInfo
x Int
y -> CPUInfo
x {cpuCoresPerSocket = y})
cpuInfoTotalSocketsLens :: Lens' CPUInfo Int
cpuInfoTotalSocketsLens :: Lens' CPUInfo Int
cpuInfoTotalSocketsLens = (CPUInfo -> Int)
-> (CPUInfo -> Int -> CPUInfo) -> Lens' CPUInfo Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens CPUInfo -> Int
cpuTotalSockets (\CPUInfo
x Int
y -> CPUInfo
x {cpuTotalSockets = y})
cpuInfoTotalCoresLens :: Lens' CPUInfo Int
cpuInfoTotalCoresLens :: Lens' CPUInfo Int
cpuInfoTotalCoresLens = (CPUInfo -> Int)
-> (CPUInfo -> Int -> CPUInfo) -> Lens' CPUInfo Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens CPUInfo -> Int
cpuTotalCores (\CPUInfo
x Int
y -> CPUInfo
x {cpuTotalCores = y})
cpuInfoMHZLens :: Lens' CPUInfo Int
cpuInfoMHZLens :: Lens' CPUInfo Int
cpuInfoMHZLens = (CPUInfo -> Int)
-> (CPUInfo -> Int -> CPUInfo) -> Lens' CPUInfo Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens CPUInfo -> Int
cpuMHZ (\CPUInfo
x Int
y -> CPUInfo
x {cpuMHZ = y})
cpuInfoModelLens :: Lens' CPUInfo Text
cpuInfoModelLens :: Lens' CPUInfo Text
cpuInfoModelLens = (CPUInfo -> Text)
-> (CPUInfo -> Text -> CPUInfo) -> Lens' CPUInfo Text
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens CPUInfo -> Text
cpuModel (\CPUInfo
x Text
y -> CPUInfo
x {cpuModel = y})
cpuInfoVendorLens :: Lens' CPUInfo Text
cpuInfoVendorLens :: Lens' CPUInfo Text
cpuInfoVendorLens = (CPUInfo -> Text)
-> (CPUInfo -> Text -> CPUInfo) -> Lens' CPUInfo Text
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens CPUInfo -> Text
cpuVendor (\CPUInfo
x Text
y -> CPUInfo
x {cpuVendor = y})
data NodeProcessInfo = NodeProcessInfo
{
NodeProcessInfo -> Bool
nodeProcessMLockAll :: Bool,
NodeProcessInfo -> Maybe Int
nodeProcessMaxFileDescriptors :: Maybe Int,
NodeProcessInfo -> PID
nodeProcessId :: PID,
NodeProcessInfo -> NominalDiffTime
nodeProcessRefreshInterval :: NominalDiffTime
}
deriving stock (NodeProcessInfo -> NodeProcessInfo -> Bool
(NodeProcessInfo -> NodeProcessInfo -> Bool)
-> (NodeProcessInfo -> NodeProcessInfo -> Bool)
-> Eq NodeProcessInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NodeProcessInfo -> NodeProcessInfo -> Bool
== :: NodeProcessInfo -> NodeProcessInfo -> Bool
$c/= :: NodeProcessInfo -> NodeProcessInfo -> Bool
/= :: 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
$cshowsPrec :: Int -> NodeProcessInfo -> ShowS
showsPrec :: Int -> NodeProcessInfo -> ShowS
$cshow :: NodeProcessInfo -> String
show :: NodeProcessInfo -> String
$cshowList :: [NodeProcessInfo] -> ShowS
showList :: [NodeProcessInfo] -> ShowS
Show)
nodeProcessInfoMLockAllLens :: Lens' NodeProcessInfo Bool
nodeProcessInfoMLockAllLens :: Lens' NodeProcessInfo Bool
nodeProcessInfoMLockAllLens = (NodeProcessInfo -> Bool)
-> (NodeProcessInfo -> Bool -> NodeProcessInfo)
-> Lens' NodeProcessInfo Bool
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeProcessInfo -> Bool
nodeProcessMLockAll (\NodeProcessInfo
x Bool
y -> NodeProcessInfo
x {nodeProcessMLockAll = y})
nodeProcessInfoMaxFileDescriptorsLens :: Lens' NodeProcessInfo (Maybe Int)
nodeProcessInfoMaxFileDescriptorsLens :: Lens' NodeProcessInfo (Maybe Int)
nodeProcessInfoMaxFileDescriptorsLens = (NodeProcessInfo -> Maybe Int)
-> (NodeProcessInfo -> Maybe Int -> NodeProcessInfo)
-> Lens' NodeProcessInfo (Maybe Int)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeProcessInfo -> Maybe Int
nodeProcessMaxFileDescriptors (\NodeProcessInfo
x Maybe Int
y -> NodeProcessInfo
x {nodeProcessMaxFileDescriptors = y})
nodeProcessInfoIdLens :: Lens' NodeProcessInfo PID
nodeProcessInfoIdLens :: Lens' NodeProcessInfo PID
nodeProcessInfoIdLens = (NodeProcessInfo -> PID)
-> (NodeProcessInfo -> PID -> NodeProcessInfo)
-> Lens' NodeProcessInfo PID
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeProcessInfo -> PID
nodeProcessId (\NodeProcessInfo
x PID
y -> NodeProcessInfo
x {nodeProcessId = y})
nodeProcessInfoRefreshIntervalLens :: Lens' NodeProcessInfo NominalDiffTime
nodeProcessInfoRefreshIntervalLens :: Lens' NodeProcessInfo NominalDiffTime
nodeProcessInfoRefreshIntervalLens = (NodeProcessInfo -> NominalDiffTime)
-> (NodeProcessInfo -> NominalDiffTime -> NodeProcessInfo)
-> Lens' NodeProcessInfo NominalDiffTime
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens NodeProcessInfo -> NominalDiffTime
nodeProcessRefreshInterval (\NodeProcessInfo
x NominalDiffTime
y -> NodeProcessInfo
x {nodeProcessRefreshInterval = y})
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 a. a -> Parser a
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 a. a -> Parser a
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. (a -> b) -> Maybe a -> Maybe b
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 a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ((StringlyTypedDouble -> Double)
-> Maybe StringlyTypedDouble -> Maybe Double
forall a b. (a -> b) -> Maybe a -> Maybe b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. (a -> b) -> Maybe a -> Maybe b
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 a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ((StringlyTypedDouble -> Double)
-> Maybe StringlyTypedDouble -> Maybe Double
forall a b. (a -> b) -> Maybe a -> Maybe b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a. a -> Parser a
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 a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> JVMBufferPoolStats -> Parser JVMBufferPoolStats
forall a. a -> Parser a
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 a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> JVMGCStats -> Parser JVMGCStats
forall a. a -> Parser a
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 a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> JVMGCStats -> Parser JVMGCStats
forall a. a -> Parser a
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> JVMPoolStats -> Parser JVMPoolStats
forall a. a -> Parser a
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 a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> JVMPoolStats -> Parser JVMPoolStats
forall a. a -> Parser a
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 a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> JVMPoolStats -> Parser JVMPoolStats
forall a. a -> Parser a
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe LoadAvgs -> Parser (Maybe LoadAvgs)
forall a. a -> Parser a
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a. String -> Parser a
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 a. a -> Parser 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 a b. (a -> b) -> Maybe a -> Maybe b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ((MS -> NominalDiffTime) -> Maybe MS -> Maybe NominalDiffTime
forall a b. (a -> b) -> Maybe a -> Maybe b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ((MS -> NominalDiffTime) -> Maybe MS -> Maybe NominalDiffTime
forall a b. (a -> b) -> Maybe a -> Maybe b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ((MS -> NominalDiffTime) -> Maybe MS -> Maybe NominalDiffTime
forall a b. (a -> b) -> Maybe a -> Maybe b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ((MS -> NominalDiffTime) -> Maybe MS -> Maybe NominalDiffTime
forall a b. (a -> b) -> Maybe a -> Maybe b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FullNodeId -> Parser FullNodeId
forall a. a -> Parser a
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FullNodeId -> Parser FullNodeId
forall a. a -> Parser a
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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
-> VersionNumber
-> Text
-> JVMVersion
-> PID
-> NodeJVMInfo
NodeJVMInfo
([JVMMemoryPool]
-> [JVMGCCollector]
-> JVMMemoryInfo
-> UTCTime
-> Text
-> VersionNumber
-> Text
-> JVMVersion
-> PID
-> NodeJVMInfo)
-> Parser [JVMMemoryPool]
-> Parser
([JVMGCCollector]
-> JVMMemoryInfo
-> UTCTime
-> Text
-> VersionNumber
-> 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
-> VersionNumber
-> Text
-> JVMVersion
-> PID
-> NodeJVMInfo)
-> Parser [JVMGCCollector]
-> Parser
(JVMMemoryInfo
-> UTCTime
-> Text
-> VersionNumber
-> Text
-> JVMVersion
-> PID
-> NodeJVMInfo)
forall a b. Parser (a -> b) -> Parser a -> Parser b
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
-> VersionNumber
-> Text
-> JVMVersion
-> PID
-> NodeJVMInfo)
-> Parser JVMMemoryInfo
-> Parser
(UTCTime
-> Text
-> VersionNumber
-> Text
-> JVMVersion
-> PID
-> NodeJVMInfo)
forall a b. Parser (a -> b) -> Parser a -> Parser b
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
-> VersionNumber
-> Text
-> JVMVersion
-> PID
-> NodeJVMInfo)
-> Parser UTCTime
-> Parser
(Text -> VersionNumber -> Text -> JVMVersion -> PID -> NodeJVMInfo)
forall a b. Parser (a -> b) -> Parser a -> Parser b
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 -> VersionNumber -> Text -> JVMVersion -> PID -> NodeJVMInfo)
-> Parser Text
-> Parser
(VersionNumber -> Text -> JVMVersion -> PID -> NodeJVMInfo)
forall a b. Parser (a -> b) -> Parser a -> Parser b
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 (VersionNumber -> Text -> JVMVersion -> PID -> NodeJVMInfo)
-> Parser VersionNumber
-> Parser (Text -> JVMVersion -> PID -> NodeJVMInfo)
forall a b. Parser (a -> b) -> Parser a -> Parser b
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
"vm_version"
Parser (Text -> JVMVersion -> PID -> NodeJVMInfo)
-> Parser Text -> Parser (JVMVersion -> PID -> NodeJVMInfo)
forall a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a. a -> Parser a
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 a b. (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe NominalDiffTime -> Parser (Maybe NominalDiffTime)
forall a. a -> Parser a
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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"
instance FromJSON ThreadPoolSize where
parseJSON :: Value -> Parser ThreadPoolSize
parseJSON Value
v = Value -> Parser ThreadPoolSize
parseAsNumber Value
v Parser ThreadPoolSize
-> Parser ThreadPoolSize -> Parser ThreadPoolSize
forall a. Parser a -> Parser a -> Parser a
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 a. a -> m a
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 a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> ThreadPoolSize
ThreadPoolBounded Int
n)
| Bool
otherwise = String -> m ThreadPoolSize
forall a. String -> m a
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 a b c. (a -> b) -> (a, c) -> (b, c)
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 a. a -> Parser a
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 a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> ThreadPoolSize
ThreadPoolBounded Int
n)
(Maybe Int, Text)
_ -> String -> Parser ThreadPoolSize
forall a. String -> Parser a
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 a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return ThreadPoolType
ThreadPoolScaling
parse Text
"fixed" = ThreadPoolType -> m ThreadPoolType
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return ThreadPoolType
ThreadPoolFixed
parse Text
"cached" = ThreadPoolType -> m ThreadPoolType
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return ThreadPoolType
ThreadPoolCached
parse Text
"fixed_auto_queue_size" = ThreadPoolType -> m ThreadPoolType
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return ThreadPoolType
ThreadPoolFixedAutoQueueSize
parse Text
e = String -> m ThreadPoolType
forall a. String -> m a
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 a. a -> Parser a
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a. 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 a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return []
parseProfiles Value
_ = String -> Parser [a]
forall a. 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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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"
data InitialShardCount
= QuorumShards
| QuorumMinus1Shards
| FullShards
| FullMinus1Shards
| ExplicitShards Int
deriving stock (InitialShardCount -> InitialShardCount -> Bool
(InitialShardCount -> InitialShardCount -> Bool)
-> (InitialShardCount -> InitialShardCount -> Bool)
-> Eq InitialShardCount
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InitialShardCount -> InitialShardCount -> Bool
== :: InitialShardCount -> InitialShardCount -> Bool
$c/= :: InitialShardCount -> InitialShardCount -> Bool
/= :: 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
$cshowsPrec :: Int -> InitialShardCount -> ShowS
showsPrec :: Int -> InitialShardCount -> ShowS
$cshow :: InitialShardCount -> String
show :: InitialShardCount -> String
$cshowList :: [InitialShardCount] -> ShowS
showList :: [InitialShardCount] -> ShowS
Show, (forall x. InitialShardCount -> Rep InitialShardCount x)
-> (forall x. Rep InitialShardCount x -> InitialShardCount)
-> Generic InitialShardCount
forall x. Rep InitialShardCount x -> InitialShardCount
forall x. InitialShardCount -> Rep InitialShardCount x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. InitialShardCount -> Rep InitialShardCount x
from :: forall x. InitialShardCount -> Rep InitialShardCount x
$cto :: forall x. Rep InitialShardCount x -> InitialShardCount
to :: forall x. Rep InitialShardCount x -> InitialShardCount
Generic)
initialShardCountExplicitShardsPrism :: Prism' InitialShardCount Int
initialShardCountExplicitShardsPrism :: Prism' InitialShardCount Int
initialShardCountExplicitShardsPrism = (Int -> InitialShardCount)
-> (InitialShardCount -> Either InitialShardCount Int)
-> Prism' InitialShardCount Int
forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b
prism Int -> InitialShardCount
ExplicitShards InitialShardCount -> Either InitialShardCount Int
extract
where
extract :: InitialShardCount -> Either InitialShardCount Int
extract InitialShardCount
s =
case InitialShardCount
s of
ExplicitShards Int
x -> Int -> Either InitialShardCount Int
forall a b. b -> Either a b
Right Int
x
InitialShardCount
_ -> InitialShardCount -> Either InitialShardCount Int
forall a b. a -> Either a b
Left InitialShardCount
s
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 a. Parser a -> Parser a -> Parser a
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 a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure InitialShardCount
QuorumShards
parseText a
"quorum-1" = InitialShardCount -> f InitialShardCount
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure InitialShardCount
QuorumMinus1Shards
parseText a
"full" = InitialShardCount -> f InitialShardCount
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure InitialShardCount
FullShards
parseText a
"full-1" = InitialShardCount -> f InitialShardCount
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure InitialShardCount
FullMinus1Shards
parseText a
_ = f InitialShardCount
forall a. f a
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
newtype ShardsResult = ShardsResult
{ ShardsResult -> ShardResult
srShards :: ShardResult
}
deriving stock (ShardsResult -> ShardsResult -> Bool
(ShardsResult -> ShardsResult -> Bool)
-> (ShardsResult -> ShardsResult -> Bool) -> Eq ShardsResult
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ShardsResult -> ShardsResult -> Bool
== :: ShardsResult -> ShardsResult -> Bool
$c/= :: ShardsResult -> ShardsResult -> Bool
/= :: ShardsResult -> ShardsResult -> Bool
Eq, Int -> ShardsResult -> ShowS
[ShardsResult] -> ShowS
ShardsResult -> String
(Int -> ShardsResult -> ShowS)
-> (ShardsResult -> String)
-> ([ShardsResult] -> ShowS)
-> Show ShardsResult
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ShardsResult -> ShowS
showsPrec :: Int -> ShardsResult -> ShowS
$cshow :: ShardsResult -> String
show :: ShardsResult -> String
$cshowList :: [ShardsResult] -> ShowS
showList :: [ShardsResult] -> ShowS
Show)
instance FromJSON ShardsResult where
parseJSON :: Value -> Parser ShardsResult
parseJSON =
String
-> (Object -> Parser ShardsResult) -> Value -> Parser ShardsResult
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"ShardsResult" ((Object -> Parser ShardsResult) -> Value -> Parser ShardsResult)
-> (Object -> Parser ShardsResult) -> Value -> Parser ShardsResult
forall a b. (a -> b) -> a -> b
$ \Object
v ->
ShardResult -> ShardsResult
ShardsResult
(ShardResult -> ShardsResult)
-> Parser ShardResult -> Parser ShardsResult
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v
Object -> Key -> Parser ShardResult
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"_shards"
shardsResultShardsLens :: Lens' ShardsResult ShardResult
shardsResultShardsLens :: Lens' ShardsResult ShardResult
shardsResultShardsLens = (ShardsResult -> ShardResult)
-> (ShardsResult -> ShardResult -> ShardsResult)
-> Lens' ShardsResult ShardResult
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens ShardsResult -> ShardResult
srShards (\ShardsResult
x ShardResult
y -> ShardsResult
x {srShards = y})
data ShardResult = ShardResult
{ ShardResult -> Int
shardTotal :: Int,
ShardResult -> Int
shardsSuccessful :: Int,
ShardResult -> Int
shardsSkipped :: Int,
ShardResult -> Int
shardsFailed :: Int
}
deriving stock (ShardResult -> ShardResult -> Bool
(ShardResult -> ShardResult -> Bool)
-> (ShardResult -> ShardResult -> Bool) -> Eq ShardResult
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ShardResult -> ShardResult -> Bool
== :: ShardResult -> ShardResult -> Bool
$c/= :: ShardResult -> ShardResult -> Bool
/= :: 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
$cshowsPrec :: Int -> ShardResult -> ShowS
showsPrec :: Int -> ShardResult -> ShowS
$cshow :: ShardResult -> String
show :: ShardResult -> String
$cshowList :: [ShardResult] -> ShowS
showList :: [ShardResult] -> ShowS
Show)
instance FromJSON ShardResult where
parseJSON :: Value -> Parser ShardResult
parseJSON =
String
-> (Object -> Parser ShardResult) -> Value -> Parser ShardResult
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"ShardResult" ((Object -> Parser ShardResult) -> Value -> Parser ShardResult)
-> (Object -> Parser ShardResult) -> Value -> Parser ShardResult
forall a b. (a -> b) -> a -> b
$ \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 (Maybe Int)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"total" Parser (Maybe Int) -> Int -> Parser Int
forall a. Parser (Maybe a) -> a -> Parser a
.!= Int
0
Parser (Int -> Int -> Int -> ShardResult)
-> Parser Int -> Parser (Int -> Int -> ShardResult)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"successful" Parser (Maybe Int) -> Int -> Parser Int
forall a. Parser (Maybe a) -> a -> Parser a
.!= Int
0
Parser (Int -> Int -> ShardResult)
-> Parser Int -> Parser (Int -> ShardResult)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"skipped" Parser (Maybe Int) -> Int -> Parser Int
forall a. Parser (Maybe a) -> a -> Parser a
.!= Int
0
Parser (Int -> ShardResult) -> Parser Int -> Parser ShardResult
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"failed" Parser (Maybe Int) -> Int -> Parser Int
forall a. Parser (Maybe a) -> a -> Parser a
.!= Int
0
instance ToJSON ShardResult where
toJSON :: ShardResult -> Value
toJSON ShardResult {Int
shardTotal :: ShardResult -> Int
shardsSuccessful :: ShardResult -> Int
shardsSkipped :: ShardResult -> Int
shardsFailed :: ShardResult -> Int
shardTotal :: Int
shardsSuccessful :: Int
shardsSkipped :: Int
shardsFailed :: Int
..} =
[Pair] -> Value
object
[ Key
"total" Key -> Int -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Int
shardTotal,
Key
"successful" Key -> Int -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Int
shardsSuccessful,
Key
"skipped" Key -> Int -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Int
shardsSkipped,
Key
"failed" Key -> Int -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Int
shardsFailed
]
shardResultTotalLens :: Lens' ShardResult Int
shardResultTotalLens :: Lens' ShardResult Int
shardResultTotalLens = (ShardResult -> Int)
-> (ShardResult -> Int -> ShardResult) -> Lens' ShardResult Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens ShardResult -> Int
shardTotal (\ShardResult
x Int
y -> ShardResult
x {shardTotal = y})
shardsResultSuccessfulLens :: Lens' ShardResult Int
shardsResultSuccessfulLens :: Lens' ShardResult Int
shardsResultSuccessfulLens = (ShardResult -> Int)
-> (ShardResult -> Int -> ShardResult) -> Lens' ShardResult Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens ShardResult -> Int
shardsSuccessful (\ShardResult
x Int
y -> ShardResult
x {shardsSuccessful = y})
shardsResultResultSkippedLens :: Lens' ShardResult Int
shardsResultResultSkippedLens :: Lens' ShardResult Int
shardsResultResultSkippedLens = (ShardResult -> Int)
-> (ShardResult -> Int -> ShardResult) -> Lens' ShardResult Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens ShardResult -> Int
shardsSkipped (\ShardResult
x Int
y -> ShardResult
x {shardsSkipped = y})
shardsResultFailedLens :: Lens' ShardResult Int
shardsResultFailedLens :: Lens' ShardResult Int
shardsResultFailedLens = (ShardResult -> Int)
-> (ShardResult -> Int -> ShardResult) -> Lens' ShardResult Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens ShardResult -> Int
shardsFailed (\ShardResult
x Int
y -> ShardResult
x {shardsFailed = y})
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 stock (Version -> Version -> Bool
(Version -> Version -> Bool)
-> (Version -> Version -> Bool) -> Eq Version
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Version -> Version -> Bool
== :: Version -> Version -> Bool
$c/= :: Version -> Version -> Bool
/= :: 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
$cshowsPrec :: Int -> Version -> ShowS
showsPrec :: Int -> Version -> ShowS
$cshow :: Version -> String
show :: Version -> String
$cshowList :: [Version] -> ShowS
showList :: [Version] -> ShowS
Show, (forall x. Version -> Rep Version x)
-> (forall x. Rep Version x -> Version) -> Generic Version
forall x. Rep Version x -> Version
forall x. Version -> Rep Version x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Version -> Rep Version x
from :: forall x. Version -> Rep Version x
$cto :: forall x. Rep Version x -> Version
to :: forall x. Rep Version x -> Version
Generic)
instance ToJSON Version where
toJSON :: Version -> Value
toJSON Version {Bool
UTCTime
VersionNumber
BuildHash
number :: Version -> VersionNumber
build_hash :: Version -> BuildHash
build_date :: Version -> UTCTime
build_snapshot :: Version -> Bool
lucene_version :: Version -> VersionNumber
number :: VersionNumber
build_hash :: BuildHash
build_date :: UTCTime
build_snapshot :: Bool
lucene_version :: VersionNumber
..} =
[Pair] -> Value
object
[ Key
"number" Key -> VersionNumber -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= VersionNumber
number,
Key
"build_hash" Key -> BuildHash -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= BuildHash
build_hash,
Key
"build_date" Key -> UTCTime -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= UTCTime
build_date,
Key
"build_snapshot" Key -> Bool -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Bool
build_snapshot,
Key
"lucene_version" Key -> VersionNumber -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e 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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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 a b. Parser (a -> b) -> Parser a -> Parser b
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"
versionNumberLens :: Lens' Version VersionNumber
versionNumberLens :: Lens' Version VersionNumber
versionNumberLens = (Version -> VersionNumber)
-> (Version -> VersionNumber -> Version)
-> Lens' Version VersionNumber
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Version -> VersionNumber
number (\Version
x VersionNumber
y -> Version
x {number = y})
versionBuildHashLens :: Lens' Version BuildHash
versionBuildHashLens :: Lens' Version BuildHash
versionBuildHashLens = (Version -> BuildHash)
-> (Version -> BuildHash -> Version) -> Lens' Version BuildHash
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Version -> BuildHash
build_hash (\Version
x BuildHash
y -> Version
x {build_hash = y})
versionBuildDateLens :: Lens' Version UTCTime
versionBuildDateLens :: Lens' Version UTCTime
versionBuildDateLens = (Version -> UTCTime)
-> (Version -> UTCTime -> Version) -> Lens' Version UTCTime
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Version -> UTCTime
build_date (\Version
x UTCTime
y -> Version
x {build_date = y})
versionBuildSnapshotLens :: Lens' Version Bool
versionBuildSnapshotLens :: Lens' Version Bool
versionBuildSnapshotLens = (Version -> Bool)
-> (Version -> Bool -> Version) -> Lens' Version Bool
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Version -> Bool
build_snapshot (\Version
x Bool
y -> Version
x {build_snapshot = y})
versionLuceneVersionLens :: Lens' Version VersionNumber
versionLuceneVersionLens :: Lens' Version VersionNumber
versionLuceneVersionLens = (Version -> VersionNumber)
-> (Version -> VersionNumber -> Version)
-> Lens' Version VersionNumber
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Version -> VersionNumber
lucene_version (\Version
x VersionNumber
y -> Version
x {lucene_version = y})
newtype VersionNumber = VersionNumber
{VersionNumber -> Version
versionNumber :: Versions.Version}
deriving stock (VersionNumber -> VersionNumber -> Bool
(VersionNumber -> VersionNumber -> Bool)
-> (VersionNumber -> VersionNumber -> Bool) -> Eq VersionNumber
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VersionNumber -> VersionNumber -> Bool
== :: VersionNumber -> VersionNumber -> Bool
$c/= :: VersionNumber -> VersionNumber -> Bool
/= :: 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
$ccompare :: VersionNumber -> VersionNumber -> Ordering
compare :: VersionNumber -> VersionNumber -> Ordering
$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
>= :: VersionNumber -> VersionNumber -> Bool
$cmax :: VersionNumber -> VersionNumber -> VersionNumber
max :: VersionNumber -> VersionNumber -> VersionNumber
$cmin :: VersionNumber -> VersionNumber -> VersionNumber
min :: VersionNumber -> VersionNumber -> 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
$cshowsPrec :: Int -> VersionNumber -> ShowS
showsPrec :: Int -> VersionNumber -> ShowS
$cshow :: VersionNumber -> String
show :: VersionNumber -> String
$cshowList :: [VersionNumber] -> ShowS
showList :: [VersionNumber] -> ShowS
Show)
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
Versions.prettyVer (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 ParsingError Version
Versions.version Text
t of
(Left ParsingError
err) -> String -> m VersionNumber
forall a. String -> m a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> m VersionNumber) -> String -> m VersionNumber
forall a b. (a -> b) -> a -> b
$ ParsingError -> String
forall a. Show a => a -> String
show ParsingError
err
(Right Version
v) -> VersionNumber -> m VersionNumber
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Version -> VersionNumber
VersionNumber Version
v)
data HealthStatus = HealthStatus
{ HealthStatus -> Text
healthStatusClusterName :: Text,
HealthStatus -> Text
healthStatusStatus :: Text,
HealthStatus -> Bool
healthStatusTimedOut :: Bool,
HealthStatus -> Int
healthStatusNumberOfNodes :: Int,
HealthStatus -> Int
healthStatusNumberOfDataNodes :: Int,
HealthStatus -> Int
healthStatusActivePrimaryShards :: Int,
HealthStatus -> Int
healthStatusActiveShards :: Int,
HealthStatus -> Int
healthStatusRelocatingShards :: Int,
HealthStatus -> Int
healthStatusInitializingShards :: Int,
HealthStatus -> Int
healthStatusUnassignedShards :: Int,
HealthStatus -> Int
healthStatusDelayedUnassignedShards :: Int,
HealthStatus -> Int
healthStatusNumberOfPendingTasks :: Int,
HealthStatus -> Int
healthStatusNumberOfInFlightFetch :: Int,
HealthStatus -> Int
healthStatusTaskMaxWaitingInQueueMillis :: Int,
HealthStatus -> Float
healthStatusActiveShardsPercentAsNumber :: Float
}
deriving stock (HealthStatus -> HealthStatus -> Bool
(HealthStatus -> HealthStatus -> Bool)
-> (HealthStatus -> HealthStatus -> Bool) -> Eq HealthStatus
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: HealthStatus -> HealthStatus -> Bool
== :: HealthStatus -> HealthStatus -> Bool
$c/= :: HealthStatus -> HealthStatus -> Bool
/= :: HealthStatus -> HealthStatus -> Bool
Eq, Int -> HealthStatus -> ShowS
[HealthStatus] -> ShowS
HealthStatus -> String
(Int -> HealthStatus -> ShowS)
-> (HealthStatus -> String)
-> ([HealthStatus] -> ShowS)
-> Show HealthStatus
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> HealthStatus -> ShowS
showsPrec :: Int -> HealthStatus -> ShowS
$cshow :: HealthStatus -> String
show :: HealthStatus -> String
$cshowList :: [HealthStatus] -> ShowS
showList :: [HealthStatus] -> ShowS
Show)
instance FromJSON HealthStatus where
parseJSON :: Value -> Parser HealthStatus
parseJSON =
String
-> (Object -> Parser HealthStatus) -> Value -> Parser HealthStatus
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"HealthStatus" ((Object -> Parser HealthStatus) -> Value -> Parser HealthStatus)
-> (Object -> Parser HealthStatus) -> Value -> Parser HealthStatus
forall a b. (a -> b) -> a -> b
$ \Object
v ->
Text
-> Text
-> Bool
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Float
-> HealthStatus
HealthStatus
(Text
-> Text
-> Bool
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Float
-> HealthStatus)
-> Parser Text
-> Parser
(Text
-> Bool
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Float
-> HealthStatus)
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
"cluster_name"
Parser
(Text
-> Bool
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Float
-> HealthStatus)
-> Parser Text
-> Parser
(Bool
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Float
-> HealthStatus)
forall a b. Parser (a -> b) -> Parser a -> Parser b
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
"status"
Parser
(Bool
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Float
-> HealthStatus)
-> Parser Bool
-> Parser
(Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Float
-> HealthStatus)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v
Object -> Key -> Parser Bool
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"timed_out"
Parser
(Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Float
-> HealthStatus)
-> Parser Int
-> Parser
(Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Float
-> HealthStatus)
forall a b. Parser (a -> b) -> Parser a -> Parser b
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
"number_of_nodes"
Parser
(Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Float
-> HealthStatus)
-> Parser Int
-> Parser
(Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Float
-> HealthStatus)
forall a b. Parser (a -> b) -> Parser a -> Parser b
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
"number_of_data_nodes"
Parser
(Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Float
-> HealthStatus)
-> Parser Int
-> Parser
(Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Float
-> HealthStatus)
forall a b. Parser (a -> b) -> Parser a -> Parser b
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
"active_primary_shards"
Parser
(Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Float
-> HealthStatus)
-> Parser Int
-> Parser
(Int
-> Int -> Int -> Int -> Int -> Int -> Int -> Float -> HealthStatus)
forall a b. Parser (a -> b) -> Parser a -> Parser b
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
"active_shards"
Parser
(Int
-> Int -> Int -> Int -> Int -> Int -> Int -> Float -> HealthStatus)
-> Parser Int
-> Parser
(Int -> Int -> Int -> Int -> Int -> Int -> Float -> HealthStatus)
forall a b. Parser (a -> b) -> Parser a -> Parser b
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
"relocating_shards"
Parser
(Int -> Int -> Int -> Int -> Int -> Int -> Float -> HealthStatus)
-> Parser Int
-> Parser
(Int -> Int -> Int -> Int -> Int -> Float -> HealthStatus)
forall a b. Parser (a -> b) -> Parser a -> Parser b
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
"initializing_shards"
Parser (Int -> Int -> Int -> Int -> Int -> Float -> HealthStatus)
-> Parser Int
-> Parser (Int -> Int -> Int -> Int -> Float -> HealthStatus)
forall a b. Parser (a -> b) -> Parser a -> Parser b
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
"unassigned_shards"
Parser (Int -> Int -> Int -> Int -> Float -> HealthStatus)
-> Parser Int
-> Parser (Int -> Int -> Int -> Float -> HealthStatus)
forall a b. Parser (a -> b) -> Parser a -> Parser b
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
"delayed_unassigned_shards"
Parser (Int -> Int -> Int -> Float -> HealthStatus)
-> Parser Int -> Parser (Int -> Int -> Float -> HealthStatus)
forall a b. Parser (a -> b) -> Parser a -> Parser b
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
"number_of_pending_tasks"
Parser (Int -> Int -> Float -> HealthStatus)
-> Parser Int -> Parser (Int -> Float -> HealthStatus)
forall a b. Parser (a -> b) -> Parser a -> Parser b
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
"number_of_in_flight_fetch"
Parser (Int -> Float -> HealthStatus)
-> Parser Int -> Parser (Float -> HealthStatus)
forall a b. Parser (a -> b) -> Parser a -> Parser b
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
"task_max_waiting_in_queue_millis"
Parser (Float -> HealthStatus)
-> Parser Float -> Parser HealthStatus
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v
Object -> Key -> Parser Float
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"active_shards_percent_as_number"
healthStatusClusterNameLens :: Lens' HealthStatus Text
healthStatusClusterNameLens :: Lens' HealthStatus Text
healthStatusClusterNameLens = (HealthStatus -> Text)
-> (HealthStatus -> Text -> HealthStatus)
-> Lens' HealthStatus Text
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens HealthStatus -> Text
healthStatusClusterName (\HealthStatus
x Text
y -> HealthStatus
x {healthStatusClusterName = y})
healthStatusStatusLens :: Lens' HealthStatus Text
healthStatusStatusLens :: Lens' HealthStatus Text
healthStatusStatusLens = (HealthStatus -> Text)
-> (HealthStatus -> Text -> HealthStatus)
-> Lens' HealthStatus Text
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens HealthStatus -> Text
healthStatusStatus (\HealthStatus
x Text
y -> HealthStatus
x {healthStatusStatus = y})
healthStatusTimedOutLens :: Lens' HealthStatus Bool
healthStatusTimedOutLens :: Lens' HealthStatus Bool
healthStatusTimedOutLens = (HealthStatus -> Bool)
-> (HealthStatus -> Bool -> HealthStatus)
-> Lens' HealthStatus Bool
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens HealthStatus -> Bool
healthStatusTimedOut (\HealthStatus
x Bool
y -> HealthStatus
x {healthStatusTimedOut = y})
healthStatusNumberOfNodesLens :: Lens' HealthStatus Int
healthStatusNumberOfNodesLens :: Lens' HealthStatus Int
healthStatusNumberOfNodesLens = (HealthStatus -> Int)
-> (HealthStatus -> Int -> HealthStatus) -> Lens' HealthStatus Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens HealthStatus -> Int
healthStatusNumberOfNodes (\HealthStatus
x Int
y -> HealthStatus
x {healthStatusNumberOfNodes = y})
healthStatusNumberOfDataNodesLens :: Lens' HealthStatus Int
healthStatusNumberOfDataNodesLens :: Lens' HealthStatus Int
healthStatusNumberOfDataNodesLens = (HealthStatus -> Int)
-> (HealthStatus -> Int -> HealthStatus) -> Lens' HealthStatus Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens HealthStatus -> Int
healthStatusNumberOfDataNodes (\HealthStatus
x Int
y -> HealthStatus
x {healthStatusNumberOfDataNodes = y})
healthStatusActivePrimaryShardsLens :: Lens' HealthStatus Int
healthStatusActivePrimaryShardsLens :: Lens' HealthStatus Int
healthStatusActivePrimaryShardsLens = (HealthStatus -> Int)
-> (HealthStatus -> Int -> HealthStatus) -> Lens' HealthStatus Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens HealthStatus -> Int
healthStatusActivePrimaryShards (\HealthStatus
x Int
y -> HealthStatus
x {healthStatusActivePrimaryShards = y})
healthStatusActiveShardsLens :: Lens' HealthStatus Int
healthStatusActiveShardsLens :: Lens' HealthStatus Int
healthStatusActiveShardsLens = (HealthStatus -> Int)
-> (HealthStatus -> Int -> HealthStatus) -> Lens' HealthStatus Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens HealthStatus -> Int
healthStatusActiveShards (\HealthStatus
x Int
y -> HealthStatus
x {healthStatusActiveShards = y})
healthStatusRelocatingShardsLens :: Lens' HealthStatus Int
healthStatusRelocatingShardsLens :: Lens' HealthStatus Int
healthStatusRelocatingShardsLens = (HealthStatus -> Int)
-> (HealthStatus -> Int -> HealthStatus) -> Lens' HealthStatus Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens HealthStatus -> Int
healthStatusRelocatingShards (\HealthStatus
x Int
y -> HealthStatus
x {healthStatusRelocatingShards = y})
healthStatusInitializingShardsLens :: Lens' HealthStatus Int
healthStatusInitializingShardsLens :: Lens' HealthStatus Int
healthStatusInitializingShardsLens = (HealthStatus -> Int)
-> (HealthStatus -> Int -> HealthStatus) -> Lens' HealthStatus Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens HealthStatus -> Int
healthStatusInitializingShards (\HealthStatus
x Int
y -> HealthStatus
x {healthStatusInitializingShards = y})
healthStatusUnassignedShardsLens :: Lens' HealthStatus Int
healthStatusUnassignedShardsLens :: Lens' HealthStatus Int
healthStatusUnassignedShardsLens = (HealthStatus -> Int)
-> (HealthStatus -> Int -> HealthStatus) -> Lens' HealthStatus Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens HealthStatus -> Int
healthStatusUnassignedShards (\HealthStatus
x Int
y -> HealthStatus
x {healthStatusUnassignedShards = y})
healthStatusDelayedUnassignedShardsLens :: Lens' HealthStatus Int
healthStatusDelayedUnassignedShardsLens :: Lens' HealthStatus Int
healthStatusDelayedUnassignedShardsLens = (HealthStatus -> Int)
-> (HealthStatus -> Int -> HealthStatus) -> Lens' HealthStatus Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens HealthStatus -> Int
healthStatusDelayedUnassignedShards (\HealthStatus
x Int
y -> HealthStatus
x {healthStatusDelayedUnassignedShards = y})
healthStatusNumberOfPendingTasksLens :: Lens' HealthStatus Int
healthStatusNumberOfPendingTasksLens :: Lens' HealthStatus Int
healthStatusNumberOfPendingTasksLens = (HealthStatus -> Int)
-> (HealthStatus -> Int -> HealthStatus) -> Lens' HealthStatus Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens HealthStatus -> Int
healthStatusNumberOfPendingTasks (\HealthStatus
x Int
y -> HealthStatus
x {healthStatusNumberOfPendingTasks = y})
healthStatusNumberOfInFlightFetchLens :: Lens' HealthStatus Int
healthStatusNumberOfInFlightFetchLens :: Lens' HealthStatus Int
healthStatusNumberOfInFlightFetchLens = (HealthStatus -> Int)
-> (HealthStatus -> Int -> HealthStatus) -> Lens' HealthStatus Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens HealthStatus -> Int
healthStatusNumberOfInFlightFetch (\HealthStatus
x Int
y -> HealthStatus
x {healthStatusNumberOfInFlightFetch = y})
healthStatusTaskMaxWaitingInQueueMillisLens :: Lens' HealthStatus Int
healthStatusTaskMaxWaitingInQueueMillisLens :: Lens' HealthStatus Int
healthStatusTaskMaxWaitingInQueueMillisLens = (HealthStatus -> Int)
-> (HealthStatus -> Int -> HealthStatus) -> Lens' HealthStatus Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens HealthStatus -> Int
healthStatusTaskMaxWaitingInQueueMillis (\HealthStatus
x Int
y -> HealthStatus
x {healthStatusTaskMaxWaitingInQueueMillis = y})
healthStatusActiveShardsPercentAsNumberLens :: Lens' HealthStatus Float
healthStatusActiveShardsPercentAsNumberLens :: Lens' HealthStatus Float
healthStatusActiveShardsPercentAsNumberLens = (HealthStatus -> Float)
-> (HealthStatus -> Float -> HealthStatus)
-> Lens' HealthStatus Float
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens HealthStatus -> Float
healthStatusActiveShardsPercentAsNumber (\HealthStatus
x Float
y -> HealthStatus
x {healthStatusActiveShardsPercentAsNumber = y})
data IndexedDocument = IndexedDocument
{ IndexedDocument -> Text
idxDocIndex :: Text,
IndexedDocument -> Maybe Text
idxDocType :: Maybe Text,
IndexedDocument -> Text
idxDocId :: Text,
IndexedDocument -> Int
idxDocVersion :: Int,
IndexedDocument -> Text
idxDocResult :: Text,
IndexedDocument -> ShardResult
idxDocShards :: ShardResult,
IndexedDocument -> Int
idxDocSeqNo :: Int,
IndexedDocument -> Int
idxDocPrimaryTerm :: Int
}
deriving stock (IndexedDocument -> IndexedDocument -> Bool
(IndexedDocument -> IndexedDocument -> Bool)
-> (IndexedDocument -> IndexedDocument -> Bool)
-> Eq IndexedDocument
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: IndexedDocument -> IndexedDocument -> Bool
== :: IndexedDocument -> IndexedDocument -> Bool
$c/= :: IndexedDocument -> IndexedDocument -> Bool
/= :: IndexedDocument -> IndexedDocument -> Bool
Eq, Int -> IndexedDocument -> ShowS
[IndexedDocument] -> ShowS
IndexedDocument -> String
(Int -> IndexedDocument -> ShowS)
-> (IndexedDocument -> String)
-> ([IndexedDocument] -> ShowS)
-> Show IndexedDocument
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> IndexedDocument -> ShowS
showsPrec :: Int -> IndexedDocument -> ShowS
$cshow :: IndexedDocument -> String
show :: IndexedDocument -> String
$cshowList :: [IndexedDocument] -> ShowS
showList :: [IndexedDocument] -> ShowS
Show)
{-# DEPRECATED idxDocType "deprecated since ElasticSearch 6.0" #-}
instance FromJSON IndexedDocument where
parseJSON :: Value -> Parser IndexedDocument
parseJSON =
String
-> (Object -> Parser IndexedDocument)
-> Value
-> Parser IndexedDocument
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"IndexedDocument" ((Object -> Parser IndexedDocument)
-> Value -> Parser IndexedDocument)
-> (Object -> Parser IndexedDocument)
-> Value
-> Parser IndexedDocument
forall a b. (a -> b) -> a -> b
$ \Object
v ->
Text
-> Maybe Text
-> Text
-> Int
-> Text
-> ShardResult
-> Int
-> Int
-> IndexedDocument
IndexedDocument
(Text
-> Maybe Text
-> Text
-> Int
-> Text
-> ShardResult
-> Int
-> Int
-> IndexedDocument)
-> Parser Text
-> Parser
(Maybe Text
-> Text
-> Int
-> Text
-> ShardResult
-> Int
-> Int
-> IndexedDocument)
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
(Maybe Text
-> Text
-> Int
-> Text
-> ShardResult
-> Int
-> Int
-> IndexedDocument)
-> Parser (Maybe Text)
-> Parser
(Text
-> Int -> Text -> ShardResult -> Int -> Int -> IndexedDocument)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v
Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"_type"
Parser
(Text
-> Int -> Text -> ShardResult -> Int -> Int -> IndexedDocument)
-> Parser Text
-> Parser
(Int -> Text -> ShardResult -> Int -> Int -> IndexedDocument)
forall a b. Parser (a -> b) -> Parser a -> Parser b
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
(Int -> Text -> ShardResult -> Int -> Int -> IndexedDocument)
-> Parser Int
-> Parser (Text -> ShardResult -> Int -> Int -> IndexedDocument)
forall a b. Parser (a -> b) -> Parser a -> Parser b
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
"_version"
Parser (Text -> ShardResult -> Int -> Int -> IndexedDocument)
-> Parser Text
-> Parser (ShardResult -> Int -> Int -> IndexedDocument)
forall a b. Parser (a -> b) -> Parser a -> Parser b
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
"result"
Parser (ShardResult -> Int -> Int -> IndexedDocument)
-> Parser ShardResult -> Parser (Int -> Int -> IndexedDocument)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v
Object -> Key -> Parser ShardResult
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"_shards"
Parser (Int -> Int -> IndexedDocument)
-> Parser Int -> Parser (Int -> IndexedDocument)
forall a b. Parser (a -> b) -> Parser a -> Parser b
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
"_seq_no"
Parser (Int -> IndexedDocument)
-> Parser Int -> Parser IndexedDocument
forall a b. Parser (a -> b) -> Parser a -> Parser b
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
"_primary_term"
indexedDocumentIndexLens :: Lens' IndexedDocument Text
indexedDocumentIndexLens :: Lens' IndexedDocument Text
indexedDocumentIndexLens = (IndexedDocument -> Text)
-> (IndexedDocument -> Text -> IndexedDocument)
-> Lens' IndexedDocument Text
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens IndexedDocument -> Text
idxDocIndex (\IndexedDocument
x Text
y -> IndexedDocument
x {idxDocIndex = y})
indexedDocumentTypeLens :: Lens' IndexedDocument (Maybe Text)
indexedDocumentTypeLens :: Lens' IndexedDocument (Maybe Text)
indexedDocumentTypeLens = (IndexedDocument -> Maybe Text)
-> (IndexedDocument -> Maybe Text -> IndexedDocument)
-> Lens' IndexedDocument (Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens IndexedDocument -> Maybe Text
idxDocType (\IndexedDocument
x Maybe Text
y -> IndexedDocument
x {idxDocType = y})
indexedDocumentIdLens :: Lens' IndexedDocument Text
indexedDocumentIdLens :: Lens' IndexedDocument Text
indexedDocumentIdLens = (IndexedDocument -> Text)
-> (IndexedDocument -> Text -> IndexedDocument)
-> Lens' IndexedDocument Text
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens IndexedDocument -> Text
idxDocId (\IndexedDocument
x Text
y -> IndexedDocument
x {idxDocId = y})
indexedDocumentVersionLens :: Lens' IndexedDocument Int
indexedDocumentVersionLens :: Lens' IndexedDocument Int
indexedDocumentVersionLens = (IndexedDocument -> Int)
-> (IndexedDocument -> Int -> IndexedDocument)
-> Lens' IndexedDocument Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens IndexedDocument -> Int
idxDocVersion (\IndexedDocument
x Int
y -> IndexedDocument
x {idxDocVersion = y})
indexedDocumentResultLens :: Lens' IndexedDocument Text
indexedDocumentResultLens :: Lens' IndexedDocument Text
indexedDocumentResultLens = (IndexedDocument -> Text)
-> (IndexedDocument -> Text -> IndexedDocument)
-> Lens' IndexedDocument Text
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens IndexedDocument -> Text
idxDocResult (\IndexedDocument
x Text
y -> IndexedDocument
x {idxDocResult = y})
indexedDocumentShardsLens :: Lens' IndexedDocument ShardResult
indexedDocumentShardsLens :: Lens' IndexedDocument ShardResult
indexedDocumentShardsLens = (IndexedDocument -> ShardResult)
-> (IndexedDocument -> ShardResult -> IndexedDocument)
-> Lens' IndexedDocument ShardResult
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens IndexedDocument -> ShardResult
idxDocShards (\IndexedDocument
x ShardResult
y -> IndexedDocument
x {idxDocShards = y})
indexedDocumentSeqNoLens :: Lens' IndexedDocument Int
indexedDocumentSeqNoLens :: Lens' IndexedDocument Int
indexedDocumentSeqNoLens = (IndexedDocument -> Int)
-> (IndexedDocument -> Int -> IndexedDocument)
-> Lens' IndexedDocument Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens IndexedDocument -> Int
idxDocSeqNo (\IndexedDocument
x Int
y -> IndexedDocument
x {idxDocSeqNo = y})
indexedDocumentPrimaryTermLens :: Lens' IndexedDocument Int
indexedDocumentPrimaryTermLens :: Lens' IndexedDocument Int
indexedDocumentPrimaryTermLens = (IndexedDocument -> Int)
-> (IndexedDocument -> Int -> IndexedDocument)
-> Lens' IndexedDocument Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens IndexedDocument -> Int
idxDocPrimaryTerm (\IndexedDocument
x Int
y -> IndexedDocument
x {idxDocPrimaryTerm = y})
data DeletedDocuments = DeletedDocuments
{ DeletedDocuments -> Int
delDocsTook :: Int,
DeletedDocuments -> Bool
delDocsTimedOut :: Bool,
DeletedDocuments -> Int
delDocsTotal :: Int,
DeletedDocuments -> Int
delDocsDeleted :: Int,
DeletedDocuments -> Int
delDocsBatches :: Int,
DeletedDocuments -> Int
delDocsVersionConflicts :: Int,
DeletedDocuments -> Int
delDocsNoops :: Int,
DeletedDocuments -> DeletedDocumentsRetries
delDocsRetries :: DeletedDocumentsRetries,
DeletedDocuments -> Int
delDocsThrottledMillis :: Int,
DeletedDocuments -> Float
delDocsRequestsPerSecond :: Float,
DeletedDocuments -> Int
delDocsThrottledUntilMillis :: Int,
DeletedDocuments -> [Value]
delDocsFailures :: [Value]
}
deriving stock (DeletedDocuments -> DeletedDocuments -> Bool
(DeletedDocuments -> DeletedDocuments -> Bool)
-> (DeletedDocuments -> DeletedDocuments -> Bool)
-> Eq DeletedDocuments
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DeletedDocuments -> DeletedDocuments -> Bool
== :: DeletedDocuments -> DeletedDocuments -> Bool
$c/= :: DeletedDocuments -> DeletedDocuments -> Bool
/= :: DeletedDocuments -> DeletedDocuments -> Bool
Eq, Int -> DeletedDocuments -> ShowS
[DeletedDocuments] -> ShowS
DeletedDocuments -> String
(Int -> DeletedDocuments -> ShowS)
-> (DeletedDocuments -> String)
-> ([DeletedDocuments] -> ShowS)
-> Show DeletedDocuments
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DeletedDocuments -> ShowS
showsPrec :: Int -> DeletedDocuments -> ShowS
$cshow :: DeletedDocuments -> String
show :: DeletedDocuments -> String
$cshowList :: [DeletedDocuments] -> ShowS
showList :: [DeletedDocuments] -> ShowS
Show)
instance FromJSON DeletedDocuments where
parseJSON :: Value -> Parser DeletedDocuments
parseJSON =
String
-> (Object -> Parser DeletedDocuments)
-> Value
-> Parser DeletedDocuments
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"DeletedDocuments" ((Object -> Parser DeletedDocuments)
-> Value -> Parser DeletedDocuments)
-> (Object -> Parser DeletedDocuments)
-> Value
-> Parser DeletedDocuments
forall a b. (a -> b) -> a -> b
$ \Object
v ->
Int
-> Bool
-> Int
-> Int
-> Int
-> Int
-> Int
-> DeletedDocumentsRetries
-> Int
-> Float
-> Int
-> [Value]
-> DeletedDocuments
DeletedDocuments
(Int
-> Bool
-> Int
-> Int
-> Int
-> Int
-> Int
-> DeletedDocumentsRetries
-> Int
-> Float
-> Int
-> [Value]
-> DeletedDocuments)
-> Parser Int
-> Parser
(Bool
-> Int
-> Int
-> Int
-> Int
-> Int
-> DeletedDocumentsRetries
-> Int
-> Float
-> Int
-> [Value]
-> DeletedDocuments)
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
"took"
Parser
(Bool
-> Int
-> Int
-> Int
-> Int
-> Int
-> DeletedDocumentsRetries
-> Int
-> Float
-> Int
-> [Value]
-> DeletedDocuments)
-> Parser Bool
-> Parser
(Int
-> Int
-> Int
-> Int
-> Int
-> DeletedDocumentsRetries
-> Int
-> Float
-> Int
-> [Value]
-> DeletedDocuments)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v
Object -> Key -> Parser Bool
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"timed_out"
Parser
(Int
-> Int
-> Int
-> Int
-> Int
-> DeletedDocumentsRetries
-> Int
-> Float
-> Int
-> [Value]
-> DeletedDocuments)
-> Parser Int
-> Parser
(Int
-> Int
-> Int
-> Int
-> DeletedDocumentsRetries
-> Int
-> Float
-> Int
-> [Value]
-> DeletedDocuments)
forall a b. Parser (a -> b) -> Parser a -> Parser b
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
"total"
Parser
(Int
-> Int
-> Int
-> Int
-> DeletedDocumentsRetries
-> Int
-> Float
-> Int
-> [Value]
-> DeletedDocuments)
-> Parser Int
-> Parser
(Int
-> Int
-> Int
-> DeletedDocumentsRetries
-> Int
-> Float
-> Int
-> [Value]
-> DeletedDocuments)
forall a b. Parser (a -> b) -> Parser a -> Parser b
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
"deleted"
Parser
(Int
-> Int
-> Int
-> DeletedDocumentsRetries
-> Int
-> Float
-> Int
-> [Value]
-> DeletedDocuments)
-> Parser Int
-> Parser
(Int
-> Int
-> DeletedDocumentsRetries
-> Int
-> Float
-> Int
-> [Value]
-> DeletedDocuments)
forall a b. Parser (a -> b) -> Parser a -> Parser b
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
"batches"
Parser
(Int
-> Int
-> DeletedDocumentsRetries
-> Int
-> Float
-> Int
-> [Value]
-> DeletedDocuments)
-> Parser Int
-> Parser
(Int
-> DeletedDocumentsRetries
-> Int
-> Float
-> Int
-> [Value]
-> DeletedDocuments)
forall a b. Parser (a -> b) -> Parser a -> Parser b
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
"version_conflicts"
Parser
(Int
-> DeletedDocumentsRetries
-> Int
-> Float
-> Int
-> [Value]
-> DeletedDocuments)
-> Parser Int
-> Parser
(DeletedDocumentsRetries
-> Int -> Float -> Int -> [Value] -> DeletedDocuments)
forall a b. Parser (a -> b) -> Parser a -> Parser b
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
"noops"
Parser
(DeletedDocumentsRetries
-> Int -> Float -> Int -> [Value] -> DeletedDocuments)
-> Parser DeletedDocumentsRetries
-> Parser (Int -> Float -> Int -> [Value] -> DeletedDocuments)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v
Object -> Key -> Parser DeletedDocumentsRetries
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"retries"
Parser (Int -> Float -> Int -> [Value] -> DeletedDocuments)
-> Parser Int
-> Parser (Float -> Int -> [Value] -> DeletedDocuments)
forall a b. Parser (a -> b) -> Parser a -> Parser b
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
"throttled_millis"
Parser (Float -> Int -> [Value] -> DeletedDocuments)
-> Parser Float -> Parser (Int -> [Value] -> DeletedDocuments)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v
Object -> Key -> Parser Float
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"requests_per_second"
Parser (Int -> [Value] -> DeletedDocuments)
-> Parser Int -> Parser ([Value] -> DeletedDocuments)
forall a b. Parser (a -> b) -> Parser a -> Parser b
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
"throttled_until_millis"
Parser ([Value] -> DeletedDocuments)
-> Parser [Value] -> Parser DeletedDocuments
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v
Object -> Key -> Parser [Value]
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"failures"
deletedDocumentsTookLens :: Lens' DeletedDocuments Int
deletedDocumentsTookLens :: Lens' DeletedDocuments Int
deletedDocumentsTookLens = (DeletedDocuments -> Int)
-> (DeletedDocuments -> Int -> DeletedDocuments)
-> Lens' DeletedDocuments Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens DeletedDocuments -> Int
delDocsTook (\DeletedDocuments
x Int
y -> DeletedDocuments
x {delDocsTook = y})
deletedDocumentsTimedOutLens :: Lens' DeletedDocuments Bool
deletedDocumentsTimedOutLens :: Lens' DeletedDocuments Bool
deletedDocumentsTimedOutLens = (DeletedDocuments -> Bool)
-> (DeletedDocuments -> Bool -> DeletedDocuments)
-> Lens' DeletedDocuments Bool
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens DeletedDocuments -> Bool
delDocsTimedOut (\DeletedDocuments
x Bool
y -> DeletedDocuments
x {delDocsTimedOut = y})
deletedDocumentsTotalLens :: Lens' DeletedDocuments Int
deletedDocumentsTotalLens :: Lens' DeletedDocuments Int
deletedDocumentsTotalLens = (DeletedDocuments -> Int)
-> (DeletedDocuments -> Int -> DeletedDocuments)
-> Lens' DeletedDocuments Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens DeletedDocuments -> Int
delDocsTotal (\DeletedDocuments
x Int
y -> DeletedDocuments
x {delDocsTotal = y})
deletedDocumentsDeletedLens :: Lens' DeletedDocuments Int
deletedDocumentsDeletedLens :: Lens' DeletedDocuments Int
deletedDocumentsDeletedLens = (DeletedDocuments -> Int)
-> (DeletedDocuments -> Int -> DeletedDocuments)
-> Lens' DeletedDocuments Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens DeletedDocuments -> Int
delDocsDeleted (\DeletedDocuments
x Int
y -> DeletedDocuments
x {delDocsDeleted = y})
deletedDocumentsBatchesLens :: Lens' DeletedDocuments Int
deletedDocumentsBatchesLens :: Lens' DeletedDocuments Int
deletedDocumentsBatchesLens = (DeletedDocuments -> Int)
-> (DeletedDocuments -> Int -> DeletedDocuments)
-> Lens' DeletedDocuments Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens DeletedDocuments -> Int
delDocsBatches (\DeletedDocuments
x Int
y -> DeletedDocuments
x {delDocsBatches = y})
deletedDocumentsVersionConflictsLens :: Lens' DeletedDocuments Int
deletedDocumentsVersionConflictsLens :: Lens' DeletedDocuments Int
deletedDocumentsVersionConflictsLens = (DeletedDocuments -> Int)
-> (DeletedDocuments -> Int -> DeletedDocuments)
-> Lens' DeletedDocuments Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens DeletedDocuments -> Int
delDocsVersionConflicts (\DeletedDocuments
x Int
y -> DeletedDocuments
x {delDocsVersionConflicts = y})
deletedDocumentsNoopsLens :: Lens' DeletedDocuments Int
deletedDocumentsNoopsLens :: Lens' DeletedDocuments Int
deletedDocumentsNoopsLens = (DeletedDocuments -> Int)
-> (DeletedDocuments -> Int -> DeletedDocuments)
-> Lens' DeletedDocuments Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens DeletedDocuments -> Int
delDocsNoops (\DeletedDocuments
x Int
y -> DeletedDocuments
x {delDocsNoops = y})
deletedDocumentsRetriesLens :: Lens' DeletedDocuments DeletedDocumentsRetries
deletedDocumentsRetriesLens :: Lens' DeletedDocuments DeletedDocumentsRetries
deletedDocumentsRetriesLens = (DeletedDocuments -> DeletedDocumentsRetries)
-> (DeletedDocuments
-> DeletedDocumentsRetries -> DeletedDocuments)
-> Lens' DeletedDocuments DeletedDocumentsRetries
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens DeletedDocuments -> DeletedDocumentsRetries
delDocsRetries (\DeletedDocuments
x DeletedDocumentsRetries
y -> DeletedDocuments
x {delDocsRetries = y})
deletedDocumentsThrottledMillisLens :: Lens' DeletedDocuments Int
deletedDocumentsThrottledMillisLens :: Lens' DeletedDocuments Int
deletedDocumentsThrottledMillisLens = (DeletedDocuments -> Int)
-> (DeletedDocuments -> Int -> DeletedDocuments)
-> Lens' DeletedDocuments Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens DeletedDocuments -> Int
delDocsThrottledMillis (\DeletedDocuments
x Int
y -> DeletedDocuments
x {delDocsThrottledMillis = y})
deletedDocumentsRequestsPerSecondLens :: Lens' DeletedDocuments Float
deletedDocumentsRequestsPerSecondLens :: Lens' DeletedDocuments Float
deletedDocumentsRequestsPerSecondLens = (DeletedDocuments -> Float)
-> (DeletedDocuments -> Float -> DeletedDocuments)
-> Lens' DeletedDocuments Float
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens DeletedDocuments -> Float
delDocsRequestsPerSecond (\DeletedDocuments
x Float
y -> DeletedDocuments
x {delDocsRequestsPerSecond = y})
deletedDocumentsThrottledUntilMillisLens :: Lens' DeletedDocuments Int
deletedDocumentsThrottledUntilMillisLens :: Lens' DeletedDocuments Int
deletedDocumentsThrottledUntilMillisLens = (DeletedDocuments -> Int)
-> (DeletedDocuments -> Int -> DeletedDocuments)
-> Lens' DeletedDocuments Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens DeletedDocuments -> Int
delDocsThrottledUntilMillis (\DeletedDocuments
x Int
y -> DeletedDocuments
x {delDocsThrottledUntilMillis = y})
deletedDocumentsFailuresLens :: Lens' DeletedDocuments [Value]
deletedDocumentsFailuresLens :: Lens' DeletedDocuments [Value]
deletedDocumentsFailuresLens = (DeletedDocuments -> [Value])
-> (DeletedDocuments -> [Value] -> DeletedDocuments)
-> Lens' DeletedDocuments [Value]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens DeletedDocuments -> [Value]
delDocsFailures (\DeletedDocuments
x [Value]
y -> DeletedDocuments
x {delDocsFailures = y})
data DeletedDocumentsRetries = DeletedDocumentsRetries
{ DeletedDocumentsRetries -> Int
delDocsRetriesBulk :: Int,
DeletedDocumentsRetries -> Int
delDocsRetriesSearch :: Int
}
deriving stock (DeletedDocumentsRetries -> DeletedDocumentsRetries -> Bool
(DeletedDocumentsRetries -> DeletedDocumentsRetries -> Bool)
-> (DeletedDocumentsRetries -> DeletedDocumentsRetries -> Bool)
-> Eq DeletedDocumentsRetries
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DeletedDocumentsRetries -> DeletedDocumentsRetries -> Bool
== :: DeletedDocumentsRetries -> DeletedDocumentsRetries -> Bool
$c/= :: DeletedDocumentsRetries -> DeletedDocumentsRetries -> Bool
/= :: DeletedDocumentsRetries -> DeletedDocumentsRetries -> Bool
Eq, Int -> DeletedDocumentsRetries -> ShowS
[DeletedDocumentsRetries] -> ShowS
DeletedDocumentsRetries -> String
(Int -> DeletedDocumentsRetries -> ShowS)
-> (DeletedDocumentsRetries -> String)
-> ([DeletedDocumentsRetries] -> ShowS)
-> Show DeletedDocumentsRetries
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DeletedDocumentsRetries -> ShowS
showsPrec :: Int -> DeletedDocumentsRetries -> ShowS
$cshow :: DeletedDocumentsRetries -> String
show :: DeletedDocumentsRetries -> String
$cshowList :: [DeletedDocumentsRetries] -> ShowS
showList :: [DeletedDocumentsRetries] -> ShowS
Show)
instance FromJSON DeletedDocumentsRetries where
parseJSON :: Value -> Parser DeletedDocumentsRetries
parseJSON =
String
-> (Object -> Parser DeletedDocumentsRetries)
-> Value
-> Parser DeletedDocumentsRetries
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"DeletedDocumentsRetries" ((Object -> Parser DeletedDocumentsRetries)
-> Value -> Parser DeletedDocumentsRetries)
-> (Object -> Parser DeletedDocumentsRetries)
-> Value
-> Parser DeletedDocumentsRetries
forall a b. (a -> b) -> a -> b
$ \Object
v ->
Int -> Int -> DeletedDocumentsRetries
DeletedDocumentsRetries
(Int -> Int -> DeletedDocumentsRetries)
-> Parser Int -> Parser (Int -> DeletedDocumentsRetries)
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
"bulk"
Parser (Int -> DeletedDocumentsRetries)
-> Parser Int -> Parser DeletedDocumentsRetries
forall a b. Parser (a -> b) -> Parser a -> Parser b
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
"search"
deletedDocumentsRetriesBulkLens :: Lens' DeletedDocumentsRetries Int
deletedDocumentsRetriesBulkLens :: Lens' DeletedDocumentsRetries Int
deletedDocumentsRetriesBulkLens = (DeletedDocumentsRetries -> Int)
-> (DeletedDocumentsRetries -> Int -> DeletedDocumentsRetries)
-> Lens' DeletedDocumentsRetries Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens DeletedDocumentsRetries -> Int
delDocsRetriesBulk (\DeletedDocumentsRetries
x Int
y -> DeletedDocumentsRetries
x {delDocsRetriesBulk = y})
deletedDocumentsRetriesSearchLens :: Lens' DeletedDocumentsRetries Int
deletedDocumentsRetriesSearchLens :: Lens' DeletedDocumentsRetries Int
deletedDocumentsRetriesSearchLens = (DeletedDocumentsRetries -> Int)
-> (DeletedDocumentsRetries -> Int -> DeletedDocumentsRetries)
-> Lens' DeletedDocumentsRetries Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens DeletedDocumentsRetries -> Int
delDocsRetriesSearch (\DeletedDocumentsRetries
x Int
y -> DeletedDocumentsRetries
x {delDocsRetriesSearch = y})