| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Data.GI.CodeGen.API
Synopsis
- data API
- data GIRInfo = GIRInfo {
- girPCPackages :: [Text]
- girNSName :: Text
- girNSVersion :: Text
- girAPIs :: [(Name, API)]
- girCTypes :: Map Text Name
- loadGIRInfo :: Bool -> Text -> Maybe Text -> [FilePath] -> [GIRRule] -> IO (GIRInfo, [GIRInfo])
- loadRawGIRInfo :: Bool -> Text -> Maybe Text -> [FilePath] -> IO GIRInfo
- data GIRRule
- = GIRSetAttr (GIRPath, Name) Text
- | GIRDeleteAttr GIRPath Name
- | GIRAddNode GIRPath Name
- | GIRDeleteNode GIRPath
- type GIRPath = [GIRNodeSpec]
- data GIRNodeSpec
- = GIRNamed GIRNameTag
- | GIRType Text
- | GIRTypedName Text GIRNameTag
- data GIRNameTag
- = GIRPlainName Text
- | GIRRegex Text
- data Name = Name {}
- data Transfer
- data AllocationInfo = AllocationInfo {}
- data AllocationOp
- = AllocationOpUnknown
- | AllocationOp Text
- unknownAllocationInfo :: AllocationInfo
- data Direction
- data Scope
- data DeprecationInfo
- data EnumerationMember = EnumerationMember {
- enumMemberName :: Text
- enumMemberValue :: Int64
- enumMemberCId :: Text
- enumMemberDoc :: Documentation
- data PropertyFlag
- data MethodType
- data Constant = Constant {
- constantType :: Type
- constantValue :: Text
- constantCType :: Text
- constantDocumentation :: Documentation
- constantDeprecated :: Maybe DeprecationInfo
- data Arg = Arg {
- argCName :: Text
- argType :: Type
- direction :: Direction
- mayBeNull :: Bool
- argDoc :: Documentation
- argScope :: Scope
- argClosure :: Int
- argDestroy :: Int
- argCallerAllocates :: Bool
- transfer :: Transfer
- data Callable = Callable {}
- data Function = Function {
- fnSymbol :: Text
- fnMovedTo :: Maybe Text
- fnCallable :: Callable
- data Signal = Signal {
- sigName :: Text
- sigCallable :: Callable
- sigDeprecated :: Maybe DeprecationInfo
- sigDetailed :: Bool
- sigDoc :: Documentation
- 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 {
- cbCallable :: Callable
- cbCType :: Maybe Text
- cbDocumentation :: Documentation
- data Interface = Interface {
- ifTypeInit :: Maybe Text
- ifCType :: Maybe Text
- ifDocumentation :: Documentation
- ifPrerequisites :: [Name]
- ifProperties :: [Property]
- ifSignals :: [Signal]
- ifMethods :: [Method]
- ifAllocationInfo :: AllocationInfo
- ifDeprecated :: Maybe DeprecationInfo
- data Method = Method {
- methodName :: Name
- methodSymbol :: Text
- methodType :: MethodType
- methodMovedTo :: Maybe Text
- methodCallable :: Callable
- data Object = Object {
- objParent :: Maybe Name
- objTypeInit :: Text
- objTypeName :: Text
- objCType :: Maybe Text
- objRefFunc :: Maybe Text
- objUnrefFunc :: Maybe Text
- objInterfaces :: [Name]
- objDeprecated :: Maybe DeprecationInfo
- objDocumentation :: Documentation
- objMethods :: [Method]
- objProperties :: [Property]
- objSignals :: [Signal]
- data Enumeration = Enumeration {
- enumMembers :: [EnumerationMember]
- enumErrorDomain :: Maybe Text
- enumTypeInit :: Maybe Text
- enumDocumentation :: Documentation
- enumCType :: Text
- enumStorageBytes :: Int
- enumDeprecated :: Maybe DeprecationInfo
- data Flags = Flags Enumeration
- data Union = Union {
- unionIsBoxed :: Bool
- unionAllocationInfo :: AllocationInfo
- unionDocumentation :: Documentation
- unionSize :: Int
- unionTypeInit :: Maybe Text
- unionFields :: [Field]
- unionMethods :: [Method]
- unionCType :: Maybe Text
- unionDeprecated :: Maybe DeprecationInfo
Documentation
An element in the exposed API
Constructors
| GIRInfo | |
Fields
| |
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
| Eq AllocationOp Source # | |
Defined in Data.GI.GIR.Allocation | |
| Show AllocationOp Source # | |
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.
Constructors
| DirectionIn | |
| DirectionOut | |
| DirectionInout |
Constructors
| ScopeTypeInvalid | |
| ScopeTypeCall | |
| ScopeTypeAsync | |
| ScopeTypeNotified |
data DeprecationInfo Source #
Deprecation information on a symbol.
Instances
| Eq DeprecationInfo Source # | |
Defined in Data.GI.GIR.Deprecation Methods (==) :: DeprecationInfo -> DeprecationInfo -> Bool # (/=) :: DeprecationInfo -> DeprecationInfo -> Bool # | |
| Show DeprecationInfo Source # | |
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 | |
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
| Eq PropertyFlag Source # | |
Defined in Data.GI.GIR.Property | |
| Show PropertyFlag Source # | |
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
| Eq MethodType Source # | |
Defined in Data.GI.GIR.Method | |
| Show MethodType Source # | |
Defined in Data.GI.GIR.Method Methods showsPrec :: Int -> MethodType -> ShowS # show :: MethodType -> String # showList :: [MethodType] -> ShowS # | |
Info about a constant.
Constructors
| Constant | |
Fields
| |
Constructors
| Arg | |
Fields
| |
Constructors
| Callable | |
Fields
| |
Instances
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
| |