chart-svg-0.4.1.1: Charting library targetting SVGs.
Safe HaskellSafe-Inferred
LanguageGHC2021

Chart.Markup.Parser

Contents

Description

Much of the parsing logic is based on the XML productions found in https://www.w3.org/TR/xml/#NT-content

As an Xml parser, this is very incomplete and rudimentary, hence not calling it an xml parser.

My other reference was https://www.w3schools.com/xml/xml_syntax.asp (don't laugh).

Synopsis

Documentation

markupP :: Parser Error Markup Source #

Main parser for a single Markup (xml-like) element

>>> runParser markupP "<foo>Hello World.</foo>"
OK (Markup {tag = "foo", atts = Attributes {attMap = fromList []}, contents = [Content "Hello World."]}) ""

contentP :: Parser Error Content Source #

Inner contents of an element.

>>> runParser (some contentP) "<foo>Hello World.</foo>content<!-- comment -->"
OK [MarkupLeaf (Markup {tag = "foo", atts = Attributes {attMap = fromList []}, contents = [Content "Hello World."]}),Content "content",Comment " comment "] ""

data XmlDocument Source #

An XML document as pre production rule [1]

Instances

Instances details
Show XmlDocument Source # 
Instance details

Defined in Chart.Markup.Parser

Eq XmlDocument Source # 
Instance details

Defined in Chart.Markup.Parser

xmlDocument :: Parser Error XmlDocument Source #

Note that the library builds a Markup as per the SVG standards and not a Document.

>>> runParser (ws_ *> xmlDocument) exampleDocument
OK (XmlDocument "<?xml version=\"1.0\" standalone=\"yes\" ?>\n\n<!--open the DOCTYPE declaration -\n  the open square bracket indicates an internal DTD-->\n<!DOCTYPE foo [\n\n<!--define the internal DTD-->\n  <!ELEMENT foo (#PCDATA)>\n\n<!--close the DOCTYPE declaration-->\n]>\n" (Markup {tag = "foo", atts = Attributes {attMap = fromList []}, contents = [Content "Hello World."]}) [XmlMisc {xmiscType = XMiscS, xmiscContent = "\n"}]) ""

xmlProlog :: Parser e ByteString Source #

xml production rule [22]

The library doesn't do any analysis of the prolog string nor produces it, hence it is just parsed as a ByteString

>>> runParser (ws_ *> xmlProlog) exampleDocument
OK "<?xml version=\"1.0\" standalone=\"yes\" ?>\n\n<!--open the DOCTYPE declaration -\n  the open square bracket indicates an internal DTD-->\n<!DOCTYPE foo [\n\n<!--define the internal DTD-->\n  <!ELEMENT foo (#PCDATA)>\n\n<!--close the DOCTYPE declaration-->\n]>\n" "<foo>Hello World.</foo>\n"

xmlXMLDecl :: Parser e ByteString Source #

XML declaration as per production rule [23]

>>> runParserMaybe xmlXMLDecl "<?xml version=\"1.0\" standalone=\"yes\" ?>"
Just "<?xml version=\"1.0\" standalone=\"yes\" ?>"

xmlDoctypedecl :: Parser e ByteString Source #

Doctype declaration as per production rule [28]

>>> runParserMaybe xmlDoctypedecl "<!DOCTYPE foo [ declarations ]>"
Just "<!DOCTYPE foo [ declarations ]>"

data XmlMiscType Source #

Whether an XmlMisc is comment or whitespace

Instances

Instances details
Generic XmlMiscType Source # 
Instance details

Defined in Chart.Markup.Parser

Associated Types

type Rep XmlMiscType :: Type -> Type #

Show XmlMiscType Source # 
Instance details

Defined in Chart.Markup.Parser

Eq XmlMiscType Source # 
Instance details

Defined in Chart.Markup.Parser

type Rep XmlMiscType Source # 
Instance details

Defined in Chart.Markup.Parser

