libjenkins-0.9.0: Jenkins API interface
Safe HaskellSafe-Inferred
LanguageHaskell2010

Jenkins.Rest.Method

Description

Jenkins REST API methods

Synopsis

Construct URLs

Path

text :: Text -> Method 'Complete f Source #

Use a string as an URI segment

>>> pp (text "foo")
"foo"

Note: with -XOverloadedStrings extension enabled it's possible to use string literals as segments of the Jenkins API method URL

>>> pp' "foo"
"foo"

Note: don't put / in the string literal unless you want it URL-encoded, use (-/-) instead

>>> pp' "foo/bar"
"foo%2Fbar"

int :: Int -> Method 'Complete f Source #

Use an integer as an URI segment

>>> pp (int 4)
"4"

(-/-) :: Method 'Complete f -> Method 'Complete f -> Method 'Complete f infixr 5 Source #

Combine two paths

>>> pp ("foo" -/- "bar" -/- "baz")
"foo/bar/baz"

Query

(-=-) :: Text -> Text -> Method 'Query f infix 7 Source #

Make a key-value pair

>>> pp ("foo" -=- "bar")
"foo=bar"

(-&-) :: Method 'Query f -> Method 'Query f -> Method 'Query f infixr 5 Source #

Create the union of two queries

>>> pp ("foo" -=- "bar" -&- "baz")
"foo=bar&baz"

query :: [(Text, Maybe Text)] -> Method 'Query f Source #

Take a list of key-value pairs and render them as a query

>>> pp (query [("foo", Nothing), ("bar", Just "baz"), ("quux", Nothing)])
"foo&bar=baz&quux"
>>> pp (query [])
""

Put together the segments and the query

(-?-) :: Method 'Complete f -> Method 'Query f -> Method 'Complete f infix 1 Source #

Put path and query together

>>> pp ("qux" -/- "quux" -?- "foo" -=- "bar" -&- "baz")
"qux/quux?foo=bar&baz"
>>> pp ("" -?- "foo" -=- "bar")
"foo=bar"
>>> pp ("/" -?- "foo" -=- "bar")
"%2F?foo=bar"

Format

data Formatter g Source #

Formatters know how to append the "api/$format" string to the method URL

json :: Formatter 'Json Source #

Append the JSON formatting request to the method URL

>>> format json "foo"
"foo/api/json"

xml :: Formatter 'Xml Source #

Append the XML formatting request to the method URL

>>> format xml "foo"
"foo/api/xml"

python :: Formatter 'Python Source #

Append the Python formatting request to the method URL

>>> format python "foo"
"foo/api/python"

plain :: Formatter f Source #

The formatter that does exactly nothing

>>> format plain "foo"
"foo"

Shortcuts

job :: Text -> Method 'Complete f Source #

Job data

>>> format json (job "name")
"job/name/api/json"
>>> pp (job "name" -/- "config.xml")
"job/name/config.xml"

build :: Text -> Int -> Method 'Complete f Source #

Job build data

>>> format json (build "name" 4)
"job/name/4/api/json"

view :: Text -> Method 'Complete f Source #

View data

>>> format xml (view "name")
"view/name/api/xml"

queue :: Method 'Complete f Source #

Build queue data

>>> format python queue
"queue/api/python"

overallLoad :: Method 'Complete f Source #

Server statistics

>>> format xml overallLoad
"overallLoad/api/xml"

computer :: Method 'Complete f Source #

Nodes data

>>> format python computer
"computer/api/python"

Types

data Method :: Type -> Format -> * Source #

Jenkins RESTFul API method encoding

Instances

Instances details
IsString (Method 'Complete f) Source # 
Instance details

Defined in Jenkins.Rest.Method.Internal

IsString (Method 'Query f) Source # 
Instance details

Defined in Jenkins.Rest.Method.Internal

Methods

fromString :: String -> Method 'Query f #

t ~ 'Complete => Num (Method t f) Source #

Only to support numeric literals

Instance details

Defined in Jenkins.Rest.Method.Internal

Methods

(+) :: Method t f -> Method t f -> Method t f #

(-) :: Method t f -> Method t f -> Method t f #

(*) :: Method t f -> Method t f -> Method t f #

negate :: Method t f -> Method t f #

abs :: Method t f -> Method t f #

signum :: Method t f -> Method t f #

fromInteger :: Integer -> Method t f #

Show (SFormat f) => Show (Method t f) Source # 
Instance details

Defined in Jenkins.Rest.Method.Internal

Methods

showsPrec :: Int -> Method t f -> ShowS #

show :: Method t f -> String #

showList :: [Method t f] -> ShowS #

data Type Source #

Method types

Constructors

Query 
Complete 

Instances

Instances details
Data Type Source # 
Instance details

Defined in Jenkins.Rest.Method.Internal

Methods

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

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

toConstr :: Type -> Constr #

dataTypeOf :: Type -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Type Source # 
Instance details

Defined in Jenkins.Rest.Method.Internal

Methods

showsPrec :: Int -> Type -> ShowS #

show :: Type -> String #

showList :: [Type] -> ShowS #

Eq Type Source # 
Instance details

Defined in Jenkins.Rest.Method.Internal

Methods

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

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

data Format Source #

Response formats

Constructors

Json 
Xml 
Python 

Instances

Instances details
Data Format Source # 
Instance details

Defined in Jenkins.Rest.Method.Internal

Methods

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

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

toConstr :: Format -> Constr #

dataTypeOf :: Format -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Format Source # 
Instance details

Defined in Jenkins.Rest.Method.Internal

Eq Format Source # 
Instance details

Defined in Jenkins.Rest.Method.Internal

Methods

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

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