-- | Parsing of structs.
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 Text
structTypeInit :: Maybe Text,
    Struct -> Maybe Text
structCType :: Maybe Text,
    Struct -> Int
structSize :: Int,
    Struct -> Maybe Name
gtypeStructFor :: Maybe Name,
    -- https://bugzilla.gnome.org/show_bug.cgi?id=560248
    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 -> String
(Int -> Struct -> ShowS)
-> (Struct -> String) -> ([Struct] -> ShowS) -> Show Struct
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Struct] -> ShowS
$cshowList :: [Struct] -> ShowS
show :: Struct -> String
$cshow :: Struct -> String
showsPrec :: Int -> Struct -> ShowS
$cshowsPrec :: Int -> 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 Text)
queryAttrWithNamespace GIRXMLNamespace
GLibGIRNS "is-gtype-struct-for" Parser (Maybe Text)
-> (Maybe Text -> ReaderT ParseContext (Except Text) (Maybe Name))
-> ReaderT ParseContext (Except Text) (Maybe Name)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
               Just t :: Text
t -> ((Name -> Maybe Name)
-> Parser Name -> ReaderT ParseContext (Except Text) (Maybe Name)
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 Text) (Maybe Name))
-> (Text -> Parser Name)
-> Text
-> ReaderT ParseContext (Except Text) (Maybe Name)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Parser Name
qualifyName) Text
t
               Nothing -> Maybe Name -> ReaderT ParseContext (Except Text) (Maybe Name)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Name
forall a. Maybe a
Nothing
  Maybe Text
typeInit <- GIRXMLNamespace -> Name -> Parser (Maybe Text)
queryAttrWithNamespace GIRXMLNamespace
GLibGIRNS "get-type"
  Maybe Text
maybeCType <- Parser (Maybe Text)
queryCType
  Bool
disguised <- Name -> Bool -> (Text -> Parser Bool) -> Parser Bool
forall a. Name -> a -> (Text -> Parser a) -> Parser a
optionalAttr "disguised" Bool
False Text -> Parser Bool
parseBool
  Bool
forceVisible <- Name -> Bool -> (Text -> Parser Bool) -> Parser Bool
forall a. Name -> a -> (Text -> Parser a) -> Parser a
optionalAttr "haskell-gi-force-visible" Bool
False Text -> Parser Bool
parseBool
  [Field]
fields <- Parser [Field]
parseFields
  [Method]
constructors <- Text -> Parser Method -> Parser [Method]
forall a. Text -> Parser a -> Parser [a]
parseChildrenWithLocalName "constructor" (MethodType -> Parser Method
parseMethod MethodType
Constructor)
  [Method]
methods <- Text -> Parser Method -> Parser [Method]
forall a. Text -> Parser a -> Parser [a]
parseChildrenWithLocalName "method" (MethodType -> Parser Method
parseMethod MethodType
OrdinaryMethod)
  [Method]
functions <- Text -> Parser Method -> Parser [Method]
forall a. Text -> Parser a -> Parser [a]
parseChildrenWithLocalName "function" (MethodType -> Parser Method
parseMethod MethodType
MemberFunction)
  (Name, Struct) -> Parser (Name, Struct)
forall (m :: * -> *) a. Monad m => a -> m a
return (Name
name,
          Struct :: Bool
-> AllocationInfo
-> Maybe Text
-> Maybe Text
-> Int
-> Maybe Name
-> Bool
-> Bool
-> [Field]
-> [Method]
-> Maybe DeprecationInfo
-> Documentation
-> Struct
Struct {
            structIsBoxed :: Bool
structIsBoxed = String -> Bool
forall a. HasCallStack => String -> a
error ("[boxed] unfixed struct " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Name -> String
forall a. Show a => a -> String
show Name
name)
          , structAllocationInfo :: AllocationInfo
structAllocationInfo = AllocationInfo
unknownAllocationInfo
          , structTypeInit :: Maybe Text
structTypeInit = Maybe Text
typeInit
          , structCType :: Maybe Text
structCType = Maybe Text
maybeCType
          , structSize :: Int
structSize = String -> Int
forall a. HasCallStack => String -> a
error ("[size] unfixed struct " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Name -> String
forall a. Show a => a -> String
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
          })