Copyright | (c) Finlay Thompson, 2015 |
---|---|
License | BSD3 |
Maintainer | finlay.thompson@gmail.com |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
- github :: (HasClient (AddHeaders api), HasGitHub (Client (AddHeaders api))) => Proxy api -> EmbedGitHub (Client (AddHeaders api))
- data AuthToken
- type GitHub = ReaderT (Maybe AuthToken) (StateT GitHubState (EitherT ServantError IO))
- runGitHub :: GitHub a -> Maybe AuthToken -> IO (Either ServantError a)
- data GitHubState = GitHubState {}
- class HasGitHub a where
- embedGitHub :: a -> EmbedGitHub a
- type family EmbedGitHub a :: *
- type family AddHeaders a :: *
- type family ReadHeaders a :: *
- type Single a = Maybe Text -> Maybe AuthToken -> EitherT ServantError IO a
- type Paginated a = Maybe Text -> Maybe AuthToken -> Maybe Int -> Maybe Int -> EitherT ServantError IO (Headers `[Header "Link" Text]` [a])
- setUserAgent :: Text -> GitHub ()
- resetPagination :: GitHub ()
- recurseOff :: GitHub ()
- recurseOn :: GitHub ()
- pageSize :: Int -> GitHub ()
- getLinks :: GitHub (Maybe [Link])
Documentation
github :: (HasClient (AddHeaders api), HasGitHub (Client (AddHeaders api))) => Proxy api -> EmbedGitHub (Client (AddHeaders api)) Source
Token used to authorize access to the GitHub API. see https://developer.github.com/v3/oauth/
Eq AuthToken Source | |
IsString AuthToken Source | |
ToText AuthToken Source | |
HasGitHub (Paginated a) Source | Instance for the case where we have paginated results |
HasGitHub (Single a) Source | Instance for the case where we have single result |
HasGitHub (a -> b -> c -> Paginated d) Source | |
HasGitHub (a -> b -> Paginated c) Source | |
HasGitHub (a -> Paginated b) Source | |
HasGitHub (a -> b -> c -> Single d) Source | |
HasGitHub (a -> b -> Single c) Source | |
HasGitHub (a -> Single b) Source |
type GitHub = ReaderT (Maybe AuthToken) (StateT GitHubState (EitherT ServantError IO)) Source
The GitHub
monad provides execution context
data GitHubState Source
GitHubState options that control which headers are provided to the API
and stores the Link
header result
class HasGitHub a where Source
This class defines how the client code is actually called.
embedGitHub :: a -> EmbedGitHub a Source
HasGitHub (Paginated a) Source | Instance for the case where we have paginated results |
HasGitHub (Single a) Source | Instance for the case where we have single result |
HasGitHub (a -> b -> c -> Paginated d) Source | |
HasGitHub (a -> b -> Paginated c) Source | |
HasGitHub (a -> Paginated b) Source | |
HasGitHub (a -> b -> c -> Single d) Source | |
HasGitHub (a -> b -> Single c) Source | |
HasGitHub (a -> Single b) Source |
type family EmbedGitHub a :: * Source
Closed type family for recursively defining the GitHub client funciton types
EmbedGitHub (Single a) = GitHub a | |
EmbedGitHub (Paginated a) = GitHub [a] | |
EmbedGitHub (a -> b) = a -> EmbedGitHub b |
type family AddHeaders a :: * Source
Closed type family that adds standard headers to the incoming servant API type. The extra headers are put after any arguments types.
AddHeaders ((sym :: Symbol) :> last) = (sym :: Symbol) :> AddHeaders last | |
AddHeaders (first :> last) = first :> AddHeaders last | |
AddHeaders last = Header "User-Agent" Text :> (Header "Authorization" AuthToken :> ReadHeaders last) |
type family ReadHeaders a :: * Source
Closed type family that adds headers necessary for pagination. In particular, it captures the Link header from the response.
ReadHeaders (Get cts [res]) = QueryParam "page" Int :> (QueryParam "per_page" Int :> Get cts (Headers `[Header "Link" Text]` [res])) | |
ReadHeaders (Post cts [res]) = QueryParam "page" Int :> (QueryParam "per_page" Int :> Post cts (Headers `[Header "Link" Text]` [res])) | |
ReadHeaders (Delete cts [res]) = QueryParam "page" Int :> (QueryParam "per_page" Int :> Delete cts (Headers `[Header "Link" Text]` [res])) | |
ReadHeaders (Put cts [res]) = QueryParam "page" Int :> (QueryParam "per_page" Int :> Put cts (Headers `[Header "Link" Text]` [res])) | |
ReadHeaders (Patch cts [res]) = QueryParam "page" Int :> (QueryParam "per_page" Int :> Patch cts (Headers `[Header "Link" Text]` [res])) | |
ReadHeaders otherwise = otherwise |
type Single a = Maybe Text -> Maybe AuthToken -> EitherT ServantError IO a Source
Client function that returns a single result
type Paginated a = Maybe Text -> Maybe AuthToken -> Maybe Int -> Maybe Int -> EitherT ServantError IO (Headers `[Header "Link" Text]` [a]) Source
Client function that returns a list of results, and is therefore paginated
setUserAgent :: Text -> GitHub () Source
Overide default value for User-agent header. Note, GitHub requires that a User-agent header be set.
resetPagination :: GitHub () Source
Set next page back to 1, and remove the links
recurseOff :: GitHub () Source
Turn automatic recusive behaviour on and off.
If recursive is on, paginated results will be automatically followed and concated together.
Turn automatic recusive behaviour on and off.
If recursive is on, paginated results will be automatically followed and concated together.