{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE OverloadedStrings #-}
module TestContainers.Docker.State
( State,
containerState,
Status (..),
stateStatus,
stateOOMKilled,
statePid,
stateExitCode,
stateError,
stateStartedAt,
stateFinishedAt,
)
where
import Control.Exception (Exception, throw)
import Data.Aeson (Value)
import qualified Data.Aeson.Optics as Optics
import Data.Text (Text)
import Optics.Operators ((^?))
import Optics.Optic ((%))
import TestContainers.Docker.Internal (InspectOutput)
data StateInvalidException = StateInvalidException
deriving stock (StateInvalidException -> StateInvalidException -> Bool
forall (a :: OpticKind).
(a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StateInvalidException -> StateInvalidException -> Bool
$c/= :: StateInvalidException -> StateInvalidException -> Bool
== :: StateInvalidException -> StateInvalidException -> Bool
$c== :: StateInvalidException -> StateInvalidException -> Bool
Eq, Int -> StateInvalidException -> ShowS
[StateInvalidException] -> ShowS
StateInvalidException -> String
forall (a :: OpticKind).
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StateInvalidException] -> ShowS
$cshowList :: [StateInvalidException] -> ShowS
show :: StateInvalidException -> String
$cshow :: StateInvalidException -> String
showsPrec :: Int -> StateInvalidException -> ShowS
$cshowsPrec :: Int -> StateInvalidException -> ShowS
Show)
instance Exception StateInvalidException
data Status
= Created
| Running
| Paused
| Restarting
| Removing
| Exited
| Dead
| Other Text
deriving (Status -> Status -> Bool
forall (a :: OpticKind).
(a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Status -> Status -> Bool
$c/= :: Status -> Status -> Bool
== :: Status -> Status -> Bool
$c== :: Status -> Status -> Bool
Eq, Int -> Status -> ShowS
[Status] -> ShowS
Status -> String
forall (a :: OpticKind).
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Status] -> ShowS
$cshowList :: [Status] -> ShowS
show :: Status -> String
$cshow :: Status -> String
showsPrec :: Int -> Status -> ShowS
$cshowsPrec :: Int -> Status -> ShowS
Show)
newtype State = State Value
containerState :: InspectOutput -> State
containerState :: Value -> State
containerState Value
inspectOutput =
case Value
inspectOutput forall (k :: OpticKind) (s :: OpticKind) (is :: IxList)
(a :: OpticKind).
Is k An_AffineFold =>
s -> Optic' k is s a -> Maybe a
^? forall (t :: OpticKind).
AsValue t =>
Key -> AffineTraversal' t Value
Optics.key Key
"State" of
Just Value
state -> Value -> State
State Value
state
Maybe Value
Nothing -> Value -> State
State Value
"dummy"
stateStatus :: State -> Status
stateStatus :: State -> Status
stateStatus (State Value
value) =
case Value
value
forall (k :: OpticKind) (s :: OpticKind) (is :: IxList)
(a :: OpticKind).
Is k An_AffineFold =>
s -> Optic' k is s a -> Maybe a
^? forall (t :: OpticKind).
AsValue t =>
Key -> AffineTraversal' t Value
Optics.key Key
"Status"
forall (k :: OpticKind) (l :: OpticKind) (m :: OpticKind)
(is :: IxList) (js :: IxList) (ks :: IxList) (s :: OpticKind)
(t :: OpticKind) (u :: OpticKind) (v :: OpticKind) (a :: OpticKind)
(b :: OpticKind).
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% forall (t :: OpticKind). AsValue t => Prism' t Text
Optics._String of
Just Text
"created" -> Status
Created
Just Text
"running" -> Status
Running
Just Text
"paused" -> Status
Paused
Just Text
"restarting" -> Status
Restarting
Just Text
"removing" -> Status
Removing
Just Text
"exited" -> Status
Exited
Just Text
"dead" -> Status
Dead
Just Text
other -> Text -> Status
Other Text
other
Maybe Text
Nothing -> forall a (e :: OpticKind). Exception e => e -> a
throw StateInvalidException
StateInvalidException
stateOOMKilled :: State -> Bool
stateOOMKilled :: State -> Bool
stateOOMKilled (State Value
value) =
case Value
value
forall (k :: OpticKind) (s :: OpticKind) (is :: IxList)
(a :: OpticKind).
Is k An_AffineFold =>
s -> Optic' k is s a -> Maybe a
^? forall (t :: OpticKind).
AsValue t =>
Key -> AffineTraversal' t Value
Optics.key Key
"OOMKilled"
forall (k :: OpticKind) (l :: OpticKind) (m :: OpticKind)
(is :: IxList) (js :: IxList) (ks :: IxList) (s :: OpticKind)
(t :: OpticKind) (u :: OpticKind) (v :: OpticKind) (a :: OpticKind)
(b :: OpticKind).
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% forall (t :: OpticKind). AsValue t => Prism' t Bool
Optics._Bool of
Just Bool
True -> Bool
True
Maybe Bool
_ -> Bool
False
statePid :: State -> Maybe Int
statePid :: State -> Maybe Int
statePid (State Value
value) =
case Value
value
forall (k :: OpticKind) (s :: OpticKind) (is :: IxList)
(a :: OpticKind).
Is k An_AffineFold =>
s -> Optic' k is s a -> Maybe a
^? forall (t :: OpticKind).
AsValue t =>
Key -> AffineTraversal' t Value
Optics.key Key
"Pid"
forall (k :: OpticKind) (l :: OpticKind) (m :: OpticKind)
(is :: IxList) (js :: IxList) (ks :: IxList) (s :: OpticKind)
(t :: OpticKind) (u :: OpticKind) (v :: OpticKind) (a :: OpticKind)
(b :: OpticKind).
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% forall (t :: OpticKind). AsNumber t => Prism' t Integer
Optics._Integer of
Just Integer
pid -> forall (a :: OpticKind). a -> Maybe a
Just (forall (a :: OpticKind) (b :: OpticKind).
(Integral a, Num b) =>
a -> b
fromIntegral Integer
pid)
Maybe Integer
_ -> forall (a :: OpticKind). Maybe a
Nothing
stateExitCode :: State -> Maybe Int
stateExitCode :: State -> Maybe Int
stateExitCode (State Value
value) =
case Value
value
forall (k :: OpticKind) (s :: OpticKind) (is :: IxList)
(a :: OpticKind).
Is k An_AffineFold =>
s -> Optic' k is s a -> Maybe a
^? forall (t :: OpticKind).
AsValue t =>
Key -> AffineTraversal' t Value
Optics.key Key
"ExitCode"
forall (k :: OpticKind) (l :: OpticKind) (m :: OpticKind)
(is :: IxList) (js :: IxList) (ks :: IxList) (s :: OpticKind)
(t :: OpticKind) (u :: OpticKind) (v :: OpticKind) (a :: OpticKind)
(b :: OpticKind).
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% forall (t :: OpticKind). AsNumber t => Prism' t Integer
Optics._Integer of
Just Integer
exitCode -> forall (a :: OpticKind). a -> Maybe a
Just (forall (a :: OpticKind) (b :: OpticKind).
(Integral a, Num b) =>
a -> b
fromIntegral Integer
exitCode)
Maybe Integer
_ -> forall (a :: OpticKind). Maybe a
Nothing
stateError :: State -> Maybe Text
stateError :: State -> Maybe Text
stateError (State Value
value) =
case Value
value
forall (k :: OpticKind) (s :: OpticKind) (is :: IxList)
(a :: OpticKind).
Is k An_AffineFold =>
s -> Optic' k is s a -> Maybe a
^? forall (t :: OpticKind).
AsValue t =>
Key -> AffineTraversal' t Value
Optics.key Key
"Error"
forall (k :: OpticKind) (l :: OpticKind) (m :: OpticKind)
(is :: IxList) (js :: IxList) (ks :: IxList) (s :: OpticKind)
(t :: OpticKind) (u :: OpticKind) (v :: OpticKind) (a :: OpticKind)
(b :: OpticKind).
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% forall (t :: OpticKind). AsValue t => Prism' t Text
Optics._String of
Just Text
err -> forall (a :: OpticKind). a -> Maybe a
Just Text
err
Maybe Text
_ -> forall (a :: OpticKind). Maybe a
Nothing
stateStartedAt :: State -> Maybe Text
stateStartedAt :: State -> Maybe Text
stateStartedAt (State Value
value) =
case Value
value
forall (k :: OpticKind) (s :: OpticKind) (is :: IxList)
(a :: OpticKind).
Is k An_AffineFold =>
s -> Optic' k is s a -> Maybe a
^? forall (t :: OpticKind).
AsValue t =>
Key -> AffineTraversal' t Value
Optics.key Key
"StartedAt"
forall (k :: OpticKind) (l :: OpticKind) (m :: OpticKind)
(is :: IxList) (js :: IxList) (ks :: IxList) (s :: OpticKind)
(t :: OpticKind) (u :: OpticKind) (v :: OpticKind) (a :: OpticKind)
(b :: OpticKind).
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% forall (t :: OpticKind). AsValue t => Prism' t Text
Optics._String of
Just Text
err -> forall (a :: OpticKind). a -> Maybe a
Just Text
err
Maybe Text
_ -> forall (a :: OpticKind). Maybe a
Nothing
stateFinishedAt :: State -> Maybe Text
stateFinishedAt :: State -> Maybe Text
stateFinishedAt (State Value
value) =
case Value
value
forall (k :: OpticKind) (s :: OpticKind) (is :: IxList)
(a :: OpticKind).
Is k An_AffineFold =>
s -> Optic' k is s a -> Maybe a
^? forall (t :: OpticKind).
AsValue t =>
Key -> AffineTraversal' t Value
Optics.key Key
"FinishedAt"
forall (k :: OpticKind) (l :: OpticKind) (m :: OpticKind)
(is :: IxList) (js :: IxList) (ks :: IxList) (s :: OpticKind)
(t :: OpticKind) (u :: OpticKind) (v :: OpticKind) (a :: OpticKind)
(b :: OpticKind).
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% forall (t :: OpticKind). AsValue t => Prism' t Text
Optics._String of
Just Text
err -> forall (a :: OpticKind). a -> Maybe a
Just Text
err
Maybe Text
_ -> forall (a :: OpticKind). Maybe a
Nothing