fbrnch-0.7.3: Build and create Fedora package repos and branches
Safe HaskellNone
LanguageHaskell2010

Fedora.Koji

Synopsis

Documentation

newtype BuildID Source #

Constructors

BuildId Int 

kojiBuildTarget Source #

Arguments

:: String

hubUrl

-> String

target

-> IO (Maybe (String, String))

(build-tag,dest-tag)

kojiGetBuildID Source #

Arguments

:: String

hub url

-> String

NVR

-> IO (Maybe BuildID) 

kojiGetBuildTaskID Source #

Arguments

:: String

hub url

-> String

NVR

-> IO (Maybe TaskID) 

kojiLatestBuild Source #

Arguments

:: String

hub

-> String

tag

-> String

pkg

-> IO (Maybe Struct) 

kojiLatestBuildRepo Source #

Arguments

:: String

hub

-> String

tag

-> Int

event

-> String

pkg

-> IO (Maybe Struct) 

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

opts

-> Struct

qopts

-> IO [TaskID] 

data KojiBuild Source #

Constructors

KojiBuild 

Instances

Instances details
Show KojiBuild Source # 
Instance details

Defined in Fedora.Koji

newtype PackageID Source #

Constructors

PackageId Int 

newtype TagID Source #

Constructors

TagId Int 

Instances

Instances details
Show TagID Source # 
Instance details

Defined in Fedora.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 Fedora.Koji

newtype UserID Source #

Constructors

UserId Int 

Instances

Instances details
Show UserID Source # 
Instance details

Defined in Fedora.Koji

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

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

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

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

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 #