haskell-gi-0.24.5: Generate Haskell bindings for GObject Introspection capable libraries
Safe HaskellNone
LanguageHaskell2010

Data.GI.CodeGen.API

Synopsis

Documentation

data API Source #

An element in the exposed API

Instances

Instances details
Show API Source # 
Instance details

Defined in Data.GI.CodeGen.API

Methods

showsPrec :: Int -> API -> ShowS

show :: API -> String

showList :: [API] -> ShowS

data GIRInfo Source #

Constructors

GIRInfo 

Fields

Instances

Instances details
Show GIRInfo Source # 
Instance details

Defined in Data.GI.CodeGen.API

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.

GIRDeleteAttr GIRPath Name

Delete the given attribute

GIRAddNode GIRPath Name

Add a child node at the given selector.

GIRDeleteNode GIRPath

Delete any nodes matching the given selector.

Instances

Instances details
Show GIRRule Source # 
Instance details

Defined in Data.GI.CodeGen.API

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 GIRNameTag

Node with the given "name" attr.

GIRType Text

Node of the given type.

GIRTypedName Text GIRNameTag

Combination of the above.

Instances

Instances details
Show GIRNodeSpec Source # 
Instance details

Defined in Data.GI.CodeGen.API

Methods

showsPrec :: Int -> GIRNodeSpec -> ShowS

show :: GIRNodeSpec -> String

showList :: [GIRNodeSpec] -> ShowS

data GIRNameTag Source #

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

Constructors

GIRPlainName Text 
GIRRegex Text 

Instances

Instances details
Show GIRNameTag Source # 
Instance details

Defined in Data.GI.CodeGen.API

Methods

showsPrec :: Int -> GIRNameTag -> ShowS

show :: GIRNameTag -> String

showList :: [GIRNameTag] -> ShowS

data Name Source #

Name for a symbol in the GIR file.

Constructors

Name 

Fields

Instances

Instances details
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

Instances details
Eq Transfer Source # 
Instance details

Defined in Data.GI.GIR.BasicTypes

Methods

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

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

Ord Transfer Source # 
Instance details

Defined in Data.GI.GIR.BasicTypes

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

Defined in Data.GI.GIR.BasicTypes

Methods

showsPrec :: Int -> Transfer -> ShowS

show :: Transfer -> String

showList :: [Transfer] -> ShowS

data AllocationInfo Source #

Allocation/deallocation information for a given foreign pointer.

Instances

Instances details
Show AllocationInfo Source # 
Instance details

Defined in Data.GI.GIR.Allocation

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

Instances details
Eq AllocationOp Source # 
Instance details

Defined in Data.GI.GIR.Allocation

Methods

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

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

Show AllocationOp Source # 
Instance details

Defined in Data.GI.GIR.Allocation

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

Instances details
Eq Direction Source # 
Instance details

Defined in Data.GI.GIR.Arg

Methods

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

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

Ord Direction Source # 
Instance details

Defined in Data.GI.GIR.Arg

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

Defined in Data.GI.GIR.Arg

Methods

showsPrec :: Int -> Direction -> ShowS

show :: Direction -> String

showList :: [Direction] -> ShowS

data Scope Source #

Instances

Instances details
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.

Instances

Instances details
Eq DeprecationInfo Source # 
Instance details

Defined in Data.GI.GIR.Deprecation

Show DeprecationInfo Source # 
Instance details

Defined in Data.GI.GIR.Deprecation

Methods

showsPrec :: Int -> DeprecationInfo -> ShowS

show :: DeprecationInfo -> String

showList :: [DeprecationInfo] -> ShowS

data EnumerationMember Source #

Member of an enumeration.

Constructors

EnumerationMember 

Instances

Instances details
Show EnumerationMember Source # 
Instance details

Defined in Data.GI.GIR.Enum

Methods

showsPrec :: Int -> EnumerationMember -> ShowS

show :: EnumerationMember -> String

showList :: [EnumerationMember] -> ShowS

data PropertyFlag Source #

Instances

Instances details
Eq PropertyFlag Source # 
Instance details

Defined in Data.GI.GIR.Property

Methods

(==) :: PropertyFlag -> PropertyFlag -> Bool

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

Show PropertyFlag Source # 
Instance details

Defined in Data.GI.GIR.Property

Methods

showsPrec :: Int -> PropertyFlag -> ShowS

