servant-github-0.1.0.6: 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 # 
ToHttpApiData 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 -> d -> e -> g -> h -> i -> k -> l -> m -> Paginated f) Source # 

Methods

embedGitHub :: (a -> b -> c -> d -> e -> g -> h -> i -> k -> l -> m -> Paginated f) -> EmbedGitHub (a -> b -> c -> d -> e -> g -> h -> i -> k -> l -> m -> Paginated f) Source #

HasGitHub (a -> b -> c -> d -> e -> g -> h -> i -> k -> l -> Paginated f) Source # 

Methods

embedGitHub :: (a -> b -> c -> d -> e -> g -> h -> i -> k -> l -> Paginated f) -> EmbedGitHub (a -> b -> c -> d -> e -> g -> h -> i -> k -> l -> Paginated f) Source #

HasGitHub (a -> b -> c -> d -> e -> g -> h -> i -> k -> Paginated f) Source # 

Methods

embedGitHub :: (a -> b -> c -> d -> e -> g -> h -> i -> k -> Paginated f) -> EmbedGitHub (a -> b -> c -> d -> e -> g -> h -> i -> k -> Paginated f) Source #

HasGitHub (a -> b -> c -> d -> e -> g -> h -> i -> Paginated f) Source # 

Methods

embedGitHub :: (a -> b -> c -> d -> e -> g -> h -> i -> Paginated f) -> EmbedGitHub (a -> b -> c -> d -> e -> g -> h -> i -> Paginated f) Source #

HasGitHub (a -> b -> c -> d -> e -> g -> h -> Paginated f) Source # 

Methods

embedGitHub :: (a -> b -> c -> d -> e -> g -> h -> Paginated f) -> EmbedGitHub (a -> b -> c -> d -> e -> g -> h -> Paginated f) Source #

HasGitHub (a -> b -> c -> d -> e -> g -> Paginated f) Source # 

Methods

embedGitHub :: (a -> b -> c -> d -> e -> g -> Paginated f) -> EmbedGitHub (a -> b -> c -> d -> e -> g -> Paginated f) Source #

HasGitHub (a -> b -> c -> d -> e -> Paginated f) Source # 

Methods

embedGitHub :: (a -> b -> c -> d -> e -> Paginated f) -> EmbedGitHub (a -> b -> c -> d -> e -> Paginated f) Source #

HasGitHub (a -> b -> c -> d -> Paginated e) Source # 

Methods

embedGitHub :: (a -> b -> c -> d -> Paginated e) -> EmbedGitHub (a -> b -> c -> d -> Paginated e) Source #

HasGitHub (a -> b -> c -> Paginated d) Source # 

Methods

embedGitHub :: (a -> b -> c -> Paginated d) -> EmbedGitHub (a -> b -> c -> Paginated d) Source #

HasGitHub (a -> b -> Paginated c) Source # 

Methods

embedGitHub :: (a -> b -> Paginated c) -> EmbedGitHub (a -> b -> Paginated c) Source #

HasGitHub (a -> Paginated b) Source # 

Methods

embedGitHub :: (a -> Paginated b) -> EmbedGitHub (a -> Paginated b) Source #

HasGitHub (a -> b -> c -> d -> e -> Single f) Source # 

Methods

embedGitHub :: (a -> b -> c -> d -> e -> Single f) -> EmbedGitHub (a -> b -> c -> d -> e -> Single f) Source #

HasGitHub (a -> b -> c -> d -> Single e) Source # 

Methods

embedGitHub :: (a -> b -> c -> d -> Single e) -> EmbedGitHub (a -> b -> c -> d -> Single e) Source #

HasGitHub (a -> b -> c -> Single d) Source # 

Methods

embedGitHub :: (a -> b -> c -> Single d) -> EmbedGitHub (a -> b -> c -> Single d) Source #

HasGitHub (a -> b -> Single c) Source # 

Methods

embedGitHub :: (a -> b -> Single c) -> EmbedGitHub (a -> b -> Single c) Source #

HasGitHub (a -> Single b) Source # 

Methods

embedGitHub :: (a -> Single b) -> EmbedGitHub (a -> Single b) Source #

type GitHub = ReaderT (Maybe AuthToken) (StateT GitHubState ClientM) Source #

The GitHub monad provides execution context

runGitHubNotApiClientM :: ClientM a -> IO (Either ServantError a) Source #

Most of the time we must use api.github.com, but calling loginoauthaccess_token only works if sent to github.com.

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

class HasGitHub a where Source #

This class defines how the client code is actually called.

Minimal complete definition

embedGitHub

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 -> d -> e -> g -> h -> i -> k -> l -> m -> Paginated f) Source # 

Methods

embedGitHub :: (a -> b -> c -> d -> e -> g -> h -> i -> k -> l -> m -> Paginated f) -> EmbedGitHub (a -> b -> c -> d -> e -> g -> h -> i -> k -> l -> m -> Paginated f) Source #

HasGitHub (a -> b -> c -> d -> e -> g -> h -> i -> k -> l -> Paginated f) Source # 

Methods

