haskell-gi-0.20: Generate Haskell bindings for GObject Introspection capable libraries

Safe HaskellNone
LanguageHaskell98

Data.GI.GIR.Parser

Description

The Parser monad.

Synopsis

Documentation

type Parser a = ReaderT ParseContext (Except ParseError) a Source #

Monad where parsers live: we carry a context around, and can throw errors that abort the parsing.

type ParseError = Text Source #

A message describing a parsing error in human readable form.

parseError :: ParseError -> Parser a Source #

Throw a parse error.

runParser :: Text -> Map Alias Type -> Element -> Parser a -> Either ParseError a Source #

Run the given parser, returning either success or an error.

parseName :: Parser Name Source #

Get the qualified name for the current element.

parseDeprecation :: Parser (Maybe DeprecationInfo) Source #

Parse the deprecation text, if present.

parseDocumentation :: Parser (Maybe Documentation) Source #

Parse the documentation text, if present.

parseIntegral :: Integral a => Text -> Parser a Source #

Parse a signed integral number.

parseBool :: Text -> Parser Bool Source #

A boolean value given by a numerical constant.

parseChildrenWithLocalName :: Text -> Parser a -> Parser [a] Source #

Parse all the introspectable subelements with the given local name.

parseAllChildrenWithLocalName :: Text -> Parser a -> Parser [a] Source #

Parse all subelements with the given local name.

parseChildrenWithNSName :: GIRXMLNamespace -> Text -> Parser a -> Parser [a] Source #

Parse all introspectable children with the given namespace and local name.

getAttr :: Name -> Parser Text Source #

Return the value of an attribute for the given element. If the attribute is not present this throws an error.

getAttrWithNamespace :: GIRXMLNamespace -> Name -> Parser Text Source #

Like getAttr, but allow for specifying the namespace.

queryAttr :: Name -> Parser (Maybe Text) Source #

Return the value of an attribute if it is present, and Nothing otherwise.

queryAttrWithNamespace :: GIRXMLNamespace -> Name -> Parser (Maybe Text) Source #

Like queryAttr, but allow for specifying the namespace.

optionalAttr :: Name -> a -> (Text -> Parser a) -> Parser a Source #

Ask for an optional attribute, applying the given parser to it. If the argument does not exist return the default value provided.

currentNamespace :: Parser Text Source #

Return the current namespace.

qualifyName :: Text -> Parser Name Source #

Build a Name out of the (possibly qualified) supplied name. If the supplied name is unqualified we qualify with the current namespace, and otherwise we simply parse it.

resolveQualifiedTypeName :: Name -> Parser Type Source #

Check whether there is an alias for the given name, and return the corresponding type in case it exists, and otherwise a TInterface.

data Name Source #

Name for a symbol in the GIR file.

Constructors

Name 

Fields

Instances

Eq Name Source # 

Methods

(==) :: Name -> Name -> Bool #

(/=) :: Name -> Name -> Bool #

Ord Name Source # 

Methods

compare :: Name -> Name -> Ordering #

(<) :: Name -> Name -> Bool #

(<=) :: Name -> Name -> Bool #

(>) :: Name -> Name -> Bool #

(>=) :: Name -> Name -> Bool #

max :: Name -> Name -> Name #

min :: Name -> Name -> Name #

Show Name Source # 

Methods

showsPrec :: Int -> Name -> ShowS #

show :: Name -> String #

showList :: [Name] -> ShowS #

data Element :: * #

Instances

Eq Element 

Methods

(==) :: Element -> Element -> Bool #

(/=) :: Element -> Element -> Bool #

Data Element 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Element -> c Element #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Element #

toConstr :: Element -> Constr #

dataTypeOf :: Element -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Element) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Element) #

gmapT :: (forall b. Data b => b -> b) -> Element -> Element #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Element -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Element -> r #

gmapQ :: (forall d. Data d => d -> u) -> Element -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Element -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Element -> m Element #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Element -> m Element #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Element -> m Element #

Ord Element 
Show Element 
NFData Element 

Methods

rnf :: Element -> () #

ToMarkup Element 

Methods

toMarkup :: Element -> Markup

preEscapedToMarkup :: Element -> Markup

data GIRXMLNamespace Source #

GIR namespaces we know about.

Constructors

GLibGIRNS 
CGIRNS