{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE TypeOperators #-}
module Test.Sandwich.Contexts.Kubernetes.FindImages (
findAllImages
, findAllImages'
) where
import Control.Lens
import Data.Aeson (FromJSON)
import qualified Data.Aeson as A
import Data.Aeson.Lens
import Data.Text as T
import qualified Data.Yaml as Yaml
import Kubernetes.OpenAPI.Model as Kubernetes
import Kubernetes.OpenAPI.ModelLens as Kubernetes
import Relude
import Test.Sandwich.Contexts.Kubernetes.Util.Aeson
findAllImages :: Text -> [Text]
findAllImages :: Text -> [Text]
findAllImages = (Text -> [Text]) -> [Text] -> [Text]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
Relude.concatMap Text -> [Text]
findAllImages' ([Text] -> [Text]) -> (Text -> [Text]) -> Text -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HasCallStack => Text -> Text -> [Text]
Text -> Text -> [Text]
T.splitOn Text
"---\n"
findAllImages' :: Text -> [Text]
findAllImages' :: Text -> [Text]
findAllImages' (Text -> Either ParseException V1Pod
forall a. FromJSON a => Text -> Either ParseException a
decode -> Right x :: V1Pod
x@(V1Pod {v1PodKind :: V1Pod -> Maybe Text
v1PodKind=(Just Text
"Pod")})) = [Text] -> (V1PodSpec -> [Text]) -> Maybe V1PodSpec -> [Text]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] V1PodSpec -> [Text]
imagesFromPodSpec (V1Pod -> Maybe V1PodSpec
v1PodSpec V1Pod
x)
findAllImages' (Text -> Either ParseException V1Deployment
forall a. FromJSON a => Text -> Either ParseException a
decode -> Right x :: V1Deployment
x@(V1Deployment {v1DeploymentKind :: V1Deployment -> Maybe Text
v1DeploymentKind=(Just Text
"Deployment")})) = [Text] -> (V1PodSpec -> [Text]) -> Maybe V1PodSpec -> [Text]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] V1PodSpec -> [Text]
imagesFromPodSpec Maybe V1PodSpec
maybePodSpec
where
maybePodSpec :: Maybe V1PodSpec
maybePodSpec :: Maybe V1PodSpec
maybePodSpec = V1Deployment
x V1Deployment
-> Getting (First V1PodSpec) V1Deployment V1PodSpec
-> Maybe V1PodSpec
forall s a. s -> Getting (First a) s a -> Maybe a
^? ((Maybe V1DeploymentSpec
-> Const (First V1PodSpec) (Maybe V1DeploymentSpec))
-> V1Deployment -> Const (First V1PodSpec) V1Deployment
Lens_' V1Deployment (Maybe V1DeploymentSpec)
v1DeploymentSpecL ((Maybe V1DeploymentSpec
-> Const (First V1PodSpec) (Maybe V1DeploymentSpec))
-> V1Deployment -> Const (First V1PodSpec) V1Deployment)
-> ((V1PodSpec -> Const (First V1PodSpec) V1PodSpec)
-> Maybe V1DeploymentSpec
-> Const (First V1PodSpec) (Maybe V1DeploymentSpec))
-> Getting (First V1PodSpec) V1Deployment V1PodSpec
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (V1DeploymentSpec -> Const (First V1PodSpec) V1DeploymentSpec)
-> Maybe V1DeploymentSpec
-> Const (First V1PodSpec) (Maybe V1DeploymentSpec)
forall a b (p :: * -> * -> *) (f :: * -> *).
(Choice p, Applicative f) =>
p a (f b) -> p (Maybe a) (f (Maybe b))
_Just ((V1DeploymentSpec -> Const (First V1PodSpec) V1DeploymentSpec)
-> Maybe V1DeploymentSpec
-> Const (First V1PodSpec) (Maybe V1DeploymentSpec))
-> ((V1PodSpec -> Const (First V1PodSpec) V1PodSpec)
-> V1DeploymentSpec -> Const (First V1PodSpec) V1DeploymentSpec)
-> (V1PodSpec -> Const (First V1PodSpec) V1PodSpec)
-> Maybe V1DeploymentSpec
-> Const (First V1PodSpec) (Maybe V1DeploymentSpec)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (V1PodTemplateSpec -> Const (First V1PodSpec) V1PodTemplateSpec)
-> V1DeploymentSpec -> Const (First V1PodSpec) V1DeploymentSpec
Lens_' V1DeploymentSpec V1PodTemplateSpec
v1DeploymentSpecTemplateL ((V1PodTemplateSpec -> Const (First V1PodSpec) V1PodTemplateSpec)
-> V1DeploymentSpec -> Const (First V1PodSpec) V1DeploymentSpec)
-> ((V1PodSpec -> Const (First V1PodSpec) V1PodSpec)
-> V1PodTemplateSpec -> Const (First V1PodSpec) V1PodTemplateSpec)
-> (V1PodSpec -> Const (First V1PodSpec) V1PodSpec)
-> V1DeploymentSpec
-> Const (First V1PodSpec) V1DeploymentSpec
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe V1PodSpec -> Const (First V1PodSpec) (Maybe V1PodSpec))
-> V1PodTemplateSpec -> Const (First V1PodSpec) V1PodTemplateSpec
Lens_' V1PodTemplateSpec (Maybe V1PodSpec)
v1PodTemplateSpecSpecL ((Maybe V1PodSpec -> Const (First V1PodSpec) (Maybe V1PodSpec))
-> V1PodTemplateSpec -> Const (First V1PodSpec) V1PodTemplateSpec)
-> ((V1PodSpec -> Const (First V1PodSpec) V1PodSpec)
-> Maybe V1PodSpec -> Const (First V1PodSpec) (Maybe V1PodSpec))
-> (V1PodSpec -> Const (First V1PodSpec) V1PodSpec)
-> V1PodTemplateSpec
-> Const (First V1PodSpec) V1PodTemplateSpec
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (V1PodSpec -> Const (First V1PodSpec) V1PodSpec)
-> Maybe V1PodSpec -> Const (First V1PodSpec) (Maybe V1PodSpec)
forall a b (p :: * -> * -> *) (f :: * -> *).
(Choice p, Applicative f) =>
p a (f b) -> p (Maybe a) (f (Maybe b))
_Just)
findAllImages' (Text -> Either ParseException V1StatefulSet
forall a. FromJSON a => Text -> Either ParseException a
decode -> Right x :: V1StatefulSet
x@(V1StatefulSet {v1StatefulSetKind :: V1StatefulSet -> Maybe Text
v1StatefulSetKind=(Just Text
"StatefulSet")})) = [Text] -> (V1PodSpec -> [Text]) -> Maybe V1PodSpec -> [Text]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] V1PodSpec -> [Text]
imagesFromPodSpec Maybe V1PodSpec
maybePodSpec
where
maybePodSpec :: Maybe V1PodSpec
maybePodSpec :: Maybe V1PodSpec
maybePodSpec = V1StatefulSet
x V1StatefulSet
-> Getting (First V1PodSpec) V1StatefulSet V1PodSpec
-> Maybe V1PodSpec
forall s a. s -> Getting (First a) s a -> Maybe a
^? ((Maybe V1StatefulSetSpec
-> Const (First V1PodSpec) (Maybe V1StatefulSetSpec))
-> V1StatefulSet -> Const (First V1PodSpec) V1StatefulSet
Lens_' V1StatefulSet (Maybe V1StatefulSetSpec)
v1StatefulSetSpecL ((Maybe V1StatefulSetSpec
-> Const (First V1PodSpec) (Maybe V1StatefulSetSpec))
-> V1StatefulSet -> Const (First V1PodSpec) V1StatefulSet)
-> ((V1PodSpec -> Const (First V1PodSpec) V1PodSpec)
-> Maybe V1StatefulSetSpec
-> Const (First V1PodSpec) (Maybe V1StatefulSetSpec))
-> Getting (First V1PodSpec) V1StatefulSet V1PodSpec
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (V1StatefulSetSpec -> Const (First V1PodSpec) V1StatefulSetSpec)
-> Maybe V1StatefulSetSpec
-> Const (First V1PodSpec) (Maybe V1StatefulSetSpec)
forall a b (p :: * -> * -> *) (f :: * -> *).
(Choice p, Applicative f) =>
p a (f b) -> p (Maybe a) (f (Maybe b))
_Just ((V1StatefulSetSpec -> Const (First V1PodSpec) V1StatefulSetSpec)
-> Maybe V1StatefulSetSpec
-> Const (First V1PodSpec) (Maybe V1StatefulSetSpec))
-> ((V1PodSpec -> Const (First V1PodSpec) V1PodSpec)
-> V1StatefulSetSpec -> Const (First V1PodSpec) V1StatefulSetSpec)
-> (V1PodSpec -> Const (First V1PodSpec) V1PodSpec)
-> Maybe V1StatefulSetSpec
-> Const (First V1PodSpec) (Maybe V1StatefulSetSpec)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (V1PodTemplateSpec -> Const (First V1PodSpec) V1PodTemplateSpec)
-> V1StatefulSetSpec -> Const (First V1PodSpec) V1StatefulSetSpec
Lens_' V1StatefulSetSpec V1PodTemplateSpec
v1StatefulSetSpecTemplateL ((V1PodTemplateSpec -> Const (First V1PodSpec) V1PodTemplateSpec)
-> V1StatefulSetSpec -> Const (First V1PodSpec) V1StatefulSetSpec)
-> ((V1PodSpec -> Const (First V1PodSpec) V1PodSpec)
-> V1PodTemplateSpec -> Const (First V1PodSpec) V1PodTemplateSpec)
-> (V1PodSpec -> Const (First V1PodSpec) V1PodSpec)
-> V1StatefulSetSpec
-> Const (First V1PodSpec) V1StatefulSetSpec
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe V1PodSpec -> Const (First V1PodSpec) (Maybe V1PodSpec))
-> V1PodTemplateSpec -> Const (First V1PodSpec) V1PodTemplateSpec
Lens_' V1PodTemplateSpec (Maybe V1PodSpec)
v1PodTemplateSpecSpecL ((Maybe V1PodSpec -> Const (First V1PodSpec) (Maybe V1PodSpec))
-> V1PodTemplateSpec -> Const (First V1PodSpec) V1PodTemplateSpec)
-> ((V1PodSpec -> Const (First V1PodSpec) V1PodSpec)
-> Maybe V1PodSpec -> Const (First V1PodSpec) (Maybe V1PodSpec))
-> (V1PodSpec -> Const (First V1PodSpec) V1PodSpec)
-> V1PodTemplateSpec
-> Const (First V1PodSpec) V1PodTemplateSpec
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (V1PodSpec -> Const (First V1PodSpec) V1PodSpec)
-> Maybe V1PodSpec -> Const (First V1PodSpec) (Maybe V1PodSpec)
forall a b (p :: * -> * -> *) (f :: * -> *).
(Choice p, Applicative f) =>
p a (f b) -> p (Maybe a) (f (Maybe b))
_Just)
findAllImages' (Text -> Either ParseException V1DaemonSet
forall a. FromJSON a => Text -> Either ParseException a
decode -> Right x :: V1DaemonSet
x@(V1DaemonSet {v1DaemonSetKind :: V1DaemonSet -> Maybe Text
v1DaemonSetKind=(Just Text
"DaemonSet")})) = [Text] -> (V1PodSpec -> [Text]) -> Maybe V1PodSpec -> [Text]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] V1PodSpec -> [Text]
imagesFromPodSpec Maybe V1PodSpec
maybePodSpec
where
maybePodSpec :: Maybe V1PodSpec
maybePodSpec :: Maybe V1PodSpec
maybePodSpec = V1DaemonSet
x V1DaemonSet
-> Getting (First V1PodSpec) V1DaemonSet V1PodSpec
-> Maybe V1PodSpec
forall s a. s -> Getting (First a) s a -> Maybe a
^? ((Maybe V1DaemonSetSpec
-> Const (First V1PodSpec) (Maybe V1DaemonSetSpec))
-> V1DaemonSet -> Const (First V1PodSpec) V1DaemonSet
Lens_' V1DaemonSet (Maybe V1DaemonSetSpec)
v1DaemonSetSpecL ((Maybe V1DaemonSetSpec
-> Const (First V1PodSpec) (Maybe V1DaemonSetSpec))
-> V1DaemonSet -> Const (First V1PodSpec) V1DaemonSet)
-> ((V1PodSpec -> Const (First V1PodSpec) V1PodSpec)
-> Maybe V1DaemonSetSpec
-> Const (First V1PodSpec) (Maybe V1DaemonSetSpec))
-> Getting (First V1PodSpec) V1DaemonSet V1PodSpec
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (V1DaemonSetSpec -> Const (First V1PodSpec) V1DaemonSetSpec)
-> Maybe V1DaemonSetSpec
-> Const (First V1PodSpec) (Maybe V1DaemonSetSpec)
forall a b (p :: * -> * -> *) (f :: * -> *).
(Choice p, Applicative f) =>
p a (f b) -> p (Maybe a) (f (Maybe b))
_Just ((V1DaemonSetSpec -> Const (First V1PodSpec) V1DaemonSetSpec)
-> Maybe V1DaemonSetSpec
-> Const (First V1PodSpec) (Maybe V1DaemonSetSpec))
-> ((V1PodSpec -> Const (First V1PodSpec) V1PodSpec)
-> V1DaemonSetSpec -> Const (First V1PodSpec) V1DaemonSetSpec)
-> (V1PodSpec -> Const (First V1PodSpec) V1PodSpec)
-> Maybe V1DaemonSetSpec
-> Const (First V1PodSpec) (Maybe V1DaemonSetSpec)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (V1PodTemplateSpec -> Const (First V1PodSpec) V1PodTemplateSpec)
-> V1DaemonSetSpec -> Const (First V1PodSpec) V1DaemonSetSpec
Lens_' V1DaemonSetSpec V1PodTemplateSpec
v1DaemonSetSpecTemplateL ((V1PodTemplateSpec -> Const (First V1PodSpec) V1PodTemplateSpec)
-> V1DaemonSetSpec -> Const (First V1PodSpec) V1DaemonSetSpec)
-> ((V1PodSpec -> Const (First V1PodSpec) V1PodSpec)
-> V1PodTemplateSpec -> Const (First V1PodSpec) V1PodTemplateSpec)
-> (V1PodSpec -> Const (First V1PodSpec) V1PodSpec)
-> V1DaemonSetSpec
-> Const (First V1PodSpec) V1DaemonSetSpec
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe V1PodSpec -> Const (First V1PodSpec) (Maybe V1PodSpec))
-> V1PodTemplateSpec -> Const (First V1PodSpec) V1PodTemplateSpec
Lens_' V1PodTemplateSpec (Maybe V1PodSpec)
v1PodTemplateSpecSpecL ((Maybe V1PodSpec -> Const (First V1PodSpec) (Maybe V1PodSpec))
-> V1PodTemplateSpec -> Const (First V1PodSpec) V1PodTemplateSpec)
-> ((V1PodSpec -> Const (First V1PodSpec) V1PodSpec)
-> Maybe V1PodSpec -> Const (First V1PodSpec) (Maybe V1PodSpec))
-> (V1PodSpec -> Const (First V1PodSpec) V1PodSpec)
-> V1PodTemplateSpec
-> Const (First V1PodSpec) V1PodTemplateSpec
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (V1PodSpec -> Const (First V1PodSpec) V1PodSpec)
-> Maybe V1PodSpec -> Const (First V1PodSpec) (Maybe V1PodSpec)
forall a b (p :: * -> * -> *) (f :: * -> *).
(Choice p, Applicative f) =>
p a (f b) -> p (Maybe a) (f (Maybe b))
_Just)
findAllImages' (Text -> Either ParseException Value
forall a. FromJSON a => Text -> Either ParseException a
decode -> Right x :: Value
x@(A.Object KeyMap Value
obj))
| Just (A.String Text
"Tenant") <- Text -> KeyMap Value -> Maybe Value
forall v. Text -> KeyMap v -> Maybe v
aesonLookup Text
"kind" KeyMap Value
obj
, Just (A.String Text
img) <- Value
x Value -> Getting (First Value) Value Value -> Maybe Value
forall s a. s -> Getting (First a) s a -> Maybe a
^? ((KeyMap Value -> Const (First Value) (KeyMap Value))
-> Value -> Const (First Value) Value
forall t. AsValue t => Prism' t (KeyMap Value)
Prism' Value (KeyMap Value)
_Object ((KeyMap Value -> Const (First Value) (KeyMap Value))
-> Value -> Const (First Value) Value)
-> ((Value -> Const (First Value) Value)
-> KeyMap Value -> Const (First Value) (KeyMap Value))
-> Getting (First Value) Value Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Index (KeyMap Value)
-> Traversal' (KeyMap Value) (IxValue (KeyMap Value))
forall m. Ixed m => Index m -> Traversal' m (IxValue m)
ix Key
Index (KeyMap Value)
"spec" ((IxValue (KeyMap Value)
-> Const (First Value) (IxValue (KeyMap Value)))
-> KeyMap Value -> Const (First Value) (KeyMap Value))
-> ((Value -> Const (First Value) Value)
-> IxValue (KeyMap Value)
-> Const (First Value) (IxValue (KeyMap Value)))
-> (Value -> Const (First Value) Value)
-> KeyMap Value
-> Const (First Value) (KeyMap Value)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (KeyMap Value -> Const (First Value) (KeyMap Value))
-> IxValue (KeyMap Value)
-> Const (First Value) (IxValue (KeyMap Value))
forall t. AsValue t => Prism' t (KeyMap Value)
Prism' (IxValue (KeyMap Value)) (KeyMap Value)
_Object ((KeyMap Value -> Const (First Value) (KeyMap Value))
-> IxValue (KeyMap Value)
-> Const (First Value) (IxValue (KeyMap Value)))
-> ((Value -> Const (First Value) Value)
-> KeyMap Value -> Const (First Value) (KeyMap Value))
-> (Value -> Const (First Value) Value)
-> IxValue (KeyMap Value)
-> Const (First Value) (IxValue (KeyMap Value))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Index (KeyMap Value)
-> Traversal' (KeyMap Value) (IxValue (KeyMap Value))
forall m. Ixed m => Index m -> Traversal' m (IxValue m)
ix Key
Index (KeyMap Value)
"image") = [Text
img]
findAllImages' Text
_ = []
imagesFromPodSpec :: V1PodSpec -> [Text]
imagesFromPodSpec :: V1PodSpec -> [Text]
imagesFromPodSpec V1PodSpec
x = (V1Container -> Maybe Text) -> [V1Container] -> [Text]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe V1Container -> Maybe Text
v1ContainerImage [V1Container]
allContainers
where
allContainers :: [V1Container]
allContainers = V1PodSpec
x V1PodSpec
-> Getting [V1Container] V1PodSpec [V1Container] -> [V1Container]
forall s a. s -> Getting a s a -> a
^. Getting [V1Container] V1PodSpec [V1Container]
Lens_' V1PodSpec [V1Container]
v1PodSpecContainersL [V1Container] -> [V1Container] -> [V1Container]
forall a. Semigroup a => a -> a -> a
<> [V1Container] -> Maybe [V1Container] -> [V1Container]
forall a. a -> Maybe a -> a
fromMaybe [] (V1PodSpec
x V1PodSpec
-> Getting (Maybe [V1Container]) V1PodSpec (Maybe [V1Container])
-> Maybe [V1Container]
forall s a. s -> Getting a s a -> a
^. Getting (Maybe [V1Container]) V1PodSpec (Maybe [V1Container])
Lens_' V1PodSpec (Maybe [V1Container])
v1PodSpecInitContainersL)
decode :: FromJSON a => Text -> Either Yaml.ParseException a
decode :: forall a. FromJSON a => Text -> Either ParseException a
decode = ByteString -> Either ParseException a
forall a. FromJSON a => ByteString -> Either ParseException a
Yaml.decodeEither' (ByteString -> Either ParseException a)
-> (Text -> ByteString) -> Text -> Either ParseException a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
forall a b. ConvertUtf8 a b => a -> b
encodeUtf8