{-# LANGUAGE CPP #-}
#if __GLASGOW_HASKELL__
{-# LANGUAGE DeriveDataTypeable #-}
#if MIN_VERSION_base(4,4,0)
{-# LANGUAGE DeriveGeneric #-}
#endif
#endif

-- |
-- Module: Data.XML.Types
-- Copyright: 2010-2011 John Millikin
-- License: MIT
--
-- Basic types for representing XML.
--
-- The idea is to have a full set of appropriate types, which various XML
-- libraries can share. Instead of having equivalent-but-incompatible types
-- for every binding, parser, or client, they all share the same types can
-- can thus interoperate easily.
--
-- This library contains complete types for most parts of an XML document,
-- including the prologue, node tree, and doctype. Some basic combinators
-- are included for common tasks, including traversing the node tree and
-- filtering children.
--
module Data.XML.Types
	( -- * Types

	  -- ** Document prologue
	  Document (..)
	, Prologue (..)
	, Instruction (..)
	, Miscellaneous (..)

	-- ** Document body
	, Node (..)
	, Element (..)
	, Content (..)
	, Name (..)

	-- ** Doctypes
	, Doctype (..)
	, ExternalID (..)

	-- ** Incremental processing
	, Event (..)

	-- * Combinators

	-- ** Filters
	, isElement
	, isInstruction
	, isContent
	, isComment
	, isNamed

	-- ** Element traversal
	, elementChildren
	, elementContent
	, elementText

	-- ** Node traversal
	, nodeChildren
	, nodeContent
	, nodeText

	-- ** Attributes
	, hasAttribute
	, hasAttributeText
	, attributeContent
	, attributeText
	) where

import           Control.Monad ((>=>))
import           Data.Function (on)
import           Data.Maybe (isJust)
import           Data.String (IsString, fromString)
import           Data.Text (Text)
import qualified Data.Text as T
import           Control.DeepSeq (NFData(rnf))

#if __GLASGOW_HASKELL__
import           Data.Typeable (Typeable)
import           Data.Data (Data)

#if MIN_VERSION_base(4,4,0)
import           GHC.Generics (Generic)
#endif
#endif

data Document = Document
	{ Document -> Prologue
documentPrologue :: Prologue
	, Document -> Element
documentRoot :: Element
	, Document -> [Miscellaneous]
documentEpilogue :: [Miscellaneous]
	}
	deriving (Document -> Document -> Bool
(Document -> Document -> Bool)
-> (Document -> Document -> Bool) -> Eq Document
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Document -> Document -> Bool
== :: Document -> Document -> Bool
$c/= :: Document -> Document -> Bool
/= :: Document -> Document -> Bool
Eq, Eq Document
Eq Document
-> (Document -> Document -> Ordering)
-> (Document -> Document -> Bool)
-> (Document -> Document -> Bool)
-> (Document -> Document -> Bool)
-> (Document -> Document -> Bool)
-> (Document -> Document -> Document)
-> (Document -> Document -> Document)
-> Ord Document
Document -> Document -> Bool
Document -> Document -> Ordering
Document -> Document -> Document
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Document -> Document -> Ordering
compare :: Document -> Document -> Ordering
$c< :: Document -> Document -> Bool
< :: Document -> Document -> Bool
$c<= :: Document -> Document -> Bool
<= :: Document -> Document -> Bool
$c> :: Document -> Document -> Bool
> :: Document -> Document -> Bool
$c>= :: Document -> Document -> Bool
>= :: Document -> Document -> Bool
$cmax :: Document -> Document -> Document
max :: Document -> Document -> Document
$cmin :: Document -> Document -> Document
min :: Document -> Document -> Document
Ord, Int -> Document -> ShowS
[Document] -> ShowS
Document -> String
(Int -> Document -> ShowS)
-> (Document -> String) -> ([Document] -> ShowS) -> Show Document
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Document -> ShowS
showsPrec :: Int -> Document -> ShowS
$cshow :: Document -> String
show :: Document -> String
$cshowList :: [Document] -> ShowS
showList :: [Document] -> ShowS
Show
#if __GLASGOW_HASKELL__
	, Typeable Document
Typeable Document
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> Document -> c Document)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Document)
-> (Document -> Constr)
-> (Document -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Document))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Document))
-> ((forall b. Data b => b -> b) -> Document -> Document)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> Document -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> Document -> r)
-> (forall u. (forall d. Data d => d -> u) -> Document -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Document -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Document -> m Document)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Document -> m Document)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Document -> m Document)
-> Data Document
Document -> Constr
Document -> DataType
(forall b. Data b => b -> b) -> Document -> Document
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Document -> u
forall u. (forall d. Data d => d -> u) -> Document -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Document -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Document -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Document -> m Document
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Document -> m Document
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Document
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Document -> c Document
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Document)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Document)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Document -> c Document
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Document -> c Document
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Document
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Document
$ctoConstr :: Document -> Constr
toConstr :: Document -> Constr
$cdataTypeOf :: Document -> DataType
dataTypeOf :: Document -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Document)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Document)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Document)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Document)
$cgmapT :: (forall b. Data b => b -> b) -> Document -> Document
gmapT :: (forall b. Data b => b -> b) -> Document -> Document
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Document -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Document -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Document -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Document -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Document -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Document -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Document -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Document -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Document -> m Document
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Document -> m Document
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Document -> m Document
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Document -> m Document
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Document -> m Document
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Document -> m Document
Data, Typeable
#if MIN_VERSION_base(4,4,0)
	, (forall x. Document -> Rep Document x)
-> (forall x. Rep Document x -> Document) -> Generic Document
forall x. Rep Document x -> Document
forall x. Document -> Rep Document x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Document -> Rep Document x
from :: forall x. Document -> Rep Document x
$cto :: forall x. Rep Document x -> Document
to :: forall x. Rep Document x -> Document
Generic
#endif
#endif
	)

instance NFData Document where
	rnf :: Document -> ()
rnf (Document Prologue
a Element
b [Miscellaneous]
c) = Prologue -> ()
forall a. NFData a => a -> ()
rnf Prologue
a () -> () -> ()
forall a b. a -> b -> b
`seq` Element -> ()
forall a. NFData a => a -> ()
rnf Element
b () -> () -> ()
forall a b. a -> b -> b
`seq` [Miscellaneous] -> ()
forall a. NFData a => a -> ()
rnf [Miscellaneous]
c () -> () -> ()
forall a b. a -> b -> b
`seq` ()

