ReviewBoard-0.2.2: Haskell bindings to ReviewBoardSource codeContentsIndex
ReviewBoard.Api
Portabilityportable
Stabilityexperimental
Maintaineradam.smyczek@gmail.com
Contents
API calls
Users and groups
Review request
Review
Others
Util functions
Example
Description

ReviewBoard API

This module provides the basic ReviewBoard API calls. All calls are executed inside the RBAction monad that represents a session to the ReviewBoard server. A login to the server is performed in the RBAction run method runRBAction.

All actions return the RBResponse object that can be a RBok with the response JSValue or RBerr containing the error message and the encoded response, if received. Errors are handled in two ways:

  • Network errors, for example connection errors throw an exception.
  • Response errors resulting in for example invalid request parameters are handled using the rbErrHandler (by default print to stdin).

For API details see ReviewBoard project page http://code.google.com/p/reviewboard/

Synopsis
module ReviewBoard.Core
module ReviewBoard.Browser
module ReviewBoard.Request
userList :: Maybe String -> RBAction RBResponse
groupList :: Maybe String -> RBAction RBResponse
groupStar :: String -> RBAction RBResponse
groupUnstar :: String -> RBAction RBResponse
reviewRequest :: Integer -> RBAction RBResponse
reviewRequestByChangenum :: Integer -> Integer -> RBAction RBResponse
reviewRequestNew :: String -> Maybe String -> RBAction RBResponse
reviewRequestDelete :: Integer -> RBAction RBResponse
reviewRequestSet :: Integer -> [(RRField, String)] -> RBAction RBResponse
reviewRequestSetField :: Integer -> RRField -> String -> RBAction RBResponse
reviewRequestSaveDraft :: Integer -> RBAction RBResponse
reviewRequestDiscardDraft :: Integer -> RBAction RBResponse
reviewRequestStar :: Integer -> RBAction RBResponse
reviewRequestUnstar :: Integer -> RBAction RBResponse
reviewRequestDiffNew :: Integer -> String -> FilePath -> RBAction RBResponse
reviewRequestScreenshotNew :: Integer -> FilePath -> RBAction RBResponse
reviewRequestListAll :: Maybe String -> RBAction RBResponse
reviewRequestListToGroup :: String -> Maybe String -> RBAction RBResponse
reviewRequestListToUser :: String -> Bool -> Maybe String -> RBAction RBResponse
reviewRequestListFromUser :: String -> Maybe String -> RBAction RBResponse
reviewAll :: Integer -> RBAction RBResponse
reviewSaveDraft :: Integer -> RBAction RBResponse
reviewDeleteDraft :: Integer -> RBAction RBResponse
reviewPublishDraft :: Integer -> RBAction RBResponse
repositoryList :: RBAction RBResponse
execRBAction :: String -> String -> String -> RBAction a -> IO a
Documentation
module ReviewBoard.Core
module ReviewBoard.Browser
module ReviewBoard.Request
API calls
Users and groups
userList :: Maybe String -> RBAction RBResponseSource
Search for a user or list all users if user is Nothing
groupList :: Maybe String -> RBAction RBResponseSource
Search for a group or list all group if Nothing
groupStar :: String -> RBAction RBResponseSource
Star group for group name
groupUnstar :: String -> RBAction RBResponseSource
Unstar group for group name
Review request
reviewRequest :: Integer -> RBAction RBResponseSource
Get review request by id.
reviewRequestByChangenum :: Integer -> Integer -> RBAction RBResponseSource
Get review request by repository id and changenum id
reviewRequestNew :: String -> Maybe String -> RBAction RBResponseSource
Create new review request using the provided repository path and an optional submit_as user. The returned response contains the id of the new created review request that can be accessed using rrId helper function.
reviewRequestDelete :: Integer -> RBAction RBResponseSource
Delete review request with request id.
reviewRequestSet :: Integer -> [(RRField, String)] -> RBAction RBResponseSource
Set fields to review request draft with id.
reviewRequestSetField :: Integer -> RRField -> String -> RBAction RBResponseSource
Set one field for review request draft with id.
reviewRequestSaveDraft :: Integer -> RBAction RBResponseSource
Discard review request draft for id.
reviewRequestDiscardDraft :: Integer -> RBAction RBResponseSource
Save review request draft whith id.
reviewRequestStar :: Integer -> RBAction RBResponseSource
Star review request for id
reviewRequestUnstar :: Integer -> RBAction RBResponseSource
Star review request for id
reviewRequestDiffNew :: Integer -> String -> FilePath -> RBAction RBResponseSource
Add a new diff to a review request with id, file path and the basedir parameter.
reviewRequestScreenshotNew :: Integer -> FilePath -> RBAction RBResponseSource
Add a new screenshot with file path to a review request with id
reviewRequestListAll :: Maybe String -> RBAction RBResponseSource
List all review requests with an optional status
reviewRequestListToGroup :: String -> Maybe String -> RBAction RBResponseSource
List review request assigned to a group with an optional status
reviewRequestListToUser :: String -> Bool -> Maybe String -> RBAction RBResponseSource
List review request assigned to a user, directly or not with an optional status
reviewRequestListFromUser :: String -> Maybe String -> RBAction RBResponseSource
List review request from a user with an optional status
Review
reviewAll :: Integer -> RBAction RBResponseSource
List all reviews for review request id
reviewSaveDraft :: Integer -> RBAction RBResponseSource
Save review draft for review request id
reviewDeleteDraft :: Integer -> RBAction RBResponseSource
Delete review draft for review request id
reviewPublishDraft :: Integer -> RBAction RBResponseSource
Publish review request draft for id
Others
repositoryList :: RBAction RBResponseSource
List repositories
Util functions
execRBAction :: String -> String -> String -> RBAction a -> IO aSource
Execute a ReviewBoard action using the provided URL, user and password.
Example

The following RBAction creates a new review request draft, sets some fields and uploads a diff file:

    import ReviewBoard.Api
    import qualified ReviewBoard.Response as R
    newRRAction :: RBAction ()
    newRRAction = do
        rsp <- reviewRequestNew "repository" Nothing
        case rsp of
            RBok r -> do
                let id = R.id . R.review_request $ r
                reviewRequestsSetField id TARGET_PEOPLE "reviewers"
                reviewRequestsSetField id DESCRIPTION "Request description"
                reviewRequestsDiffNew  id "basedir" "diffFileName"
                reviewRequestSaveDraft id
                liftIO $ print "Done."
            RBerr s -> throwError s

To run this action, execute:

   execRBAction "url" "user" "password" newRRAction
Produced by Haddock version 2.3.0