module Data.GI.GIR.Struct
( Struct(..)
, parseStruct
) where
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 Struct = Struct {
Struct -> Bool
structIsBoxed :: Bool,
Struct -> AllocationInfo
structAllocationInfo :: AllocationInfo,
Struct -> Maybe ParseError
structTypeInit :: Maybe Text,
Struct -> Maybe ParseError
structCType :: Maybe Text,
Struct -> Int
structSize :: Int,
Struct -> Maybe Name
gtypeStructFor :: Maybe Name,
Struct -> Bool
structIsDisguised :: Bool,
Struct -> Bool
structForceVisible :: Bool,
Struct -> [Field]
structFields :: [Field],
Struct -> [Method]
structMethods :: [Method],
Struct -> Maybe DeprecationInfo
structDeprecated :: Maybe DeprecationInfo,
Struct -> Documentation
structDocumentation :: Documentation }
deriving Int -> Struct -> ShowS
[Struct] -> ShowS
Struct -> [Char]
(Int -> Struct -> ShowS)
-> (Struct -> [Char]) -> ([Struct] -> ShowS) -> Show Struct
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Struct -> ShowS
showsPrec :: Int -> Struct -> ShowS
$cshow :: Struct -> [Char]
show :: Struct -> [Char]
$cshowList :: [Struct] -> ShowS
showList :: [Struct] -> ShowS
Show
parseStruct :: Parser (Name, Struct)
parseStruct :: Parser (Name, Struct)
parseStruct = do
Name
name <- Parser Name
parseName
Maybe DeprecationInfo
deprecated <- Parser (Maybe DeprecationInfo)
parseDeprecation
Documentation
doc <- Parser Documentation
parseDocumentation
Maybe Name
structFor <- GIRXMLNamespace -> Name -> Parser (Maybe ParseError)
queryAttrWithNamespace GIRXMLNamespace
GLibGIRNS Name
"is-gtype-struct-for" Parser (Maybe ParseError)
-> (Maybe ParseError
-> ReaderT ParseContext (Except ParseError) (Maybe Name))
-> ReaderT ParseContext (Except ParseError) (Maybe Name)
forall a b.
ReaderT ParseContext (Except ParseError) a
-> (a -> ReaderT ParseContext (Except ParseError) b)
-> ReaderT ParseContext (Except ParseError) b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Just ParseError
t -> ((Name -> Maybe Name)
-> Parser Name
-> ReaderT ParseContext (Except ParseError) (Maybe Name)
forall a b.
(a -> b)
-> ReaderT ParseContext (Except ParseError) a
-> ReaderT ParseContext (Except ParseError) b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Name -> Maybe Name
forall a. a -> Maybe a
Just (Parser Name
-> ReaderT ParseContext (Except ParseError) (Maybe Name))
-> (ParseError -> Parser Name)
-> ParseError
-> ReaderT ParseContext (Except ParseError) (Maybe Name)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParseError -> Parser Name
qualifyName) ParseError
t
Maybe ParseError
Nothing -> Maybe Name -> ReaderT ParseContext (Except ParseError) (Maybe Name)
forall a. a -> ReaderT ParseContext (Except ParseError) a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Name
forall a. Maybe a
Nothing
Maybe ParseError
typeInit <- GIRXMLNamespace -> Name -> Parser (Maybe ParseError)
queryAttrWithNamespace GIRXMLNamespace
GLibGIRNS Name
"get-type"
Maybe ParseError
maybeCType <- Parser (Maybe ParseError)
queryCType
Bool
disguised <- Name -> Bool -> (ParseError -> Parser Bool) -> Parser Bool
forall a. Name -> a -> (ParseError -> Parser a) -> Parser a
optionalAttr Name
"disguised" Bool
False ParseError -> Parser Bool
parseBool
Bool
forceVisible <- Name -> Bool -> (ParseError -> Parser Bool) -> Parser Bool
forall a. Name -> a -> (ParseError -> Parser a) -> Parser a
optionalAttr Name
"haskell-gi-force-visible" Bool
False ParseError -> Parser Bool
parseBool
[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)
(Name, Struct) -> Parser (Name, Struct)
forall a. a -> ReaderT ParseContext (Except ParseError) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Name
name,
Struct {
structIsBoxed :: Bool
structIsBoxed = [Char] -> Bool
forall a. HasCallStack => [Char] -> a
error ([Char]
"[boxed] unfixed struct " [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ Name -> [Char]
forall a. Show a => a -> [Char]
show Name
name)
, structAllocationInfo :: AllocationInfo
structAllocationInfo = AllocationInfo
unknownAllocationInfo
, structTypeInit :: Maybe ParseError
structTypeInit = Maybe ParseError
typeInit
, structCType :: Maybe ParseError
structCType = Maybe ParseError
maybeCType
, structSize :: Int
structSize = [Char] -> Int
forall a. HasCallStack => [Char] -> a
error ([Char]
"[size] unfixed struct " [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ Name -> [Char]
forall a. Show a => a -> [Char]
show Name
name)
, gtypeStructFor :: Maybe Name
gtypeStructFor = Maybe Name
structFor
, structIsDisguised :: Bool
structIsDisguised = Bool
disguised
, structForceVisible :: Bool
structForceVisible = Bool
forceVisible
, structFields :: [Field]
structFields = [Field]
fields
, structMethods :: [Method]
structMethods = [Method]
constructors [Method] -> [Method] -> [Method]
forall a. [a] -> [a] -> [a]
++ [Method]
methods [Method] -> [Method] -> [Method]
forall a. [a] -> [a] -> [a]
++ [Method]
functions
, structDeprecated :: Maybe DeprecationInfo
structDeprecated = Maybe DeprecationInfo
deprecated
, structDocumentation :: Documentation
structDocumentation = Documentation
doc
})