module Jenkins.Rest
(
run
, JenkinsT
, Jenkins
, Master(..)
, get
, stream
, post
, post_
, orElse
, orElse_
, locally
, module Jenkins.Rest.Method
, concurrently
, Jenkins.Rest.traverse
, Jenkins.Rest.traverse_
, postXml
, groovy
, reload
, restart
, forceRestart
, JenkinsException(..)
, liftIO
, Http.Request
) where
import Control.Applicative ((<$))
import qualified Control.Exception as Unlifted
import Control.Monad.IO.Class (MonadIO(..))
import Control.Monad.Trans.Control (MonadBaseControl(..))
import Control.Monad.Trans.Resource (MonadResource)
import qualified Data.ByteString.Lazy as Lazy
import qualified Data.ByteString as Strict
import Data.Conduit (ResumableSource)
import Data.Data (Data, Typeable)
import qualified Data.Foldable as F
import Data.Monoid (mempty)
import Data.Text (Text)
import qualified Data.Text.Lazy as Text.Lazy
import qualified Data.Text.Lazy.Encoding as Text.Lazy
import Data.Traversable (sequence)
import qualified Network.HTTP.Conduit as Http
import qualified Network.HTTP.Types as Http
import Prelude hiding (sequence)
import Jenkins.Rest.Internal
import Jenkins.Rest.Method
import Jenkins.Rest.Method.Internal
run :: (MonadIO m, MonadBaseControl IO m) => Master -> JenkinsT m a -> m (Either JenkinsException a)
run m jenk = try (runInternal (url m) (user m) (apiToken m) jenk)
try :: MonadBaseControl IO m => m a -> m (Either JenkinsException a)
try m = sequence . fmap restoreM =<< liftBaseWith (\magic -> Unlifted.try (magic m))
type Jenkins = JenkinsT IO
data Master = Master
{ url :: String
, user :: Text
, apiToken :: Text
} deriving (Show, Eq, Typeable, Data)
get :: Formatter f -> (forall g. Method Complete g) -> JenkinsT m Lazy.ByteString
get (Formatter f) m = liftJ (Get (f m) id)
stream
:: MonadResource m
=> Formatter f -> (forall g. Method Complete g) -> JenkinsT m (ResumableSource m Strict.ByteString)
stream (Formatter f) m = liftJ (Stream (f m) id)
post :: (forall f. Method Complete f) -> Lazy.ByteString -> JenkinsT m Lazy.ByteString
post m body = liftJ (Post m body id)
post_ :: (forall f. Method Complete f) -> JenkinsT m Lazy.ByteString
post_ m = post m mempty
orElse :: JenkinsT m a -> (JenkinsException -> JenkinsT m a) -> JenkinsT m a
orElse a b = liftJ (Or a b)
orElse_ :: JenkinsT m a -> JenkinsT m a -> JenkinsT m a
orElse_ a b = orElse a (\_ -> b)
locally :: (Http.Request -> Http.Request) -> JenkinsT m a -> JenkinsT m a
locally f j = liftJ (With f j id)
concurrently :: JenkinsT m a -> JenkinsT m b -> JenkinsT m (a, b)
concurrently ja jb = liftJ (Conc ja jb (,))
traverse :: (a -> JenkinsT m b) -> [a] -> JenkinsT m [b]
traverse f = foldr go (return [])
where
go x xs = do (y, ys) <- concurrently (f x) xs; return (y : ys)
traverse_ :: F.Foldable f => (a -> JenkinsT m b) -> f a -> JenkinsT m ()
traverse_ f = F.foldr (\x xs -> () <$ concurrently (f x) xs) (return ())
postXml :: (forall f. Method Complete f) -> Lazy.ByteString -> JenkinsT m Lazy.ByteString
postXml m = locally (\r -> r { Http.requestHeaders = xmlHeader : Http.requestHeaders r }) . post m
where
xmlHeader = ("Content-Type", "text/xml")
groovy
:: Text.Lazy.Text
-> JenkinsT m Text.Lazy.Text
groovy script = locally (\r -> r { Http.requestHeaders = ascii : Http.requestHeaders r }) $
liftJ (Post "scriptText" body Text.Lazy.decodeUtf8)
where
body = Lazy.fromChunks
[Http.renderSimpleQuery False [("script", Lazy.toStrict (Text.Lazy.encodeUtf8 script))]]
ascii = ("Content-Type", "application/x-www-form-urlencoded")
reload :: JenkinsT m ()
reload = () <$ post_ "reload"
restart :: JenkinsT m ()
restart = () <$ post_ "safeRestart"
forceRestart :: JenkinsT m ()
forceRestart = () <$ post_ "restart"