koji-0.0.2: Koji buildsystem XML-RPC API bindings
Safe HaskellNone
LanguageHaskell2010

Distribution.Koji

Description

A library for accessing a Koji hub via its XMLRPC API.

Synopsis

Documentation

newtype BuildID Source #

Constructors

BuildId Int 

buildIDInfo :: BuildID -> BuildInfo Source #

map a buildid into a buildinfo

fedoraKojiHub :: String Source #

main Fedora Koji Hub

centosKojiHub :: String Source #

Centos Koji mbox Hub

kojiBuildTags Source #

Arguments

:: String

hub url

-> BuildInfo 
-> IO [String] 

Get the tags of a build

kojiBuildTarget Source #

Arguments

:: String

hubUrl

-> String

target

-> IO (Maybe (String, String))

(build-tag,dest-tag)

Get the build and dest tags for a target.

kojiGetBuildID Source #

Arguments

:: String

hub url

-> String

NVR

-> IO (Maybe BuildID) 

Get the buildid of an nvr build

kojiGetBuildState Source #

Arguments

:: String

hub url

-> BuildInfo 
-> IO (Maybe BuildState) 

Get the state of a build

kojiGetBuildTaskID Source #

Arguments

:: String

hub url

-> String

NVR

-> IO (Maybe TaskID) 

Get the task of an nvr build

kojiGetCurrentRepo :: String -> String -> IO (Maybe Struct) Source #

Get current repo info for tag

kojiGetRepo Source #

Arguments

:: String

hub url

-> String

tag

-> Maybe RepoState 
-> Maybe Int

event

-> IO (Maybe Struct)

result

Get repo info for tag

kojiGetTaskInfo Source #

Arguments

:: String

hub url

-> TaskID 
-> IO (Maybe Struct) 

Get info about a task

kojiGetTaskChildren Source #

Arguments

:: String

hub url

-> TaskID 
-> Bool 
-> IO [Struct] 

Get the children tasks of a task

kojiGetTaskState Source #

Arguments

:: String

hub url

-> TaskID 
-> IO (Maybe TaskState) 

Get the state of a taskid

kojiGetUserID Source #

Arguments

:: String

hub url

-> String

user

-> IO (Maybe UserID) 

Get the userid for the named user

kojiLatestBuild Source #

Arguments

:: String

hub

-> String

tag

-> String

pkg

-> IO (Maybe Struct) 

Get the latest build of a package in a tag

kojiLatestBuildRepo Source #

Arguments

:: String

hub

-> String

tag

-> Int

event

-> String

pkg

-> IO (Maybe Struct) 

Get latest build in a tag for package at a time event.

Used for example to implement waitrepo

kojiListSideTags Source #

Arguments

:: String

hubUrl

-> Maybe String

basetag

-> Maybe String

user

-> IO [String]

list of sidetags

List sidetags (preferably for user and/or basetag)

kojiListTaskIDs Source #

Arguments

:: String

hub url

-> Struct

options

-> Struct

query opts

-> IO [TaskID] 

List tasks filtered by query options

kojiUserBuildTasks Source #

Arguments

:: String

hub url

-> UserID 
-> Maybe String

source

-> Maybe String

target

-> IO [TaskID] 

List the open tasks of a user (matching source/target)

data KojiBuild Source #

Build metadata

Constructors

KojiBuild 

Instances

Instances details
Show KojiBuild Source # 
Instance details

Defined in Distribution.Koji

kojiListTaggedBuilds Source #

Arguments

:: String

hub url

-> Bool

latest

-> String

tag

-> IO [KojiBuild] 

List builds in a tag

newtype PackageID Source #

Constructors

PackageId Int 

newtype TagID Source #

Constructors

TagId Int 

Instances

Instances details
Show TagID Source # 
Instance details

Defined in Distribution.Koji

Methods

showsPrec :: Int -> TagID -> ShowS #

show :: TagID -> String #

showList :: [TagID] -> ShowS #

newtype TaskID Source #

Constructors

TaskId Int 

Instances

Instances details
Show TaskID Source # 
Instance details

Defined in Distribution.Koji

newtype UserID Source #

Constructors

UserId Int 

Instances

Instances details
Show UserID Source # 
Instance details

Defined in Distribution.Koji

displayID :: ID a => a -> String Source #

getID :: ID a => a -> Int Source #

readID :: ID a => Struct -> Maybe a Source #

openTaskStates :: [TaskState] Source #

Open task states

type Struct = [(String, Value)] Source #

lookupStruct :: XmlRpcType a => String -> Struct -> Maybe a Source #

Lookup a key in a XML result

data Value #

An XML-RPC value.

Constructors

ValueInt Int

int, i4, or i8

ValueBool Bool

bool

ValueString String

string

ValueUnwrapped String

no inner element

ValueDouble Double

double

ValueDateTime LocalTime

dateTime.iso8601

ValueBase64 ByteString

base 64. NOTE that you should provide the raw data; the haxr library takes care of doing the base-64 encoding.

ValueStruct [(String, Value)]

struct

ValueArray [Value]

array

ValueNil

nil

Instances

Instances details
Eq Value 
Instance details

Defined in Network.XmlRpc.Internals

Methods

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

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

Show Value 
Instance details

Defined in Network.XmlRpc.Internals

Methods

showsPrec :: Int -> Value -> ShowS #

show :: Value -> String #

showList :: [Value] -> ShowS #

XmlRpcType Value

Exists to allow explicit type conversions.

Instance details

Defined in Network.XmlRpc.Internals

Methods

toValue :: Value -> Value #

fromValue :: forall (m :: Type -> Type). MonadFail m => Value -> Err m Value #

getType :: Value -> Type #