libjenkins-0.6.0: Jenkins API interface

Safe HaskellNone
LanguageHaskell2010

Jenkins.Rest

Contents

Description

Jenkins REST API interface

This module is intended to be imported qualified.

Synopsis

Query Jenkins

run :: (MonadIO m, MonadBaseControl IO m, HasMaster t) => t -> JenkinsT m a -> m (Result a) Source

Run a JenkinsT action

A successful Result is either Disconnect or Ok v

If a JenkinsException is thrown by performing a request to Jenkins, runJenkins will catch and wrap it in Exception. Other exceptions will propagate further

data JenkinsT m a Source

The value of this type describes Jenkins REST API requests sequence

type Jenkins = JenkinsT IO Source

A handy type synonym for the kind of JenkinsT actions that's used the most

data Result v Source

The result of Jenkins REST API queries

Constructors

Exception JenkinsException

Exception was thrown while making requests to Jenkins

Disconnect

The client was explicitly disconnected by the user

Ok v

The result of uninterrupted execution of a JenkinsT value

Instances

Show v => Show (Result v) 
Typeable (* -> *) Result 

class HasMaster t where Source

Jenkins master node connection settings

Minimal complete definition

master

Methods

master :: Lens' t Master Source

url :: HasMaster t => Lens' t String Source

Jenkins master node URL

user :: HasMaster t => Lens' t Text Source

Jenkins user

apiToken :: HasMaster t => Lens' t Text Source

Jenkins user's password or API token

Instances

data Master Source

Jenkins master node connection settings token

defaultMaster :: Master Source

Default Jenkins master node connection settings token

view url      defaultConnectInfo = "http://example.com/jenkins"
view user     defaultConnectInfo = "jenkins"
view apiToken defaultConnectInfo = "secret"

Combinators

get :: Formatter f -> (forall g. Method Complete g) -> JenkinsT m ByteString Source

Perform a GET request

While the return type is the lazy Bytestring, the entire response sits in the memory anyway: lazy I/O is not used at the least

post :: (forall f. Method Complete f) -> ByteString -> JenkinsT m () Source

Perform a POST request

post_ :: (forall f. Method Complete f) -> JenkinsT m () Source

Perform a POST request without a payload

orElse :: JenkinsT m a -> (JenkinsException -> JenkinsT m a) -> JenkinsT m a Source

A simple exception handler. If an exception is raised while the action is executed the handler is executed with it as an argument

orElse_ :: JenkinsT m a -> JenkinsT m a -> JenkinsT m a Source

A simpler exception handler

orElse_ a b = orElse a (_ -> b)

locally :: (Request -> Request) -> JenkinsT m a -> JenkinsT m a Source

locally f x modifies the base Request with f for the execution of x (think local)

This is useful for setting the appropriate headers, response timeouts and the like

disconnect :: JenkinsT m a Source

Disconnect from Jenkins. The following actions are ignored.

Method

Concurrency

concurrently :: JenkinsT m a -> JenkinsT m b -> JenkinsT m (a, b) Source

Run two actions concurrently

traverse :: (a -> JenkinsT m b) -> [a] -> JenkinsT m [b] Source

Map every list element to an action, run them concurrently and collect the results

traverse : traverse :: concurrently : liftA2 (,)

traverse_ :: Foldable f => (a -> JenkinsT m b) -> f a -> JenkinsT m () Source

Map every list element to an action and run them concurrently ignoring the results

traverse_ : traverse_ :: concurrently : liftA2 (,)

Convenience

postXml :: (forall f. Method Complete f) -> ByteString -> JenkinsT m () Source

Perform a POST request to Jenkins with the XML document

Sets up the correct Content-Type header. Mostly useful for updating config.xml files for jobs, views, etc

reload :: JenkinsT m a Source

Reload jenkins configuration from disk

Performs /reload and disconnects

restart :: JenkinsT m a Source

Restart jenkins safely

Performs /safeRestart and disconnects

/safeRestart allows all running jobs to complete

forceRestart :: JenkinsT m a Source

Restart jenkins

Performs /restart and disconnects

/restart restart Jenkins immediately, without waiting for the completion of the building and/or waiting jobs

Optics

_Exception :: Prism (Result a) (Result a) JenkinsException JenkinsException Source

A prism into Jenkins error

_Disconnect :: Prism' (Result a) () Source

A prism into disconnect

_Ok :: Prism (Result a) (Result b) a b Source

A prism into result

newtype JenkinsException Source

The kind of exceptions that can be thrown by performing requests to the Jenkins REST API

Reexports

liftIO :: MonadIO m => forall a. IO a -> m a

Lift a computation from the IO monad.

data Request :: *

All information on how to connect to a host and what should be sent in the HTTP request.

If you simply wish to download from a URL, see parseUrl.

The constructor for this data type is not exposed. Instead, you should use either the def method to retrieve a default instance, or parseUrl to construct from a URL, and then use the records below to make modifications. This approach allows http-client to add configuration options without breaking backwards compatibility.

For example, to construct a POST request, you could do something like:

initReq <- parseUrl "http://www.example.com/path"
let req = initReq
            { method = "POST"
            }

For more information, please see http://www.yesodweb.com/book/settings-types.

Since 0.1.0