github-0.26: Access to the GitHub API, v3.

Safe HaskellNone
LanguageHaskell2010

GitHub.Data.Deployments

Documentation

data DeploymentQueryOption Source #

Instances
Eq DeploymentQueryOption Source # 
Instance details

Defined in GitHub.Data.Deployments

Data DeploymentQueryOption Source # 
Instance details

Defined in GitHub.Data.Deployments

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DeploymentQueryOption -> c DeploymentQueryOption #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DeploymentQueryOption #

toConstr :: DeploymentQueryOption -> Constr #

dataTypeOf :: DeploymentQueryOption -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DeploymentQueryOption) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DeploymentQueryOption) #

gmapT :: (forall b. Data b => b -> b) -> DeploymentQueryOption -> DeploymentQueryOption #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DeploymentQueryOption -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DeploymentQueryOption -> r #

gmapQ :: (forall d. Data d => d -> u) -> DeploymentQueryOption -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DeploymentQueryOption -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DeploymentQueryOption -> m DeploymentQueryOption #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DeploymentQueryOption -> m DeploymentQueryOption #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DeploymentQueryOption -> m DeploymentQueryOption #

Ord DeploymentQueryOption Source # 
Instance details

Defined in GitHub.Data.Deployments

Show DeploymentQueryOption Source # 
Instance details

Defined in GitHub.Data.Deployments

Generic DeploymentQueryOption Source # 
Instance details

Defined in GitHub.Data.Deployments

Associated Types

type Rep DeploymentQueryOption :: Type -> Type #

Binary DeploymentQueryOption Source # 
Instance details

Defined in GitHub.Data.Deployments

NFData DeploymentQueryOption Source # 
Instance details

Defined in GitHub.Data.Deployments

Methods

rnf :: DeploymentQueryOption -> () #

type Rep DeploymentQueryOption Source # 
Instance details

Defined in GitHub.Data.Deployments

type Rep DeploymentQueryOption = D1 (MetaData "DeploymentQueryOption" "GitHub.Data.Deployments" "github-0.26-NGv9yMkIfb3ssAFkCPufN" False) ((C1 (MetaCons "DeploymentQuerySha" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) :+: C1 (MetaCons "DeploymentQueryRef" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))) :+: (C1 (MetaCons "DeploymentQueryTask" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) :+: C1 (MetaCons "DeploymentQueryEnvironment" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))

data Deployment a Source #

Instances
Eq a => Eq (Deployment a) Source # 
Instance details

Defined in GitHub.Data.Deployments

Methods

(==) :: Deployment a -> Deployment a -> Bool #

(/=) :: Deployment a -> Deployment a -> Bool #

Data a => Data (Deployment a) Source # 
Instance details

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 :: (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) #

Ord a => Ord (Deployment a) Source # 
Instance details

Defined in GitHub.Data.Deployments

Show a => Show (Deployment a) Source # 
Instance details

Defined in GitHub.Data.Deployments

Generic (Deployment a) Source # 
Instance details

Defined in GitHub.Data.Deployments

Associated Types

type Rep (Deployment a) :: Type -> Type #

Methods

from :: Deployment a -> Rep (Deployment a) x #

to :: Rep (Deployment a) x -> Deployment a #

FromJSON a => FromJSON (Deployment a) Source # 
Instance details

Defined in GitHub.Data.Deployments

Binary a => Binary (Deployment a) Source # 
Instance details

Defined in GitHub.Data.Deployments

Methods

put :: Deployment a -> Put #

get :: Get (Deployment a) #

putList :: [Deployment a] -> Put #

NFData a => NFData (Deployment a) Source # 
Instance details

Defined in GitHub.Data.Deployments

Methods

rnf :: Deployment a -> () #

type Rep (Deployment a) Source # 
Instance details

Defined in GitHub.Data.Deployments

