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

Safe HaskellNone
LanguageHaskell98

Data.GI.CodeGen.API

Synopsis

Documentation

data GIRInfo Source #

Constructors

GIRInfo 
Instances
Show GIRInfo Source # 
Instance details

Defined in Data.GI.CodeGen.API

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.

GIRAddNode GIRPath Name

Add a child node at the given selector.

GIRDeleteNode GIRPath

Delete any nodes matching the given selector.

Instances
Show GIRRule Source # 
Instance details

Defined in Data.GI.CodeGen.API

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 GIRNameTag

Node with the given "name" attr.

GIRType Text

Node of the given type.

GIRTypedName Text GIRNameTag

Combination of the above.

Instances
Show GIRNodeSpec Source # 
Instance details

Defined in Data.GI.CodeGen.API

data GIRNameTag Source #

A name tag, which is either a name or a regular expression.

Instances
Show GIRNameTag Source # 
Instance details

Defined in Data.GI.CodeGen.API

data Name Source #

Name for a symbol in the GIR file.

Constructors

Name 

Fields

Instances
Eq Name Source # 
Instance details

Defined in Data.GI.GIR.BasicTypes

Methods

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

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

Ord Name Source # 
Instance details

Defined in Data.GI.GIR.BasicTypes

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 # 
Instance details

Defined in Data.GI.GIR.BasicTypes

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 # 
Instance details

Defined in Data.GI.GIR.BasicTypes

Ord Transfer Source # 
Instance details

Defined in Data.GI.GIR.BasicTypes

Show Transfer Source # 
Instance details

Defined in Data.GI.GIR.BasicTypes

data AllocationInfo Source #

Allocation/deallocation information for a given foreign pointer.

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.

unknownAllocationInfo :: AllocationInfo Source #

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

data Scope Source #

Instances
Eq Scope Source # 
Instance details

Defined in Data.GI.GIR.Arg

Methods

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

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

Ord Scope Source # 
Instance details

Defined in Data.GI.GIR.Arg

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 # 
Instance details

Defined in Data.GI.GIR.Arg

Methods

showsPrec :: Int -> Scope -> ShowS #

show :: Scope -> String #

showList :: [Scope] -> ShowS #

data DeprecationInfo Source #

Deprecation information on a symbol.

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 # 
Instance details

Defined in Data.GI.GIR.Method

Show MethodType Source # 
Instance details

Defined in Data.GI.GIR.Method

data Arg Source #

Constructors

Arg 

Fields

Instances
Eq Arg Source # 
Instance details

Defined in Data.GI.GIR.Arg

Methods

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

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

Ord Arg Source # 
Instance details

Defined in Data.GI.GIR.Arg

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 # 
Instance details

Defined in Data.GI.GIR.Arg

Methods

showsPrec :: Int -> Arg -> ShowS #

show :: Arg -> String #

showList :: [Arg] -> ShowS #

data Function Source #

Constructors

Function 
Instances
Show Function Source # 
Instance details

Defined in Data.GI.GIR.Function

data Signal Source #

Instances
Eq Signal Source # 
Instance details

Defined in Data.GI.GIR.Signal

Methods

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

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

Show Signal Source # 
Instance details

Defined in Data.GI.GIR.Signal

data Callback Source #

Instances
Show Callback Source # 
Instance details

Defined in Data.GI.GIR.Callback

data Method Source #

Instances
Eq Method Source # 
Instance details

Defined in Data.GI.GIR.Method

Methods

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

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

Show Method Source # 
Instance details

Defined in Data.GI.GIR.Method

data Flags Source #

Constructors

Flags Enumeration 
Instances
Show Flags Source # 
Instance details

Defined in Data.GI.GIR.Flags

Methods

showsPrec :: Int -> Flags -> ShowS #

show :: Flags -> String #

showList :: [Flags] -> ShowS #