github-rest-1.0.0: Query the GitHub REST API programmatically

MaintainerBrandon Chinn <brandon@leapyear.io>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

GitHub.REST

Contents

Description

Definitions for querying the GitHub REST API. See README.md for an example.

Synopsis

Monad transformer and type-class for querying the GitHub REST API

class MonadFail m => MonadGitHubREST m where Source #

A type class for monads that can query the GitHub REST API.

Example:

-- create the "foo" branch
queryGitHub GHEndpoint
  { method = POST
  , endpoint = "/repos/:owner/:repo/git/refs"
  , endpointVals =
    [ "owner" := "alice"
    , "repo" := "my-project"
    ]
  , ghData =
    [ "ref" := "refs/heads/foo"
    , "sha" := "1234567890abcdef"
    ]
  }

It's recommended that you create functions for the API endpoints you're using:

deleteBranch branch = queryGitHub GHEndpoint
  { method = DELETE
  , endpoint = "/repos/:owner/:repo/git/refs/:ref"
  , endpointVals =
    [ "owner" := "alice"
    , "repo" := "my-project"
    , "ref" := "heads/" <> branch
    ]
  , ghData = []
  }

Minimal complete definition

queryGitHubPage'

Methods

queryGitHubPage' :: FromJSON a => GHEndpoint -> m (Either (Text, Text) (a, PageLinks)) Source #

Query GitHub, returning Right (payload, links) if successful, where payload is the response that GitHub sent back and links containing any pagination links GitHub may have sent back. If the response could not be decoded as JSON, returns Left (error message, response from server).

Errors on network connection failures or if GitHub sent back an error message. Use githubTry if you wish to handle GitHub errors.

queryGitHubPage :: FromJSON a => GHEndpoint -> m (a, PageLinks) Source #

queryGitHubPage', except calls fail if JSON decoding fails.

queryGitHub :: FromJSON a => GHEndpoint -> m a Source #

queryGitHubPage, except ignoring pagination links.

queryGitHubAll :: (FromJSON a, Monoid a) => GHEndpoint -> m a Source #

Repeatedly calls queryGitHubPage for each page returned by GitHub and concatenates the results.

queryGitHub_ :: GHEndpoint -> m () Source #

queryGitHub, except ignores the result.

Instances
MonadGitHubREST m => MonadGitHubREST (MaybeT m) Source # 
Instance details

Defined in GitHub.REST.Monad.Class

(MonadIO m, MonadFail m) => MonadGitHubREST (GitHubT m) Source # 
Instance details

Defined in GitHub.REST.Monad

MonadGitHubREST m => MonadGitHubREST (ExceptT e m) Source # 
Instance details

Defined in GitHub.REST.Monad.Class

MonadGitHubREST m => MonadGitHubREST (IdentityT m) Source # 
Instance details

Defined in GitHub.REST.Monad.Class

MonadGitHubREST m => MonadGitHubREST (StateT s m) Source # 
Instance details

Defined in GitHub.REST.Monad.Class

MonadGitHubREST m => MonadGitHubREST (StateT s m) Source # 
Instance details

Defined in GitHub.REST.Monad.Class

(Monoid w, MonadGitHubREST m) => MonadGitHubREST (WriterT w m) Source # 
Instance details

Defined in GitHub.REST.Monad.Class

(Monoid w, MonadGitHubREST m) => MonadGitHubREST (WriterT w m) Source # 
Instance details

Defined in GitHub.REST.Monad.Class

MonadGitHubREST m => MonadGitHubREST (ReaderT r m) Source # 
Instance details

Defined in GitHub.REST.Monad.Class

(Monoid w, MonadGitHubREST m) => MonadGitHubREST (RWST r w s m) Source # 
Instance details

Defined in GitHub.REST.Monad.Class

(Monoid w, MonadGitHubREST m) => MonadGitHubREST (RWST r w s m) Source # 
Instance details

Defined in GitHub.REST.Monad.Class

data GitHubT m a Source #

A simple monad that can run REST calls.

Instances
MonadTrans GitHubT Source # 
Instance details

Defined in GitHub.REST.Monad

Methods

lift :: Monad m => m a -> GitHubT m a #

Monad m => Monad (GitHubT m) Source # 
Instance details

Defined in GitHub.REST.Monad

Methods

(>>=) :: GitHubT m a -> (a -> GitHubT m b) -> GitHubT m b #

(>>) :: GitHubT m a -> GitHubT m b -> GitHubT m b #

return :: a -> GitHubT m a #

