ogma-language-xmlspec-1.6.0: Ogma: Runtime Monitor translator: XML Frontend
Safe HaskellSafe-Inferred
LanguageHaskell2010

Language.XMLSpec.Parser

Contents

Description

Parser for Ogma specs stored in XML files.

Synopsis

Documentation

data XMLFormat Source #

List of XPath routes to the elements we need to parse.

The optional paths denote elements that may not exist. If they are nothing, those elements are not parsed in the input file.

The subfields are applied on each string matching the parent element. That is, the internal var ID XPath will be a applied to the strings returned when applying the internal vars XPath (if it exists). Paths whose names are plural denote expected lists of elements.

The components of a tuple (String, Maybe (String, String)) mean the following: if a string is present but the second component is Nothing, then the string is the XPath expression to be used. If a Just value is present, the first element of its inner tuple represents a key, and the second element represents an XPath expression that will produce a value when evaluated globally in the file. After evaluating that expression, the key must be found in the first string of the three and replaced with the result of evaluating the expression.

parseXMLSpec Source #

Arguments

:: (String -> IO (Either String a))

Parser for expressions.

-> a 
-> XMLFormat

XPaths for spec locations.

-> String

String containing XML

-> IO (Either String (Spec a)) 

Parse an XML file and extract a Spec from it.

An auxiliary function must be provided to parse the requirement expressions.

Fails if any of the XPaths in the argument XMLFormat are not valid expressions, of the XML is malformed, or if the elements are not found with the frequency expected (e.g., an external variable id is not found even though external variables are found).

type XPathExpr = String Source #

Internal representation of an XPath expression.

resolveIndirectly :: String -> (String, Maybe (String, String)) -> ExceptT String IO XPathExpr Source #

Resolve an indirect XPath query, returning an XPath expression.

resolveIndirectly' :: String -> (String, Maybe (String, String)) -> ExceptT String IO [XPathExpr] Source #

Resolve an indirect XPath query, returning a list of XPath expressions.

checkXPathExpr :: String -> Either String XPathExpr Source #

Check that an XPath expression is syntactically correct.

parseXMLFormat :: XMLFormat -> String -> ExceptT String IO XMLFormatInternal Source #

Check an XMLFormat and return an internal representation.

Fails with an error message if any of the given expressions are not a valid XPath expression.

executeXPath :: String -> String -> IO [String] Source #

Execute an XPath query in an XML string, returning the list of strings that match the path.

Auxiliary

textUnescape :: String -> String Source #

Unescape <, > and & in a string.

swapMaybeEither :: Maybe (Either a b) -> Either a (Maybe b) Source #

Swap the Maybe and Either layers of a value.

swapMaybeExceptT :: Monad m => Maybe (ExceptT a m b) -> ExceptT a m (Maybe b) Source #

Swap the Maybe and Either layers of a value.

listToEither :: String -> [String] -> Either String String Source #

Convert a list to an Either, failing if the list provided does not have exactly one value.

replace :: String -> String -> String -> String Source #

Replace a string by another string

concatMapM :: Monad m => (a -> m [b]) -> [a] -> m [b] Source #

Map a monadic action over the elements of a container and concatenate the resulting lists.