License | BSD-3-Clause |
---|---|
Maintainer | Oleg Grenrus <oleg.grenrus@iki.fi> |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- type Request = GenRequest MtJSON
- data GenRequest (mt :: MediaType *) (rw :: RW) a where
- Query :: Paths -> QueryString -> GenRequest mt rw a
- PagedQuery :: (a ~ t b, Foldable t, Semigroup a) => Paths -> QueryString -> FetchCount -> GenRequest mt rw a
- Command :: CommandMethod -> Paths -> ByteString -> GenRequest mt RW a
- query :: Paths -> QueryString -> Request mt a
- pagedQuery :: FromJSON a => Paths -> QueryString -> FetchCount -> Request mt (Vector a)
- command :: CommandMethod -> Paths -> ByteString -> Request RW a
- data RW
- data CommandMethod
- toMethod :: CommandMethod -> Method
- data FetchCount
- = FetchAtLeast !Word
- | FetchAll
- data MediaType a
- type Paths = [Text]
- class IsPathPart a where
- toPathPart :: a -> Text
- type QueryString = [(ByteString, Maybe ByteString)]
- type Count = Int
Request
type Request = GenRequest MtJSON Source #
Most requests ask for JSON
.
data GenRequest (mt :: MediaType *) (rw :: RW) a where Source #
Github request data type.
rw
describes whether authentication is required. It's required for non-GET
requests.mt
describes the media type, i.e. how the response should be interpreted.a
is the result type
Query :: Paths -> QueryString -> GenRequest mt rw a | |
PagedQuery :: (a ~ t b, Foldable t, Semigroup a) => Paths -> QueryString -> FetchCount -> GenRequest mt rw a | |
Command | Command |
|
Instances
Smart constructors
pagedQuery :: FromJSON a => Paths -> QueryString -> FetchCount -> Request mt (Vector a) Source #
command :: CommandMethod -> Paths -> ByteString -> Request RW a Source #
Auxiliary types
Type used as with DataKinds
to tag whether requests need authentication
or aren't read-only.
RO | Read-only, doesn't necessarily requires authentication |
RA | Read authenticated |
RW | Read-write, requires authentication |
Instances
Bounded RW Source # | |
Enum RW Source # | |
Eq RW Source # | |
Data RW Source # | |
Defined in GitHub.Data.Request gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RW -> c RW # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RW # dataTypeOf :: RW -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RW) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RW) # gmapT :: (forall b. Data b => b -> b) -> RW -> RW # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RW -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RW -> r # gmapQ :: (forall d. Data d => d -> u) -> RW -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> RW -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RW -> m RW # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RW -> m RW # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RW -> m RW # | |
Ord RW Source # | |
Read RW Source # | |
Show RW Source # | |
Generic RW Source # | |
type Rep RW Source # | |
Defined in GitHub.Data.Request |
data CommandMethod Source #
Http method of requests with body.
Instances
toMethod :: CommandMethod -> Method Source #
data FetchCount Source #
PagedQuery
returns just some results, using this data we can specify how
many pages we want to fetch.
Instances
MtJSON | application/vnd.github.v3+json |
MtRaw |
|
MtDiff |
|
MtPatch |
|
MtSha |
|
MtStar |
|
MtRedirect | https://developer.github.com/v3/repos/contents/#get-archive-link |
MtStatus | Parse status |
MtUnit | Always succeeds |
MtPreview a | Some other (preview) type; this is an extension point. |
Instances
Eq a => Eq (MediaType a) Source # | |
Data a => Data (MediaType a) Source # | |
Defined in GitHub.Data.Request gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MediaType a -> c (MediaType a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MediaType a) # toConstr :: MediaType a -> Constr # dataTypeOf :: MediaType a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (MediaType a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MediaType a)) # gmapT :: (forall b. Data b => b -> b) -> MediaType a -> MediaType a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MediaType a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MediaType a -> r # gmapQ :: (forall d. Data d => d -> u) -> MediaType a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> MediaType a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> MediaType a -> m (MediaType a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MediaType a -> m (MediaType a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MediaType a -> m (MediaType a) # | |
Ord a => Ord (MediaType a) Source # | |
Defined in GitHub.Data.Request | |
Read a => Read (MediaType a) Source # | |
Show a => Show (MediaType a) Source # | |
Generic (MediaType a) Source # | |
type Rep (MediaType a) Source # | |
Defined in GitHub.Data.Request type Rep (MediaType a) = D1 (MetaData "MediaType" "GitHub.Data.Request" "github-0.26-NGv9yMkIfb3ssAFkCPufN" False) (((C1 (MetaCons "MtJSON" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "MtRaw" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "MtDiff" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "MtPatch" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "MtSha" PrefixI False) (U1 :: Type -> Type)))) :+: ((C1 (MetaCons "MtStar" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "MtRedirect" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "MtStatus" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "MtUnit" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "MtPreview" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))))) |
class IsPathPart a where Source #
toPathPart :: a -> Text Source #
Instances
IsPathPart IssueNumber Source # | |
Defined in GitHub.Data.Request toPathPart :: IssueNumber -> Text Source # | |
IsPathPart ArchiveFormat Source # | |
Defined in GitHub.Data.Repos toPathPart :: ArchiveFormat -> Text Source # | |
IsPathPart (Name a) Source # | |
Defined in GitHub.Data.Request toPathPart :: Name a -> Text Source # | |
IsPathPart (Id a) Source # | |
Defined in GitHub.Data.Request toPathPart :: Id a -> Text Source # |
type QueryString = [(ByteString, Maybe ByteString)] Source #
Request query string