data Prologue = Prologue
	{ Prologue -> [Miscellaneous]
prologueBefore :: [Miscellaneous]
	, Prologue -> Maybe Doctype
prologueDoctype :: Maybe Doctype
	, Prologue -> [Miscellaneous]
prologueAfter :: [Miscellaneous]
	}
	deriving (Prologue -> Prologue -> Bool
(Prologue -> Prologue -> Bool)
-> (Prologue -> Prologue -> Bool) -> Eq Prologue
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Prologue -> Prologue -> Bool
== :: Prologue -> Prologue -> Bool
$c/= :: Prologue -> Prologue -> Bool
/= :: Prologue -> Prologue -> Bool
Eq, Eq Prologue
Eq Prologue
-> (Prologue -> Prologue -> Ordering)
-> (Prologue -> Prologue -> Bool)
-> (Prologue -> Prologue -> Bool)
-> (Prologue -> Prologue -> Bool)
-> (Prologue -> Prologue -> Bool)
-> (Prologue -> Prologue -> Prologue)
-> (Prologue -> Prologue -> Prologue)
-> Ord Prologue
Prologue -> Prologue -> Bool
Prologue -> Prologue -> Ordering
Prologue -> Prologue -> Prologue
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Prologue -> Prologue -> Ordering
compare :: Prologue -> Prologue -> Ordering
$c< :: Prologue -> Prologue -> Bool
< :: Prologue -> Prologue -> Bool
$c<= :: Prologue -> Prologue -> Bool
<= :: Prologue -> Prologue -> Bool
$c> :: Prologue -> Prologue -> Bool
> :: Prologue -> Prologue -> Bool
$c>= :: Prologue -> Prologue -> Bool
>= :: Prologue -> Prologue -> Bool
$cmax :: Prologue -> Prologue -> Prologue
max :: Prologue -> Prologue -> Prologue
$cmin :: Prologue -> Prologue -> Prologue
min :: Prologue -> Prologue -> Prologue
Ord, Int -> Prologue -> ShowS
[Prologue] -> ShowS
Prologue -> String
(Int -> Prologue -> ShowS)
-> (Prologue -> String) -> ([Prologue] -> ShowS) -> Show Prologue
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Prologue -> ShowS
showsPrec :: Int -> Prologue -> ShowS
$cshow :: Prologue -> String
show :: Prologue -> String
$cshowList :: [Prologue] -> ShowS
showList :: [Prologue] -> ShowS
Show
#if __GLASGOW_HASKELL__
	, Typeable Prologue
Typeable Prologue
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> Prologue -> c Prologue)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Prologue)
-> (Prologue -> Constr)
-> (Prologue -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Prologue))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Prologue))
-> ((forall b. Data b => b -> b) -> Prologue -> Prologue)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> Prologue -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> Prologue -> r)
-> (forall u. (forall d. Data d => d -> u) -> Prologue -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Prologue -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Prologue -> m Prologue)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Prologue -> m Prologue)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Prologue -> m Prologue)
-> Data Prologue
Prologue -> Constr
Prologue -> DataType
(forall b. Data b => b -> b) -> Prologue -> Prologue
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Prologue -> u
forall u. (forall d. Data d => d -> u) -> Prologue -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Prologue -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Prologue -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Prologue -> m Prologue
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Prologue -> m Prologue
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Prologue
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Prologue -> c Prologue
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Prologue)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Prologue)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Prologue -> c Prologue
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Prologue -> c Prologue
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Prologue
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Prologue
$ctoConstr :: Prologue -> Constr
toConstr :: Prologue -> Constr
$cdataTypeOf :: Prologue -> DataType
dataTypeOf :: Prologue -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Prologue)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Prologue)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Prologue)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Prologue)
$cgmapT :: (forall b. Data b => b -> b) -> Prologue -> Prologue
gmapT :: (forall b. Data b => b -> b) -> Prologue -> Prologue
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Prologue -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Prologue -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Prologue -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Prologue -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Prologue -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Prologue -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Prologue -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Prologue -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Prologue -> m Prologue
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Prologue -> m Prologue
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Prologue -> m Prologue
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Prologue -> m Prologue
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Prologue -> m Prologue
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Prologue -> m Prologue
Data, Typeable
#if MIN_VERSION_base(4,4,0)
	, (forall x. Prologue -> Rep Prologue x)
-> (forall x. Rep Prologue x -> Prologue) -> Generic Prologue
forall x. Rep Prologue x -> Prologue
forall x. Prologue -> Rep Prologue x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Prologue -> Rep Prologue x
from :: forall x. Prologue -> Rep Prologue x
$cto :: forall x. Rep Prologue x -> Prologue
to :: forall x. Rep Prologue x -> Prologue
Generic
#endif
#endif
	)

instance NFData Prologue where
	rnf :: Prologue -> ()
rnf (Prologue [Miscellaneous]
a Maybe Doctype
b [Miscellaneous]
c) = [Miscellaneous] -> ()
forall a. NFData a => a -> ()
rnf [Miscellaneous]
a () -> () -> ()
forall a b. a -> b -> b
`seq` Maybe Doctype -> ()
forall a. NFData a => a -> ()
rnf Maybe Doctype
b () -> () -> ()
forall a b. a -> b -> b
`seq` [Miscellaneous] -> ()
forall a. NFData a => a -> ()
rnf [Miscellaneous]
c () -> () -> ()
forall a b. a -> b -> b
`seq` ()

data Instruction = Instruction
	{ Instruction -> Text
instructionTarget :: Text
	, Instruction -> Text
instructionData :: Text
	}
	deriving (Instruction -> Instruction -> Bool
(Instruction -> Instruction -> Bool)
-> (Instruction -> Instruction -> Bool) -> Eq Instruction
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Instruction -> Instruction -> Bool
== :: Instruction -> Instruction -> Bool
$c/= :: Instruction -> Instruction -> Bool
/= :: Instruction -> Instruction -> Bool
Eq, Eq Instruction
Eq Instruction
-> (Instruction -> Instruction -> Ordering)
-> (Instruction -> Instruction -> Bool)
-> (Instruction -> Instruction -> Bool)
-> (Instruction -> Instruction -> Bool)
-> (Instruction -> Instruction -> Bool)
-> (Instruction -> Instruction -> Instruction)
-> (Instruction -> Instruction -> Instruction)
-> Ord Instruction
Instruction -> Instruction -> Bool
Instruction -> Instruction -> Ordering
Instruction -> Instruction -> Instruction
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Instruction -> Instruction -> Ordering
compare :: Instruction -> Instruction -> Ordering
$c< :: Instruction -> Instruction -> Bool
< :: Instruction -> Instruction -> Bool
$c<= :: Instruction -> Instruction -> Bool
<= :: Instruction -> Instruction -> Bool
$c> :: Instruction -> Instruction -> Bool
> :: Instruction -> Instruction -> Bool
$c>= :: Instruction -> Instruction -> Bool
>= :: Instruction -> Instruction -> Bool
$cmax :: Instruction -> Instruction -> Instruction
max :: Instruction -> Instruction -> Instruction
$cmin :: Instruction -> Instruction -> Instruction
min :: Instruction -> Instruction -> Instruction
Ord, Int -> Instruction -> ShowS
[Instruction] -> ShowS
Instruction -> String
(Int -> Instruction -> ShowS)
-> (Instruction -> String)
-> ([Instruction] -> ShowS)
-> Show Instruction
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Instruction -> ShowS
showsPrec :: Int -> Instruction -> ShowS
$cshow :: Instruction -> String
show :: Instruction -> String
$cshowList :: [Instruction] -> ShowS
showList :: [Instruction] -> ShowS
Show
#if __GLASGOW_HASKELL__
	, Typeable Instruction
Typeable Instruction
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> Instruction -> c Instruction)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Instruction)
-> (Instruction -> Constr)
-> (Instruction -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Instruction))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c Instruction))
-> ((forall b. Data b => b -> b) -> Instruction -> Instruction)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> Instruction -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> Instruction -> r)
-> (forall u. (forall d. Data d => d -> u) -> Instruction -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> Instruction -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Instruction -> m Instruction)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Instruction -> m Instruction)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Instruction -> m Instruction)
-> Data Instruction
Instruction -> Constr
Instruction -> DataType
(forall b. Data b => b -> b) -> Instruction -> Instruction
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Instruction -> u
forall u. (forall d. Data d => d -> u) -> Instruction -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Instruction -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Instruction -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Instruction -> m Instruction
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Instruction -> m Instruction
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Instruction
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Instruction -> c Instruction
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Instruction)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c Instruction)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Instruction -> c Instruction
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Instruction -> c Instruction
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Instruction
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Instruction
$ctoConstr :: Instruction -> Constr
toConstr :: Instruction -> Constr
$cdataTypeOf :: Instruction -> DataType
dataTypeOf :: Instruction -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Instruction)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Instruction)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c Instruction)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c Instruction)
$cgmapT :: (forall b. Data b => b -> b) -> Instruction -> Instruction
gmapT :: (forall b. Data b => b -> b) -> Instruction -> Instruction
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Instruction -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Instruction -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Instruction -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Instruction -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Instruction -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Instruction -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Instruction -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Instruction -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Instruction -> m Instruction
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Instruction -> m Instruction
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Instruction -> m Instruction
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Instruction -> m Instruction
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Instruction -> m Instruction
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Instruction -> m Instruction
Data, Typeable
#if MIN_VERSION_base(4,4,0)
	, (forall x. Instruction -> Rep Instruction x)
