haskell-gi-0.17.2: Generate Haskell bindings for GObject Introspection capable libraries

Safe HaskellNone
LanguageHaskell98

Data.GI.CodeGen.API

Synopsis

Documentation

data GIRInfo Source #

Constructors

GIRInfo 

Fields

Instances

Show GIRInfo Source # 

Methods

showsPrec :: Int -> GIRInfo -> ShowS

show :: GIRInfo -> String

showList :: [GIRInfo] -> ShowS

loadGIRInfo Source #

Arguments

:: Bool

verbose

-> Text

name

-> Maybe Text

version

-> [FilePath]

extra paths to search

-> [GIRRule]

fixups

-> IO (GIRInfo, [GIRInfo])

(parsed doc, parsed deps)

Load and parse a GIR file, including its dependencies.

loadRawGIRInfo Source #

Arguments

:: Bool

verbose

-> Text

name

-> Maybe Text

version

-> [FilePath]

extra paths to search

-> IO GIRInfo

bare parsed document

Bare minimum loading and parsing of a single repository, without loading or parsing its dependencies, resolving aliases, or fixing up structs or interfaces.

data GIRRule Source #

A rule for modifying the GIR file.

Constructors

GIRSetAttr (GIRPath, Name) Text

(Path to element, attrName), newValue

Instances

Show GIRRule Source # 

Methods

showsPrec :: Int -> GIRRule -> ShowS

show :: GIRRule -> String

showList :: [GIRRule] -> ShowS

type GIRPath = [GIRNodeSpec] Source #

Path to a node in the GIR file, starting from the document root of the GIR file. This is a very simplified version of something like XPath.

data GIRNodeSpec Source #

Node selector for a path in the GIR file.

Constructors

GIRNamed Text

Node with the given "name" attr.

GIRType Text

Node of the given type.

GIRTypedName Text Text

Combination of the above.

Instances

Show GIRNodeSpec Source # 

Methods

showsPrec :: Int -> GIRNodeSpec -> ShowS

show :: GIRNodeSpec -> String

showList :: [GIRNodeSpec] -> ShowS

data Name Source #

Name for a symbol in the GIR file.

Constructors

Name 

Fields

Instances

Eq Name Source # 

Methods

(==) :: Name -> Name -> Bool

(/=) :: Name -> Name -> Bool

Ord Name Source # 

Methods

compare :: Name -> Name -> Ordering

(<) :: Name -> Name -> Bool

(<=) :: Name -> Name -> Bool

(>) :: Name -> Name -> Bool

(>=) :: Name -> Name -> Bool

max :: Name -> Name -> Name

min :: Name -> Name -> Name

Show Name Source # 

Methods

showsPrec :: Int -> Name -> ShowS

show :: Name -> String

showList :: [Name] -> ShowS

data Transfer Source #

Transfer mode for an argument or property.

Instances

Eq Transfer Source # 

Methods

(==) :: Transfer -> Transfer -> Bool

(/=) :: Transfer -> Transfer -> Bool

Ord Transfer Source # 

Methods

compare :: Transfer -> Transfer -> Ordering

(<) :: Transfer -> Transfer -> Bool

(<=) :: Transfer -> Transfer -> Bool

(>) :: Transfer -> Transfer -> Bool

(>=) :: Transfer -> Transfer -> Bool

max :: Transfer -> Transfer -> Transfer

min :: Transfer -> Transfer -> Transfer

Show Transfer Source # 

Methods

showsPrec :: Int -> Transfer -> ShowS

show :: Transfer -> String

showList :: [Transfer] -> ShowS

data AllocationInfo Source #

Allocation/deallocation information for a given foreign pointer.

Instances

Show AllocationInfo Source # 

Methods

showsPrec :: Int -> AllocationInfo -> ShowS

show :: AllocationInfo -> String

showList :: [AllocationInfo] -> ShowS

data AllocationOp Source #

Information about a given allocation operation. It is either disallowed, allowed via the given function, or it is unknown at the current stage how to perform the operation.

Constructors

AllocationOpUnknown 
AllocationOp Text 

Instances

Eq AllocationOp Source # 

Methods

(==) :: AllocationOp -> AllocationOp -> Bool

(/=) :: AllocationOp -> AllocationOp -> Bool

Show AllocationOp Source # 

Methods

showsPrec :: Int -> AllocationOp -> ShowS

show :: AllocationOp -> String

showList :: [AllocationOp] -> ShowS

unknownAllocationInfo :: AllocationInfo Source #

A convenience function, filling in all the allocation info to unknown.

data Direction Source #

Instances

Eq Direction Source # 

Methods

(==) :: Direction -> Direction -> Bool

(/=) :: Direction -> Direction -> Bool

Ord Direction Source # 

Methods

compare :: Direction -> Direction -> Ordering

(<) :: Direction -> Direction -> Bool

(<=) :: Direction -> Direction -> Bool

(>) :: Direction -> Direction -> Bool

(>=) :: Direction -> Direction -> Bool

max :: Direction -> Direction -> Direction

min :: Direction -> Direction -> Direction

Show Direction Source # 

Methods

showsPrec :: Int -> Direction -> ShowS

show :: Direction -> String

showList :: [Direction] -> ShowS

data Scope Source #

Instances

Eq Scope Source # 

Methods

(==) :: Scope -> Scope -> Bool

(/=) :: Scope -> Scope -> Bool