show :: PropertyFlag -> String

showList :: [PropertyFlag] -> ShowS

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

Instances details
Eq MethodType Source # 
Instance details

Defined in Data.GI.GIR.Method

Methods

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

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

Show MethodType Source # 
Instance details

Defined in Data.GI.GIR.Method

Methods

showsPrec :: Int -> MethodType -> ShowS

show :: MethodType -> String

showList :: [MethodType] -> ShowS

data Constant Source #

Info about a constant.

Instances

Instances details
Show Constant Source # 
Instance details

Defined in Data.GI.GIR.Constant

Methods

showsPrec :: Int -> Constant -> ShowS

show :: Constant -> String

showList :: [Constant] -> ShowS

data Arg Source #

Constructors

Arg 

Fields

Instances

Instances details
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 Callable Source #

Constructors

Callable 

Fields

Instances

Instances details
Eq Callable Source # 
Instance details

Defined in Data.GI.GIR.Callable

Methods

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

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

Show Callable Source # 
Instance details

Defined in Data.GI.GIR.Callable

Methods

showsPrec :: Int -> Callable -> ShowS

show :: Callable -> String

showList :: [Callable] -> ShowS

data Function Source #

Constructors

Function 

Fields

Instances

Instances details
Show Function Source # 
Instance details

Defined in Data.GI.GIR.Function

Methods

showsPrec :: Int -> Function -> ShowS

show :: Function -> String

showList :: [Function] -> ShowS

data Signal Source #

Constructors

Signal 

Instances

Instances details
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

Methods

showsPrec :: Int -> Signal -> ShowS

show :: Signal -> String

showList :: [Signal] -> ShowS

data Property Source #

Instances

Instances details
Eq Property Source # 
Instance details

Defined in Data.GI.GIR.Property

Methods

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

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

Show Property Source # 
Instance details

Defined in Data.GI.GIR.Property

Methods

showsPrec :: Int -> Property -> ShowS

show :: Property -> String

showList :: [Property] -> ShowS

data Field Source #

Constructors

Field 

Fields

Instances

Instances details
Show Field Source # 
Instance details

Defined in Data.GI.GIR.Field

Methods

showsPrec :: Int -> Field -> ShowS

show :: Field -> String

showList :: [Field] -> ShowS

data Struct Source #

Instances

Instances details
Show Struct Source # 
Instance details

Defined in Data.GI.GIR.Struct

Methods

showsPrec :: Int -> Struct -> ShowS

show :: Struct -> String

showList :: [Struct] -> ShowS

data Callback Source #

Constructors

Callback 

Instances

Instances details
Show Callback Source # 
Instance details

Defined in Data.GI.GIR.Callback

Methods

showsPrec :: Int -> Callback -> ShowS

show :: Callback -> String

showList :: [Callback] -> ShowS

data Interface Source #

Instances

Instances details
Show Interface Source # 
Instance details

Defined in Data.GI.GIR.Interface

Methods

showsPrec :: Int -> Interface -> ShowS

show :: Interface -> String

showList :: [Interface] -> ShowS

data Method Source #

Constructors

Method 

Fields

Instances

Instances details
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

Methods

showsPrec :: Int -> Method -> ShowS

show :: Method -> String

showList :: [Method] -> ShowS

data Object Source #

Constructors

Object 

Fields

Instances

Instances details
Show Object Source # 
Instance details

Defined in Data.GI.GIR.Object

Methods

showsPrec :: Int -> Object -> ShowS

show :: Object -> String

showList :: [Object] -> ShowS

data Enumeration Source #

Constructors

Enumeration 

Fields

Instances

Instances details
Show Enumeration Source # 
Instance details

Defined in Data.GI.GIR.Enum

Methods

showsPrec :: Int -> Enumeration -> ShowS

show :: Enumeration -> String

showList :: [Enumeration] -> ShowS

data Flags Source #

Constructors

Flags Enumeration 

Instances

Instances details
Show Flags Source # 
Instance details

Defined in Data.GI.GIR.Flags

Methods

showsPrec :: Int -> Flags -> ShowS

show :: Flags -> String

showList :: [Flags] -> ShowS

data Union Source #

Instances

Instances details
Show Union Source # 
Instance details

Defined in Data.GI.GIR.Union

Methods

showsPrec :: Int -> Union -> ShowS

show :: Union -> String

showList :: [Union] -> ShowS