-> (forall x. Rep Instruction x -> Instruction)
-> Generic Instruction
forall x. Rep Instruction x -> Instruction
forall x. Instruction -> Rep Instruction x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Instruction -> Rep Instruction x
from :: forall x. Instruction -> Rep Instruction x
$cto :: forall x. Rep Instruction x -> Instruction
to :: forall x. Rep Instruction x -> Instruction
Generic
#endif
#endif
	)

instance NFData Instruction where
	rnf :: Instruction -> ()
rnf (Instruction Text
a Text
b) = Text -> ()
forall a. NFData a => a -> ()
rnf Text
a () -> () -> ()
forall a b. a -> b -> b
`seq` Text -> ()
forall a. NFData a => a -> ()
rnf Text
b () -> () -> ()
forall a b. a -> b -> b
`seq` ()

data Miscellaneous
	= MiscInstruction Instruction
	| MiscComment Text
	deriving (Miscellaneous -> Miscellaneous -> Bool
(Miscellaneous -> Miscellaneous -> Bool)
-> (Miscellaneous -> Miscellaneous -> Bool) -> Eq Miscellaneous
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Miscellaneous -> Miscellaneous -> Bool
== :: Miscellaneous -> Miscellaneous -> Bool
$c/= :: Miscellaneous -> Miscellaneous -> Bool
/= :: Miscellaneous -> Miscellaneous -> Bool
Eq, Eq Miscellaneous
Eq Miscellaneous
-> (Miscellaneous -> Miscellaneous -> Ordering)
-> (Miscellaneous -> Miscellaneous -> Bool)
-> (Miscellaneous -> Miscellaneous -> Bool)
-> (Miscellaneous -> Miscellaneous -> Bool)
-> (Miscellaneous -> Miscellaneous -> Bool)
-> (Miscellaneous -> Miscellaneous -> Miscellaneous)
-> (Miscellaneous -> Miscellaneous -> Miscellaneous)
-> Ord Miscellaneous
Miscellaneous -> Miscellaneous -> Bool
Miscellaneous -> Miscellaneous -> Ordering
Miscellaneous -> Miscellaneous -> Miscellaneous
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Miscellaneous -> Miscellaneous -> Ordering
compare :: Miscellaneous -> Miscellaneous -> Ordering
$c< :: Miscellaneous -> Miscellaneous -> Bool
< :: Miscellaneous -> Miscellaneous -> Bool
$c<= :: Miscellaneous -> Miscellaneous -> Bool
<= :: Miscellaneous -> Miscellaneous -> Bool
$c> :: Miscellaneous -> Miscellaneous -> Bool
> :: Miscellaneous -> Miscellaneous -> Bool
$c>= :: Miscellaneous -> Miscellaneous -> Bool
>= :: Miscellaneous -> Miscellaneous -> Bool
$cmax :: Miscellaneous -> Miscellaneous -> Miscellaneous
max :: Miscellaneous -> Miscellaneous -> Miscellaneous
$cmin :: Miscellaneous -> Miscellaneous -> Miscellaneous
min :: Miscellaneous -> Miscellaneous -> Miscellaneous
Ord, Int -> Miscellaneous -> ShowS
[Miscellaneous] -> ShowS
Miscellaneous -> String
(Int -> Miscellaneous -> ShowS)
-> (Miscellaneous -> String)
-> ([Miscellaneous] -> ShowS)
-> Show Miscellaneous
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Miscellaneous -> ShowS
showsPrec :: Int -> Miscellaneous -> ShowS
$cshow :: Miscellaneous -> String
show :: Miscellaneous -> String
$cshowList :: [Miscellaneous] -> ShowS
showList :: [Miscellaneous] -> ShowS
Show
#if __GLASGOW_HASKELL__
	, Typeable Miscellaneous
Typeable Miscellaneous
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> Miscellaneous -> c Miscellaneous)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Miscellaneous)
-> (Miscellaneous -> Constr)
-> (Miscellaneous -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Miscellaneous))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c Miscellaneous))
-> ((forall b. Data b => b -> b) -> Miscellaneous -> Miscellaneous)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> Miscellaneous -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> Miscellaneous -> r)
-> (forall u. (forall d. Data d => d -> u) -> Miscellaneous -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> Miscellaneous -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Miscellaneous -> m Miscellaneous)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Miscellaneous -> m Miscellaneous)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Miscellaneous -> m Miscellaneous)
-> Data Miscellaneous
Miscellaneous -> Constr
Miscellaneous -> DataType
(forall b. Data b => b -> b) -> Miscellaneous -> Miscellaneous
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Miscellaneous -> u
forall u. (forall d. Data d => d -> u) -> Miscellaneous -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Miscellaneous -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Miscellaneous -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Miscellaneous -> m Miscellaneous
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Miscellaneous -> m Miscellaneous
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Miscellaneous
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Miscellaneous -> c Miscellaneous
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Miscellaneous)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c Miscellaneous)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Miscellaneous -> c Miscellaneous
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Miscellaneous -> c Miscellaneous
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Miscellaneous
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Miscellaneous
$ctoConstr :: Miscellaneous -> Constr
toConstr :: Miscellaneous -> Constr
$cdataTypeOf :: Miscellaneous -> DataType
dataTypeOf :: Miscellaneous -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Miscellaneous)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Miscellaneous)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c Miscellaneous)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c Miscellaneous)
$cgmapT :: (forall b. Data b => b -> b) -> Miscellaneous -> Miscellaneous
gmapT :: (forall b. Data b => b -> b) -> Miscellaneous -> Miscellaneous
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Miscellaneous -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Miscellaneous -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Miscellaneous -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Miscellaneous -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Miscellaneous -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Miscellaneous -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Miscellaneous -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Miscellaneous -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Miscellaneous -> m Miscellaneous
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Miscellaneous -> m Miscellaneous
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Miscellaneous -> m Miscellaneous
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Miscellaneous -> m Miscellaneous
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Miscellaneous -> m Miscellaneous
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Miscellaneous -> m Miscellaneous
Data, Typeable
#if MIN_VERSION_base(4,4,0)
	, (forall x. Miscellaneous -> Rep Miscellaneous x)
-> (forall x. Rep Miscellaneous x -> Miscellaneous)
-> Generic Miscellaneous
forall x. Rep Miscellaneous x -> Miscellaneous
forall x. Miscellaneous -> Rep Miscellaneous x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Miscellaneous -> Rep Miscellaneous x
from :: forall x. Miscellaneous -> Rep Miscellaneous x
$cto :: forall x. Rep Miscellaneous x -> Miscellaneous
to :: forall x. Rep Miscellaneous x -> Miscellaneous
Generic
#endif
#endif
	)

instance NFData Miscellaneous where
	rnf :: Miscellaneous -> ()
rnf (MiscInstruction Instruction
a) = Instruction -> ()
forall a. NFData a => a -> ()
rnf Instruction
a () -> () -> ()
forall a b. a -> b -> b
`seq` ()
	rnf (MiscComment Text
a)     = Text -> ()
forall a. NFData a => a -> ()
rnf Text
a () -> () -> ()
forall a b. a -> b -> b
`seq` ()

