Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data AdmissionReviewRequest = AdmissionReviewRequest {
- apiVersion :: Text
- kind :: Text
- request :: AdmissionRequest
- data AdmissionReviewResponse = AdmissionReviewResponse {
- apiVersion :: Text
- kind :: Text
- response :: AdmissionResponse
- admissionReviewResponse :: AdmissionResponse -> AdmissionReviewResponse
- data AdmissionRequest = AdmissionRequest {
- uid :: UID
- kind :: GroupVersionKind
- resource :: GroupVersionResource
- subResource :: Maybe Text
- requestKind :: Maybe GroupVersionKind
- requestResource :: Maybe GroupVersionResource
- requestSubResource :: Maybe Text
- name :: Maybe Text
- namespace :: Maybe Text
- operation :: Operation
- userInfo :: UserInfo
- object :: Maybe Value
- oldObject :: Maybe Value
- dryRun :: Maybe Bool
- options :: Maybe Value
- data AdmissionResponse = AdmissionResponse {}
- newtype UID = UID Text
- data Operation
- data UserInfo = UserInfo {}
- data GroupVersionKind = GroupVersionKind {}
- data GroupVersionResource = GroupVersionResource {}
- data RawExtension = RawExtension {}
- data Status = Status {}
- data ListMeta = ListMeta {}
- data StatusStatus
- data StatusReason
- data StatusDetails = StatusDetails {}
- data StatusCause = StatusCause {}
- data CauseType
- data TypeMeta = TypeMeta {}
- data PatchType = JSONPatch
- data PatchOperation = PatchOperation {}
- newtype Patch = Patch [PatchOperation]
- data PatchOp
- lowerFirst :: String -> String
Documentation
data AdmissionReviewRequest Source #
This is the type of the request that arrives for the admission webhook see https://godoc.org/k8s.io/api/admission/v1beta1#AdmissionReview
Instances
data AdmissionReviewResponse Source #
This is the type of the response returned to the admission webhook see https://godoc.org/k8s.io/api/admission/v1beta1#AdmissionReview
Instances
data AdmissionRequest Source #
AdmissionRequest | |
|
Instances
data AdmissionResponse Source #
AdmissionResponse describes an admission response. see: https://godoc.org/k8s.io/api/admission/v1beta1#AdmissionResponse
AdmissionResponse | |
|
Instances
UID is a type that holds unique ID values, including UUIDs. Because we don't ONLY use UUIDs, this is an alias to string Being a type captures intent and helps make sure that UIDs and names do not get conflated.
Operation is the type of resource operation being checked for admission control
Instances
Show Operation Source # | |
Generic Operation Source # | |
ToJSON Operation Source # | |
Defined in Kubernetes.Webhook.Types | |
FromJSON Operation Source # | |
type Rep Operation Source # | |
Defined in Kubernetes.Webhook.Types type Rep Operation = D1 (MetaData "Operation" "Kubernetes.Webhook.Types" "kubernetes-webhook-haskell-0.2.0.1-4tZKSOtYpWBIcF63fJw3Bd" False) ((C1 (MetaCons "Create" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Update" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Delete" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Connect" PrefixI False) (U1 :: Type -> Type))) |
UserInfo holds the information about the user needed to implement the user.Info interface.
UserInfo | |
|
Instances
Show UserInfo Source # | |
Generic UserInfo Source # | |
ToJSON UserInfo Source # | |
Defined in Kubernetes.Webhook.Types | |
FromJSON UserInfo Source # | |
type Rep UserInfo Source # | |
Defined in Kubernetes.Webhook.Types type Rep UserInfo = D1 (MetaData "UserInfo" "Kubernetes.Webhook.Types" "kubernetes-webhook-haskell-0.2.0.1-4tZKSOtYpWBIcF63fJw3Bd" False) (C1 (MetaCons "UserInfo" PrefixI True) ((S1 (MetaSel (Just "username") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "uid") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Text)) :*: (S1 (MetaSel (Just "groups") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe [Text])) :*: S1 (MetaSel (Just "extra") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe (HashMap Text [Text])))))) |
data GroupVersionKind Source #
GroupVersionKind unambiguously identifies a kind.
Instances
data GroupVersionResource Source #
GroupVersionResource unambiguously identifies a resource.
Instances
data RawExtension Source #
RawExtension is used to hold extensions in external versions.
Instances
Status is a return value for calls that don't return other objects.
Status | |
|
Instances
ListMeta | |
|
Instances
Show ListMeta Source # | |
Generic ListMeta Source # | |
ToJSON ListMeta Source # | |
Defined in Kubernetes.Webhook.Types | |
FromJSON ListMeta Source # | |
type Rep ListMeta Source # | |
Defined in Kubernetes.Webhook.Types type Rep ListMeta = D1 (MetaData "ListMeta" "Kubernetes.Webhook.Types" "kubernetes-webhook-haskell-0.2.0.1-4tZKSOtYpWBIcF63fJw3Bd" False) (C1 (MetaCons "ListMeta" PrefixI True) ((S1 (MetaSel (Just "selfLink") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "resourceVersion") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "continue") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "remainingItemCount") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe Integer))))) |
data StatusStatus Source #
Instances
Show StatusStatus Source # | |
Defined in Kubernetes.Webhook.Types showsPrec :: Int -> StatusStatus -> ShowS # show :: StatusStatus -> String # showList :: [StatusStatus] -> ShowS # | |
Generic StatusStatus Source # | |
Defined in Kubernetes.Webhook.Types type Rep StatusStatus :: Type -> Type # from :: StatusStatus -> Rep StatusStatus x # to :: Rep StatusStatus x -> StatusStatus # | |
ToJSON StatusStatus Source # | |
Defined in Kubernetes.Webhook.Types toJSON :: StatusStatus -> Value # toEncoding :: StatusStatus -> Encoding # toJSONList :: [StatusStatus] -> Value # toEncodingList :: [StatusStatus] -> Encoding # | |
FromJSON StatusStatus Source # | |
Defined in Kubernetes.Webhook.Types parseJSON :: Value -> Parser StatusStatus # parseJSONList :: Value -> Parser [StatusStatus] # | |
type Rep StatusStatus Source # | |
Defined in Kubernetes.Webhook.Types |
data StatusReason Source #
StatusReason is an enumeration of possible failure causes. Each StatusReason must map to a single HTTP status code, but multiple reasons may map to the same HTTP status code. https://godoc.org/k8s.io/apimachinery/pkg/apis/meta/v1#StatusReason
Instances
data StatusDetails Source #
StatusDetails is a set of additional properties that MAY be set by the server to provide additional information about a response. The Reason field of a Status object defines what attributes will be set. Clients must ignore fields that do not match the defined type of each attribute, and should assume that any attribute may be empty, invalid, or under defined.
StatusDetails | |
|
Instances
data StatusCause Source #
StatusCause | |
|
Instances
CauseType is a machine readable value providing more detail about what occurred in a status response. An operation may have multiple causes for a status (whether Failure or Success).
FieldValueNotFound | |
FieldValueRequired | |
FieldValueDuplicate | |
FieldValueInvalid | |
FieldValueNotSupported | |
UnexpectedServerResponse | |
FieldManagerConflict |
Instances
Show CauseType Source # | |
Generic CauseType Source # | |
ToJSON CauseType Source # | |
Defined in Kubernetes.Webhook.Types | |
FromJSON CauseType Source # | |
type Rep CauseType Source # | |
Defined in Kubernetes.Webhook.Types type Rep CauseType = D1 (MetaData "CauseType" "Kubernetes.Webhook.Types" "kubernetes-webhook-haskell-0.2.0.1-4tZKSOtYpWBIcF63fJw3Bd" False) ((C1 (MetaCons "FieldValueNotFound" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "FieldValueRequired" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "FieldValueDuplicate" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "FieldValueInvalid" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "FieldValueNotSupported" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "UnexpectedServerResponse" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "FieldManagerConflict" PrefixI False) (U1 :: Type -> Type)))) |
TypeMeta | |
|
Instances
Show TypeMeta Source # | |
Generic TypeMeta Source # | |
ToJSON TypeMeta Source # | |
Defined in Kubernetes.Webhook.Types | |
FromJSON TypeMeta Source # | |
type Rep TypeMeta Source # | |
Defined in Kubernetes.Webhook.Types type Rep TypeMeta = D1 (MetaData "TypeMeta" "Kubernetes.Webhook.Types" "kubernetes-webhook-haskell-0.2.0.1-4tZKSOtYpWBIcF63fJw3Bd" False) (C1 (MetaCons "TypeMeta" PrefixI True) (S1 (MetaSel (Just "kind") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "apiVersion") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe Text)))) |
data PatchOperation Source #
Instances
Patch type as per RFC-6902 See http://jsonpatch.com for documentation
Instances
Show Patch Source # | |
Generic Patch Source # | |
ToJSON Patch Source # | The Patch needs to be base64-encoded |
Defined in Kubernetes.Webhook.Types | |
FromJSON Patch Source # | |
type Rep Patch Source # | |
Defined in Kubernetes.Webhook.Types type Rep Patch = D1 (MetaData "Patch" "Kubernetes.Webhook.Types" "kubernetes-webhook-haskell-0.2.0.1-4tZKSOtYpWBIcF63fJw3Bd" True) (C1 (MetaCons "Patch" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [PatchOperation]))) |
Instances
Show PatchOp Source # | |
Generic PatchOp Source # | |
ToJSON PatchOp Source # | |
Defined in Kubernetes.Webhook.Types | |
FromJSON PatchOp Source # | |
type Rep PatchOp Source # | |
Defined in Kubernetes.Webhook.Types type Rep PatchOp = D1 (MetaData "PatchOp" "Kubernetes.Webhook.Types" "kubernetes-webhook-haskell-0.2.0.1-4tZKSOtYpWBIcF63fJw3Bd" False) ((C1 (MetaCons "Add" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Copy" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Move" PrefixI False) (U1 :: Type -> Type))) :+: (C1 (MetaCons "Remove" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Replace" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Test" PrefixI False) (U1 :: Type -> Type)))) |
lowerFirst :: String -> String Source #