type Rep (Deployment a) = D1 (MetaData "Deployment" "GitHub.Data.Deployments" "github-0.26-NGv9yMkIfb3ssAFkCPufN" 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
Eq a => Eq (CreateDeployment a) Source # 
Instance details

Defined in GitHub.Data.Deployments

Data a => Data (CreateDeployment a) Source # 
Instance details

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 :: (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) #

Ord a => Ord (CreateDeployment a) Source # 
Instance details

Defined in GitHub.Data.Deployments

Show a => Show (CreateDeployment a) Source # 
Instance details

Defined in GitHub.Data.Deployments

Generic (CreateDeployment a) Source # 
Instance details

Defined in GitHub.Data.Deployments

Associated Types

type Rep (CreateDeployment a) :: Type -> Type #

ToJSON a => ToJSON (CreateDeployment a) Source # 
Instance details

Defined in GitHub.Data.Deployments

Binary a => Binary (CreateDeployment a) Source # 
Instance details

Defined in GitHub.Data.Deployments

NFData a => NFData (CreateDeployment a) Source # 
Instance details

Defined in GitHub.Data.Deployments

Methods

rnf :: CreateDeployment a -> () #

type Rep (CreateDeployment a) Source # 
Instance details

Defined in GitHub.Data.Deployments

type Rep (CreateDeployment a) = D1 (MetaData "CreateDeployment" "GitHub.Data.Deployments" "github-0.26-NGv9yMkIfb3ssAFkCPufN" 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 #

Instances
Eq DeploymentStatus Source # 
Instance details

Defined in GitHub.Data.Deployments

Data DeploymentStatus Source # 
Instance details

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 :: (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 #

Ord DeploymentStatus Source # 
Instance details

Defined in GitHub.Data.Deployments

Show DeploymentStatus Source # 
Instance details

Defined in GitHub.Data.Deployments

Generic DeploymentStatus Source # 
Instance details

Defined in GitHub.Data.Deployments

Associated Types

type Rep DeploymentStatus :: Type -> Type #

FromJSON DeploymentStatus Source # 
Instance details

Defined in GitHub.Data.Deployments

Binary DeploymentStatus Source # 
Instance details

Defined in GitHub.Data.Deployments

NFData DeploymentStatus Source # 
Instance details

Defined in GitHub.Data.Deployments

Methods

rnf :: DeploymentStatus -> () #

type Rep DeploymentStatus Source # 
Instance details

Defined in GitHub.Data.Deployments

type Rep DeploymentStatus = D1 (MetaData "DeploymentStatus" "GitHub.Data.Deployments" "github-0.26-NGv9yMkIfb3ssAFkCPufN" 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 #

Instances
Eq DeploymentStatusState Source # 
Instance details

Defined in GitHub.Data.Deployments

Data DeploymentStatusState Source # 
Instance details

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 :: (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 #

Ord DeploymentStatusState Source # 
Instance details

Defined in GitHub.Data.Deployments

Show DeploymentStatusState Source # 
Instance details

Defined in GitHub.Data.Deployments

Generic DeploymentStatusState Source # 
Instance details

Defined in GitHub.Data.Deployments

Associated Types

type Rep DeploymentStatusState :: Type -> Type #

ToJSON DeploymentStatusState Source # 
Instance details

Defined in GitHub.Data.Deployments

FromJSON DeploymentStatusState Source # 
Instance details

Defined in GitHub.Data.Deployments

Binary DeploymentStatusState Source # 
Instance details

Defined in GitHub.Data.Deployments

NFData DeploymentStatusState Source # 
Instance details

Defined in GitHub.Data.Deployments

Methods

rnf :: DeploymentStatusState -> () #

type Rep DeploymentStatusState Source # 
Instance details

Defined in GitHub.Data.Deployments

type Rep DeploymentStatusState = D1 (MetaData "DeploymentStatusState" "GitHub.Data.Deployments" "github-0.26-NGv9yMkIfb3ssAFkCPufN" 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
Eq CreateDeploymentStatus Source # 
Instance details

Defined in GitHub.Data.Deployments

Data CreateDeploymentStatus Source # 
Instance details

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 :: (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 #

Ord CreateDeploymentStatus Source # 
Instance details

Defined in GitHub.Data.Deployments

Show CreateDeploymentStatus Source # 
Instance details

Defined in GitHub.Data.Deployments

Generic CreateDeploymentStatus Source # 
Instance details

Defined in GitHub.Data.Deployments

Associated Types

type Rep CreateDeploymentStatus :: Type -> Type #

ToJSON CreateDeploymentStatus Source # 
Instance details

Defined in GitHub.Data.Deployments

Binary CreateDeploymentStatus Source # 
Instance details

Defined in GitHub.Data.Deployments

NFData CreateDeploymentStatus Source # 
Instance details

Defined in GitHub.Data.Deployments

Methods

rnf :: CreateDeploymentStatus -> () #

type Rep CreateDeploymentStatus Source # 
Instance details

Defined in GitHub.Data.Deployments

type Rep CreateDeploymentStatus = D1 (MetaData "CreateDeploymentStatus" "GitHub.Data.Deployments" "github-0.26-NGv9yMkIfb3ssAFkCPufN" 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)))))