data Node
	= NodeElement Element
	| NodeInstruction Instruction
	| NodeContent Content
	| NodeComment Text
	deriving (Node -> Node -> Bool
(Node -> Node -> Bool) -> (Node -> Node -> Bool) -> Eq Node
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Node -> Node -> Bool
== :: Node -> Node -> Bool
$c/= :: Node -> Node -> Bool
/= :: Node -> Node -> Bool
Eq, Eq Node
Eq Node
-> (Node -> Node -> Ordering)
-> (Node -> Node -> Bool)
-> (Node -> Node -> Bool)
-> (Node -> Node -> Bool)
-> (Node -> Node -> Bool)
-> (Node -> Node -> Node)
-> (Node -> Node -> Node)
-> Ord Node
Node -> Node -> Bool
Node -> Node -> Ordering
Node -> Node -> Node
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Node -> Node -> Ordering
compare :: Node -> Node -> Ordering
$c< :: Node -> Node -> Bool
< :: Node -> Node -> Bool
$c<= :: Node -> Node -> Bool
<= :: Node -> Node -> Bool
$c> :: Node -> Node -> Bool
> :: Node -> Node -> Bool
$c>= :: Node -> Node -> Bool
>= :: Node -> Node -> Bool
$cmax :: Node -> Node -> Node
max :: Node -> Node -> Node
$cmin :: Node -> Node -> Node
min :: Node -> Node -> Node
Ord, Int -> Node -> ShowS
[Node] -> ShowS
Node -> String
(Int -> Node -> ShowS)
-> (Node -> String) -> ([Node] -> ShowS) -> Show Node
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Node -> ShowS
showsPrec :: Int -> Node -> ShowS
$cshow :: Node -> String
show :: Node -> String
$cshowList :: [Node] -> ShowS
showList :: [Node] -> ShowS
Show
#if __GLASGOW_HASKELL__
	, Typeable Node
Typeable Node
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> Node -> c Node)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Node)
-> (Node -> Constr)
-> (Node -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Node))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Node))
-> ((forall b. Data b => b -> b) -> Node -> Node)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Node -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Node -> r)
-> (forall u. (forall d. Data d => d -> u) -> Node -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Node -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Node -> m Node)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Node -> m Node)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Node -> m Node)
-> Data Node
Node -> Constr
Node -> DataType
(forall b. Data b => b -> b) -> Node -> Node
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Node -> u
forall u. (forall d. Data d => d -> u) -> Node -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Node -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Node -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Node -> m Node
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Node -> m Node
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Node
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Node -> c Node
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Node)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Node)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Node -> c Node
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Node -> c Node
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Node
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Node
$ctoConstr :: Node -> Constr
toConstr :: Node -> Constr
$cdataTypeOf :: Node -> DataType
dataTypeOf :: Node -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Node)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Node)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Node)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Node)
$cgmapT :: (forall b. Data b => b -> b) -> Node -> Node
gmapT :: (forall b. Data b => b -> b) -> Node -> Node
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Node -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Node -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Node -> r
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Node -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Node -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Node -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Node -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Node -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Node -> m Node
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Node -> m Node
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Node -> m Node
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Node -> m Node
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Node -> m Node
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Node -> m Node
Data, Typeable
#if MIN_VERSION_base(4,4,0)
	, (forall x. Node -> Rep Node x)
-> (forall x. Rep Node x -> Node) -> Generic Node
forall x. Rep Node x -> Node
forall x. Node -> Rep Node x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Node -> Rep Node x
from :: forall x. Node -> Rep Node x
$cto :: forall x. Rep Node x -> Node
to :: forall x. Rep Node x -> Node
Generic
#endif
#endif
	)

instance NFData Node where
	rnf :: Node -> ()
rnf (NodeElement Element
a)     = Element -> ()
forall a. NFData a => a -> ()
rnf Element
a () -> () -> ()
forall a b. a -> b -> b
`seq` ()
	rnf (NodeInstruction Instruction
a) = Instruction -> ()
forall a. NFData a => a -> ()
rnf Instruction
a () -> () -> ()
forall a b. a -> b -> b
`seq` ()
	rnf (NodeContent Content
a)     = Content -> ()
forall a. NFData a => a -> ()
rnf Content
a () -> () -> ()
forall a b. a -> b -> b
`seq` ()
	rnf (NodeComment Text
a)     = Text -> ()
forall a. NFData a => a -> ()
rnf Text
a () -> () -> ()
forall a b. a -> b -> b
`seq` ()

instance IsString Node where
	fromString :: String -> Node
fromString = Content -> Node
NodeContent (Content -> Node) -> (String -> Content) -> String -> Node
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Content
forall a. IsString a => String -> a
fromString

data Element = Element
	{ Element -> Name
elementName :: Name
	, Element -> [(Name, [Content])]
elementAttributes :: [(Name, [Content])]
	, Element -> [Node]
elementNodes :: [Node]
	}
	deriving (Element -> Element -> Bool
(Element -> Element -> Bool)
-> (Element -> Element -> Bool) -> Eq Element
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Element -> Element -> Bool
== :: Element -> Element -> Bool
$c/= :: Element -> Element -> Bool
/= :: Element -> Element -> Bool
Eq, Eq Element
Eq Element
-> (Element -> Element -> Ordering)
-> (Element -> Element -> Bool)
-> (Element -> Element -> Bool)
-> (Element -> Element -> Bool)
-> (Element -> Element -> Bool)
-> (Element -> Element -> Element)
-> (Element -> Element -> Element)
-> Ord Element
Element -> Element -> Bool
Element -> Element -> Ordering
Element -> Element -> Element
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Element -> Element -> Ordering
compare :: Element -> Element -> Ordering
$c< :: Element -> Element -> Bool
< :: Element -> Element -> Bool
$c<= :: Element -> Element -> Bool
<= :: Element -> Element -> Bool
$c> :: Element -> Element -> Bool
> :: Element -> Element -> Bool
$c>= :: Element -> Element -> Bool
>= :: Element -> Element -> Bool
$cmax :: Element -> Element -> Element
max :: Element -> Element -> Element
$cmin :: Element -> Element -> Element
min :: Element -> Element -> Element
Ord, Int -> Element -> ShowS
[Element] -> ShowS
Element -> String
(Int -> Element -> ShowS)
-> (Element -> String) -> ([Element] -> ShowS) -> Show Element
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Element -> ShowS
showsPrec :: Int -> Element -> ShowS
$cshow :: Element -> String
show :: Element -> String
$cshowList :: [Element] -> ShowS
showList :: [Element] -> ShowS
Show
#if __GLASGOW_HASKELL__
	, Typeable Element
Typeable Element
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> Element -> c Element)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Element)
-> (Element -> Constr)
-> (Element -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Element))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Element))
-> ((forall b. Data b => b -> b) -> Element -> Element)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> Element -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> Element -> r)
-> (forall u. (forall d. Data d => d -> u) -> Element -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Element -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Element -> m Element)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Element -> m Element)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Element -> m Element)
-> Data Element
Element -> Constr
Element -> DataType
(forall b. Data b => b -> b) -> Element -> Element
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Element -> u
forall u. (forall d. Data d => d -> u) -> Element -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Element -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Element -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Element -> m Element
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Element -> m Element
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Element
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Element -> c Element
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Element)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Element)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Element -> c Element
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Element -> c Element
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Element
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Element
$ctoConstr :: Element -> Constr
toConstr :: Element -> Constr
$cdataTypeOf :: Element -> DataType
dataTypeOf :: Element -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Element)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Element)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Element)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Element)
$cgmapT :: (forall b. Data b => b -> b) -> Element -> Element
gmapT :: (forall b. Data b => b -> b) -> Element -> Element
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Element -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Element -> r
$cgmapQr :: forall r r'.
(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
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Element -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Element -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Element -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Element -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Element -> m Element
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Element -> m Element
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Element -> m Element
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Element -> m Element
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Element -> m Element
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Element -> m Element
Data, Typeable
#if MIN_VERSION_base(4,4,0)
	, (forall x. Element -> Rep Element x)
-> (forall x. Rep Element x -> Element) -> Generic Element
forall x. Rep Element x -> Element
forall x. Element -> Rep Element x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Element -> Rep Element x
from :: forall x. Element -> Rep Element x
$cto :: forall x. Rep Element x -> Element
to :: forall x. Rep Element x -> Element
Generic
#endif
#endif
	)

instance NFData Element where
	rnf :: Element -> ()
