libjenkins-0.8.4: 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) => Master -> JenkinsT m a -> m (Either JenkinsException a) Source #

Run a JenkinsT action

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

data JenkinsT m a Source #

The value of this type describes Jenkins REST API requests sequence

Instances

MonadTrans JenkinsT Source # 

Methods

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

MonadError e m => MonadError e (JenkinsT m) Source # 

Methods

throwError :: e -> JenkinsT m a #

catchError :: JenkinsT m a -> (e -> JenkinsT m a) -> JenkinsT m a #

MonadReader r m => MonadReader r (JenkinsT m) Source # 

Methods

ask :: JenkinsT m r #

local :: (r -> r) -> JenkinsT m a -> JenkinsT m a #

reader :: (r -> a) -> JenkinsT m a #

MonadState s m => MonadState s (JenkinsT m) Source # 

Methods

get :: JenkinsT m s #

put :: s -> JenkinsT m () #

state :: (s -> (a, s)) -> JenkinsT m a #

MonadWriter w m => MonadWriter w (JenkinsT m) Source # 

Methods

writer :: (a, w) -> JenkinsT m a #

tell :: w -> JenkinsT m () #

listen :: JenkinsT m a -> JenkinsT m (a, w) #

pass :: JenkinsT m (a, w -> w) -> JenkinsT m a #

Monad (JenkinsT m) Source # 

Methods

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

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

return :: a -> JenkinsT m a #

fail :: String -> JenkinsT m a #

Functor (JenkinsT m) Source # 

Methods

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

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

Applicative (JenkinsT m) Source # 

Methods

pure :: a -> JenkinsT m a #

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

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

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

MonadIO m => MonadIO (JenkinsT m) Source # 

Methods

liftIO :: IO a -> JenkinsT m a #

type Jenkins = JenkinsT IO Source #

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

data Master Source #

Jenkins master node connection settings token

Constructors

Master 

Fields

Instances

Eq Master Source # 

Methods

(==) :: Master -> Master -> Bool #

(/=) :: Master -> Master -> Bool #

Data Master Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Master -> c Master #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Master #

toConstr :: Master -> Constr #

dataTypeOf :: Master -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Master) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Master) #

gmapT :: (forall b. Data b => b -> b) -> Master -> Master #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Master -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Master -> r #

gmapQ :: (forall d. Data d => d -> u) -> Master -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Master -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Master -> m Master #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Master -> m Master #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Master -> m Master #

Show Master Source # 

Combinators

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

Perform a GET request

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

stream :: MonadResource m => Formatter f -> (forall g. Method Complete g) -> JenkinsT m (ResumableSource m ByteString) Source #

Perform a streaming GET request

stream, unlike get, is constant-space

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

Perform a POST request

post_ :: (forall f. Method Complete f) -> JenkinsT m ByteString 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

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 ByteString 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

groovy Source #

Arguments

:: Text

Groovy source code

-> JenkinsT m Text 

Perform a POST request to /scriptText

reload :: JenkinsT m () Source #

Reload jenkins configuration from disk

Performs /reload

restart :: JenkinsT m () Source #

Restart jenkins safely

Performs /safeRestart

/safeRestart allows all running jobs to complete

forceRestart :: JenkinsT m () Source #

Restart jenkins

Performs /restart

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

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 parseRequest.

The constructor for this data type is not exposed. Instead, you should use either the defaultRequest value, or parseRequest 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 <- parseRequest "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

Instances