servant-github-0.1.0.2: Bindings to GitHub API using servant.

Copyright(c) Finlay Thompson, 2015
LicenseBSD3
Maintainerfinlay.thompson@gmail.com
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Network.GitHub.Client

Description

 

Synopsis

Documentation

github :: (HasClient (AddHeaders api), HasGitHub (Client (AddHeaders api))) => Proxy api -> EmbedGitHub (Client (AddHeaders api)) Source

Wrapper around the servant client function, that takes care of the extra headers that required for the GitHub monad.

data AuthToken Source

Token used to authorize access to the GitHub API. see https://developer.github.com/v3/oauth/

Instances

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

runGitHub :: GitHub a -> Maybe AuthToken -> IO (Either ServantError a) Source

You need to provide a 'Maybe AuthToken' to lift a GitHub computation into the IO monad.

data GitHubState Source

GitHubState options that control which headers are provided to the API and stores the Link header result

Constructors

GitHubState 

Fields

perPage :: Int

The number of records returned per page

page :: Int

The page number returned

links :: Maybe [Link]

Contains the returned Link header, if available.

recurse :: Bool

Flag to set the recursive mode on

useragent :: Text

Text to send as User-agent

class HasGitHub a where Source

This class defines how the client code is actually called.

Methods

embedGitHub :: a -> EmbedGitHub a Source

Instances

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

Equations

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.

Equations

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.

Equations

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.

recurseOn :: GitHub () Source

Turn automatic recusive behaviour on and off.

If recursive is on, paginated results will be automatically followed and concated together.

pageSize :: Int -> GitHub () Source

The default number of records per page is set to 100. Smaller pages can be set, but not bigger than 100.

getLinks :: GitHub (Maybe [Link]) Source

Return the Link header. This is only set when there are futher pages.