rnf (Element Name
a [(Name, [Content])]
b [Node]
c) = Name -> ()
forall a. NFData a => a -> ()
rnf Name
a () -> () -> ()
forall a b. a -> b -> b
`seq` [(Name, [Content])] -> ()
forall a. NFData a => a -> ()
rnf [(Name, [Content])]
b () -> () -> ()
forall a b. a -> b -> b
`seq` [Node] -> ()
forall a. NFData a => a -> ()
rnf [Node]
c () -> () -> ()
forall a b. a -> b -> b
`seq` ()

data Content
	= ContentText Text
	| ContentEntity Text -- ^ For pass-through parsing
	deriving (Content -> Content -> Bool
(Content -> Content -> Bool)
-> (Content -> Content -> Bool) -> Eq Content
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Content -> Content -> Bool
== :: Content -> Content -> Bool
$c/= :: Content -> Content -> Bool
/= :: Content -> Content -> Bool
Eq, Eq Content
Eq Content
-> (Content -> Content -> Ordering)
-> (Content -> Content -> Bool)
-> (Content -> Content -> Bool)
-> (Content -> Content -> Bool)
-> (Content -> Content -> Bool)
-> (Content -> Content -> Content)
-> (Content -> Content -> Content)
-> Ord Content
Content -> Content -> Bool
Content -> Content -> Ordering
Content -> Content -> Content
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Content -> Content -> Ordering
compare :: Content -> Content -> Ordering
$c< :: Content -> Content -> Bool
< :: Content -> Content -> Bool
$c<= :: Content -> Content -> Bool
<= :: Content -> Content -> Bool
$c> :: Content -> Content -> Bool
> :: Content -> Content -> Bool
$c>= :: Content -> Content -> Bool
>= :: Content -> Content -> Bool
$cmax :: Content -> Content -> Content
max :: Content -> Content -> Content
$cmin :: Content -> Content -> Content
min :: Content -> Content -> Content
Ord, Int -> Content -> ShowS
[Content] -> ShowS
Content -> String
(Int -> Content -> ShowS)
-> (Content -> String) -> ([Content] -> ShowS) -> Show Content
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Content -> ShowS
showsPrec :: Int -> Content -> ShowS
$cshow :: Content -> String
show :: Content -> String
$cshowList :: [Content] -> ShowS
showList :: [Content] -> ShowS
Show
#if __GLASGOW_HASKELL__
	, Typeable Content
Typeable Content
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> Content -> c Content)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Content)
-> (Content -> Constr)
-> (Content -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Content))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Content))
-> ((forall b. Data b => b -> b) -> Content -> Content)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> Content -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> Content -> r)
-> (forall u. (forall d. Data d => d -> u) -> Content -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Content -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Content -> m Content)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Content -> m Content)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Content -> m Content)
-> Data Content
Content -> Constr
Content -> DataType
(forall b. Data b => b -> b) -> Content -> Content
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Content -> u
forall u. (forall d. Data d => d -> u) -> Content -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Content -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Content -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Content -> m Content
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Content -> m Content
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Content
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Content -> c Content
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Content)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Content)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Content -> c Content
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Content -> c Content
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Content
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Content
$ctoConstr :: Content -> Constr
toConstr :: Content -> Constr
$cdataTypeOf :: Content -> DataType
dataTypeOf :: Content -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Content)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Content)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Content)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Content)
$cgmapT :: (forall b. Data b => b -> b) -> Content -> Content
gmapT :: (forall b. Data b => b -> b) -> Content -> Content
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Content -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Content -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Content -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Content -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Content -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Content -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Content -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Content -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Content -> m Content
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Content -> m Content
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Content -> m Content
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Content -> m Content
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Content -> m Content
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Content -> m Content
Data, Typeable
#if MIN_VERSION_base(4,4,0)
	, (forall x. Content -> Rep Content x)
-> (forall x. Rep Content x -> Content) -> Generic Content
forall x. Rep Content x -> Content
forall x. Content -> Rep Content x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Content -> Rep Content x
from :: forall x. Content -> Rep Content x
$cto :: forall x. Rep Content x -> Content
to :: forall x. Rep Content x -> Content
Generic
#endif
#endif
	)

instance NFData Content where
	rnf :: Content -> ()
rnf (ContentText Text
a)   = Text -> ()
forall a. NFData a => a -> ()
rnf Text
a () -> () -> ()
forall a b. a -> b -> b
`seq` ()
	rnf (ContentEntity Text
a) = Text -> ()
forall a. NFData a => a -> ()
rnf Text
a () -> () -> ()
forall a b. a -> b -> b
`seq` ()

instance IsString Content where
	fromString :: String -> Content
fromString = Text -> Content
ContentText (Text -> Content) -> (String -> Text) -> String -> Content
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
forall a. IsString a => String -> a
fromString

-- | A fully qualified name.
--
-- Prefixes are not semantically important; they are included only to
-- simplify pass-through parsing. When comparing names with 'Eq' or 'Ord'
-- methods, prefixes are ignored.
--
-- The @IsString@ instance supports Clark notation; see
-- <http://www.jclark.com/xml/xmlns.htm> and
-- <http://infohost.nmt.edu/tcc/help/pubs/pylxml/etree-QName.html>. Use
-- the @OverloadedStrings@ language extension for very simple @Name@
-- construction:
--
-- > myname :: Name
-- > myname = "{http://example.com/ns/my-namespace}my-name"
--
data Name = Name
	{ Name -> Text
nameLocalName :: Text
	, Name -> Maybe Text
nameNamespace :: Maybe Text
	, Name -> Maybe Text
namePrefix :: Maybe Text
	}
	deriving (Int -> Name -> ShowS
[Name] -> ShowS
Name -> String
(Int -> Name -> ShowS)
-> (Name -> String) -> ([Name] -> ShowS) -> Show Name
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Name -> ShowS
showsPrec :: Int -> Name -> ShowS
$cshow :: Name -> String
show :: Name -> String
$cshowList :: [Name] -> ShowS
showList :: [Name] -> ShowS
Show
#if __GLASGOW_HASKELL__
	, Typeable Name
Typeable Name
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> Name -> c Name)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Name)
-> (Name -> Constr)
-> (Name -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Name))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Name))
-> ((forall b. Data b => b -> b) -> Name -> Name)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Name -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Name -> r)
-> (forall u. (forall d. Data d => d -> u) -> Name -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Name -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Name -> m Name)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Name -> m Name)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Name -> m Name)
-> Data Name
Name -> Constr
Name -> DataType
(forall b. Data b => b -> b) -> Name -> Name
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Name -> u
forall u. (forall d. Data d => d -> u) -> Name -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Name -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Name -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Name -> m Name
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Name -> m Name
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Name
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Name -> c Name
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Name)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Name)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Name -> c Name
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Name -> c Name
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Name
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Name
$ctoConstr :: Name -> Constr
toConstr :: Name -> Constr
$cdataTypeOf :: Name -> DataType
dataTypeOf :: Name -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Name)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Name)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Name)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Name)
$cgmapT :: (forall b. Data b => b -> b) -> Name -> Name
gmapT :: (forall b. Data b => b -> b) -> Name -> Name
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Name -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Name -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Name -> r
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Name -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Name -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Name -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Name -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Name -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Name -> m Name
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Name -> m Name
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Name -> m Name
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Name -> m Name
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Name -> m Name
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Name -> m Name
Data, Typeable
#if MIN_VERSION_base(4,4,0)
	, (forall x. Name -> Rep Name x)
-> (forall x. Rep Name x -> Name) -> Generic Name
forall x. Rep Name x -> Name
forall x. Name -> Rep Name x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Name -> Rep Name x
from :: forall x. Name -> Rep Name x
$cto :: forall x. Rep Name x -> Name
to :: forall x. Rep Name x -> Name
Generic
#endif
#endif
	)

instance Eq Name where
	== :: Name -> Name -> Bool
