libjenkins-0.5.0: Jenkins API interface

Safe HaskellNone
LanguageHaskell2010

Jenkins.Rest

Contents

Description

Jenkins REST API interface

Synopsis

Query Jenkins

data Jenkins a Source

Jenkins REST API query sequence description

class HasConnectInfo t where Source

Convenience class aimed at elimination of long chains of lenses to access jenkins connection configuration

For example, if you have a configuration record in your application:

data Config = Config
  { ...
  , _jenkinsConnectInfo :: ConnectInfo
  , ...
  }

you can make it an instance of HasConnectInfo:

instance HasConnectInfo Config where
  connectInfo f x = (p -> x { _jenkinsConnectInfo = p }) <$> f (_jenkinsConnectInfo x)

and then use e.g. view jenkinsUrl config to get the url part of the jenkins connection

data ConnectInfo Source

Jenkins connection settings

_jenkinsApiToken may be user's password, Jenkins does not make any distinction between these concepts

Constructors

ConnectInfo 

Fields

_jenkinsUrl :: String

Jenkins URL, e.g. http://example.com/jenkins

_jenkinsPort :: Int

Jenkins port, e.g. 8080

_jenkinsUser :: Text

Jenkins user, e.g. jenkins

_jenkinsApiToken :: Text

Jenkins user API token

defaultConnectInfo :: ConnectInfo Source

Default Jenkins connection settings

defaultConnectInfo = ConnectInfo
  { _jenkinsUrl      = "http://example.com/jenkins"
  , _jenkinsPort     = 8080
  , _jenkinsUser     = "jenkins"
  , _jenkinsApiToken = ""
  }

data Result e v Source

The result of Jenkins REST API queries

Constructors

Error e

Exception e was thrown while querying Jenkins

Disconnect

The client was explicitly disconnected

Result v

Querying successfully finished the with value v

Instances

(Eq e, Eq v) => Eq (Result e v) 
(Data e, Data v) => Data (Result e v) 
(Ord e, Ord v) => Ord (Result e v) 
(Show e, Show v) => Show (Result e v) 
Generic (Result e v) 
Typeable (* -> * -> *) Result 
type Rep (Result e v) 

runJenkins :: HasConnectInfo t => t -> Jenkins a -> IO (Result JenkinsException a) Source

Query Jenkins API using Jenkins description

Successful result is either Disconnect or Result v

If HttpException was thrown by http-conduit, runJenkins catches it and wraps in Error. Other exceptions are not catched

Combinators

get :: Method Complete f -> Jenkins ByteString Source

GET query

While the return type is a lazy bytestring, the entire response sits in memory anyway: lazy I/O is not used

getS :: Method Complete f -> Jenkins (ResumableSource (ResourceT IO) ByteString) Source

GET query

If you don't close the source eventually (either explicitly with closeResumableSource or implicitly by reading from it) it will leak a socket.

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

POST query (with a payload)

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

POST query (without payload)

concurrently :: Jenkins a -> Jenkins b -> Jenkins (a, b) Source

Do both queries concurrently

orElse :: Jenkins a -> Jenkins a -> Jenkins a Source

orElse a b runs a and only runs b if a has thrown a JenkinsException

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

Lift a computation from the IO monad.

with :: (Request -> Request) -> Jenkins a -> Jenkins a Source

Make local changes to the Request

Method

Convenience

postXML :: (forall f. Method Complete f) -> Document -> Jenkins () Source

POST job's config.xml (or any other xml, really) in xml-conduit format

traverseC :: (a -> Jenkins b) -> [a] -> Jenkins [b] Source

Make a bunch of queries concurrently

traverseC_ :: (a -> Jenkins b) -> [a] -> Jenkins () Source

Make a bunch of queries concurrently ignoring their results

reload :: Jenkins a Source

Reload jenkins configuration from disk

Calls /reload and disconnects

restart :: Jenkins a Source

Restart jenkins safely

Calls /safeRestart and disconnects

/safeRestart allows all running jobs to complete

forceRestart :: Jenkins a Source

Force jenkins to restart without waiting for running jobs to finish

Calls /restart and disconnects

Optics

jenkinsUrl :: HasConnectInfo t => Lens' t String Source

A lens into Jenkins URL

jenkinsPort :: HasConnectInfo t => Lens' t Int Source

A lens into Jenkins port

jenkinsUser :: HasConnectInfo t => Lens' t Text Source

A lens into Jenkins user

jenkinsApiToken :: HasConnectInfo t => Lens' t Text Source

A lens into Jenkins user API token

jenkinsPassword :: HasConnectInfo t => Lens' t Text Source

A lens into Jenkins password

jenkinsPassword = jenkinsApiToken

_Error :: Prism (Result e a) (Result e' a) e e' Source

A prism into Jenkins error

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

A prism into disconnect

_Result :: Prism (Result e a) (Result e b) a b Source

A prism into result

Reexports

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