-- Copyright (c) 2016-present, SoundCloud Ltd. -- All rights reserved. -- -- This source code is distributed under the terms of a MIT license, -- found in the LICENSE file. {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE TemplateHaskell #-} module Kubernetes.Model.V1.ComponentStatusList ( ComponentStatusList (..) , kind , apiVersion , metadata , items , mkComponentStatusList ) where import Control.Lens.TH (makeLenses) import Data.Aeson.TH (defaultOptions, deriveJSON, fieldLabelModifier) import Data.Text (Text) import GHC.Generics (Generic) import Kubernetes.Model.Unversioned.ListMeta (ListMeta) import Kubernetes.Model.V1.ComponentStatus (ComponentStatus) import Prelude hiding (drop, error, max, min) import qualified Prelude as P import Test.QuickCheck (Arbitrary, arbitrary) import Test.QuickCheck.Instances () -- | Status of all the conditions for the component as a list of ComponentStatus objects. data ComponentStatusList = ComponentStatusList { _kind :: !(Maybe Text) , _apiVersion :: !(Maybe Text) , _metadata :: !(Maybe ListMeta) , _items :: !([ComponentStatus]) } deriving (Show, Eq, Generic) makeLenses ''ComponentStatusList $(deriveJSON defaultOptions{fieldLabelModifier = (\n -> if n == "_type_" then "type" else P.drop 1 n)} ''ComponentStatusList) instance Arbitrary ComponentStatusList where arbitrary = ComponentStatusList <$> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary -- | Use this method to build a ComponentStatusList mkComponentStatusList :: [ComponentStatus] -> ComponentStatusList mkComponentStatusList xitemsx = ComponentStatusList Nothing Nothing Nothing xitemsx