(==) = (Maybe Text, Text) -> (Maybe Text, Text) -> Bool
forall a. Eq a => a -> a -> Bool
(==) ((Maybe Text, Text) -> (Maybe Text, Text) -> Bool)
-> (Name -> (Maybe Text, Text)) -> Name -> Name -> Bool
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` (\Name
x -> (Name -> Maybe Text
nameNamespace Name
x, Name -> Text
nameLocalName Name
x))

instance Ord Name where
	compare :: Name -> Name -> Ordering
compare = (Maybe Text, Text) -> (Maybe Text, Text) -> Ordering
forall a. Ord a => a -> a -> Ordering
compare ((Maybe Text, Text) -> (Maybe Text, Text) -> Ordering)
-> (Name -> (Maybe Text, Text)) -> Name -> Name -> Ordering
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` (\Name
x -> (Name -> Maybe Text
nameNamespace Name
x, Name -> Text
nameLocalName Name
x))

instance IsString Name where
	fromString :: String -> Name
fromString String
"" = Text -> Maybe Text -> Maybe Text -> Name
Name Text
T.empty Maybe Text
forall a. Maybe a
Nothing Maybe Text
forall a. Maybe a
Nothing
	fromString full :: String
full@(Char
'{':String
rest) = case (Char -> Bool) -> String -> (String, String)
forall a. (a -> Bool) -> [a] -> ([a], [a])
break (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'}') String
rest of
		(String
_, String
"") -> String -> Name
forall a. HasCallStack => String -> a
error (String
"Invalid Clark notation: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ ShowS
forall a. Show a => a -> String
show String
full)
		(String
ns, String
local) -> Text -> Maybe Text -> Maybe Text -> Name
Name (String -> Text
T.pack (Int -> ShowS
forall a. Int -> [a] -> [a]
drop Int
1 String
local)) (Text -> Maybe Text
forall a. a -> Maybe a
Just (String -> Text
T.pack String
ns)) Maybe Text
forall a. Maybe a
Nothing
	fromString String
local = Text -> Maybe Text -> Maybe Text -> Name
Name (String -> Text
T.pack String
local) Maybe Text
forall a. Maybe a
Nothing Maybe Text
forall a. Maybe a
Nothing

instance NFData Name where
	rnf :: Name -> ()
rnf (Name Text
a Maybe Text
b Maybe Text
c) = Text -> ()
forall a. NFData a => a -> ()
rnf Text
a () -> () -> ()
forall a b. a -> b -> b
`seq` Maybe Text -> ()
forall a. NFData a => a -> ()
rnf Maybe Text
b () -> () -> ()
forall a b. a -> b -> b
`seq` Maybe Text -> ()
forall a. NFData a => a -> ()
rnf Maybe Text
c () -> () -> ()
forall a b. a -> b -> b
`seq` ()

-- | Note: due to the incredible complexity of DTDs, this type only supports
-- external subsets. I've tried adding internal subset types, but they
-- quickly gain more code than the rest of this module put together.
--
-- It is possible that some future version of this library might support
-- internal subsets, but I am no longer actively working on adding them.
data Doctype = Doctype
	{ Doctype -> Text
doctypeName :: Text
	, Doctype -> Maybe ExternalID
doctypeID :: Maybe ExternalID
	}
	deriving (Doctype -> Doctype -> Bool
(Doctype -> Doctype -> Bool)
-> (Doctype -> Doctype -> Bool) -> Eq Doctype
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Doctype -> Doctype -> Bool
== :: Doctype -> Doctype -> Bool
$c/= :: Doctype -> Doctype -> Bool
/= :: Doctype -> Doctype -> Bool
Eq, Eq Doctype
Eq Doctype
-> (Doctype -> Doctype -> Ordering)
-> (Doctype -> Doctype -> Bool)
-> (Doctype -> Doctype -> Bool)
-> (Doctype -> Doctype -> Bool)
-> (Doctype -> Doctype -> Bool)
-> (Doctype -> Doctype -> Doctype)
-> (Doctype -> Doctype -> Doctype)
-> Ord Doctype
Doctype -> Doctype -> Bool
Doctype -> Doctype -> Ordering
Doctype -> Doctype -> Doctype
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Doctype -> Doctype -> Ordering
compare :: Doctype -> Doctype -> Ordering
$c< :: Doctype -> Doctype -> Bool
< :: Doctype -> Doctype -> Bool
$c<= :: Doctype -> Doctype -> Bool
<= :: Doctype -> Doctype -> Bool
$c> :: Doctype -> Doctype -> Bool
> :: Doctype -> Doctype -> Bool
$c>= :: Doctype -> Doctype -> Bool
>= :: Doctype -> Doctype -> Bool
$cmax :: Doctype -> Doctype -> Doctype
max :: Doctype -> Doctype -> Doctype
$cmin :: Doctype -> Doctype -> Doctype
min :: Doctype -> Doctype -> Doctype
Ord, Int -> Doctype -> ShowS
[Doctype] -> ShowS
Doctype -> String
(Int -> Doctype -> ShowS)
-> (Doctype -> String) -> ([Doctype] -> ShowS) -> Show Doctype
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Doctype -> ShowS
showsPrec :: Int -> Doctype -> ShowS
$cshow :: Doctype -> String
show :: Doctype -> String
$cshowList :: [Doctype] -> ShowS
showList :: [Doctype] -> ShowS
Show
#if __GLASGOW_HASKELL__
	, Typeable Doctype
Typeable Doctype
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> Doctype -> c Doctype)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Doctype)
-> (Doctype -> Constr)
-> (Doctype -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Doctype))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Doctype))
-> ((forall b. Data b => b -> b) -> Doctype -> Doctype)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> Doctype -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> Doctype -> r)
-> (forall u. (forall d. Data d => d -> u) -> Doctype -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Doctype -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Doctype -> m Doctype)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Doctype -> m Doctype)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Doctype -> m Doctype)
-> Data Doctype
Doctype -> Constr
Doctype -> DataType
(forall b. Data b => b -> b) -> Doctype -> Doctype
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Doctype -> u
forall u. (forall d. Data d => d -> u) -> Doctype -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Doctype -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Doctype -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Doctype -> m Doctype
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Doctype -> m Doctype
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Doctype
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Doctype -> c Doctype
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Doctype)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Doctype)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Doctype -> c Doctype
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Doctype -> c Doctype
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Doctype
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Doctype
$ctoConstr :: Doctype -> Constr
toConstr :: Doctype -> Constr
$cdataTypeOf :: Doctype -> DataType
dataTypeOf :: Doctype -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Doctype)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Doctype)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Doctype)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Doctype)
$cgmapT :: (forall b. Data b => b -> b) -> Doctype -> Doctype
gmapT :: (forall b. Data b => b -> b) -> Doctype -> Doctype
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Doctype -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Doctype -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Doctype -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Doctype -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Doctype -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Doctype -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Doctype -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Doctype -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Doctype -> m Doctype
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Doctype -> m Doctype
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Doctype -> m Doctype
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Doctype -> m Doctype
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Doctype -> m Doctype
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Doctype -> m Doctype
Data, Typeable
#if MIN_VERSION_base(4,4,0)
	, (forall x. Doctype -> Rep Doctype x)
-> (forall x. Rep Doctype x -> Doctype) -> Generic Doctype
forall x. Rep Doctype x -> Doctype
forall x. Doctype -> Rep Doctype x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Doctype -> Rep Doctype x
from :: forall x. Doctype -> Rep Doctype x
$cto :: forall x. Rep Doctype x -> Doctype
to :: forall x. Rep Doctype x -> Doctype
Generic
#endif
#endif
	)

instance NFData Doctype where
	rnf :: Doctype -> ()
rnf (Doctype Text
a Maybe ExternalID
b) = Text -> ()
forall a. NFData a => a -> ()
rnf Text
a () -> () -> ()
forall a b. a -> b -> b
`seq` Maybe ExternalID -> ()
forall a. NFData a => a -> ()
rnf Maybe ExternalID
b () -> () -> ()
forall a b. a -> b -> b
`seq` ()