Ord Scope Source # 

Methods

compare :: Scope -> Scope -> Ordering

(<) :: Scope -> Scope -> Bool

(<=) :: Scope -> Scope -> Bool

(>) :: Scope -> Scope -> Bool

(>=) :: Scope -> Scope -> Bool

max :: Scope -> Scope -> Scope

min :: Scope -> Scope -> Scope

Show Scope Source # 

Methods

showsPrec :: Int -> Scope -> ShowS

show :: Scope -> String

showList :: [Scope] -> ShowS

deprecatedPragma :: Text -> Maybe DeprecationInfo -> Text Source #

Encode the given DeprecationInfo for the given symbol as a deprecation pragma.

data DeprecationInfo Source #

Deprecation information on a symbol.

Instances

data MethodType Source #

Constructors

Constructor

Constructs an instance of the parent type

MemberFunction

A function in the namespace

OrdinaryMethod

A function taking the parent instance as first argument.

Instances

Eq MethodType Source # 

Methods

(==) :: MethodType -> MethodType -> Bool

(/=) :: MethodType -> MethodType -> Bool

Show MethodType Source # 

Methods

showsPrec :: Int -> MethodType -> ShowS

show :: MethodType -> String

showList :: [MethodType] -> ShowS

data Constant Source #

Info about a constant.

Constructors

Constant 

Instances

Show Constant Source # 

Methods

showsPrec :: Int -> Constant -> ShowS

show :: Constant -> String

showList :: [Constant] -> ShowS

data Arg Source #

Constructors

Arg 

Fields

Instances

Eq Arg Source # 

Methods

(==) :: Arg -> Arg -> Bool

(/=) :: Arg -> Arg -> Bool

Ord Arg Source # 

Methods

compare :: Arg -> Arg -> Ordering

(<) :: Arg -> Arg -> Bool

(<=) :: Arg -> Arg -> Bool

(>) :: Arg -> Arg -> Bool

(>=) :: Arg -> Arg -> Bool

max :: Arg -> Arg -> Arg

min :: Arg -> Arg -> Arg

Show Arg Source # 

Methods

showsPrec :: Int -> Arg -> ShowS

show :: Arg -> String

showList :: [Arg] -> ShowS

data Callable Source #

Constructors

Callable 

Instances

Eq Callable Source # 

Methods

(==) :: Callable -> Callable -> Bool

(/=) :: Callable -> Callable -> Bool

Show Callable Source # 

Methods

showsPrec :: Int -> Callable -> ShowS

show :: Callable -> String

showList :: [Callable] -> ShowS

data Function Source #

Constructors

Function 

Fields

Instances

Show Function Source # 

Methods

showsPrec :: Int -> Function -> ShowS

show :: Function -> String

showList :: [Function] -> ShowS

data Signal Source #

Constructors

Signal 

Instances

Eq Signal Source # 

Methods

(==) :: Signal -> Signal -> Bool

(/=) :: Signal -> Signal -> Bool

Show Signal Source # 

Methods

showsPrec :: Int -> Signal -> ShowS

show :: Signal -> String

showList :: [Signal] -> ShowS

data Property Source #

Constructors

Property 

Instances

Eq Property Source # 

Methods

(==) :: Property -> Property -> Bool

(/=) :: Property -> Property -> Bool

Show Property Source # 

Methods

showsPrec :: Int -> Property -> ShowS

show :: Property -> String

showList :: [Property] -> ShowS

data Field Source #

Constructors

Field 

Instances

Show Field Source # 

Methods

showsPrec :: Int -> Field -> ShowS

show :: Field -> String

showList :: [Field] -> ShowS

data Struct Source #

Instances

Show Struct Source # 

Methods

showsPrec :: Int -> Struct -> ShowS

show :: Struct -> String

showList :: [Struct] -> ShowS

data Callback Source #

Constructors

Callback Callable 

Instances

Show Callback Source # 

Methods

showsPrec :: Int -> Callback -> ShowS

show :: Callback -> String

showList :: [Callback] -> ShowS

data Interface Source #

Constructors

Interface 

Instances

Show Interface Source # 

Methods

showsPrec :: Int -> Interface -> ShowS

show :: Interface -> String

showList :: [Interface] -> ShowS

data Method Source #

Constructors

Method 

Instances

Eq Method Source # 

Methods

(==) :: Method -> Method -> Bool

(/=) :: Method -> Method -> Bool

Show Method Source # 

Methods

showsPrec :: Int -> Method -> ShowS

show :: Method -> String

showList :: [Method] -> ShowS

data Object Source #

Instances

Show Object Source # 

Methods

showsPrec :: Int -> Object -> ShowS

show :: Object -> String

showList :: [Object] -> ShowS

data Enumeration Source #

Constructors

Enumeration 

Fields

Instances

Show Enumeration Source # 

Methods

showsPrec :: Int -> Enumeration -> ShowS

show :: Enumeration -> String

showList :: [Enumeration] -> ShowS

data Flags Source #

Constructors

Flags Enumeration 

Instances

Show Flags Source # 

Methods

showsPrec :: Int -> Flags -> ShowS

show :: Flags -> String

showList :: [Flags] -> ShowS

data Union Source #

Instances

Show Union Source # 

Methods

showsPrec :: Int -> Union -> ShowS

show :: Union -> String

showList :: [Union] -> ShowS