Safe Haskell | None |
---|---|
Language | Haskell2010 |
GitHub.Data.Deployments
Documentation
data DeploymentQueryOption Source #
Constructors
DeploymentQuerySha !Text | |
DeploymentQueryRef !Text | |
DeploymentQueryTask !Text | |
DeploymentQueryEnvironment !Text |
Instances
data Deployment a Source #
Constructors
Deployment | |
Fields
|
Instances
FromJSON a => FromJSON (Deployment a) Source # | |||||
Defined in GitHub.Data.Deployments Methods parseJSON :: Value -> Parser (Deployment a) # parseJSONList :: Value -> Parser [Deployment a] # omittedField :: Maybe (Deployment a) # | |||||
Data a => Data (Deployment a) Source # | |||||
Defined in GitHub.Data.Deployments Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Deployment a -> c (Deployment a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Deployment a) # toConstr :: Deployment a -> Constr # dataTypeOf :: Deployment a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Deployment a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Deployment a)) # gmapT :: (forall b. Data b => b -> b) -> Deployment a -> Deployment a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Deployment a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Deployment a -> r # gmapQ :: (forall d. Data d => d -> u) -> Deployment a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Deployment a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Deployment a -> m (Deployment a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Deployment a -> m (Deployment a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Deployment a -> m (Deployment a) # | |||||
Generic (Deployment a) Source # | |||||
Defined in GitHub.Data.Deployments Associated Types
| |||||
Show a => Show (Deployment a) Source # | |||||
Defined in GitHub.Data.Deployments Methods showsPrec :: Int -> Deployment a -> ShowS # show :: Deployment a -> String # showList :: [Deployment a] -> ShowS # | |||||
Binary a => Binary (Deployment a) Source # | |||||
Defined in GitHub.Data.Deployments | |||||
NFData a => NFData (Deployment a) Source # | |||||
Defined in GitHub.Data.Deployments Methods rnf :: Deployment a -> () # | |||||
Eq a => Eq (Deployment a) Source # | |||||
Defined in GitHub.Data.Deployments | |||||
Ord a => Ord (Deployment a) Source # | |||||
Defined in GitHub.Data.Deployments Methods compare :: Deployment a -> Deployment a -> Ordering # (<) :: Deployment a -> Deployment a -> Bool # (<=) :: Deployment a -> Deployment a -> Bool # (>) :: Deployment a -> Deployment a -> Bool # (>=) :: Deployment a -> Deployment a -> Bool # max :: Deployment a -> Deployment a -> Deployment a # min :: Deployment a -> Deployment a -> Deployment a # | |||||
type Rep (Deployment a) Source # | |||||
Defined in GitHub.Data.Deployments type Rep (Deployment a) = D1 ('MetaData "Deployment" "GitHub.Data.Deployments" "github-0.30-7PDLbEAlB9u1WnWZZQOkWM" 'False) (C1 ('MetaCons "Deployment" 'PrefixI 'True) (((S1 ('MetaSel ('Just "deploymentUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: (S1 ('MetaSel ('Just "deploymentId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Id (Deployment a))) :*: S1 ('MetaSel ('Just "deploymentSha") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Name (Deployment a))))) :*: (S1 ('MetaSel ('Just "deploymentRef") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "deploymentTask") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "deploymentPayload") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe a))))) :*: ((S1 ('MetaSel ('Just "deploymentEnvironment") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "deploymentDescription") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "deploymentCreator") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SimpleUser))) :*: ((S1 ('MetaSel ('Just "deploymentCreatedAt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UTCTime) :*: S1 ('MetaSel ('Just "deploymentUpdatedAt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UTCTime)) :*: (S1 ('MetaSel ('Just "deploymentStatusesUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "deploymentRepositoryUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL)))))) |
data CreateDeployment a Source #
Constructors
CreateDeployment | |
Fields
|
Instances
ToJSON a => ToJSON (CreateDeployment a) Source # | |||||
Defined in GitHub.Data.Deployments Methods toJSON :: CreateDeployment a -> Value # toEncoding :: CreateDeployment a -> Encoding # toJSONList :: [CreateDeployment a] -> Value # toEncodingList :: [CreateDeployment a] -> Encoding # omitField :: CreateDeployment a -> Bool # | |||||
Data a => Data (CreateDeployment a) Source # | |||||
Defined in GitHub.Data.Deployments Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CreateDeployment a -> c (CreateDeployment a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (CreateDeployment a) # toConstr :: CreateDeployment a -> Constr # dataTypeOf :: CreateDeployment a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (CreateDeployment a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (CreateDeployment a)) # gmapT :: (forall b. Data b => b -> b) -> CreateDeployment a -> CreateDeployment a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CreateDeployment a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CreateDeployment a -> r # gmapQ :: (forall d. Data d => d -> u) -> CreateDeployment a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> CreateDeployment a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> CreateDeployment a -> m (CreateDeployment a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CreateDeployment a -> m (CreateDeployment a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CreateDeployment a -> m (CreateDeployment a) # | |||||
Generic (CreateDeployment a) Source # | |||||
Defined in GitHub.Data.Deployments Associated Types
Methods from :: CreateDeployment a -> Rep (CreateDeployment a) x # to :: Rep (CreateDeployment a) x -> CreateDeployment a # | |||||
Show a => Show (CreateDeployment a) Source # | |||||
Defined in GitHub.Data.Deployments Methods showsPrec :: Int -> CreateDeployment a -> ShowS # show :: CreateDeployment a -> String # showList :: [CreateDeployment a] -> ShowS # | |||||
Binary a => Binary (CreateDeployment a) Source # | |||||
Defined in GitHub.Data.Deployments Methods put :: CreateDeployment a -> Put # get :: Get (CreateDeployment a) # putList :: [CreateDeployment a] -> Put # | |||||
NFData a => NFData (CreateDeployment a) Source # | |||||
Defined in GitHub.Data.Deployments Methods rnf :: CreateDeployment a -> () # | |||||
Eq a => Eq (CreateDeployment a) Source # | |||||
Defined in GitHub.Data.Deployments Methods (==) :: CreateDeployment a -> CreateDeployment a -> Bool # (/=) :: CreateDeployment a -> CreateDeployment a -> Bool # | |||||
Ord a => Ord (CreateDeployment a) Source # | |||||
Defined in GitHub.Data.Deployments Methods compare :: CreateDeployment a -> CreateDeployment a -> Ordering # (<) :: CreateDeployment a -> CreateDeployment a -> Bool # (<=) :: CreateDeployment a -> CreateDeployment a -> Bool # (>) :: CreateDeployment a -> CreateDeployment a -> Bool # (>=) :: CreateDeployment a -> CreateDeployment a -> Bool # max :: CreateDeployment a -> CreateDeployment a -> CreateDeployment a # min :: CreateDeployment a -> CreateDeployment a -> CreateDeployment a # | |||||
type Rep (CreateDeployment a) Source # | |||||
Defined in GitHub.Data.Deployments type Rep (CreateDeployment a) = D1 ('MetaData "CreateDeployment" "GitHub.Data.Deployments" "github-0.30-7PDLbEAlB9u1WnWZZQOkWM" 'False) (C1 ('MetaCons "CreateDeployment" 'PrefixI 'True) ((S1 ('MetaSel ('Just "createDeploymentRef") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "createDeploymentTask") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "createDeploymentAutoMerge") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Bool)))) :*: ((S1 ('MetaSel ('Just "createDeploymentRequiredContexts") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe (Vector Text))) :*: S1 ('MetaSel ('Just "createDeploymentPayload") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe a))) :*: (S1 ('MetaSel ('Just "createDeploymentEnvironment") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "createDeploymentDescription") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)))))) |
data DeploymentStatus Source #
Constructors
DeploymentStatus | |
Fields
|
Instances
FromJSON DeploymentStatus Source # | |||||
Defined in GitHub.Data.Deployments Methods parseJSON :: Value -> Parser DeploymentStatus # parseJSONList :: Value -> Parser [DeploymentStatus] # | |||||
Data DeploymentStatus Source # | |||||
Defined in GitHub.Data.Deployments Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DeploymentStatus -> c DeploymentStatus # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DeploymentStatus # toConstr :: DeploymentStatus -> Constr # dataTypeOf :: DeploymentStatus -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DeploymentStatus) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DeploymentStatus) # gmapT :: (forall b. Data b => b -> b) -> DeploymentStatus -> DeploymentStatus # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DeploymentStatus -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DeploymentStatus -> r # gmapQ :: (forall d. Data d => d -> u) -> DeploymentStatus -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DeploymentStatus -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DeploymentStatus -> m DeploymentStatus # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DeploymentStatus -> m DeploymentStatus # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DeploymentStatus -> m DeploymentStatus # | |||||
Generic DeploymentStatus Source # | |||||
Defined in GitHub.Data.Deployments Associated Types
Methods from :: DeploymentStatus -> Rep DeploymentStatus x # to :: Rep DeploymentStatus x -> DeploymentStatus # | |||||
Show DeploymentStatus Source # | |||||
Defined in GitHub.Data.Deployments Methods showsPrec :: Int -> DeploymentStatus -> ShowS # show :: DeploymentStatus -> String # showList :: [DeploymentStatus] -> ShowS # | |||||
Binary DeploymentStatus Source # | |||||
Defined in GitHub.Data.Deployments Methods put :: DeploymentStatus -> Put # get :: Get DeploymentStatus # putList :: [DeploymentStatus] -> Put # | |||||
NFData DeploymentStatus Source # | |||||
Defined in GitHub.Data.Deployments Methods rnf :: DeploymentStatus -> () # | |||||
Eq DeploymentStatus Source # | |||||
Defined in GitHub.Data.Deployments Methods (==) :: DeploymentStatus -> DeploymentStatus -> Bool # (/=) :: DeploymentStatus -> DeploymentStatus -> Bool # | |||||
Ord DeploymentStatus Source # | |||||
Defined in GitHub.Data.Deployments Methods compare :: DeploymentStatus -> DeploymentStatus -> Ordering # (<) :: DeploymentStatus -> DeploymentStatus -> Bool # (<=) :: DeploymentStatus -> DeploymentStatus -> Bool # (>) :: DeploymentStatus -> DeploymentStatus -> Bool # (>=) :: DeploymentStatus -> DeploymentStatus -> Bool # max :: DeploymentStatus -> DeploymentStatus -> DeploymentStatus # min :: DeploymentStatus -> DeploymentStatus -> DeploymentStatus # | |||||
type Rep DeploymentStatus Source # | |||||
Defined in GitHub.Data.Deployments type Rep DeploymentStatus = D1 ('MetaData "DeploymentStatus" "GitHub.Data.Deployments" "github-0.30-7PDLbEAlB9u1WnWZZQOkWM" 'False) (C1 ('MetaCons "DeploymentStatus" 'PrefixI 'True) (((S1 ('MetaSel ('Just "deploymentStatusUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "deploymentStatusId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Id DeploymentStatus))) :*: (S1 ('MetaSel ('Just "deploymentStatusState") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 DeploymentStatusState) :*: (S1 ('MetaSel ('Just "deploymentStatusCreator") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SimpleUser) :*: S1 ('MetaSel ('Just "deploymentStatusDescription") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)))) :*: ((S1 ('MetaSel ('Just "deploymentStatusTargetUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "deploymentStatusCreatedAt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UTCTime)) :*: (S1 ('MetaSel ('Just "deploymentStatusUpdatedAt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UTCTime) :*: (S1 ('MetaSel ('Just "deploymentStatusDeploymentUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "deploymentStatusRepositoryUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL)))))) |
data DeploymentStatusState Source #
Constructors
DeploymentStatusError | |
DeploymentStatusFailure | |
DeploymentStatusPending | |
DeploymentStatusSuccess | |
DeploymentStatusInactive |
Instances
FromJSON DeploymentStatusState Source # | |||||
Defined in GitHub.Data.Deployments Methods parseJSON :: Value -> Parser DeploymentStatusState # parseJSONList :: Value -> Parser [DeploymentStatusState] # | |||||
ToJSON DeploymentStatusState Source # | |||||
Defined in GitHub.Data.Deployments Methods toJSON :: DeploymentStatusState -> Value # toEncoding :: DeploymentStatusState -> Encoding # toJSONList :: [DeploymentStatusState] -> Value # toEncodingList :: [DeploymentStatusState] -> Encoding # omitField :: DeploymentStatusState -> Bool # | |||||
Data DeploymentStatusState Source # | |||||
Defined in GitHub.Data.Deployments Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DeploymentStatusState -> c DeploymentStatusState # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DeploymentStatusState # toConstr :: DeploymentStatusState -> Constr # dataTypeOf :: DeploymentStatusState -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DeploymentStatusState) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DeploymentStatusState) # gmapT :: (forall b. Data b => b -> b) -> DeploymentStatusState -> DeploymentStatusState # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DeploymentStatusState -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DeploymentStatusState -> r # gmapQ :: (forall d. Data d => d -> u) -> DeploymentStatusState -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DeploymentStatusState -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DeploymentStatusState -> m DeploymentStatusState # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DeploymentStatusState -> m DeploymentStatusState # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DeploymentStatusState -> m DeploymentStatusState # | |||||
Generic DeploymentStatusState Source # | |||||
Defined in GitHub.Data.Deployments Associated Types
Methods from :: DeploymentStatusState -> Rep DeploymentStatusState x # to :: Rep DeploymentStatusState x -> DeploymentStatusState # | |||||
Show DeploymentStatusState Source # | |||||
Defined in GitHub.Data.Deployments Methods showsPrec :: Int -> DeploymentStatusState -> ShowS # show :: DeploymentStatusState -> String # showList :: [DeploymentStatusState] -> ShowS # | |||||
Binary DeploymentStatusState Source # | |||||
Defined in GitHub.Data.Deployments Methods put :: DeploymentStatusState -> Put # get :: Get DeploymentStatusState # putList :: [DeploymentStatusState] -> Put # | |||||
NFData DeploymentStatusState Source # | |||||
Defined in GitHub.Data.Deployments Methods rnf :: DeploymentStatusState -> () # | |||||
Eq DeploymentStatusState Source # | |||||
Defined in GitHub.Data.Deployments Methods (==) :: DeploymentStatusState -> DeploymentStatusState -> Bool # (/=) :: DeploymentStatusState -> DeploymentStatusState -> Bool # | |||||
Ord DeploymentStatusState Source # | |||||
Defined in GitHub.Data.Deployments Methods compare :: DeploymentStatusState -> DeploymentStatusState -> Ordering # (<) :: DeploymentStatusState -> DeploymentStatusState -> Bool # (<=) :: DeploymentStatusState -> DeploymentStatusState -> Bool # (>) :: DeploymentStatusState -> DeploymentStatusState -> Bool # (>=) :: DeploymentStatusState -> DeploymentStatusState -> Bool # max :: DeploymentStatusState -> DeploymentStatusState -> DeploymentStatusState # min :: DeploymentStatusState -> DeploymentStatusState -> DeploymentStatusState # | |||||
type Rep DeploymentStatusState Source # | |||||
Defined in GitHub.Data.Deployments type Rep DeploymentStatusState = D1 ('MetaData "DeploymentStatusState" "GitHub.Data.Deployments" "github-0.30-7PDLbEAlB9u1WnWZZQOkWM" 'False) ((C1 ('MetaCons "DeploymentStatusError" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DeploymentStatusFailure" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DeploymentStatusPending" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DeploymentStatusSuccess" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DeploymentStatusInactive" 'PrefixI 'False) (U1 :: Type -> Type)))) |
data CreateDeploymentStatus Source #
Constructors
CreateDeploymentStatus | |
Fields
|
Instances
ToJSON CreateDeploymentStatus Source # | |||||
Defined in GitHub.Data.Deployments Methods toJSON :: CreateDeploymentStatus -> Value # toEncoding :: CreateDeploymentStatus -> Encoding # toJSONList :: [CreateDeploymentStatus] -> Value # toEncodingList :: [CreateDeploymentStatus] -> Encoding # omitField :: CreateDeploymentStatus -> Bool # | |||||
Data CreateDeploymentStatus Source # | |||||
Defined in GitHub.Data.Deployments Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CreateDeploymentStatus -> c CreateDeploymentStatus # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CreateDeploymentStatus # toConstr :: CreateDeploymentStatus -> Constr # dataTypeOf :: CreateDeploymentStatus -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CreateDeploymentStatus) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CreateDeploymentStatus) # gmapT :: (forall b. Data b => b -> b) -> CreateDeploymentStatus -> CreateDeploymentStatus # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CreateDeploymentStatus -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CreateDeploymentStatus -> r # gmapQ :: (forall d. Data d => d -> u) -> CreateDeploymentStatus -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> CreateDeploymentStatus -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> CreateDeploymentStatus -> m CreateDeploymentStatus # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CreateDeploymentStatus -> m CreateDeploymentStatus # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CreateDeploymentStatus -> m CreateDeploymentStatus # | |||||
Generic CreateDeploymentStatus Source # | |||||
Defined in GitHub.Data.Deployments Associated Types
Methods from :: CreateDeploymentStatus -> Rep CreateDeploymentStatus x # to :: Rep CreateDeploymentStatus x -> CreateDeploymentStatus # | |||||
Show CreateDeploymentStatus Source # | |||||
Defined in GitHub.Data.Deployments Methods showsPrec :: Int -> CreateDeploymentStatus -> ShowS # show :: CreateDeploymentStatus -> String # showList :: [CreateDeploymentStatus] -> ShowS # | |||||
Binary CreateDeploymentStatus Source # | |||||
Defined in GitHub.Data.Deployments Methods put :: CreateDeploymentStatus -> Put # get :: Get CreateDeploymentStatus # putList :: [CreateDeploymentStatus] -> Put # | |||||
NFData CreateDeploymentStatus Source # | |||||
Defined in GitHub.Data.Deployments Methods rnf :: CreateDeploymentStatus -> () # | |||||
Eq CreateDeploymentStatus Source # | |||||
Defined in GitHub.Data.Deployments Methods (==) :: CreateDeploymentStatus -> CreateDeploymentStatus -> Bool # (/=) :: CreateDeploymentStatus -> CreateDeploymentStatus -> Bool # | |||||
Ord CreateDeploymentStatus Source # | |||||
Defined in GitHub.Data.Deployments Methods compare :: CreateDeploymentStatus -> CreateDeploymentStatus -> Ordering # (<) :: CreateDeploymentStatus -> CreateDeploymentStatus -> Bool # (<=) :: CreateDeploymentStatus -> CreateDeploymentStatus -> Bool # (>) :: CreateDeploymentStatus -> CreateDeploymentStatus -> Bool # (>=) :: CreateDeploymentStatus -> CreateDeploymentStatus -> Bool # max :: CreateDeploymentStatus -> CreateDeploymentStatus -> CreateDeploymentStatus # min :: CreateDeploymentStatus -> CreateDeploymentStatus -> CreateDeploymentStatus # | |||||
type Rep CreateDeploymentStatus Source # | |||||
Defined in GitHub.Data.Deployments type Rep CreateDeploymentStatus = D1 ('MetaData "CreateDeploymentStatus" "GitHub.Data.Deployments" "github-0.30-7PDLbEAlB9u1WnWZZQOkWM" 'False) (C1 ('MetaCons "CreateDeploymentStatus" 'PrefixI 'True) (S1 ('MetaSel ('Just "createDeploymentStatusState") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 DeploymentStatusState) :*: (S1 ('MetaSel ('Just "createDeploymentStatusTargetUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "createDeploymentStatusDescription") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text))))) |