fail :: String -> GitHubT m a #

Functor m => Functor (GitHubT m) Source # 
Instance details

Defined in GitHub.REST.Monad

Methods

fmap :: (a -> b) -> GitHubT m a -> GitHubT m b #

(<$) :: a -> GitHubT m b -> GitHubT m a #

MonadFail m => MonadFail (GitHubT m) Source # 
Instance details

Defined in GitHub.REST.Monad

Methods

fail :: String -> GitHubT m a #

Applicative m => Applicative (GitHubT m) Source # 
Instance details

Defined in GitHub.REST.Monad

Methods

pure :: a -> GitHubT m a #

(<*>) :: GitHubT m (a -> b) -> GitHubT m a -> GitHubT m b #

liftA2 :: (a -> b -> c) -> GitHubT m a -> GitHubT m b -> GitHubT m c #

(*>) :: GitHubT m a -> GitHubT m b -> GitHubT m b #

(<*) :: GitHubT m a -> GitHubT m b -> GitHubT m a #

MonadIO m => MonadIO (GitHubT m) Source # 
Instance details

Defined in GitHub.REST.Monad

Methods

liftIO :: IO a -> GitHubT m a #

MonadUnliftIO m => MonadUnliftIO (GitHubT m) Source # 
Instance details

Defined in GitHub.REST.Monad

Methods

askUnliftIO :: GitHubT m (UnliftIO (GitHubT m)) #

withRunInIO :: ((forall a. GitHubT m a -> IO a) -> IO b) -> GitHubT m b #

(MonadIO m, MonadFail m) => MonadGitHubREST (GitHubT m) Source # 
Instance details

Defined in GitHub.REST.Monad

data GitHubState Source #

Constructors

GitHubState 

Fields

runGitHubT :: MonadIO m => GitHubState -> GitHubT m a -> m a Source #

Run the given GitHubT action with the given token and user agent.

The token will be sent with each API request -- see Token. The user agent is also required for each API request -- see https://developer.github.com/v3/#user-agent-required.

GitHub authentication

GitHub Endpoints

data GHEndpoint Source #

A call to a GitHub API endpoint.

Constructors

GHEndpoint 

Fields

  • method :: StdMethod
     
  • endpoint :: Text

    The GitHub API endpoint, with colon-prefixed components that will be replaced; e.g. "/users/:username/repos"

  • endpointVals :: EndpointVals

    Key-value pairs to replace colon-prefixed components in endpoint; e.g. [ "username" := ("alice" :: Text) ]

  • ghData :: GitHubData

    Key-value pairs to send in the request body; e.g. [ "sort" := ("created" :: Text), "direction" := ("asc" :: Text) ]

KeyValue pairs

data KeyValue where Source #

A type representing a key-value pair.

Constructors

(:=) :: (Show v, ToJSON v) => Text -> v -> KeyValue infixr 1 
Instances
Show KeyValue Source # 
Instance details

Defined in GitHub.REST.KeyValue

ToJSON [KeyValue] Source # 
Instance details

Defined in GitHub.REST.KeyValue

Helpers

githubTry :: MonadUnliftIO m => m a -> m (Either Value a) Source #

Handle 422 exceptions thrown by the GitHub REST API.

Most client errors are 422, since we should always be sending valid JSON. If an endpoint throws different error codes, use githubTry'.

https://developer.github.com/v3/#client-errors

githubTry' :: MonadUnliftIO m => Status -> m a -> m (Either Value a) Source #

Handle the given exception thrown by the GitHub REST API.

(.:) :: FromJSON a => Value -> Text -> a Source #

Get the given key from the Value, erroring if it doesn't exist.

Re-exports

data StdMethod #

HTTP standard method (as defined by RFC 2616, and PATCH which is defined by RFC 5789).

Constructors

GET 
POST 
HEAD 
PUT 
DELETE 
TRACE 
CONNECT 
OPTIONS 
PATCH 
Instances
Bounded StdMethod 
Instance details

Defined in Network.HTTP.Types.Method

Enum StdMethod 
Instance details

Defined in Network.HTTP.Types.Method

Eq StdMethod 
Instance details

Defined in Network.HTTP.Types.Method

Ord StdMethod 
Instance details

Defined in Network.HTTP.Types.Method

Read StdMethod 
Instance details

Defined in Network.HTTP.Types.Method

Show StdMethod 
Instance details

Defined in Network.HTTP.Types.Method

Ix StdMethod 
Instance details

Defined in Network.HTTP.Types.Method