hercules-ci-api-0.7.2.1: Hercules CI API definition with Servant
Safe HaskellSafe-Inferred
LanguageHaskell2010

Hercules.API

Synopsis

Documentation

api :: Proxy (API auth) Source #

servantClientApi :: Proxy (ClientServantAPI auth) Source #

useApi :: forall subapi api mode. (GenericServant api mode, GenericServant subapi mode) => (api mode -> ToServant subapi mode) -> api mode -> subapi mode #

enterApiE :: forall {k} subapi api mode (a :: k). (GenericServant (api a) mode, GenericServant (subapi a) mode) => api a mode -> (api a mode -> ToServant (subapi a) mode) -> subapi a mode #

type API auth = HerculesServantAPI auth :<|> ("api" :> SwaggerSchemaUI "v1" "swagger.json") Source #

data HerculesAPI auth f Source #

Instances

Instances details
Generic (HerculesAPI auth f) Source # 
Instance details

Defined in Hercules.API

Associated Types

type Rep (HerculesAPI auth f) :: Type -> Type #

Methods

from :: HerculesAPI auth f -> Rep (HerculesAPI auth f) x #

to :: Rep (HerculesAPI auth f) x -> HerculesAPI auth f #

type Rep (HerculesAPI auth f) Source # 
Instance details

Defined in Hercules.API

data ClientAPI auth f Source #

Instances

Instances details
Generic (ClientAPI auth f) Source # 
Instance details

Defined in Hercules.API

Associated Types

type Rep (ClientAPI auth f) :: Type -> Type #

Methods

from :: ClientAPI auth f -> Rep (ClientAPI auth f) x #

to :: Rep (ClientAPI auth f) x -> ClientAPI auth f #

type Rep (ClientAPI auth f) Source # 
Instance details

Defined in Hercules.API

type AddAPIVersion api = "api" :> ("v1" :> api) Source #

data Id (a :: k) #

Instances

Instances details
FromJSON (Id a) 
Instance details

Defined in Hercules.API.Id

Methods

parseJSON :: Value -> Parser (Id a) #

parseJSONList :: Value -> Parser [Id a] #

FromJSONKey (Id a) 
Instance details

Defined in Hercules.API.Id

ToJSON (Id a) 
Instance details

Defined in Hercules.API.Id

Methods

toJSON :: Id a -> Value #

toEncoding :: Id a -> Encoding #

toJSONList :: [Id a] -> Value #

toEncodingList :: [Id a] -> Encoding #

ToJSONKey (Id a) 
Instance details

Defined in Hercules.API.Id

Generic (Id a) 
Instance details

Defined in Hercules.API.Id

Associated Types

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

Methods

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

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

Show (Id a) 
Instance details

Defined in Hercules.API.Id

Methods

showsPrec :: Int -> Id a -> ShowS #

show :: Id a -> String #

showList :: [Id a] -> ShowS #

NFData (Id a) 
Instance details

Defined in Hercules.API.Id

Methods

rnf :: Id a -> () #

Eq (Id a) 
Instance details

Defined in Hercules.API.Id

Methods

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

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

Ord (Id a) 
Instance details

Defined in Hercules.API.Id

Methods

compare :: Id a -> Id a -> Ordering #

(<) :: Id a -> Id a -> Bool #

(<=) :: Id a -> Id a -> Bool #

(>) :: Id a -> Id a -> Bool #

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

max :: Id a -> Id a -> Id a #

min :: Id a -> Id a -> Id a #

Hashable (Id a) 
Instance details

Defined in Hercules.API.Id

Methods

hashWithSalt :: Int -> Id a -> Int #

hash :: Id a -> Int #

FromHttpApiData (Id a) 
Instance details

Defined in Hercules.API.Id

ToHttpApiData (Id a) 
Instance details

Defined in Hercules.API.Id

ToParamSchema (Id a) 
Instance details

Defined in Hercules.API.Id

Methods

toParamSchema :: forall (t :: SwaggerKind Type). Proxy (Id a) -> ParamSchema t #

ToSchema (Id a) 
Instance details

Defined in Hercules.API.Id

type Rep (Id a) 
Instance details

Defined in Hercules.API.Id