data ExternalID
	= SystemID Text
	| PublicID Text Text
	deriving (ExternalID -> ExternalID -> Bool
(ExternalID -> ExternalID -> Bool)
-> (ExternalID -> ExternalID -> Bool) -> Eq ExternalID
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ExternalID -> ExternalID -> Bool
== :: ExternalID -> ExternalID -> Bool
$c/= :: ExternalID -> ExternalID -> Bool
/= :: ExternalID -> ExternalID -> Bool
Eq, Eq ExternalID
Eq ExternalID
-> (ExternalID -> ExternalID -> Ordering)
-> (ExternalID -> ExternalID -> Bool)
-> (ExternalID -> ExternalID -> Bool)
-> (ExternalID -> ExternalID -> Bool)
-> (ExternalID -> ExternalID -> Bool)
-> (ExternalID -> ExternalID -> ExternalID)
-> (ExternalID -> ExternalID -> ExternalID)
-> Ord ExternalID
ExternalID -> ExternalID -> Bool
ExternalID -> ExternalID -> Ordering
ExternalID -> ExternalID -> ExternalID
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ExternalID -> ExternalID -> Ordering
compare :: ExternalID -> ExternalID -> Ordering
$c< :: ExternalID -> ExternalID -> Bool
< :: ExternalID -> ExternalID -> Bool
$c<= :: ExternalID -> ExternalID -> Bool
<= :: ExternalID -> ExternalID -> Bool
$c> :: ExternalID -> ExternalID -> Bool
> :: ExternalID -> ExternalID -> Bool
$c>= :: ExternalID -> ExternalID -> Bool
>= :: ExternalID -> ExternalID -> Bool
$cmax :: ExternalID -> ExternalID -> ExternalID
max :: ExternalID -> ExternalID -> ExternalID
$cmin :: ExternalID -> ExternalID -> ExternalID
min :: ExternalID -> ExternalID -> ExternalID
Ord, Int -> ExternalID -> ShowS
[ExternalID] -> ShowS
ExternalID -> String
(Int -> ExternalID -> ShowS)
-> (ExternalID -> String)
-> ([ExternalID] -> ShowS)
-> Show ExternalID
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ExternalID -> ShowS
showsPrec :: Int -> ExternalID -> ShowS
$cshow :: ExternalID -> String
show :: ExternalID -> String
$cshowList :: [ExternalID] -> ShowS
showList :: [ExternalID] -> ShowS
Show
#if __GLASGOW_HASKELL__
	, Typeable ExternalID
Typeable ExternalID
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> ExternalID -> c ExternalID)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c ExternalID)
-> (ExternalID -> Constr)
-> (ExternalID -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c ExternalID))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c ExternalID))
-> ((forall b. Data b => b -> b) -> ExternalID -> ExternalID)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> ExternalID -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> ExternalID -> r)
-> (forall u. (forall d. Data d => d -> u) -> ExternalID -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> ExternalID -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> ExternalID -> m ExternalID)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> ExternalID -> m ExternalID)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> ExternalID -> m ExternalID)
-> Data ExternalID
ExternalID -> Constr
ExternalID -> DataType
(forall b. Data b => b -> b) -> ExternalID -> ExternalID
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> ExternalID -> u
forall u. (forall d. Data d => d -> u) -> ExternalID -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ExternalID -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ExternalID -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ExternalID -> m ExternalID
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ExternalID -> m ExternalID
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ExternalID
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ExternalID -> c ExternalID
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ExternalID)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ExternalID)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ExternalID -> c ExternalID
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ExternalID -> c ExternalID
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ExternalID
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ExternalID
$ctoConstr :: ExternalID -> Constr
toConstr :: ExternalID -> Constr
$cdataTypeOf :: ExternalID -> DataType
dataTypeOf :: ExternalID -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ExternalID)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ExternalID)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ExternalID)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ExternalID)
$cgmapT :: (forall b. Data b => b -> b) -> ExternalID -> ExternalID
gmapT :: (forall b. Data b => b -> b) -> ExternalID -> ExternalID
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ExternalID -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ExternalID -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ExternalID -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ExternalID -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ExternalID -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> ExternalID -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ExternalID -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ExternalID -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ExternalID -> m ExternalID
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ExternalID -> m ExternalID
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ExternalID -> m ExternalID
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ExternalID -> m ExternalID
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ExternalID -> m ExternalID
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ExternalID -> m ExternalID
Data, Typeable
#if MIN_VERSION_base(4,4,0)
	, (forall x. ExternalID -> Rep ExternalID x)
-> (forall x. Rep ExternalID x -> ExternalID) -> Generic ExternalID
forall x. Rep ExternalID x -> ExternalID
forall x. ExternalID -> Rep ExternalID x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ExternalID -> Rep ExternalID x
from :: forall x. ExternalID -> Rep ExternalID x
$cto :: forall x. Rep ExternalID x -> ExternalID
to :: forall x. Rep ExternalID x -> ExternalID
Generic
#endif
#endif
	)

instance NFData ExternalID where
	rnf :: ExternalID -> ()
rnf (SystemID Text
a)   = Text -> ()
forall a. NFData a => a -> ()
rnf Text
a () -> () -> ()
forall a b. a -> b -> b
`seq` ()
	rnf (PublicID Text
a Text
b) = Text -> ()
forall a. NFData a => a -> ()
rnf Text
a () -> () -> ()
forall a b. a -> b -> b
`seq` Text -> ()
forall a. NFData a => a -> ()
rnf Text
b () -> () -> ()
forall a b. a -> b -> b
`seq` ()

-- | Some XML processing tools are incremental, and work in terms of events
-- rather than node trees. The 'Event' type allows a document to be fully
-- specified as a sequence of events.
--
-- Event-based XML libraries include:
--
-- * <http://hackage.haskell.org/package/xml-enumerator>
--
-- * <http://hackage.haskell.org/package/libxml-enumerator>
--
-- * <http://hackage.haskell.org/package/expat-enumerator>
--
data Event
	= EventBeginDocument
	| EventEndDocument
	| EventBeginDoctype Text (Maybe ExternalID)
	| EventEndDoctype
	| EventInstruction Instruction
	| EventBeginElement Name [(Name, [Content])]
	| EventEndElement Name
	| EventContent Content
	| EventComment Text
	| EventCDATA Text
	deriving (Event -> Event -> Bool
(Event -> Event -> Bool) -> (Event -> Event -> Bool) -> Eq Event
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Event -> Event -> Bool
== :: Event -> Event -> Bool
$c/= :: Event -> Event -> Bool
/= :: Event -> Event -> Bool
Eq, Eq Event
Eq Event
-> (Event -> Event -> Ordering)
-> (Event -> Event -> Bool)
-> (Event -> Event -> Bool)
-> (Event -> Event -> Bool)
-> (Event -> Event -> Bool)
-> (Event -> Event -> Event)
-> (Event -> Event -> Event)
-> Ord Event
Event -> Event -> Bool
Event -> Event -> Ordering
Event -> Event -> Event
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Event -> Event -> Ordering
compare :: Event -> Event -> Ordering
$c< :: Event -> Event -> Bool
< :: Event -> Event -> Bool
$c<= :: Event -> Event -> Bool
<= :: Event -> Event -> Bool
$c> :: Event -> Event -> Bool
> :: Event -> Event -> Bool
$c>= :: Event -> Event -> Bool
>= :: Event -> Event -> Bool
$cmax :: Event -> Event -> Event
max :: Event -> Event -> Event
$cmin :: Event -> Event -> Event
min :: Event -> Event -> Event
Ord, Int -> Event -> ShowS
[Event] -> ShowS
Event -> String
(Int -> Event -> ShowS)
-> (Event -> String) -> ([Event] -> ShowS) -> Show Event
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Event -> ShowS
showsPrec :: Int -> Event -> ShowS
$cshow :: Event -> String
show :: Event -> String
$cshowList :: [Event] -> ShowS
showList :: [Event] -> ShowS
Show
#if __GLASGOW_HASKELL__
	, Typeable Event
Typeable Event
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> Event -> c Event)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Event)
-> (Event -> Constr)
-> (Event -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Event))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Event))
-> ((forall b. Data b => b -> b) -> Event -> Event)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Event -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Event -> r)
-> (forall u. (forall d. Data d => d -> u) -> Event -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Event -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Event -> m Event)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Event -> m Event)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Event -> m Event)
-> Data Event
Event -> Constr
Event -> DataType
(forall b. Data b => b -> b) -> Event -> Event
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Event -> u
forall u. (forall d. Data d => d -> u) -> Event -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Event -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Event -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Event -> m Event
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Event -> m Event
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Event
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Event -> c Event
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Event)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Event)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Event -> c Event
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Event -> c Event
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Event
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Event
$ctoConstr :: Event -> Constr
toConstr :: Event -> Constr
$cdataTypeOf :: Event -> DataType
dataTypeOf :: Event -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Event)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Event)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Event)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Event)
$cgmapT :: (forall b. Data b => b -> b) -> Event -> Event
gmapT :: (forall b. Data b => b -> b) -> Event -> Event
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Event -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Event -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Event -> r
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Event -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Event -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Event -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Event -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Event -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Event -> m Event
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Event -> m Event
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Event -> m Event
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Event -> m Event
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Event -> m Event
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Event -> m Event
Data, Typeable
#if MIN_VERSION_base(4,4,0)
	, (forall x. Event -> Rep Event x)
