| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Data.GI.CodeGen.API
Synopsis
- data API
 - data GIRInfo = GIRInfo {}
 - loadGIRInfo :: Bool -> Text -> Maybe Text -> [FilePath] -> [GIRRule] -> IO (GIRInfo, [GIRInfo])
 - loadRawGIRInfo :: Bool -> Text -> Maybe Text -> [FilePath] -> IO GIRInfo
 - data GIRRule
 - type GIRPath = [GIRNodeSpec]
 - data GIRNodeSpec
 - data GIRNameTag
 - data Name = Name {}
 - data Transfer
 - data AllocationInfo = AllocationInfo {}
 - data AllocationOp
 - unknownAllocationInfo :: AllocationInfo
 - data Direction
 - data Scope
 - data DeprecationInfo
 - data EnumerationMember = EnumerationMember {}
 - data PropertyFlag
 - data MethodType
 - data Constant = Constant {}
 - data Arg = Arg {
- argCName :: Text
 - argType :: Type
 - direction :: Direction
 - mayBeNull :: Bool
 - argDoc :: Documentation
 - argScope :: Scope
 - argClosure :: Int
 - argDestroy :: Int
 - argCallerAllocates :: Bool
 - argCallbackUserData :: Bool
 - transfer :: Transfer
 
 - data Callable = Callable {}
 - data Function = Function {}
 - data Signal = Signal {}
 - data Property = Property {}
 - data Field = Field {}
 - data Struct = Struct {
- structIsBoxed :: Bool
 - structAllocationInfo :: AllocationInfo
 - structTypeInit :: Maybe Text
 - structCType :: Maybe Text
 - structSize :: Int
 - gtypeStructFor :: Maybe Name
 - structIsDisguised :: Bool
 - structForceVisible :: Bool
 - structFields :: [Field]
 - structMethods :: [Method]
 - structDeprecated :: Maybe DeprecationInfo
 - structDocumentation :: Documentation
 
 - data Callback = Callback {}
 - data Interface = Interface {}
 - data Method = Method {}
 - data Object = Object {
- objParent :: Maybe Name
 - objTypeInit :: Text
 - objTypeName :: Text
 - objCType :: Maybe Text
 - objRefFunc :: Maybe Text
 - objUnrefFunc :: Maybe Text
 - objSetValueFunc :: Maybe Text
 - objGetValueFunc :: Maybe Text
 - objInterfaces :: [Name]
 - objDeprecated :: Maybe DeprecationInfo
 - objDocumentation :: Documentation
 - objMethods :: [Method]
 - objProperties :: [Property]
 - objSignals :: [Signal]
 
 - data Enumeration = Enumeration {}
 - data Flags = Flags Enumeration
 - data Union = Union {}
 
Documentation
An element in the exposed API
Constructors
| GIRInfo | |
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.
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.
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.  | 
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 # | |
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
| Show GIRNameTag Source # | |
Defined in Data.GI.CodeGen.API Methods showsPrec :: Int -> GIRNameTag -> ShowS # show :: GIRNameTag -> String # showList :: [GIRNameTag] -> ShowS #  | |
Transfer mode for an argument or property.
Constructors
| TransferNothing | |
| TransferContainer | |
| TransferEverything | 
data AllocationInfo Source #
Allocation/deallocation information for a given foreign pointer.
Constructors
| AllocationInfo | |
Fields  | |
Instances
| Show AllocationInfo Source # | |
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
| Show AllocationOp Source # | |
Defined in Data.GI.GIR.Allocation Methods showsPrec :: Int -> AllocationOp -> ShowS # show :: AllocationOp -> String # showList :: [AllocationOp] -> ShowS #  | |
| Eq AllocationOp Source # | |
Defined in Data.GI.GIR.Allocation  | |
unknownAllocationInfo :: AllocationInfo Source #
A convenience function, filling in all the allocation info to unknown.
Constructors
| DirectionIn | |
| DirectionOut | |
| DirectionInout | 
Instances
| Show Direction Source # | |
| Eq Direction Source # | |
| Ord Direction Source # | |
data DeprecationInfo Source #
Deprecation information on a symbol.
Instances
| Show DeprecationInfo Source # | |
Defined in Data.GI.GIR.Deprecation Methods showsPrec :: Int -> DeprecationInfo -> ShowS # show :: DeprecationInfo -> String # showList :: [DeprecationInfo] -> ShowS #  | |
| Eq DeprecationInfo Source # | |
Defined in Data.GI.GIR.Deprecation Methods (==) :: DeprecationInfo -> DeprecationInfo -> Bool # (/=) :: DeprecationInfo -> DeprecationInfo -> Bool #  | |
data EnumerationMember Source #
Member of an enumeration.
Constructors
| EnumerationMember | |
Fields  | |
Instances
| Show EnumerationMember Source # | |
Defined in Data.GI.GIR.Enum Methods showsPrec :: Int -> EnumerationMember -> ShowS # show :: EnumerationMember -> String # showList :: [EnumerationMember] -> ShowS #  | |
data PropertyFlag Source #
Instances
| Show PropertyFlag Source # | |
Defined in Data.GI.GIR.Property Methods showsPrec :: Int -> PropertyFlag -> ShowS # show :: PropertyFlag -> String # showList :: [PropertyFlag] -> ShowS #  | |
| Eq PropertyFlag Source # | |
Defined in Data.GI.GIR.Property  | |
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
| Show MethodType Source # | |
Defined in Data.GI.GIR.Method Methods showsPrec :: Int -> MethodType -> ShowS # show :: MethodType -> String # showList :: [MethodType] -> ShowS #  | |
| Eq MethodType Source # | |
Defined in Data.GI.GIR.Method  | |
Info about a constant.
Constructors
| Constant | |
Fields  | |
Constructors
| Arg | |
Fields 
  | |
Constructors
| Callable | |
Fields 
  | |
Instances
Constructors
| Function | |
Constructors
| Signal | |
Fields 
  | |
Constructors
| Property | |
Fields 
  | |
Instances
Constructors
| Field | |
Fields 
  | |
Constructors
| Struct | |
Fields 
  | |
Constructors
| Callback | |
Fields  | |
Constructors
| Interface | |
Fields 
  | |
Constructors
| Method | |
Fields 
  | |
Constructors
| Object | |
Fields 
  | |
data Enumeration Source #
Constructors
| Enumeration | |
Fields 
  | |
Instances
| Show Enumeration Source # | |
Defined in Data.GI.GIR.Enum Methods showsPrec :: Int -> Enumeration -> ShowS # show :: Enumeration -> String # showList :: [Enumeration] -> ShowS #  | |
Constructors
| Flags Enumeration | 
Constructors
| Union | |
Fields 
  | |