module Data.GI.GIR.Union
( Union(..)
, parseUnion
) where
import Data.Maybe (isJust)
import Data.Text (Text)
import Data.GI.GIR.Allocation (AllocationInfo(..), unknownAllocationInfo)
import Data.GI.GIR.Field (Field, parseFields)
import Data.GI.GIR.Method (Method, MethodType(..), parseMethod)
import Data.GI.GIR.Parser
import Data.GI.GIR.Type (queryCType)
data Union = Union {
Union -> Bool
unionIsBoxed :: Bool,
Union -> AllocationInfo
unionAllocationInfo :: AllocationInfo,
Union -> Documentation
unionDocumentation :: Documentation,
Union -> Int
unionSize :: Int,
Union -> Maybe ParseError
unionTypeInit :: Maybe Text,
Union -> [Field]
unionFields :: [Field],
Union -> [Method]
unionMethods :: [Method],
Union -> Maybe ParseError
unionCType :: Maybe Text,
Union -> Maybe DeprecationInfo
unionDeprecated :: Maybe DeprecationInfo }
deriving Int -> Union -> ShowS
[Union] -> ShowS
Union -> [Char]
(Int -> Union -> ShowS)
-> (Union -> [Char]) -> ([Union] -> ShowS) -> Show Union
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Union -> ShowS
showsPrec :: Int -> Union -> ShowS
$cshow :: Union -> [Char]
show :: Union -> [Char]
$cshowList :: [Union] -> ShowS
showList :: [Union] -> ShowS
Show
parseUnion :: Parser (Name, Union)
parseUnion :: Parser (Name, Union)
parseUnion = do
Name
name <- Parser Name
parseName
Maybe DeprecationInfo
deprecated <- Parser (Maybe DeprecationInfo)
parseDeprecation
Documentation
doc <- Parser Documentation
parseDocumentation
Maybe ParseError
typeInit <- GIRXMLNamespace -> Name -> Parser (Maybe ParseError)
queryAttrWithNamespace GIRXMLNamespace
GLibGIRNS Name
"get-type"
[Field]
fields <- Parser [Field]
parseFields
[Method]
constructors <- ParseError -> Parser Method -> Parser [Method]
forall a. ParseError -> Parser a -> Parser [a]
parseChildrenWithLocalName ParseError
"constructor" (MethodType -> Parser Method
parseMethod MethodType
Constructor)
[Method]
methods <- ParseError -> Parser Method -> Parser [Method]
forall a. ParseError -> Parser a -> Parser [a]
parseChildrenWithLocalName ParseError
"method" (MethodType -> Parser Method
parseMethod MethodType
OrdinaryMethod)
[Method]
functions <- ParseError -> Parser Method -> Parser [Method]
forall a. ParseError -> Parser a -> Parser [a]
parseChildrenWithLocalName ParseError
"function" (MethodType -> Parser Method
parseMethod MethodType
MemberFunction)
Maybe ParseError
ctype <- Parser (Maybe ParseError)
queryCType
(Name, Union) -> Parser (Name, Union)
forall a. a -> ReaderT ParseContext (Except ParseError) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Name
name,
Union {
unionIsBoxed :: Bool
unionIsBoxed = Maybe ParseError -> Bool
forall a. Maybe a -> Bool
isJust Maybe ParseError
typeInit
, unionAllocationInfo :: AllocationInfo
unionAllocationInfo = AllocationInfo
unknownAllocationInfo
, unionDocumentation :: Documentation
unionDocumentation = Documentation
doc
, unionTypeInit :: Maybe ParseError
unionTypeInit = Maybe ParseError
typeInit
, unionSize :: Int
unionSize = [Char] -> Int
forall a. HasCallStack => [Char] -> a
error ([Char]
"unfixed union size " [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ Name -> [Char]
forall a. Show a => a -> [Char]
show Name
name)
, unionFields :: [Field]
unionFields = [Field]
fields
, unionMethods :: [Method]
unionMethods = [Method]
constructors [Method] -> [Method] -> [Method]
forall a. [a] -> [a] -> [a]
++ [Method]
methods [Method] -> [Method] -> [Method]
forall a. [a] -> [a] -> [a]
++ [Method]
functions
, unionCType :: Maybe ParseError
unionCType = Maybe ParseError
ctype
, unionDeprecated :: Maybe DeprecationInfo
unionDeprecated = Maybe DeprecationInfo
deprecated
})