-> (forall x. Rep Event x -> Event) -> Generic Event
forall x. Rep Event x -> Event
forall x. Event -> Rep Event x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Event -> Rep Event x
from :: forall x. Event -> Rep Event x
$cto :: forall x. Rep Event x -> Event
to :: forall x. Rep Event x -> Event
Generic
#endif
#endif
	)

instance NFData Event where
	rnf :: Event -> ()
rnf (EventBeginDoctype Text
a Maybe ExternalID
b) = Text -> ()
forall a. NFData a => a -> ()
rnf Text
a () -> () -> ()
forall a b. a -> b -> b
`seq` Maybe ExternalID -> ()
forall a. NFData a => a -> ()
rnf Maybe ExternalID
b () -> () -> ()
forall a b. a -> b -> b
`seq` ()
	rnf (EventInstruction Instruction
a)    = Instruction -> ()
forall a. NFData a => a -> ()
rnf Instruction
a () -> () -> ()
forall a b. a -> b -> b
`seq` ()
	rnf (EventBeginElement Name
a [(Name, [Content])]
b) = Name -> ()
forall a. NFData a => a -> ()
rnf Name
a () -> () -> ()
forall a b. a -> b -> b
`seq` [(Name, [Content])] -> ()
forall a. NFData a => a -> ()
rnf [(Name, [Content])]
b () -> () -> ()
forall a b. a -> b -> b
`seq` ()
	rnf (EventEndElement Name
a)     = Name -> ()
forall a. NFData a => a -> ()
rnf Name
a () -> () -> ()
forall a b. a -> b -> b
`seq` ()
	rnf (EventContent Content
a)        = Content -> ()
forall a. NFData a => a -> ()
rnf Content
a () -> () -> ()
forall a b. a -> b -> b
`seq` ()
	rnf (EventComment Text
a)        = Text -> ()
forall a. NFData a => a -> ()
rnf Text
a () -> () -> ()
forall a b. a -> b -> b
`seq` ()
	rnf (EventCDATA Text
a)          = Text -> ()
forall a. NFData a => a -> ()
rnf Text
a () -> () -> ()
forall a b. a -> b -> b
`seq` ()
	rnf Event
_                       = ()

isElement :: Node -> [Element]
isElement :: Node -> [Element]
isElement (NodeElement Element
e) = [Element
e]
isElement Node
_ = []

isInstruction :: Node -> [Instruction]
isInstruction :: Node -> [Instruction]
isInstruction (NodeInstruction Instruction
i) = [Instruction
i]
isInstruction Node
_ = []

isContent :: Node -> [Content]
isContent :: Node -> [Content]
isContent (NodeContent Content
c) = [Content
c]
isContent Node
_ = []

isComment :: Node -> [Text]
isComment :: Node -> [Text]
isComment (NodeComment Text
t) = [Text
t]
isComment Node
_ = []

isNamed :: Name -> Element -> [Element]
isNamed :: Name -> Element -> [Element]
isNamed Name
n Element
e = [Element
e | Element -> Name
elementName Element
e Name -> Name -> Bool
forall a. Eq a => a -> a -> Bool
== Name
n]

elementChildren :: Element -> [Element]
elementChildren :: Element -> [Element]
elementChildren = Element -> [Node]
elementNodes (Element -> [Node]) -> (Node -> [Element]) -> Element -> [Element]
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> Node -> [Element]
isElement

elementContent :: Element -> [Content]
elementContent :: Element -> [Content]
elementContent = Element -> [Node]
elementNodes (Element -> [Node]) -> (Node -> [Content]) -> Element -> [Content]
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> Node -> [Content]
isContent

elementText :: Element -> [Text]
elementText :: Element -> [Text]
elementText = Element -> [Content]
elementContent (Element -> [Content]) -> (Content -> [Text]) -> Element -> [Text]
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> Content -> [Text]
contentText

nodeChildren :: Node -> [Node]
nodeChildren :: Node -> [Node]
nodeChildren = Node -> [Element]
isElement (Node -> [Element]) -> (Element -> [Node]) -> Node -> [Node]
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> Element -> [Node]
elementNodes

nodeContent :: Node -> [Content]
nodeContent :: Node -> [Content]
nodeContent = Node -> [Node]
nodeChildren (Node -> [Node]) -> (Node -> [Content]) -> Node -> [Content]
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> Node -> [Content]
isContent

nodeText :: Node -> [Text]
nodeText :: Node -> [Text]
nodeText = Node -> [Content]
nodeContent (Node -> [Content]) -> (Content -> [Text]) -> Node -> [Text]
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> Content -> [Text]
contentText

hasAttribute :: Name -> Element -> [Element]
hasAttribute :: Name -> Element -> [Element]
hasAttribute Name
name Element
e = [Element
e | Maybe [Content] -> Bool
forall a. Maybe a -> Bool
isJust (Name -> Element -> Maybe [Content]
attributeContent Name
name Element
e)]

hasAttributeText :: Name -> (Text -> Bool) -> Element -> [Element]
hasAttributeText :: Name -> (Text -> Bool) -> Element -> [Element]
hasAttributeText Name
name Text -> Bool
p Element
e = [Element
e | Bool -> (Text -> Bool) -> Maybe Text -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
False Text -> Bool
p (Name -> Element -> Maybe Text
attributeText Name
name Element
e)]

attributeContent :: Name -> Element -> Maybe [Content]
attributeContent :: Name -> Element -> Maybe [Content]
attributeContent Name
name Element
e = Name -> [(Name, [Content])] -> Maybe [Content]
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Name
name (Element -> [(Name, [Content])]
elementAttributes Element
e)

attributeText :: Name -> Element -> Maybe Text
attributeText :: Name -> Element -> Maybe Text
attributeText Name
name Element
e = ([Content] -> Text) -> Maybe [Content] -> Maybe Text
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Content] -> Text
contentFlat (Name -> Element -> Maybe [Content]
attributeContent Name
name Element
e)

contentText :: Content -> [Text]
contentText :: Content -> [Text]
contentText (ContentText Text
t) = [Text
t]
contentText (ContentEntity Text
entity) = [String -> Text
T.pack String
"&", Text
entity, String -> Text
T.pack String
";"]

contentFlat :: [Content] -> Text
contentFlat :: [Content] -> Text
contentFlat [Content]
cs = [Text] -> Text
T.concat ([Content]
cs [Content] -> (Content -> [Text]) -> [Text]
forall a b. [a] -> (a -> [b]) -> [b]
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Content -> [Text]
contentText)