Safe Haskell | None |
---|---|
Language | Haskell2010 |
The Parser monad.
Synopsis
- type Parser a = ReaderT ParseContext (Except ParseError) a
- data ParseContext = ParseContext {
- ctxNamespace :: Text
- treePosition :: [Text]
- currentElement :: Element
- knownAliases :: Map Alias Type
- type ParseError = Text
- parseError :: ParseError -> Parser a
- runParser :: Text -> Map Alias Type -> Element -> Parser a -> Either ParseError a
- parseName :: Parser Name
- parseDeprecation :: Parser (Maybe DeprecationInfo)
- parseDocumentation :: Parser Documentation
- parseIntegral :: Integral a => Text -> Parser a
- parseBool :: Text -> Parser Bool
- parseChildrenWithLocalName :: Text -> Parser a -> Parser [a]
- parseAllChildrenWithLocalName :: Text -> Parser a -> Parser [a]
- parseChildrenWithNSName :: GIRXMLNamespace -> Text -> Parser a -> Parser [a]
- getAttr :: Name -> Parser Text
- getAttrWithNamespace :: GIRXMLNamespace -> Name -> Parser Text
- queryAttr :: Name -> Parser (Maybe Text)
- queryAttrWithNamespace :: GIRXMLNamespace -> Name -> Parser (Maybe Text)
- optionalAttr :: Name -> a -> (Text -> Parser a) -> Parser a
- currentNamespace :: Parser Text
- qualifyName :: Text -> Parser Name
- resolveQualifiedTypeName :: Name -> Parser Type
- data Name = Name {}
- data Element
- data GIRXMLNamespace
- data DeprecationInfo
- data Documentation
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.
data ParseContext Source #
Info to carry around when parsing.
ParseContext | |
|
Instances
Show ParseContext Source # | |
Defined in Data.GI.GIR.Parser showsPrec :: Int -> ParseContext -> ShowS # show :: ParseContext -> String # showList :: [ParseContext] -> ShowS # |
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.
parseDeprecation :: Parser (Maybe DeprecationInfo) Source #
Parse the deprecation text, if present.
parseDocumentation :: Parser Documentation Source #
Parse the documentation info for the current node.
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.
Instances
ToMarkup Element | Note that the special element name
|
NFData Element | |
Data Element | |
Defined in Text.XML 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 :: forall r r'. (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 # | |
Show Element | |
Eq Element | |
Ord Element | |
data GIRXMLNamespace Source #
GIR namespaces we know about.
Instances
Show GIRXMLNamespace Source # | |
Defined in Data.GI.GIR.XMLUtils showsPrec :: Int -> GIRXMLNamespace -> ShowS # show :: GIRXMLNamespace -> String # showList :: [GIRXMLNamespace] -> ShowS # |
data DeprecationInfo Source #
Deprecation information on a symbol.
Instances
Show DeprecationInfo Source # | |
Defined in Data.GI.GIR.Deprecation showsPrec :: Int -> DeprecationInfo -> ShowS # show :: DeprecationInfo -> String # showList :: [DeprecationInfo] -> ShowS # | |
Eq DeprecationInfo Source # | |
Defined in Data.GI.GIR.Deprecation (==) :: DeprecationInfo -> DeprecationInfo -> Bool # (/=) :: DeprecationInfo -> DeprecationInfo -> Bool # |
data Documentation Source #
Documentation for a given element. The documentation text is
typically encoded in the gtk-doc format, see
https://developer.gnome.org/gtk-doc-manual/ . This can be parsed
with parseGtkDoc
.
Instances
Show Documentation Source # | |
Defined in Data.GI.GIR.Documentation showsPrec :: Int -> Documentation -> ShowS # show :: Documentation -> String # showList :: [Documentation] -> ShowS # | |
Eq Documentation Source # | |
Defined in Data.GI.GIR.Documentation (==) :: Documentation -> Documentation -> Bool # (/=) :: Documentation -> Documentation -> Bool # | |
Ord Documentation Source # | |
Defined in Data.GI.GIR.Documentation compare :: Documentation -> Documentation -> Ordering # (<) :: Documentation -> Documentation -> Bool # (<=) :: Documentation -> Documentation -> Bool # (>) :: Documentation -> Documentation -> Bool # (>=) :: Documentation -> Documentation -> Bool # max :: Documentation -> Documentation -> Documentation # min :: Documentation -> Documentation -> Documentation # |