module Data.GI.GIR.Interface ( Interface(..) , parseInterface ) where import Data.Text (Text) import Data.GI.GIR.Allocation (AllocationInfo, unknownAllocationInfo) import Data.GI.GIR.Method (Method, MethodType(..), parseMethod) import Data.GI.GIR.Property (Property, parseProperty) import Data.GI.GIR.Signal (Signal, parseSignal) import Data.GI.GIR.Parser import Data.GI.GIR.Type (queryCType) data Interface = Interface { Interface -> Maybe ParseError ifTypeInit :: Maybe Text, Interface -> Maybe ParseError ifCType :: Maybe Text, Interface -> Documentation ifDocumentation :: Documentation, Interface -> [Name] ifPrerequisites :: [Name], Interface -> [Property] ifProperties :: [Property], Interface -> [Signal] ifSignals :: [Signal], Interface -> [Method] ifMethods :: [Method], Interface -> AllocationInfo ifAllocationInfo :: AllocationInfo, Interface -> Maybe DeprecationInfo ifDeprecated :: Maybe DeprecationInfo } deriving Int -> Interface -> ShowS [Interface] -> ShowS Interface -> [Char] (Int -> Interface -> ShowS) -> (Interface -> [Char]) -> ([Interface] -> ShowS) -> Show Interface forall a. (Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a $cshowsPrec :: Int -> Interface -> ShowS showsPrec :: Int -> Interface -> ShowS $cshow :: Interface -> [Char] show :: Interface -> [Char] $cshowList :: [Interface] -> ShowS showList :: [Interface] -> ShowS Show parseInterface :: Parser (Name, Interface) parseInterface :: Parser (Name, Interface) parseInterface = do Name name <- Parser Name parseName [Property] props <- ParseError -> Parser Property -> Parser [Property] forall a. ParseError -> Parser a -> Parser [a] parseChildrenWithLocalName ParseError "property" Parser Property parseProperty [Signal] signals <- GIRXMLNamespace -> ParseError -> Parser Signal -> Parser [Signal] forall a. GIRXMLNamespace -> ParseError -> Parser a -> Parser [a] parseChildrenWithNSName GIRXMLNamespace GLibGIRNS ParseError "signal" Parser Signal parseSignal Maybe ParseError typeInit <- GIRXMLNamespace -> Name -> Parser (Maybe ParseError) queryAttrWithNamespace GIRXMLNamespace GLibGIRNS Name "get-type" [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) [Method] constructors <- ParseError -> Parser Method -> Parser [Method] forall a. ParseError -> Parser a -> Parser [a] parseChildrenWithLocalName ParseError "constructor" (MethodType -> Parser Method parseMethod MethodType Constructor) Maybe DeprecationInfo deprecated <- Parser (Maybe DeprecationInfo) parseDeprecation Documentation doc <- Parser Documentation parseDocumentation Maybe ParseError ctype <- Parser (Maybe ParseError) queryCType (Name, Interface) -> Parser (Name, Interface) forall a. a -> ReaderT ParseContext (Except ParseError) a forall (m :: * -> *) a. Monad m => a -> m a return (Name name, Interface { ifProperties :: [Property] ifProperties = [Property] props , ifPrerequisites :: [Name] ifPrerequisites = [Char] -> [Name] forall a. HasCallStack => [Char] -> a error ([Char] "unfixed interface " [Char] -> ShowS forall a. [a] -> [a] -> [a] ++ Name -> [Char] forall a. Show a => a -> [Char] show Name name) , ifSignals :: [Signal] ifSignals = [Signal] signals , ifTypeInit :: Maybe ParseError ifTypeInit = Maybe ParseError typeInit , ifCType :: Maybe ParseError ifCType = Maybe ParseError ctype , ifDocumentation :: Documentation ifDocumentation = Documentation doc , ifMethods :: [Method] ifMethods = [Method] constructors [Method] -> [Method] -> [Method] forall a. [a] -> [a] -> [a] ++ [Method] methods [Method] -> [Method] -> [Method] forall a. [a] -> [a] -> [a] ++ [Method] functions , ifAllocationInfo :: AllocationInfo ifAllocationInfo = AllocationInfo unknownAllocationInfo , ifDeprecated :: Maybe DeprecationInfo ifDeprecated = Maybe DeprecationInfo deprecated })