module Text.Xml.Lens.LowLevel where
import Control.Lens
import Data.Map (Map)
import Data.Text (Text)
import Text.XML
( ParseSettings, RenderSettings
, Document(..), Doctype(..), Prologue(..), ExternalID
, Node(..), Element(..), Instruction(..), Name(..), Miscellaneous(..)
)
import Text.XML.Stream.Parse (DecodeEntities)
import qualified Text.XML as XML
psDecodeEntities :: Lens' ParseSettings DecodeEntities
psDecodeEntities f ps = f (XML.psDecodeEntities ps) <&> \p -> ps { XML.psDecodeEntities = p }
rsPretty :: Lens' RenderSettings Bool
rsPretty f rs = f (XML.rsPretty rs) <&> \p -> rs { XML.rsPretty = p }
rsNamespaces :: Lens' RenderSettings [(Text, Text)]
rsNamespaces f rs = f (XML.rsNamespaces rs) <&> \p -> rs { XML.rsNamespaces = p }
rsAttrOrder :: Lens' RenderSettings (Name -> Map Name Text -> [(Name, Text)])
rsAttrOrder f rs = f (XML.rsAttrOrder rs) <&> \p -> rs { XML.rsAttrOrder = p }
documentPrologue :: Lens' Document Prologue
documentPrologue f doc = f (XML.documentPrologue doc) <&> \p -> doc { XML.documentPrologue = p }
documentRoot :: Lens' Document Element
documentRoot f doc = f (XML.documentRoot doc) <&> \p -> doc { XML.documentRoot = p }
documentEpilogue :: Lens' Document [Miscellaneous]
documentEpilogue f doc = f (XML.documentEpilogue doc) <&> \p -> doc { XML.documentEpilogue = p }
prologueBefore :: Lens' Prologue [Miscellaneous]
prologueBefore f doc = f (XML.prologueBefore doc) <&> \p -> doc { XML.prologueBefore = p }
prologueDoctype :: Lens' Prologue (Maybe Doctype)
prologueDoctype f doc = f (XML.prologueDoctype doc) <&> \p -> doc { XML.prologueDoctype = p }
prologueAfter :: Lens' Prologue [Miscellaneous]
prologueAfter f doc = f (XML.prologueAfter doc) <&> \p -> doc { XML.prologueAfter = p }
doctypeName :: Lens' Doctype Text
doctypeName f doc = f (XML.doctypeName doc) <&> \p -> doc { XML.doctypeName = p }
doctypeID :: Lens' Doctype (Maybe ExternalID)
doctypeID f doc = f (XML.doctypeID doc) <&> \p -> doc { XML.doctypeID = p }
_SystemID :: Prism' ExternalID Text
_SystemID = prism' XML.SystemID (\s -> case s of XML.SystemID e -> Just e; _ -> Nothing)
_PublicID :: Prism' ExternalID (Text, Text)
_PublicID = prism' (uncurry XML.PublicID) (\s -> case s of XML.PublicID e e' -> Just (e, e'); _ -> Nothing)
elementName :: Lens' Element Name
elementName f e = f (XML.elementName e) <&> \p -> e { XML.elementName = p }
elementAttributes :: Lens' Element (Map Name Text)
elementAttributes f e = f (XML.elementAttributes e) <&> \p -> e { XML.elementAttributes = p }
elementNodes :: Lens' Element [Node]
elementNodes f e = f (XML.elementNodes e) <&> \p -> e { XML.elementNodes = p }
nameLocalName :: Lens' Name Text
nameLocalName f n = f (XML.nameLocalName n) <&> \p -> n { XML.nameLocalName = p }
nameNamespace :: Lens' Name (Maybe Text)
nameNamespace f n = f (XML.nameNamespace n) <&> \p -> n { XML.nameNamespace = p }
namePrefix :: Lens' Name (Maybe Text)
namePrefix f n = f (XML.namePrefix n) <&> \p -> n { XML.namePrefix = p }
instructionTarget :: Lens' Instruction Text
instructionTarget f i = f (XML.instructionTarget i) <&> \p -> i { XML.instructionTarget = p }
instructionData :: Lens' Instruction Text
instructionData f i = f (XML.instructionData i) <&> \p -> i { XML.instructionData = p }
_Document :: Iso' Document (Prologue, Element, [Miscellaneous])
_Document = iso (\(Document p r e) -> (p, r, e)) (uncurry3 Document)
_Prologue :: Iso' Prologue ([Miscellaneous], Maybe Doctype, [Miscellaneous])
_Prologue = iso (\(Prologue xs d ys) -> (xs, d, ys)) (uncurry3 Prologue)
_Instruction :: Iso' Instruction (Text, Text)
_Instruction = iso (\(Instruction t d) -> (t, d)) (uncurry Instruction)
_Element :: Iso' Element (Name, Map Name Text, [Node])
_Element = iso (\(Element n as ns) -> (n, as, ns)) (uncurry3 Element)
_Name :: Iso' Name (Text, Maybe Text, Maybe Text)
_Name = iso (\(Name ln ns p) -> (ln, ns, p)) (uncurry3 Name)
_Doctype :: Iso' Doctype (Text, Maybe ExternalID)
_Doctype = iso (\(Doctype n i) -> (n, i)) (uncurry Doctype)
_NodeElement :: Prism' Node Element
_NodeElement = prism' NodeElement (\s -> case s of NodeElement e -> Just e; _ -> Nothing)
_NodeContent :: Prism' Node Text
_NodeContent = prism' NodeContent (\s -> case s of NodeContent e -> Just e; _ -> Nothing)
_NodeInstruction :: Prism' Node Instruction
_NodeInstruction = prism' NodeInstruction (\s -> case s of NodeInstruction e -> Just e; _ -> Nothing)
_NodeComment :: Prism' Node Text
_NodeComment = prism' NodeComment (\s -> case s of NodeComment e -> Just e; _ -> Nothing)
_MiscComment :: Prism' Miscellaneous Text
_MiscComment = prism' MiscComment (\s -> case s of MiscComment e -> Just e; _ -> Nothing)
_MiscInstruction :: Prism' Miscellaneous Instruction
_MiscInstruction = prism' MiscInstruction (\s -> case s of MiscInstruction e -> Just e; _ -> Nothing)
uncurry3 :: (a -> b -> c -> d) -> (a, b, c) -> d
uncurry3 f ~(a, b, c) = f a b c