embedGitHub :: (a -> b -> c -> d -> e -> g -> h -> i -> k -> l -> Paginated f) -> EmbedGitHub (a -> b -> c -> d -> e -> g -> h -> i -> k -> l -> Paginated f) Source #

HasGitHub (a -> b -> c -> d -> e -> g -> h -> i -> k -> Paginated f) Source # 

Methods

embedGitHub :: (a -> b -> c -> d -> e -> g -> h -> i -> k -> Paginated f) -> EmbedGitHub (a -> b -> c -> d -> e -> g -> h -> i -> k -> Paginated f) Source #

HasGitHub (a -> b -> c -> d -> e -> g -> h -> i -> Paginated f) Source # 

Methods

embedGitHub :: (a -> b -> c -> d -> e -> g -> h -> i -> Paginated f) -> EmbedGitHub (a -> b -> c -> d -> e -> g -> h -> i -> Paginated f) Source #

HasGitHub (a -> b -> c -> d -> e -> g -> h -> Paginated f) Source # 

Methods

embedGitHub :: (a -> b -> c -> d -> e -> g -> h -> Paginated f) -> EmbedGitHub (a -> b -> c -> d -> e -> g -> h -> Paginated f) Source #

HasGitHub (a -> b -> c -> d -> e -> g -> Paginated f) Source # 

Methods

embedGitHub :: (a -> b -> c -> d -> e -> g -> Paginated f) -> EmbedGitHub (a -> b -> c -> d -> e -> g -> Paginated f) Source #

HasGitHub (a -> b -> c -> d -> e -> Paginated f) Source # 

Methods

embedGitHub :: (a -> b -> c -> d -> e -> Paginated f) -> EmbedGitHub (a -> b -> c -> d -> e -> Paginated f) Source #

HasGitHub (a -> b -> c -> d -> Paginated e) Source # 

Methods

embedGitHub :: (a -> b -> c -> d -> Paginated e) -> EmbedGitHub (a -> b -> c -> d -> Paginated e) Source #

HasGitHub (a -> b -> c -> Paginated d) Source # 

Methods

embedGitHub :: (a -> b -> c -> Paginated d) -> EmbedGitHub (a -> b -> c -> Paginated d) Source #

HasGitHub (a -> b -> Paginated c) Source # 

Methods

embedGitHub :: (a -> b -> Paginated c) -> EmbedGitHub (a -> b -> Paginated c) Source #

HasGitHub (a -> Paginated b) Source # 

Methods

embedGitHub :: (a -> Paginated b) -> EmbedGitHub (a -> Paginated b) Source #

HasGitHub (a -> b -> c -> d -> e -> Single f) Source # 

Methods

embedGitHub :: (a -> b -> c -> d -> e -> Single f) -> EmbedGitHub (a -> b -> c -> d -> e -> Single f) Source #

HasGitHub (a -> b -> c -> d -> Single e) Source # 

Methods

embedGitHub :: (a -> b -> c -> d -> Single e) -> EmbedGitHub (a -> b -> c -> d -> Single e) Source #

HasGitHub (a -> b -> c -> Single d) Source # 

Methods

embedGitHub :: (a -> b -> c -> Single d) -> EmbedGitHub (a -> b -> c -> Single d) Source #

HasGitHub (a -> b -> Single c) Source # 

Methods

embedGitHub :: (a -> b -> Single c) -> EmbedGitHub (a -> b -> Single c) Source #

HasGitHub (a -> Single b) Source # 

Methods

embedGitHub :: (a -> Single b) -> EmbedGitHub (a -> Single b) Source #

type family EmbedGitHub a :: * where ... Source #

Closed type family for recursively defining the GitHub client funciton types

Equations

EmbedGitHub (Single a) = GitHub a 
EmbedGitHub (Paginated a) = GitHub [a] 
EmbedGitHub (CountedPaginated name a) = GitHub (CountedList name a) 
EmbedGitHub (a -> b) = a -> EmbedGitHub b 

type family AddHeaders a :: * where ... 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 :: * where ... 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 (Get cts (CountedList name res)) = QueryParam "page" Int :> (QueryParam "per_page" Int :> Get cts (Headers '[Header "Link" Text] (CountedList name res))) 
ReadHeaders (Post cts (CountedList name res)) = QueryParam "page" Int :> (QueryParam "per_page" Int :> Post cts (Headers '[Header "Link" Text] (CountedList name res))) 
ReadHeaders (Delete cts (CountedList name res)) = QueryParam "page" Int :> (QueryParam "per_page" Int :> Delete cts (Headers '[Header "Link" Text] (CountedList name res))) 
ReadHeaders (Put cts (CountedList name res)) = QueryParam "page" Int :> (QueryParam "per_page" Int :> Put cts (Headers '[Header "Link" Text] (CountedList name res))) 
ReadHeaders (Patch cts (CountedList name res)) = QueryParam "page" Int :> (QueryParam "per_page" Int :> Patch cts (Headers '[Header "Link" Text] (CountedList name res))) 
ReadHeaders otherwise = otherwise 

type Single a = Maybe Text -> Maybe AuthToken -> ClientM a Source #

Client function that returns a single result

type Paginated a = Maybe Text -> Maybe AuthToken -> Maybe Int -> Maybe Int -> ClientM (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.