type Rep XmlMiscType = D1 ('MetaData "XmlMiscType" "Chart.Markup.Parser" "chart-svg-0.4.1.1-IWqM7MKR0pA4JJOsSfAD0k" 'False) (C1 ('MetaCons "XMiscComment" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "XMiscS" 'PrefixI 'False) (U1 :: Type -> Type))

data XmlMisc Source #

A comment or whitespace outside of the main document [27]

not as per [27] (missing PI)

Instances

Instances details
Generic XmlMisc Source # 
Instance details

Defined in Chart.Markup.Parser

Associated Types

type Rep XmlMisc :: Type -> Type #

Methods

from :: XmlMisc -> Rep XmlMisc x #

to :: Rep XmlMisc x -> XmlMisc #

Show XmlMisc Source # 
Instance details

Defined in Chart.Markup.Parser

Eq XmlMisc Source # 
Instance details

Defined in Chart.Markup.Parser

Methods

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

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

type Rep XmlMisc Source # 
Instance details

Defined in Chart.Markup.Parser

type Rep XmlMisc = D1 ('MetaData "XmlMisc" "Chart.Markup.Parser" "chart-svg-0.4.1.1-IWqM7MKR0pA4JJOsSfAD0k" 'False) (C1 ('MetaCons "XmlMisc" 'PrefixI 'True) (S1 ('MetaSel ('Just "xmiscType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 XmlMiscType) :*: S1 ('MetaSel ('Just "xmiscContent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))

xmlMisc :: Parser e XmlMisc Source #

Parser for miscellaneous guff

xmlComment :: Parser e ByteString Source #

xml comment

>>> runParserMaybe xmlComment "<!-- comment -->"
Just " comment "

lt :: Parser e () Source #

opening tag

>>> runParserMaybe lt "<"
Just ()

gt :: Parser e () Source #

closing tag char

>>> runParserMaybe gt ">"
Just ()

gtc :: Parser e () Source #

self-closing tag

>>> runParserMaybe gtc "/>"
Just ()

oct :: Parser e () Source #

open closer tag

>>> runParserMaybe oct "</"
Just ()

sq :: ParserT st e () Source #

single quote

>>> runParserMaybe sq "''"
Just ()

dq :: ParserT st e () Source #

double quote

>>> runParserMaybe dq "\""
Just ()

wrappedQ :: Parser e ByteString Source #

quote or double quote wrapped

>>> runParserMaybe wrappedQ "\"quoted\""
Just "quoted"
>>> runParserMaybe wrappedQ "'quoted'"
Just "quoted"

wrappedQNoGuard :: Parser e a -> Parser e a Source #

quote or double quote wrapped

>>> runParserMaybe (wrappedQNoGuard xmlName) "\"name\""
Just "name"

but will consume quotes if the underlying parser does.

>>> runParserMaybe (wrappedQNoGuard (many anyChar)) "\"name\""
Nothing

eq :: Parser e () Source #

xml production [25]

>>> runParserMaybe eq " = "
Just ()
>>> runParserMaybe eq "="
Just ()

xmlName :: Parser e ByteString Source #

name string according to xml production rule [5]

>>> runParserMaybe xmlName "name"
Just "name"

xmlAtt :: Parser e (ByteString, ByteString) Source #

attribute pair

>>> runParserMaybe xmlAtt "style = 'fancy'"
Just ("style","fancy")

openTag :: Parser Error (ByteString, [(ByteString, ByteString)]) Source #

open xml tag as per xml production rule [40]

>>> runParserMaybe openTag "<g style='fancy'>"
Just ("g",[("style","fancy")])

closeTag :: Parser Error ByteString Source #

closing tag as per [42]

>>> runParserMaybe closeTag "</g>"
Just "g"

emptyElemTag :: Parser Error (ByteString, [(ByteString, ByteString)]) Source #

empty element tag as per [44]

>>> runParserMaybe emptyElemTag "<br/>"
Just ("br",[])

testing

exampleDocument :: ByteString Source #

Typical xml header text