type Rep (Id a) = D1 ('MetaData "Id" "Hercules.API.Id" "hercules-ci-api-core-0.1.5.0-inplace" 'True) (C1 ('MetaCons "Id" 'PrefixI 'True) (S1 ('MetaSel ('Just "idUUID") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UUID)))

data Name (a :: k) #

Instances

Instances details
FromJSON (Name a) 
Instance details

Defined in Hercules.API.Name

ToJSON (Name a) 
Instance details

Defined in Hercules.API.Name

Generic (Name a) 
Instance details

Defined in Hercules.API.Name

Associated Types

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

Methods

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

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

Show (Name a) 
Instance details

Defined in Hercules.API.Name

Methods

showsPrec :: Int -> Name a -> ShowS #

show :: Name a -> String #

showList :: [Name a] -> ShowS #

NFData (Name a) 
Instance details

Defined in Hercules.API.Name

Methods

rnf :: Name a -> () #

Eq (Name a) 
Instance details

Defined in Hercules.API.Name

Methods

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

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

Ord (Name a) 
Instance details

Defined in Hercules.API.Name

Methods

compare :: Name a -> Name a -> Ordering #

(<) :: Name a -> Name a -> Bool #

(<=) :: Name a -> Name a -> Bool #

(>) :: Name a -> Name a -> Bool #

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

max :: Name a -> Name a -> Name a #

min :: Name a -> Name a -> Name a #

Hashable (Name a) 
Instance details

Defined in Hercules.API.Name

Methods

hashWithSalt :: Int -> Name a -> Int #

hash :: Name a -> Int #

FromHttpApiData (Name a) 
Instance details

Defined in Hercules.API.Name

ToHttpApiData (Name a) 
Instance details

Defined in Hercules.API.Name

ToParamSchema (Name a) 
Instance details

Defined in Hercules.API.Name

Methods

toParamSchema :: forall (t :: SwaggerKind Type). Proxy (Name a) -> ParamSchema t #

ToSchema (Name a) 
Instance details

Defined in Hercules.API.Name

type Rep (Name a) 
Instance details

Defined in Hercules.API.Name

type Rep (Name a) = D1 ('MetaData "Name" "Hercules.API.Name" "hercules-ci-api-core-0.1.5.0-inplace" 'True) (C1 ('MetaCons "Name" 'PrefixI 'True) (S1 ('MetaSel ('Just "nameText") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

data Result e a Source #

Constructors

Ok a 
Error e 

Instances

Instances details
Foldable (Result e) Source # 
Instance details

Defined in Hercules.API.Result

Methods

fold :: Monoid m => Result e m -> m #

foldMap :: Monoid m => (a -> m) -> Result e a -> m #

foldMap' :: Monoid m => (a -> m) -> Result e a -> m #

foldr :: (a -> b -> b) -> b -> Result e a -> b #

foldr' :: (a -> b -> b) -> b -> Result e a -> b #

foldl :: (b -> a -> b) -> b -> Result e a -> b #

foldl' :: (b -> a -> b) -> b -> Result e a -> b #

foldr1 :: (a -> a -> a) -> Result e a -> a #

foldl1 :: (a -> a -> a) -> Result e a -> a #

toList :: Result e a -> [a] #

null :: Result e a -> Bool #

length :: Result e a -> Int #

elem :: Eq a => a -> Result e a -> Bool #

maximum :: Ord a => Result e a -> a #

minimum :: Ord a => Result e a -> a #

sum :: Num a => Result e a -> a #

product :: Num a => Result e a -> a #

Traversable (Result e) Source # 
Instance details

Defined in Hercules.API.Result

Methods

traverse :: Applicative f => (a -> f b) -> Result e a -> f (Result e b) #

sequenceA :: Applicative f => Result e (f a) -> f (Result e a) #

mapM :: Monad m => (a -> m b) -> Result e a -> m (Result e b) #

sequence :: Monad m => Result e (m a) -> m (Result e a) #

Functor (Result e) Source # 
Instance details

Defined in Hercules.API.Result

Methods

fmap :: (a -> b) -> Result e a -> Result e b #

(<$) :: a -> Result e b -> Result e a #

(FromJSON e, FromJSON a) => FromJSON (Result e a) Source # 
Instance details

Defined in Hercules.API.Result

Methods

parseJSON :: Value -> Parser (Result e a) #

parseJSONList :: Value -> Parser [Result e a] #

(ToJSON e, ToJSON a) => ToJSON (Result e a) Source # 
Instance details

Defined in Hercules.API.Result

Methods

toJSON :: Result e a -> Value #

toEncoding :: Result e a -> Encoding #

toJSONList :: [Result e a] -> Value #

toEncodingList :: [Result e a] -> Encoding #

Generic (Result e a) Source # 
Instance details

Defined in Hercules.API.Result

Associated Types

type Rep (Result e a) :: Type -> Type #

Methods

from :: Result e a -> Rep (Result e a) x #

to :: Rep (Result e a) x -> Result e a #

(Read a, Read e) => Read (Result e a) Source # 
Instance details

Defined in Hercules.API.Result

(Show a, Show e) => Show (Result e a) Source # 
Instance details

Defined in Hercules.API.Result

Methods

showsPrec :: Int -> Result e a -> ShowS #

show :: Result e a -> String #

showList :: [Result e a] -> ShowS #

(NFData a, NFData e) => NFData (Result e a) Source # 
Instance details

Defined in Hercules.API.Result

Methods

rnf :: Result e a -> () #

(Eq a, Eq e) => Eq (Result e a) Source # 
Instance details

Defined in Hercules.API.Result

Methods

(==) :: Result e a -> Result e a -> Bool #

(/=) :: Result e a -> Result e a -> Bool #

(Ord a, Ord e) => Ord (Result e a) Source # 
Instance details

Defined in Hercules.API.Result

Methods

compare :: Result e a -> Result e a -> Ordering #

(<) :: Result e a -> Result e a -> Bool #

(<=) :: Result e a -> Result e a -> Bool #

(>) :: Result e a -> Result e a -> Bool #

(>=) :: Result e a -> Result e a -> Bool #

max :: Result e a -> Result e a -> Result e a #

min :: Result e a -> Result e a -> Result e a #

(ToSchema e, ToSchema a) => ToSchema (Result e a) Source # 
Instance details

Defined in Hercules.API.Result

type Rep (Result e a) Source # 
Instance details

Defined in Hercules.API.Result

type Rep (Result e a) = D1 ('MetaData "Result" "Hercules.API.Result" "hercules-ci-api-0.7.2.1-inplace" 'False) (C1 ('MetaCons "Ok" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :+: C1 ('MetaCons "Error" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e)))

Reexports

data NoContent #

A type for responses without content-body.

Constructors

NoContent 

Instances

Instances details
Generic NoContent 
Instance details

Defined in Servant.API.ContentTypes

Associated Types

type Rep NoContent :: Type -> Type #

Read NoContent 
Instance details

Defined in Servant.API.ContentTypes

Show NoContent 
Instance details

Defined in Servant.API.ContentTypes

NFData NoContent 
Instance details

Defined in Servant.API.ContentTypes

Methods

rnf :: NoContent -> () #

Eq NoContent 
Instance details

Defined in Servant.API.ContentTypes

HasStatus NoContent

If an API can respond with NoContent we assume that this will happen with the status code 204 No Content. If this needs to be overridden, WithStatus can be used.

Instance details

Defined in Servant.API.UVerb

Associated Types

type StatusOf NoContent :: Nat #

(KnownNat status, AllAccept cs, SwaggerMethod method, HasSwagger (UVerb method cs as)) => HasSwagger (UVerb method cs (WithStatus status NoContent ': as) :: Type) 
Instance details

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (UVerb method cs (WithStatus status NoContent ': as)) -> Swagger #

(AllAccept cs, KnownNat status, SwaggerMethod method) => HasSwagger (Verb method status cs NoContent :: Type) 
Instance details

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (Verb method status cs NoContent) -> Swagger #

(AllAccept cs, AllToResponseHeader hs, KnownNat status, SwaggerMethod method) => HasSwagger (Verb method status cs (Headers hs NoContent) :: Type) 
Instance details

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (Verb method status cs (Headers hs NoContent)) -> Swagger #

AllMime (ctyp ': (ctyp' ': ctyps)) => AllMimeRender (ctyp ': (ctyp' ': ctyps)) NoContent 
Instance details

Defined in Servant.API.ContentTypes

Methods

allMimeRender :: Proxy (ctyp ': (ctyp' ': ctyps)) -> NoContent -> [(MediaType, ByteString)] #

Accept ctyp => AllMimeRender '[ctyp] NoContent 
Instance details

Defined in Servant.API.ContentTypes

Methods

allMimeRender :: Proxy '[ctyp] -> NoContent -> [(MediaType, ByteString)] #

type Rep NoContent 
Instance details

Defined in Servant.API.ContentTypes

type Rep NoContent = D1 ('MetaData "NoContent" "Servant.API.ContentTypes" "servant-0.19.1-AbPuKExjTsVDQZWUMMYIFY" 'False) (C1 ('MetaCons "NoContent" 'PrefixI 'False) (U1 :: Type -> Type))
type StatusOf NoContent 
Instance details

Defined in Servant.API.UVerb

type StatusOf NoContent = 204

Utilities

noContent :: Functor m => m NoContent -> m () Source #

void specialised to NoContent to soothe the compiler that rightfully warns about throwing away a do notation result. By specialising, we make sure that we still get warnings if the result type changes in the future. (We'll get an error)