-- | Parsing of unions.
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 <- Parser Name
parseName
  deprecated <- parseDeprecation
  doc <- parseDocumentation
  typeInit <- queryAttrWithNamespace GLibGIRNS "get-type"
  fields <- parseFields
  constructors <- parseChildrenWithLocalName "constructor" (parseMethod Constructor)
  methods <- parseChildrenWithLocalName "method" (parseMethod OrdinaryMethod)
  functions <- parseChildrenWithLocalName "function" (parseMethod MemberFunction)
  ctype <- queryCType

  return (name,
          Union {
            unionIsBoxed = isJust typeInit
          , unionAllocationInfo = unknownAllocationInfo
          , unionDocumentation = doc
          , unionTypeInit = typeInit
          , unionSize = error ("unfixed union size " ++ show name)
          , unionFields = fields
          , unionMethods = constructors ++ methods ++ functions
          , unionCType = ctype
          , unionDeprecated = deprecated
          })