foldrApp :: (Default a, Foldable t) => t (a -> a) -> a
foldrApp = foldr ($) def
+-- Class 'Sym_DTC'
+-- | Use a symantic (tagless final) class to encode
+-- both the parsing and the schema of DTC,
+-- when repr is respectively instanciated
+-- on 'DTC.Parser' or 'RNC.RuleWriter'.
class RNC.Sym_RNC repr => Sym_DTC repr where
position :: repr DTC.Pos
document :: repr DTC.Document
instance Sym_DTC RNC.RuleWriter where
position = RNC.RuleWriter position
-dtcRNC :: [RNC.RuleWriter ()]
-dtcRNC =
+-- | RNC schema for DTC
+schema :: [RNC.RuleWriter ()]
+schema =
[ void $ document
, void $ head
module Main where
import Control.Monad (forM_, when)
+import Control.Monad.IO.Class (MonadIO(..))
import Data.Bool
import Data.Default.Class (Default(..))
import Data.Either (Either(..))
import Data.Eq (Eq(..))
import Data.Function (($), (.))
import Data.Functor ((<$>))
+import Data.Locale
import Data.Map.Strict (Map)
import Data.Maybe (Maybe(..), fromMaybe)
import Data.Monoid (Monoid(..))
import Prelude (error)
import System.IO (IO, FilePath, hPrint, hPutStrLn, stderr, stdout)
import qualified Data.ByteString as BS
+import qualified Data.ByteString.Lazy as BSL
import qualified Data.Char as Char
import qualified Data.List as List
import qualified Data.Map.Strict as Map
import qualified Data.Text as Text
import qualified Data.Text.IO as Text
import qualified Data.Text.Lazy as TL
+import qualified Data.Text.Lazy.Encoding as TL
import qualified Data.Text.Lazy.IO as TL
+import qualified Data.TreeSeq.Strict as Tree
import qualified System.Environment as Env
import qualified Text.Blaze.Renderer.Utf8 as Blaze
import qualified Text.Blaze.Utils as Blaze
+import qualified Text.Megaparsec as P
-import Data.Locale
-
-import qualified Data.TreeSeq.Strict as Tree
-{-
-import qualified Language.DTC.Read.TCT as DTC.Read.TCT
-import qualified Language.DTC.Sym as DTC
-import qualified Language.DTC.Write.HTML5 as DTC.Write.HTML5
-import qualified Language.DTC.Write.XML as DTC.Write.XML
-import qualified Text.Blaze.DTC as Blaze.DTC
-import qualified Text.Blaze.HTML5 as Blaze.HTML5
--}
--- import qualified Language.RNC.Write as RNC
-import qualified Language.TCT as TCT
-import qualified Language.TCT.Write.Plain as TCT.Write.Plain
+-- TCT imports
+import qualified Language.TCT as TCT
import qualified Language.TCT.Write.HTML5 as TCT.Write.HTML5
+import qualified Language.TCT.Write.Plain as TCT.Write.Plain
import qualified Language.TCT.Write.XML as TCT.Write.XML
-import qualified Text.Megaparsec as P
-import Read
+-- DTC imports
+import qualified Language.DTC.Read.TCT as DTC.Read.TCT
+import qualified Language.DTC.Sym as DTC
+import qualified Language.DTC.Write.HTML5 as DTC.Write.HTML5
+import qualified Language.DTC.Write.XML as DTC.Write.XML
+import qualified Language.RNC.Write as RNC
+import qualified Text.Blaze.DTC as Blaze.DTC
+import qualified Text.Blaze.HTML5 as Blaze.HTML5
type Langs = '[FR, EN]
-type Lang = LocaleIn Langs
+type Lang = LocaleIn Langs
main :: IO ()
main = do
info (pCommand lang <**> helper) $ mconcat
[ fullDesc
, progDesc "document tool"
- , header "hdoc - TCT and DTC command line tool"
+ , header "hdoc - command line tool for TCT and DTC technical documents"
]
mainWithCommand :: Command -> IO ()
mainWithCommand (CommandTCT ArgsTCT{..}) =
readFile input $ \_fp txt ->
- case TCT.readTrees input $ TL.fromStrict txt of
+ case TCT.readTCT input txt of
Left err -> error $ P.parseErrorPretty err
Right tct -> do
when (trace_TCT trace) $ do
TctFormatHTML5 ->
Blaze.renderMarkupToByteStringIO BS.putStr $
TCT.Write.HTML5.document tct
-{-
mainWithCommand (CommandDTC ArgsDTC{..}) =
readFile input $ \_fp txt ->
- case TCT.readTCTs input txt of
+ case TCT.readTCT input txt of
Left err -> error $ P.parseErrorPretty err
Right tct -> do
when (trace_TCT trace) $ do
hPutStrLn stderr "### TCT ###"
hPrint stderr $ Tree.Pretty tct
- let xml = TCT.Write.XML.xmlDocument tct
+ let xml = TCT.Write.XML.document tct
when (trace_XML trace) $ do
hPutStrLn stderr "### XML ###"
hPrint stderr $ Tree.Pretty xml
case format of
DtcFormatXML ->
Blaze.prettyMarkupIO Blaze.DTC.indentTag BS.putStr $
- DTC.Write.XML.xmlDocument locale dtc
+ DTC.Write.XML.document locale dtc
DtcFormatHTML5 ->
Blaze.prettyMarkupIO Blaze.HTML5.indentTag BS.putStr $
- DTC.Write.HTML5.html5Document locale dtc
+ DTC.Write.HTML5.document locale dtc
mainWithCommand (CommandRNC ArgsRNC{}) =
- forM_ DTC.dtcRNC $ \w ->
- Text.hPutStrLn stdout $ RNC.renderWriter w
--}
+ forM_ DTC.schema $ \rule ->
+ Text.hPutStrLn stdout $ RNC.renderWriter rule
+
+-- * Filesystem utilities
+readFile :: MonadIO m => FilePath -> (FilePath -> TL.Text -> m a) -> m a
+readFile fp f = do
+ content <- liftIO $ BSL.readFile fp
+ f fp $ TL.decodeUtf8 content
--- * Options utils
+-- * Options utilities
instance IsList (Opt.Mod f a) where
type Item (Opt.Mod f a) = Opt.Mod f a
-- * Type 'Command'
data Command
= CommandTCT ArgsTCT
- {-
| CommandDTC ArgsDTC
| CommandRNC ArgsRNC
- -}
pCommand :: Lang -> Parser Command
pCommand lang =
, command "tct" $
info (CommandTCT <$> pArgsTCT) $
progDesc "TCT (Texte Convivial Technique) rendition."
- ] {-<|>
+ ] <|>
hsubparser
[ metavar "dtc"
, command "dtc" $
, command "rnc" $
info (CommandRNC <$> pArgsRNC) $
progDesc "RNC (RelaxNG Compact) schema."
- ]-}
+ ]
-- * Type 'Trace'
data Trace
pArgsRNC :: Parser ArgsRNC
pArgsRNC = pure ArgsRNC
-
-
-{-
- Args
- <$> strOption ( long "hello"
- <> metavar "TARGET"
- <> help "Target for the greeting")
- <*> switch ( long "quiet"
- <> short 'q'
- <> help "Whether to be quiet")
- <*> option auto ( long "enthusiasm"
- <> help "How enthusiastically to greet"
- <> showDefault
- <> value 1
- <> metavar "INT")
--}
+++ /dev/null
-module Read where
-
-import Control.Monad.IO.Class (MonadIO(..))
-import Data.Eq (Eq(..))
-import Data.Functor ((<$>))
-import Data.Text (Text)
-import System.IO (IO, FilePath, hPrint, stderr)
-import Text.Show (Show(..))
-import qualified Data.ByteString as BS
-import qualified Data.Map.Strict as Map
-import qualified Data.Text.Encoding as Enc
--- import qualified System.FilePath as FilePath
-import qualified Text.Megaparsec as P
-
-
-readFile :: MonadIO m => FilePath -> (FilePath -> Text -> m a) -> m a
-readFile fp f = do
- content <- Enc.decodeUtf8 <$> liftIO (BS.readFile fp)
- f fp content
stability: experimental
synopsis: Library and tools for technical and convivial documents
tested-with: GHC==8.2.2
-version: 1.0.0.20180211
+version: 1.0.0.20180213
Source-Repository head
location: git://git.autogeree.net/hdoc
exposed-modules:
Data.Locale
Data.TreeSeq.Strict
- -- Data.TreeSeq.Strict.Zipper
- -- Language.DTC.Document
- -- Language.DTC.Anchor
- -- Language.DTC.Read.TCT
- -- Language.DTC.Sym
- -- Language.DTC.Write.HTML5
- -- Language.DTC.Write.Plain
- -- Language.DTC.Write.XML
+ Data.TreeSeq.Strict.Zipper
+ Language.DTC.Document
+ Language.DTC.Anchor
+ Language.DTC.Read.TCT
+ Language.DTC.Sym
+ Language.DTC.Write.HTML5
+ Language.DTC.Write.Plain
+ Language.DTC.Write.XML
Language.RNC.Fixity
Language.RNC.Sym
Language.RNC.Write
cpp-options: -DPROFILING
ghc-options: -fprof-auto
build-depends:
- base >= 4.6 && < 5
- , blaze-builder
- , blaze-html
- , blaze-markup
- , bytestring
- , containers > 0.5
- , data-default-class >= 0.1.2.0
- , data-default-instances-containers
- , filepath
- , megaparsec >= 6.2
- , mono-traversable
- , strict
- , text
- , text-format
- , transformers
- , treemap
- -- , xml-types
+ base >= 4.10 && < 5
+ , blaze-builder >= 0.4
+ , blaze-html >= 0.9
+ , blaze-markup >= 0.8
+ , bytestring >= 0.10
+ , containers >= 0.5
+ , data-default-class >= 0.1
+ , data-default-instances-containers >= 0.0
+ , filepath >= 1.4
+ , megaparsec >= 6.2
+ , mono-traversable >= 1.0
+ , strict >= 0.3
+ , text >= 1.2
+ , text-format >= 0.3
+ , transformers >= 0.5
+ , treemap >= 2.3
Test-Suite hdoc-test
type: exitcode-stdio-1.0
-- HUnit
-- QuickCheck
build-depends:
- base >= 4.6 && < 5
- , blaze-markup
- , blaze-html
- , bytestring
- , containers >= 0.5 && < 0.6
- , deepseq
- , filepath
- , hdoc
+ hdoc
+ , base >= 4.10 && < 5
+ , blaze-html >= 0.9
+ , blaze-markup >= 0.8
+ , bytestring >= 0.10
+ , containers >= 0.5
+ , deepseq >= 1.4
+ , filepath >= 1.4
+ , megaparsec >= 6.3
+ , tasty >= 0.11
+ , tasty-golden >= 2.3
+ , text >= 1.2
+ , transformers >= 0.4
-- , QuickCheck >= 2.0
- , tasty >= 0.11
-- , tasty-hunit
- , tasty-golden
-- , tasty-quickcheck
- , text
- , transformers >= 0.4 && < 0.6
Executable hdoc
default-language: Haskell2010
main-is: Main.hs
hs-source-dirs: exe/cli
other-modules:
- Read
build-depends:
- base >= 4.6 && < 5
- , ansi-terminal >= 0.4 && < 0.8
- , blaze-markup
- , blaze-html
- , bytestring
- , containers >= 0.5 && < 0.6
- , Decimal
- , data-default-class
- , deepseq
+ hdoc
+ , ansi-terminal >= 0.4
+ , base >= 4.6 && < 5
+ , blaze-html >= 0.9
+ , blaze-markup >= 0.8
+ , bytestring >= 0.10
+ , containers >= 0.5
+ , data-default-class >= 0.1
+ , Decimal >= 0.4
+ , deepseq >= 1.4
+ , megaparsec >= 6.3
+ , optparse-applicative >= 0.14
+ -- , safe-exceptions >= 0.1
+ , strict >= 0.3
+ , text >= 1.2
+ , time >= 1.8
+ , transformers >= 0.4
+ , semigroups >= 0.18
-- , directory
- , optparse-applicative
- , megaparsec
-- , monad-classes
-- , mono-traversable
-- , safe >= 0.2
- , safe-exceptions
- , semigroups
- , strict
- , hdoc
- , text
- , time
- , transformers >= 0.4 && < 0.6
-- NOTE: needed for Control.Monad.Trans.Except
-- , treemap
--- /dev/null
+document = head, body
+head = about?
+about = element "about" {title* & (attribute "url" url)? & author* & editor? & date? & version? & keyword* & link* & serie* & include*}
+keyword = element "keyword" text
+version = element "version" text
+author = element "author" entity
+editor = element "editor" entity
+date = element "date" {(attribute "year" xsd:int)? & (attribute "month" xsd:nat1)? & (attribute "day" xsd:nat1)?}
+entity = name? & (attribute "street" text)? & (attribute "zipcode" text)? & (attribute "city" text)? & (attribute "region" text)? & (attribute "country" text)? & (attribute "email" text)? & (attribute "tel" text)? & (attribute "fax" text)? & (attribute "url" url)? & (attribute "org" entity)?
+link = element "link" {name? & (attribute "href" url)? & (attribute "rel" text)? & lines*}
+serie = element "serie" {name? & (attribute "key" text)?}
+alias = element "alias" {id?}
+body = (element "section" {commonAttrs, title, alias*, body} | toc | tof | index | figure | element "references" {commonAttrs, reference*} | block)*
+toc = element "toc" {commonAttrs, (attribute "depth" xsd:nat)?} | tof = element "tof" {commonAttrs, (element "ul" {(element "li" {element "para" text})*})?} | index = element "index" {commonAttrs, (element "ul" {(element "li" {element "para" {text*}})*})?} | figure = element "figure" {commonAttrs, attribute "type" text, title?, block*} | element "references" {commonAttrs = id? & class?, reference = element "reference" {id, {title* & (attribute "url" url)? & author* & editor? & date? & version? & keyword* & link* & serie* & include*}}*} | block = comment | element "para" {commonAttrs, para} | element "ol" {commonAttrs, (element "li" {block*})*} | element "ul" {commonAttrs, (element "li" {block*})*} | element "artwork" {commonAttrs, attribute "type" text, text} | element "quote" {commonAttrs, attribute "type" text, block*}
+toc = element "toc" {commonAttrs, (attribute "depth" xsd:nat)?}
+tof = element "tof" {commonAttrs, (element "ul" {(element "li" {element "para" text})*})?}
+index = element "index" {commonAttrs, (element "ul" {(element "li" {element "para" {text*}})*})?}
+figure = element "figure" {commonAttrs, attribute "type" text, title?, block*}
+element "references" {commonAttrs = id? & class?, reference = element "reference" {id, {title* & (attribute "url" url)? & author* & editor? & date? & version? & keyword* & link* & serie* & include*}}*}
+reference = element "reference" {id, {title* & (attribute "url" url)? & author* & editor? & date? & version? & keyword* & link* & serie* & include*}}
+include = element "include" {(attribute "href" path)?}
+block = comment | element "para" {commonAttrs, para} | element "ol" {commonAttrs, (element "li" {block*})*} | element "ul" {commonAttrs, (element "li" {block*})*} | element "artwork" {commonAttrs, attribute "type" text, text} | element "quote" {commonAttrs, attribute "type" text, block*}
+para = lines*
+lines = element "b" para | element "code" para | element "del" para | element "i" para | element "note" para | element "q" para | element "sc" para | element "sub" para | element "sup" para | element "u" para | element "eref" {attribute "to" url, para} | element "iref" {attribute "to" text, para} | element "ref" {to, para} | element "rref" {to, para} | element "br" empty | text
+commonAttrs = id? & class?
+ident = text
+title = element "title" para
+name = attribute "name" text
+url = text
+path = text
+to = attribute "to" ident
+id = attribute "id" ident
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE TypeApplications #-}
module Golden where
--- import qualified System.FilePath as Path
--- import qualified Text.Blaze.Utils as Blaze
+import Control.Arrow (left)
import Control.Monad (Monad(..))
import Data.Either (Either(..))
import Data.Function (($), (.))
import Data.Functor ((<$>))
+import Data.Locale
import Data.Semigroup (Semigroup(..))
import Data.String (String)
+import System.FilePath (FilePath)
import System.IO (IO)
import Text.Show (Show(..))
-import qualified Data.ByteString.Lazy as BS
+import qualified Data.ByteString.Lazy as BSL
import qualified Data.List as List
-import qualified Data.Text.Lazy as TL
+import qualified Data.Map.Strict as Map
+import qualified Data.Text as Text
+import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.Encoding as TL
import qualified Data.TreeSeq.Strict as TreeSeq
import qualified Text.Blaze.Html.Renderer.Utf8 as Blaze
+import qualified Text.Megaparsec as P
import Test.Tasty
import Test.Tasty.Golden
-import qualified Language.TCT as TCT
-import qualified Language.TCT.Debug as TCT
+-- TCT imports
+import qualified Language.TCT as TCT
+import qualified Language.TCT.Debug as TCT
import qualified Language.TCT.Write.HTML5 as TCT.Write.HTML5
import qualified Language.TCT.Write.Plain as TCT.Write.Plain
-import qualified Language.TCT.Write.XML as TCT.Write.XML
+import qualified Language.TCT.Write.XML as TCT.Write.XML
-diff :: String -> String -> [String]
-diff ref new = ["diff", "-u", ref, new]
+-- DTC imports
+import qualified Language.DTC.Document as DTC
+import qualified Language.DTC.Write.HTML5 as DTC.Write.HTML5
+import qualified Language.DTC.Write.XML as DTC.Write.XML
+import qualified Language.DTC.Read.TCT as DTC
+import qualified Language.DTC.Sym as DTC
+import qualified Language.RNC.Write as RNC
+import qualified Text.Blaze.DTC as Blaze.DTC
+import qualified Text.Blaze.Utils as Blaze
-readAST :: String -> IO (Either TCT.ErrorRead TCT.Roots)
-readAST inputFile = do
- inp <- BS.readFile inputFile
- return $ TCT.readTrees inputFile $ TL.decodeUtf8 inp
+-- * Golden testing utilities
+testGolden :: TestName -> TestName -> IO (Either String BSL.ByteString) -> TestTree
+testGolden inputFile expectedExt =
+ goldenVsStringDiff inputFile diffGolden (inputFile <> expectedExt)
+ . (>>= unLeft)
-unLeft :: Show err => Either err BS.ByteString -> IO BS.ByteString
+diffGolden :: FilePath -> FilePath -> [String]
+diffGolden ref new = ["diff", "-u", ref, new]
+
+unLeft :: Either String BSL.ByteString -> IO BSL.ByteString
unLeft = \case
- Left err -> return $ TL.encodeUtf8 $ TL.pack $ show err
- Right a -> return a
+ Left err -> return $ TL.encodeUtf8 $ TL.pack err
+ Right a -> return a
+-- * All golden tests
goldensIO :: IO TestTree
goldensIO = do
inputFiles <- List.sort <$> findByExtension [".tct"] "test/Golden"
return $
- testGroup "TCT"
- [ testGroup "AST"
- [ goldenVsStringDiff inputFile diff (inputFile <> ".ast") $
- (>>= unLeft) $
- readAST inputFile >>= \ast ->
- return $
- TL.encodeUtf8
- . TL.pack
- . TCT.runPretty 0
- <$> ast
- | inputFile <- inputFiles
- ]
- , testGroup "Plain"
- [ goldenVsStringDiff inputFile diff inputFile $
- (>>= unLeft) $
- readAST inputFile >>= \ast ->
- return $
- TL.encodeUtf8
- . (<> TL.singleton '\n')
- . TCT.Write.Plain.document
- <$> ast
- | inputFile <- inputFiles
- ]
- , testGroup "HTML5"
- [ goldenVsStringDiff inputFile diff (inputFile <> ".html5") $
- (>>= unLeft) $
- readAST inputFile >>= \ast ->
- return $
- Blaze.renderHtml
- . TCT.Write.HTML5.document
- <$> ast
- | inputFile <- inputFiles
- ]
- , testGroup "XML"
- [ goldenVsStringDiff inputFile diff (inputFile <> ".xml") $
- (>>= unLeft) $
- readAST inputFile >>= \ast ->
- return $
- TL.encodeUtf8
- . TL.pack
- . show
- . TreeSeq.Pretty
- . TCT.Write.XML.document
- <$> ast
- | inputFile <- inputFiles
- ]
+ testGroup "Hdoc"
+ [ goldensTCT inputFiles
+ , goldensDTC inputFiles
+ ]
+
+-- * 'TCT' tests
+readTCT :: FilePath -> IO (Either String TCT.Roots)
+readTCT inputFile = do
+ txt <- BSL.readFile inputFile
+ return $
+ left show $
+ TCT.readTCT inputFile $
+ TL.decodeUtf8 txt
+
+goldensTCT :: [FilePath] -> TestTree
+goldensTCT inputFiles =
+ testGroup "TCT"
+ [ testGroup "AST"
+ [ testGolden inputFile ".ast" $
+ readTCT inputFile >>= \ast ->
+ return $
+ TL.encodeUtf8
+ . TL.pack
+ . TCT.runPretty 0
+ <$> ast
+ | inputFile <- inputFiles
+ ]
+ , testGroup "Plain"
+ [ testGolden inputFile "" $
+ readTCT inputFile >>= \ast ->
+ return $
+ TL.encodeUtf8
+ . (<> TL.singleton '\n')
+ . TCT.Write.Plain.document
+ <$> ast
+ | inputFile <- inputFiles
+ ]
+ , testGroup "HTML5"
+ [ testGolden inputFile ".html5" $
+ readTCT inputFile >>= \ast ->
+ return $
+ Blaze.renderHtml
+ . TCT.Write.HTML5.document
+ <$> ast
+ | inputFile <- inputFiles
+ ]
+ , testGroup "XML"
+ [ testGolden inputFile ".xml" $
+ readTCT inputFile >>= \ast ->
+ return $
+ TL.encodeUtf8
+ . TL.pack
+ . show
+ . TreeSeq.Pretty
+ . TCT.Write.XML.document
+ <$> ast
+ | inputFile <- inputFiles
+ ]
+ ]
+
+-- * 'DTC' tests
+type Langs = '[FR, EN]
+readDTC :: FilePath -> IO (Either String DTC.Document)
+readDTC inputFile = do
+ readTCT inputFile >>= \case
+ Left err -> return $ Left err
+ Right tct ->
+ let xml = TCT.Write.XML.document tct in
+ case DTC.readDTC xml of
+ Left err -> return $ Left $ P.parseErrorPretty err
+ Right dtc -> return $ Right dtc
+
+goldensDTC :: [FilePath] -> TestTree
+goldensDTC inputFiles =
+ let locale = LocaleIn @Langs en_US in
+ let lang = Text.unpack $ textLocales Map.! locale in
+ testGroup "DTC"
+ [ testGroup "RNC"
+ [ testGolden "schema/dtc.rnc" "" $ do
+ return $
+ Right $
+ TL.encodeUtf8 $
+ TL.unlines $
+ TL.fromStrict
+ . RNC.renderWriter
+ <$> DTC.schema
+ ]
+ , testGroup "XML"
+ [ testGolden inputFile (".dtc"<>"."<>lang<>".xml") $
+ readDTC inputFile >>= \dtc ->
+ return $
+ Blaze.prettyMarkup Blaze.DTC.indentTag
+ . DTC.Write.XML.document locale
+ <$> dtc
+ | inputFile <- inputFiles
+ ]
+ , testGroup "HTML5"
+ [ testGolden inputFile (".dtc"<>"."<>lang<>".html5") $
+ readDTC inputFile >>= \dtc ->
+ return $
+ Blaze.prettyMarkup Blaze.DTC.indentTag
+ . DTC.Write.HTML5.document locale
+ <$> dtc
+ | inputFile <- inputFiles
]
+ ]
--- /dev/null
+1:1:
+unexpected <colon1> at 1:1-1:8
+expecting <about>, <artwork>, <figure>, <index>, <ol>, <para>, <quote>, <references>, <section>, <toc>, <tof>, <ul>, comment, or none
--- /dev/null
+1:1:
+unexpected <colon1> at 1:1-1:8
+expecting <about>, <artwork>, <figure>, <index>, <ol>, <para>, <quote>, <references>, <section>, <toc>, <tof>, <ul>, comment, or none
--- /dev/null
+1:1:
+unexpected <colon1> at 1:1-1:9
+expecting <about>, <artwork>, <figure>, <index>, <ol>, <para>, <quote>, <references>, <section>, <toc>, <tof>, <ul>, comment, or none
--- /dev/null
+1:1:
+unexpected <colon1> at 1:1-1:9
+expecting <about>, <artwork>, <figure>, <index>, <ol>, <para>, <quote>, <references>, <section>, <toc>, <tof>, <ul>, comment, or none
--- /dev/null
+1:1:
+unexpected <colon1> at 1:1-1:9
+expecting <about>, <artwork>, <figure>, <index>, <ol>, <para>, <quote>, <references>, <section>, <toc>, <tof>, <ul>, comment, or none
--- /dev/null
+1:1:
+unexpected <colon1> at 1:1-1:9
+expecting <about>, <artwork>, <figure>, <index>, <ol>, <para>, <quote>, <references>, <section>, <toc>, <tof>, <ul>, comment, or none
--- /dev/null
+1:1:
+unexpected <colon1> at 1:1-1:14
+expecting <about>, <artwork>, <figure>, <index>, <ol>, <para>, <quote>, <references>, <section>, <toc>, <tof>, <ul>, comment, or none
--- /dev/null
+1:1:
+unexpected <colon1> at 1:1-1:14
+expecting <about>, <artwork>, <figure>, <index>, <ol>, <para>, <quote>, <references>, <section>, <toc>, <tof>, <ul>, comment, or none
--- /dev/null
+1:1:
+unexpected <colon1> at 1:1-2:7
+expecting <about>, <artwork>, <figure>, <index>, <ol>, <para>, <quote>, <references>, <section>, <toc>, <tof>, <ul>, comment, or none
--- /dev/null
+1:1:
+unexpected <colon1> at 1:1-2:7
+expecting <about>, <artwork>, <figure>, <index>, <ol>, <para>, <quote>, <references>, <section>, <toc>, <tof>, <ul>, comment, or none
--- /dev/null
+1:1:
+unexpected <colon1> at 1:1-2:12
+expecting <about>, <artwork>, <figure>, <index>, <ol>, <para>, <quote>, <references>, <section>, <toc>, <tof>, <ul>, comment, or none
--- /dev/null
+1:1:
+unexpected <colon1> at 1:1-2:12
+expecting <about>, <artwork>, <figure>, <index>, <ol>, <para>, <quote>, <references>, <section>, <toc>, <tof>, <ul>, comment, or none
--- /dev/null
+1:1:
+unexpected <colon1> at 1:1-2:13
+expecting <about>, <artwork>, <figure>, <index>, <ol>, <para>, <quote>, <references>, <section>, <toc>, <tof>, <ul>, comment, or none
--- /dev/null
+1:1:
+unexpected <colon1> at 1:1-2:13
+expecting <about>, <artwork>, <figure>, <index>, <ol>, <para>, <quote>, <references>, <section>, <toc>, <tof>, <ul>, comment, or none
--- /dev/null
+1:1:
+unexpected <colon1> at 1:1-2:14
+expecting <about>, <artwork>, <figure>, <index>, <ol>, <para>, <quote>, <references>, <section>, <toc>, <tof>, <ul>, comment, or none
--- /dev/null
+1:1:
+unexpected <colon1> at 1:1-2:14
+expecting <about>, <artwork>, <figure>, <index>, <ol>, <para>, <quote>, <references>, <section>, <toc>, <tof>, <ul>, comment, or none
--- /dev/null
+1:1:
+unexpected <colon1> at 1:1-1:14
+expecting <about>, <artwork>, <figure>, <index>, <ol>, <para>, <quote>, <references>, <section>, <toc>, <tof>, <ul>, comment, or none
--- /dev/null
+1:1:
+unexpected <colon1> at 1:1-1:14
+expecting <about>, <artwork>, <figure>, <index>, <ol>, <para>, <quote>, <references>, <section>, <toc>, <tof>, <ul>, comment, or none
--- /dev/null
+1:1:
+unexpected <colon1> at 1:1-3:7
+expecting <about>, <artwork>, <figure>, <index>, <ol>, <para>, <quote>, <references>, <section>, <toc>, <tof>, <ul>, comment, or none
--- /dev/null
+1:1:
+unexpected <colon1> at 1:1-3:7
+expecting <about>, <artwork>, <figure>, <index>, <ol>, <para>, <quote>, <references>, <section>, <toc>, <tof>, <ul>, comment, or none
--- /dev/null
+1:1:
+unexpected <colon1> at 1:1-3:12
+expecting <about>, <artwork>, <figure>, <index>, <ol>, <para>, <quote>, <references>, <section>, <toc>, <tof>, <ul>, comment, or none
--- /dev/null
+1:1:
+unexpected <colon1> at 1:1-3:12
+expecting <about>, <artwork>, <figure>, <index>, <ol>, <para>, <quote>, <references>, <section>, <toc>, <tof>, <ul>, comment, or none
--- /dev/null
+1:1:
+unexpected <colon1> at 1:1-3:13
+expecting <about>, <artwork>, <figure>, <index>, <ol>, <para>, <quote>, <references>, <section>, <toc>, <tof>, <ul>, comment, or none
--- /dev/null
+1:1:
+unexpected <colon1> at 1:1-3:13
+expecting <about>, <artwork>, <figure>, <index>, <ol>, <para>, <quote>, <references>, <section>, <toc>, <tof>, <ul>, comment, or none
--- /dev/null
+1:1:
+unexpected <colon1> at 1:1-3:14
+expecting <about>, <artwork>, <figure>, <index>, <ol>, <para>, <quote>, <references>, <section>, <toc>, <tof>, <ul>, comment, or none
--- /dev/null
+1:1:
+unexpected <colon1> at 1:1-3:14
+expecting <about>, <artwork>, <figure>, <index>, <ol>, <para>, <quote>, <references>, <section>, <toc>, <tof>, <ul>, comment, or none
--- /dev/null
+1:1:
+unexpected <colon1> at 1:1-1:8
+expecting <about>, <artwork>, <figure>, <index>, <ol>, <para>, <quote>, <references>, <section>, <toc>, <tof>, <ul>, comment, or none
--- /dev/null
+1:1:
+unexpected <colon1> at 1:1-1:8
+expecting <about>, <artwork>, <figure>, <index>, <ol>, <para>, <quote>, <references>, <section>, <toc>, <tof>, <ul>, comment, or none
--- /dev/null
+1:1:
+unexpected <colon1> at 1:1-2:9
+expecting <about>, <artwork>, <figure>, <index>, <ol>, <para>, <quote>, <references>, <section>, <toc>, <tof>, <ul>, comment, or none
--- /dev/null
+1:1:
+unexpected <colon1> at 1:1-2:9
+expecting <about>, <artwork>, <figure>, <index>, <ol>, <para>, <quote>, <references>, <section>, <toc>, <tof>, <ul>, comment, or none
--- /dev/null
+1:1:
+unexpected <colon1> at 1:1-2:14
+expecting <about>, <artwork>, <figure>, <index>, <ol>, <para>, <quote>, <references>, <section>, <toc>, <tof>, <ul>, comment, or none
--- /dev/null
+1:1:
+unexpected <colon1> at 1:1-2:14
+expecting <about>, <artwork>, <figure>, <index>, <ol>, <para>, <quote>, <references>, <section>, <toc>, <tof>, <ul>, comment, or none
--- /dev/null
+1:1:
+unexpected <colon1> at 1:1-2:15
+expecting <about>, <artwork>, <figure>, <index>, <ol>, <para>, <quote>, <references>, <section>, <toc>, <tof>, <ul>, comment, or none
--- /dev/null
+1:1:
+unexpected <colon1> at 1:1-2:15
+expecting <about>, <artwork>, <figure>, <index>, <ol>, <para>, <quote>, <references>, <section>, <toc>, <tof>, <ul>, comment, or none
--- /dev/null
+1:1:
+unexpected <colon1> at 1:1-2:16
+expecting <about>, <artwork>, <figure>, <index>, <ol>, <para>, <quote>, <references>, <section>, <toc>, <tof>, <ul>, comment, or none
--- /dev/null
+1:1:
+unexpected <colon1> at 1:1-2:16
+expecting <about>, <artwork>, <figure>, <index>, <ol>, <para>, <quote>, <references>, <section>, <toc>, <tof>, <ul>, comment, or none
--- /dev/null
+<!DOCTYPE HTML>
+<html lang="en"><head><meta http-equiv="Content-Type" content="text/html; charset=UTF-8"><meta name="generator" content="https://hackage.haskell.org/package/hdoc"><link rel="stylesheet" type="text/css" href="style/dtc-html5.css"></head><body><p class="para" id="para1">colon1:colon2:</p></body></html>
\ No newline at end of file
--- /dev/null
+<?xml-model type="application/relax-ng-compact-syntax" href="./schema/dtc.rnc"?>
+<?xml-stylesheet type="text/xsl" href="./xsl/document.html5.en.xsl"?>
+<?html5-stylesheet type="text/xsl" href="./xsl/document.html5.en.xsl"?>
+<?atom-stylesheet type="text/xsl" href="./xsl/document.atom.en.xsl"?>
+<document>
+ <about>
+ </about>
+ <para>
+ colon1:colon2:
+ </para>
+</document>
\ No newline at end of file
--- /dev/null
+1:1:
+unexpected <colon1> at 1:1-1:16
+expecting <about>, <artwork>, <figure>, <index>, <ol>, <para>, <quote>, <references>, <section>, <toc>, <tof>, <ul>, comment, or none
--- /dev/null
+1:1:
+unexpected <colon1> at 1:1-1:16
+expecting <about>, <artwork>, <figure>, <index>, <ol>, <para>, <quote>, <references>, <section>, <toc>, <tof>, <ul>, comment, or none
--- /dev/null
+: text1
+
+ text2
+ text3
--- /dev/null
+[ Tree (Cell 1:1 4:8 (NodeHeader (HeaderColon "" "")))
+ [ Tree (Cell 1:3 1:8 NodePara)
+ [ Tree (Cell 1:3 1:8 (NodeToken (TokenText "text1"))) []
+ ]
+ , Tree (Cell 3:3 4:8 NodePara)
+ [ Tree (Cell 3:3 4:8 (NodeToken (TokenText "text2\ntext3"))) []
+ ]
+ ]
+]
\ No newline at end of file
--- /dev/null
+<!DOCTYPE HTML>
+<html lang="en"><head><meta http-equiv="Content-Type" content="text/html; charset=UTF-8"><meta name="generator" content="https://hackage.haskell.org/package/hdoc"><link rel="stylesheet" type="text/css" href="style/dtc-html5.css"></head><body><div class="figure figure-" id="figure1"><table class="figure-caption"><tbody><tr><a href="#figure1"></a><td class="figure-title">text1</td></tr></tbody></table><div class="figure-content"><p class="para" id="figure1.para1">text2
+text3</p></div></div></body></html>
\ No newline at end of file
--- /dev/null
+<?xml-model type="application/relax-ng-compact-syntax" href="./schema/dtc.rnc"?>
+<?xml-stylesheet type="text/xsl" href="./xsl/document.html5.en.xsl"?>
+<?html5-stylesheet type="text/xsl" href="./xsl/document.html5.en.xsl"?>
+<?atom-stylesheet type="text/xsl" href="./xsl/document.atom.en.xsl"?>
+<document>
+ <about>
+ </about>
+ <figure type="">
+ <title>text1</title>
+ <para>
+ text2
+ text3
+ </para>
+ </figure>
+</document>
\ No newline at end of file
--- /dev/null
+<!DOCTYPE HTML>
+<html><head><meta http-equiv="Content-Type" content="text/html; charset=UTF-8"><link rel="stylesheet" type="text/css" href="style/tct-html5.css"></head><body><a id="line-1"></a><span class="header header-colon"><span class="header-mark">:</span></span><span class="header-value"> text1
+<a id="line-2"></a>
+<a id="line-3"></a> text2
+<a id="line-4"></a> text3</span></body></html>
\ No newline at end of file
--- /dev/null
+Cell 1:1 4:8 (XmlElem figure)
+|
++- Cell 1:1 1:1 (XmlAttr type "")
+|
++- Cell 1:3 1:8 (XmlElem title)
+| |
+| `- Cell 1:3 1:8 (XmlText "text1")
+|
+`- Cell 3:3 4:8 (XmlElem para)
+ |
+ `- Cell 3:3 4:8 (XmlText "text2\ntext3")
+
--- /dev/null
+: text1
+> text2
+> text3
--- /dev/null
+[ Tree (Cell 1:1 1:8 (NodeHeader (HeaderColon "" "")))
+ [ Tree (Cell 1:3 1:8 NodePara)
+ [ Tree (Cell 1:3 1:8 (NodeToken (TokenText "text1"))) []
+ ]
+ ]
+, Tree (Cell 2:1 3:8 (NodeHeader (HeaderGreat "" "")))
+ [ Tree (Cell 2:3 3:8 NodePara)
+ [ Tree (Cell 2:3 3:8 (NodeToken (TokenText "text2\ntext3"))) []
+ ]
+ ]
+]
\ No newline at end of file
--- /dev/null
+<!DOCTYPE HTML>
+<html lang="en"><head><meta http-equiv="Content-Type" content="text/html; charset=UTF-8"><meta name="generator" content="https://hackage.haskell.org/package/hdoc"><link rel="stylesheet" type="text/css" href="style/dtc-html5.css"></head><body><div class="figure figure-" id="figure1"><table class="figure-caption"><tbody><tr><a href="#figure1"></a><td class="figure-title">text1</td></tr></tbody></table><div class="figure-content"><div class="quote quote-" id="figure1.quote1"><p class="para" id="figure1.quote1.para1">text2
+text3</p></div></div></div></body></html>
\ No newline at end of file
--- /dev/null
+<?xml-model type="application/relax-ng-compact-syntax" href="./schema/dtc.rnc"?>
+<?xml-stylesheet type="text/xsl" href="./xsl/document.html5.en.xsl"?>
+<?html5-stylesheet type="text/xsl" href="./xsl/document.html5.en.xsl"?>
+<?atom-stylesheet type="text/xsl" href="./xsl/document.atom.en.xsl"?>
+<document>
+ <about>
+ </about>
+ <figure type="">
+ <title>text1</title>
+ <quote type="">
+ <para>text2
+ text3</para>
+ </quote>
+ </figure>
+</document>
\ No newline at end of file
--- /dev/null
+<!DOCTYPE HTML>
+<html><head><meta http-equiv="Content-Type" content="text/html; charset=UTF-8"><link rel="stylesheet" type="text/css" href="style/tct-html5.css"></head><body><a id="line-1"></a><span class="header header-colon"><span class="header-mark">:</span></span><span class="header-value"> text1</span>
+<a id="line-2"></a><span class="header header-great"><span class="header-mark">></span></span><span class="header-value"> text2
+<a id="line-3"></a><span class="header header-great"><span class="header-mark">></span></span> text3</span></body></html>
\ No newline at end of file
--- /dev/null
+Cell 1:1 1:8 (XmlElem figure)
+|
++- Cell 1:1 1:1 (XmlAttr type "")
+|
++- Cell 1:3 1:8 (XmlElem title)
+| |
+| `- Cell 1:3 1:8 (XmlText "text1")
+|
+`- Cell 2:1 3:8 (XmlElem quote)
+ |
+ +- Cell 2:1 2:1 (XmlAttr type "")
+ |
+ `- Cell 2:3 3:8 (XmlElem para)
+ |
+ `- Cell 2:3 3:8 (XmlText "text2\ntext3")
+
--- /dev/null
+: text1
+| text2
+| text3
--- /dev/null
+[ Tree (Cell 1:1 1:8 (NodeHeader (HeaderColon "" "")))
+ [ Tree (Cell 1:3 1:8 NodePara)
+ [ Tree (Cell 1:3 1:8 (NodeToken (TokenText "text1"))) []
+ ]
+ ]
+, Tree (Cell 2:1 3:8 (NodeHeader (HeaderBar "" "")))
+ [ Tree (Cell 2:3 3:8 (NodeText "text2\ntext3")) []
+ ]
+]
\ No newline at end of file
--- /dev/null
+<!DOCTYPE HTML>
+<html lang="en"><head><meta http-equiv="Content-Type" content="text/html; charset=UTF-8"><meta name="generator" content="https://hackage.haskell.org/package/hdoc"><link rel="stylesheet" type="text/css" href="style/dtc-html5.css"></head><body><div class="figure figure-" id="figure1"><table class="figure-caption"><tbody><tr><a href="#figure1"></a><td class="figure-title">text1</td></tr></tbody></table><div class="figure-content"><pre class="artwork artwork-" id="figure1.artwork1">text2
+text3</pre></div></div></body></html>
\ No newline at end of file
--- /dev/null
+<?xml-model type="application/relax-ng-compact-syntax" href="./schema/dtc.rnc"?>
+<?xml-stylesheet type="text/xsl" href="./xsl/document.html5.en.xsl"?>
+<?html5-stylesheet type="text/xsl" href="./xsl/document.html5.en.xsl"?>
+<?atom-stylesheet type="text/xsl" href="./xsl/document.atom.en.xsl"?>
+<document>
+ <about>
+ </about>
+ <figure type="">
+ <title>text1</title>
+ <artwork type="">text2
+text3</artwork>
+ </figure>
+</document>
\ No newline at end of file
--- /dev/null
+<!DOCTYPE HTML>
+<html><head><meta http-equiv="Content-Type" content="text/html; charset=UTF-8"><link rel="stylesheet" type="text/css" href="style/tct-html5.css"></head><body><a id="line-1"></a><span class="header header-colon"><span class="header-mark">:</span></span><span class="header-value"> text1</span>
+<a id="line-2"></a><span class="header header-bar"><span class="header-mark">|</span></span><span class="header-value"> text2
+<a id="line-3"></a><span class="header header-bar"><span class="header-mark">|</span></span> text3</span></body></html>
\ No newline at end of file
--- /dev/null
+Cell 1:1 1:8 (XmlElem figure)
+|
++- Cell 1:1 1:1 (XmlAttr type "")
+|
++- Cell 1:3 1:8 (XmlElem title)
+| |
+| `- Cell 1:3 1:8 (XmlText "text1")
+|
+`- Cell 2:1 3:8 (XmlElem artwork)
+ |
+ +- Cell 2:1 2:1 (XmlAttr type "")
+ |
+ `- Cell 2:3 3:8 (XmlText "text2\ntext3")
+
--- /dev/null
+<!DOCTYPE HTML>
+<html lang="en"><head><meta http-equiv="Content-Type" content="text/html; charset=UTF-8"><meta name="generator" content="https://hackage.haskell.org/package/hdoc"><link rel="stylesheet" type="text/css" href="style/dtc-html5.css"></head><body><div class="quote quote-" id="quote1"><p class="para" id="quote1.para1">text1
+text2</p></div></body></html>
\ No newline at end of file
--- /dev/null
+<?xml-model type="application/relax-ng-compact-syntax" href="./schema/dtc.rnc"?>
+<?xml-stylesheet type="text/xsl" href="./xsl/document.html5.en.xsl"?>
+<?html5-stylesheet type="text/xsl" href="./xsl/document.html5.en.xsl"?>
+<?atom-stylesheet type="text/xsl" href="./xsl/document.atom.en.xsl"?>
+<document>
+ <about>
+ </about>
+ <quote type="">
+ <para>text1
+ text2</para>
+ </quote>
+</document>
\ No newline at end of file
-Cell 1:1 2:8 (XmlElem artwork)
+Cell 1:1 2:8 (XmlElem quote)
|
-+- Cell 1:1 1:1 (XmlAttr type "quote")
++- Cell 1:1 1:1 (XmlAttr type "")
|
-`- Cell 1:3 2:8 (XmlText "text1\ntext2")
+`- Cell 1:3 2:8 (XmlElem para)
+ |
+ `- Cell 1:3 2:8 (XmlText "text1\ntext2")
--- /dev/null
+<!DOCTYPE HTML>
+<html lang="en"><head><meta http-equiv="Content-Type" content="text/html; charset=UTF-8"><meta name="generator" content="https://hackage.haskell.org/package/hdoc"><link rel="stylesheet" type="text/css" href="style/dtc-html5.css"></head><body><div class="quote quote-" id="quote1"><p class="para" id="quote1.para1">text1
+text2
+text3</p></div></body></html>
\ No newline at end of file
--- /dev/null
+<?xml-model type="application/relax-ng-compact-syntax" href="./schema/dtc.rnc"?>
+<?xml-stylesheet type="text/xsl" href="./xsl/document.html5.en.xsl"?>
+<?html5-stylesheet type="text/xsl" href="./xsl/document.html5.en.xsl"?>
+<?atom-stylesheet type="text/xsl" href="./xsl/document.atom.en.xsl"?>
+<document>
+ <about>
+ </about>
+ <quote type="">
+ <para>text1
+ text2
+ text3</para>
+ </quote>
+</document>
\ No newline at end of file
-Cell 1:1 3:8 (XmlElem artwork)
+Cell 1:1 3:8 (XmlElem quote)
|
-+- Cell 1:1 1:1 (XmlAttr type "quote")
++- Cell 1:1 1:1 (XmlAttr type "")
|
-`- Cell 1:3 3:8 (XmlText "text1\ntext2\ntext3")
+`- Cell 1:3 3:8 (XmlElem para)
+ |
+ `- Cell 1:3 3:8 (XmlText "text1\ntext2\ntext3")
--- /dev/null
+<!DOCTYPE HTML>
+<html lang="en"><head><meta http-equiv="Content-Type" content="text/html; charset=UTF-8"><meta name="generator" content="https://hackage.haskell.org/package/hdoc"><link rel="stylesheet" type="text/css" href="style/dtc-html5.css"></head><body><div class="quote quote-" id="quote1"><div class="quote quote-" id="quote1.1"><p class="para" id="quote1.1.para1">text1
+text2
+text3</p></div></div></body></html>
\ No newline at end of file
--- /dev/null
+<?xml-model type="application/relax-ng-compact-syntax" href="./schema/dtc.rnc"?>
+<?xml-stylesheet type="text/xsl" href="./xsl/document.html5.en.xsl"?>
+<?html5-stylesheet type="text/xsl" href="./xsl/document.html5.en.xsl"?>
+<?atom-stylesheet type="text/xsl" href="./xsl/document.atom.en.xsl"?>
+<document>
+ <about>
+ </about>
+ <quote type="">
+ <quote type=""><para>text1
+ text2
+ text3</para></quote>
+ </quote>
+</document>
\ No newline at end of file
-Cell 1:1 3:9 (XmlElem artwork)
+Cell 1:1 3:9 (XmlElem quote)
|
-+- Cell 1:1 1:1 (XmlAttr type "quote")
++- Cell 1:1 1:1 (XmlAttr type "")
|
-`- Cell 1:2 3:9 (XmlElem artwork)
+`- Cell 1:2 3:9 (XmlElem quote)
|
- +- Cell 1:2 1:2 (XmlAttr type "quote")
+ +- Cell 1:2 1:2 (XmlAttr type "")
|
- `- Cell 1:4 3:9 (XmlText "text1\ntext2\ntext3")
+ `- Cell 1:4 3:9 (XmlElem para)
+ |
+ `- Cell 1:4 3:9 (XmlText "text1\ntext2\ntext3")
--- /dev/null
+<!DOCTYPE HTML>
+<html lang="en"><head><meta http-equiv="Content-Type" content="text/html; charset=UTF-8"><meta name="generator" content="https://hackage.haskell.org/package/hdoc"><link rel="stylesheet" type="text/css" href="style/dtc-html5.css"></head><body><div class="quote quote-" id="quote1"><div class="quote quote-" id="quote1.1"><p class="para" id="quote1.1.para1">text1
+text2
+text3</p></div></div></body></html>
\ No newline at end of file
--- /dev/null
+<?xml-model type="application/relax-ng-compact-syntax" href="./schema/dtc.rnc"?>
+<?xml-stylesheet type="text/xsl" href="./xsl/document.html5.en.xsl"?>
+<?html5-stylesheet type="text/xsl" href="./xsl/document.html5.en.xsl"?>
+<?atom-stylesheet type="text/xsl" href="./xsl/document.atom.en.xsl"?>
+<document>
+ <about>
+ </about>
+ <quote type="">
+ <quote type=""><para>text1
+ text2
+ text3</para></quote>
+ </quote>
+</document>
\ No newline at end of file
-Cell 1:1 3:10 (XmlElem artwork)
+Cell 1:1 3:10 (XmlElem quote)
|
-+- Cell 1:1 1:1 (XmlAttr type "quote")
++- Cell 1:1 1:1 (XmlAttr type "")
|
-`- Cell 1:3 3:10 (XmlElem artwork)
+`- Cell 1:3 3:10 (XmlElem quote)
|
- +- Cell 1:3 1:3 (XmlAttr type "quote")
+ +- Cell 1:3 1:3 (XmlAttr type "")
|
- `- Cell 1:5 3:10 (XmlText "text1\ntext2\ntext3")
+ `- Cell 1:5 3:10 (XmlElem para)
+ |
+ `- Cell 1:5 3:10 (XmlText "text1\ntext2\ntext3")
--- /dev/null
+<!DOCTYPE HTML>
+<html lang="en"><head><meta http-equiv="Content-Type" content="text/html; charset=UTF-8"><meta name="generator" content="https://hackage.haskell.org/package/hdoc"><link rel="stylesheet" type="text/css" href="style/dtc-html5.css"></head><body><div class="quote quote-" id="quote1"><div class="quote quote-" id="quote1.1"><div class="quote quote-" id="quote1.1.1"><p class="para" id="quote1.1.1.para1">text1
+text2
+text3</p></div></div></div></body></html>
\ No newline at end of file
--- /dev/null
+<?xml-model type="application/relax-ng-compact-syntax" href="./schema/dtc.rnc"?>
+<?xml-stylesheet type="text/xsl" href="./xsl/document.html5.en.xsl"?>
+<?html5-stylesheet type="text/xsl" href="./xsl/document.html5.en.xsl"?>
+<?atom-stylesheet type="text/xsl" href="./xsl/document.atom.en.xsl"?>
+<document>
+ <about>
+ </about>
+ <quote type="">
+ <quote type=""><quote type=""><para>text1
+ text2
+ text3</para></quote></quote>
+ </quote>
+</document>
\ No newline at end of file
-Cell 1:1 3:12 (XmlElem artwork)
+Cell 1:1 3:12 (XmlElem quote)
|
-+- Cell 1:1 1:1 (XmlAttr type "quote")
++- Cell 1:1 1:1 (XmlAttr type "")
|
-`- Cell 1:3 3:12 (XmlElem artwork)
+`- Cell 1:3 3:12 (XmlElem quote)
|
- +- Cell 1:3 1:3 (XmlAttr type "quote")
+ +- Cell 1:3 1:3 (XmlAttr type "")
|
- `- Cell 1:5 3:12 (XmlElem artwork)
+ `- Cell 1:5 3:12 (XmlElem quote)
|
- +- Cell 1:5 1:5 (XmlAttr type "quote")
+ +- Cell 1:5 1:5 (XmlAttr type "")
|
- `- Cell 1:7 3:12 (XmlText "text1\ntext2\ntext3")
+ `- Cell 1:7 3:12 (XmlElem para)
+ |
+ `- Cell 1:7 3:12 (XmlText "text1\ntext2\ntext3")
--- /dev/null
+2:3:
+unexpected <quote> at 2:3-3:12
+expecting <b>, <br>, <code>, <del>, <eref>, <i>, <iref>, <note>, <q>, <ref>, <rref>, <sc>, <sub>, <sup>, <u>, none, or text
--- /dev/null
+2:3:
+unexpected <quote> at 2:3-3:12
+expecting <b>, <br>, <code>, <del>, <eref>, <i>, <iref>, <note>, <q>, <ref>, <rref>, <sc>, <sub>, <sup>, <u>, none, or text
-Cell 1:1 3:12 (XmlElem artwork)
+Cell 1:1 3:12 (XmlElem quote)
|
-+- Cell 1:1 1:1 (XmlAttr type "quote")
++- Cell 1:1 1:1 (XmlAttr type "")
|
-+- Cell 1:3 1:8 (XmlText "text1")
-|
-`- Cell 2:3 3:12 (XmlElem artwork)
- |
- +- Cell 2:3 2:3 (XmlAttr type "quote")
+`- Cell 1:3 3:12 (XmlElem para)
|
- +- Cell 2:5 2:10 (XmlText "text2")
+ +- Cell 1:3 1:8 (XmlText "text1")
|
- `- Cell 3:5 3:12 (XmlElem artwork)
+ `- Cell 2:3 3:12 (XmlElem quote)
|
- +- Cell 3:5 3:5 (XmlAttr type "quote")
+ +- Cell 2:3 2:3 (XmlAttr type "")
|
- `- Cell 3:7 3:12 (XmlText "text3")
+ `- Cell 2:5 3:12 (XmlElem para)
+ |
+ +- Cell 2:5 2:10 (XmlText "text2")
+ |
+ `- Cell 3:5 3:12 (XmlElem quote)
+ |
+ +- Cell 3:5 3:5 (XmlAttr type "")
+ |
+ `- Cell 3:7 3:12 (XmlElem para)
+ |
+ `- Cell 3:7 3:12 (XmlText "text3")
--- /dev/null
+<!DOCTYPE HTML>
+<html lang="en"><head><meta http-equiv="Content-Type" content="text/html; charset=UTF-8"><meta name="generator" content="https://hackage.haskell.org/package/hdoc"><link rel="stylesheet" type="text/css" href="style/dtc-html5.css"></head><body><div class="quote quote-" id="quote1"><div class="quote quote-" id="quote1.1"><div class="quote quote-" id="quote1.1.1"><p class="para" id="quote1.1.1.para1">text1</p></div><p class="para" id="quote1.1.para1">text2</p></div><p class="para" id="quote1.para1">text3</p></div></body></html>
\ No newline at end of file
--- /dev/null
+<?xml-model type="application/relax-ng-compact-syntax" href="./schema/dtc.rnc"?>
+<?xml-stylesheet type="text/xsl" href="./xsl/document.html5.en.xsl"?>
+<?html5-stylesheet type="text/xsl" href="./xsl/document.html5.en.xsl"?>
+<?atom-stylesheet type="text/xsl" href="./xsl/document.atom.en.xsl"?>
+<document>
+ <about>
+ </about>
+ <quote type="">
+ <quote type=""><quote type=""><para>text1</para></quote><para>text2</para></quote><para>text3</para>
+ </quote>
+</document>
\ No newline at end of file
-Cell 1:1 3:8 (XmlElem artwork)
+Cell 1:1 3:8 (XmlElem quote)
|
-+- Cell 1:1 1:1 (XmlAttr type "quote")
++- Cell 1:1 1:1 (XmlAttr type "")
|
-+- Cell 1:3 2:10 (XmlElem artwork)
++- Cell 1:3 2:10 (XmlElem quote)
| |
-| +- Cell 1:3 1:3 (XmlAttr type "quote")
+| +- Cell 1:3 1:3 (XmlAttr type "")
| |
-| +- Cell 1:5 1:12 (XmlElem artwork)
+| +- Cell 1:5 1:12 (XmlElem quote)
| | |
-| | +- Cell 1:5 1:5 (XmlAttr type "quote")
+| | +- Cell 1:5 1:5 (XmlAttr type "")
| | |
-| | `- Cell 1:7 1:12 (XmlText "text1")
+| | `- Cell 1:7 1:12 (XmlElem para)
+| | |
+| | `- Cell 1:7 1:12 (XmlText "text1")
| |
-| `- Cell 2:5 2:10 (XmlText "text2")
+| `- Cell 2:5 2:10 (XmlElem para)
+| |
+| `- Cell 2:5 2:10 (XmlText "text2")
|
-`- Cell 3:3 3:8 (XmlText "text3")
+`- Cell 3:3 3:8 (XmlElem para)
+ |
+ `- Cell 3:3 3:8 (XmlText "text3")
--- /dev/null
+<!DOCTYPE HTML>
+<html lang="en"><head><meta http-equiv="Content-Type" content="text/html; charset=UTF-8"><meta name="generator" content="https://hackage.haskell.org/package/hdoc"><link rel="stylesheet" type="text/css" href="style/dtc-html5.css"></head><body><div class="quote quote-" id="quote1"><div class="quote quote-" id="quote1.1"><p class="para" id="quote1.1.para1">text1</p><div class="quote quote-" id="quote1.1.1"><p class="para" id="quote1.1.1.para1">text2</p></div><p class="para" id="quote1.1.para2">text3</p></div></div></body></html>
\ No newline at end of file
--- /dev/null
+<?xml-model type="application/relax-ng-compact-syntax" href="./schema/dtc.rnc"?>
+<?xml-stylesheet type="text/xsl" href="./xsl/document.html5.en.xsl"?>
+<?html5-stylesheet type="text/xsl" href="./xsl/document.html5.en.xsl"?>
+<?atom-stylesheet type="text/xsl" href="./xsl/document.atom.en.xsl"?>
+<document>
+ <about>
+ </about>
+ <quote type="">
+ <quote type=""><para>text1</para><quote type=""><para>text2</para></quote><para>text3</para></quote>
+ </quote>
+</document>
\ No newline at end of file
-Cell 1:1 3:12 (XmlElem artwork)
+Cell 1:1 3:12 (XmlElem quote)
|
-+- Cell 1:1 1:1 (XmlAttr type "quote")
++- Cell 1:1 1:1 (XmlAttr type "")
|
-`- Cell 1:3 3:12 (XmlElem artwork)
+`- Cell 1:3 3:12 (XmlElem quote)
|
- +- Cell 1:3 1:3 (XmlAttr type "quote")
+ +- Cell 1:3 1:3 (XmlAttr type "")
|
- +- Cell 1:7 1:12 (XmlText "text1")
+ +- Cell 1:7 1:12 (XmlElem para)
+ | |
+ | `- Cell 1:7 1:12 (XmlText "text1")
|
- +- Cell 2:5 2:12 (XmlElem artwork)
+ +- Cell 2:5 2:12 (XmlElem quote)
| |
- | +- Cell 2:5 2:5 (XmlAttr type "quote")
+ | +- Cell 2:5 2:5 (XmlAttr type "")
| |
- | `- Cell 2:7 2:12 (XmlText "text2")
+ | `- Cell 2:7 2:12 (XmlElem para)
+ | |
+ | `- Cell 2:7 2:12 (XmlText "text2")
|
- `- Cell 3:7 3:12 (XmlText "text3")
+ `- Cell 3:7 3:12 (XmlElem para)
+ |
+ `- Cell 3:7 3:12 (XmlText "text3")
--- /dev/null
+<!DOCTYPE HTML>
+<html lang="en"><head><meta http-equiv="Content-Type" content="text/html; charset=UTF-8"><meta name="generator" content="https://hackage.haskell.org/package/hdoc"><link rel="stylesheet" type="text/css" href="style/dtc-html5.css"></head><body><div class="quote quote-" id="quote1"><p class="para" id="quote1.para1">text1</p></div><div class="quote quote-" id="quote2"><p class="para" id="quote2.para1">text2
+text3</p></div></body></html>
\ No newline at end of file
--- /dev/null
+<?xml-model type="application/relax-ng-compact-syntax" href="./schema/dtc.rnc"?>
+<?xml-stylesheet type="text/xsl" href="./xsl/document.html5.en.xsl"?>
+<?html5-stylesheet type="text/xsl" href="./xsl/document.html5.en.xsl"?>
+<?atom-stylesheet type="text/xsl" href="./xsl/document.atom.en.xsl"?>
+<document>
+ <about>
+ </about>
+ <quote type="">
+ <para>text1</para>
+ </quote>
+ <quote type="">
+ <para>text2
+ text3</para>
+ </quote>
+</document>
\ No newline at end of file
-Cell 1:1 1:8 (XmlElem artwork)
+Cell 1:1 1:8 (XmlElem quote)
|
-+- Cell 1:1 1:1 (XmlAttr type "quote")
++- Cell 1:1 1:1 (XmlAttr type "")
|
-`- Cell 1:3 1:8 (XmlText "text1")
+`- Cell 1:3 1:8 (XmlElem para)
+ |
+ `- Cell 1:3 1:8 (XmlText "text1")
-Cell 3:1 4:8 (XmlElem artwork)
+Cell 3:1 4:8 (XmlElem quote)
|
-+- Cell 3:1 3:1 (XmlAttr type "quote")
++- Cell 3:1 3:1 (XmlAttr type "")
|
-`- Cell 3:3 4:8 (XmlText "text2\ntext3")
+`- Cell 3:3 4:8 (XmlElem para)
+ |
+ `- Cell 3:3 4:8 (XmlText "text2\ntext3")
--- /dev/null
+<!DOCTYPE HTML>
+<html lang="en"><head><meta http-equiv="Content-Type" content="text/html; charset=UTF-8"><meta name="generator" content="https://hackage.haskell.org/package/hdoc"><link rel="stylesheet" type="text/css" href="style/dtc-html5.css"></head><body><div class="quote quote-" id="quote1"><p class="para" id="quote1.para1">text1
+text2</p></div><div class="quote quote-" id="quote2"><p class="para" id="quote2.para1">text3</p></div></body></html>
\ No newline at end of file
--- /dev/null
+<?xml-model type="application/relax-ng-compact-syntax" href="./schema/dtc.rnc"?>
+<?xml-stylesheet type="text/xsl" href="./xsl/document.html5.en.xsl"?>
+<?html5-stylesheet type="text/xsl" href="./xsl/document.html5.en.xsl"?>
+<?atom-stylesheet type="text/xsl" href="./xsl/document.atom.en.xsl"?>
+<document>
+ <about>
+ </about>
+ <quote type="">
+ <para>text1
+ text2</para>
+ </quote>
+ <quote type="">
+ <para>text3</para>
+ </quote>
+</document>
\ No newline at end of file
-Cell 1:1 2:8 (XmlElem artwork)
+Cell 1:1 2:8 (XmlElem quote)
|
-+- Cell 1:1 1:1 (XmlAttr type "quote")
++- Cell 1:1 1:1 (XmlAttr type "")
|
-`- Cell 1:3 2:8 (XmlText "text1\ntext2")
+`- Cell 1:3 2:8 (XmlElem para)
+ |
+ `- Cell 1:3 2:8 (XmlText "text1\ntext2")
-Cell 4:1 4:8 (XmlElem artwork)
+Cell 4:1 4:8 (XmlElem quote)
|
-+- Cell 4:1 4:1 (XmlAttr type "quote")
++- Cell 4:1 4:1 (XmlAttr type "")
|
-`- Cell 4:3 4:8 (XmlText "text3")
+`- Cell 4:3 4:8 (XmlElem para)
+ |
+ `- Cell 4:3 4:8 (XmlText "text3")
--- /dev/null
+3:1:
+unexpected <quote> at 3:1-3:8
+expecting <b>, <br>, <code>, <del>, <eref>, <i>, <iref>, <note>, <q>, <ref>, <rref>, <sc>, <sub>, <sup>, <u>, none, or text
--- /dev/null
+3:1:
+unexpected <quote> at 3:1-3:8
+expecting <b>, <br>, <code>, <del>, <eref>, <i>, <iref>, <note>, <q>, <ref>, <rref>, <sc>, <sub>, <sup>, <u>, none, or text
-Cell 1:1 1:8 (XmlElem artwork)
+Cell 1:1 1:8 (XmlElem quote)
|
-+- Cell 1:1 1:1 (XmlAttr type "quote")
++- Cell 1:1 1:1 (XmlAttr type "")
|
-`- Cell 1:3 1:8 (XmlText "text1")
+`- Cell 1:3 1:8 (XmlElem para)
+ |
+ `- Cell 1:3 1:8 (XmlText "text1")
Cell 2:1 3:8 (XmlElem para)
|
+- Cell 2:1 2:6 (XmlText "text2")
|
-`- Cell 3:1 3:8 (XmlElem artwork)
+`- Cell 3:1 3:8 (XmlElem quote)
|
- +- Cell 3:1 3:1 (XmlAttr type "quote")
+ +- Cell 3:1 3:1 (XmlAttr type "")
|
- `- Cell 3:3 3:8 (XmlText "text3")
+ `- Cell 3:3 3:8 (XmlElem para)
+ |
+ `- Cell 3:3 3:8 (XmlText "text3")
--- /dev/null
+2:1:
+unexpected <quote> at 2:1-2:8
+expecting <b>, <br>, <code>, <del>, <eref>, <i>, <iref>, <note>, <q>, <ref>, <rref>, <sc>, <sub>, <sup>, <u>, none, or text
--- /dev/null
+2:1:
+unexpected <quote> at 2:1-2:8
+expecting <b>, <br>, <code>, <del>, <eref>, <i>, <iref>, <note>, <q>, <ref>, <rref>, <sc>, <sub>, <sup>, <u>, none, or text
|
+- Cell 1:1 1:6 (XmlText "text1")
|
-+- Cell 2:1 2:8 (XmlElem artwork)
++- Cell 2:1 2:8 (XmlElem quote)
| |
-| +- Cell 2:1 2:1 (XmlAttr type "quote")
+| +- Cell 2:1 2:1 (XmlAttr type "")
| |
-| `- Cell 2:3 2:8 (XmlText "text2")
+| `- Cell 2:3 2:8 (XmlElem para)
+| |
+| `- Cell 2:3 2:8 (XmlText "text2")
|
`- Cell 3:1 3:6 (XmlText "text3")
--- /dev/null
+<!DOCTYPE HTML>
+<html lang="en"><head><meta http-equiv="Content-Type" content="text/html; charset=UTF-8"><meta name="generator" content="https://hackage.haskell.org/package/hdoc"><link rel="stylesheet" type="text/css" href="style/dtc-html5.css"></head><body><div class="quote quote-great1" id="quote1"><p class="para" id="quote1.para1">text1
+text2</p></div></body></html>
\ No newline at end of file
--- /dev/null
+<?xml-model type="application/relax-ng-compact-syntax" href="./schema/dtc.rnc"?>
+<?xml-stylesheet type="text/xsl" href="./xsl/document.html5.en.xsl"?>
+<?html5-stylesheet type="text/xsl" href="./xsl/document.html5.en.xsl"?>
+<?atom-stylesheet type="text/xsl" href="./xsl/document.atom.en.xsl"?>
+<document>
+ <about>
+ </about>
+ <quote type="great1">
+ <para>text1
+ text2</para>
+ </quote>
+</document>
\ No newline at end of file
-Cell 1:1 2:14 (XmlElem artwork)
+Cell 1:1 2:14 (XmlElem quote)
|
+- Cell 1:1 1:1 (XmlAttr type "great1")
|
-`- Cell 1:9 2:14 (XmlText "text1\ntext2")
+`- Cell 1:9 2:14 (XmlElem para)
+ |
+ `- Cell 1:9 2:14 (XmlText "text1\ntext2")
--- /dev/null
+<!DOCTYPE HTML>
+<html lang="en"><head><meta http-equiv="Content-Type" content="text/html; charset=UTF-8"><meta name="generator" content="https://hackage.haskell.org/package/hdoc"><link rel="stylesheet" type="text/css" href="style/dtc-html5.css"></head><body><div class="quote quote-great1" id="quote1"><p class="para" id="quote1.para1">text1</p></div><div class="quote quote-great2" id="quote2"><p class="para" id="quote2.para1">text2</p></div></body></html>
\ No newline at end of file
--- /dev/null
+<?xml-model type="application/relax-ng-compact-syntax" href="./schema/dtc.rnc"?>
+<?xml-stylesheet type="text/xsl" href="./xsl/document.html5.en.xsl"?>
+<?html5-stylesheet type="text/xsl" href="./xsl/document.html5.en.xsl"?>
+<?atom-stylesheet type="text/xsl" href="./xsl/document.atom.en.xsl"?>
+<document>
+ <about>
+ </about>
+ <quote type="great1">
+ <para>text1</para>
+ </quote>
+ <quote type="great2">
+ <para>text2</para>
+ </quote>
+</document>
\ No newline at end of file
-Cell 1:1 1:14 (XmlElem artwork)
+Cell 1:1 1:14 (XmlElem quote)
|
+- Cell 1:1 1:1 (XmlAttr type "great1")
|
-`- Cell 1:9 1:14 (XmlText "text1")
+`- Cell 1:9 1:14 (XmlElem para)
+ |
+ `- Cell 1:9 1:14 (XmlText "text1")
-Cell 2:1 2:14 (XmlElem artwork)
+Cell 2:1 2:14 (XmlElem quote)
|
+- Cell 2:1 2:1 (XmlAttr type "great2")
|
-`- Cell 2:9 2:14 (XmlText "text2")
+`- Cell 2:9 2:14 (XmlElem para)
+ |
+ `- Cell 2:9 2:14 (XmlText "text2")
--- /dev/null
+<!DOCTYPE HTML>
+<html lang="en"><head><meta http-equiv="Content-Type" content="text/html; charset=UTF-8"><meta name="generator" content="https://hackage.haskell.org/package/hdoc"><link rel="stylesheet" type="text/css" href="style/dtc-html5.css"></head><body><div class="quote quote-great1" id="quote1"><div class="quote quote-great2" id="quote1.1"><p class="para" id="quote1.1.para1">text1</p></div></div><div class="quote quote-great2" id="quote2"><div class="quote quote-great1" id="quote2.1"><p class="para" id="quote2.1.para1">text2</p></div></div></body></html>
\ No newline at end of file
--- /dev/null
+<?xml-model type="application/relax-ng-compact-syntax" href="./schema/dtc.rnc"?>
+<?xml-stylesheet type="text/xsl" href="./xsl/document.html5.en.xsl"?>
+<?html5-stylesheet type="text/xsl" href="./xsl/document.html5.en.xsl"?>
+<?atom-stylesheet type="text/xsl" href="./xsl/document.atom.en.xsl"?>
+<document>
+ <about>
+ </about>
+ <quote type="great1">
+ <quote type="great2"><para>text1</para></quote>
+ </quote>
+ <quote type="great2">
+ <quote type="great1"><para>text2</para></quote>
+ </quote>
+</document>
\ No newline at end of file
-Cell 1:1 1:22 (XmlElem artwork)
+Cell 1:1 1:22 (XmlElem quote)
|
+- Cell 1:1 1:1 (XmlAttr type "great1")
|
-`- Cell 1:9 1:22 (XmlElem artwork)
+`- Cell 1:9 1:22 (XmlElem quote)
|
+- Cell 1:9 1:9 (XmlAttr type "great2")
|
- `- Cell 1:17 1:22 (XmlText "text1")
+ `- Cell 1:17 1:22 (XmlElem para)
+ |
+ `- Cell 1:17 1:22 (XmlText "text1")
-Cell 2:1 2:22 (XmlElem artwork)
+Cell 2:1 2:22 (XmlElem quote)
|
+- Cell 2:1 2:1 (XmlAttr type "great2")
|
-`- Cell 2:9 2:22 (XmlElem artwork)
+`- Cell 2:9 2:22 (XmlElem quote)
|
+- Cell 2:9 2:9 (XmlAttr type "great1")
|
- `- Cell 2:17 2:22 (XmlText "text2")
+ `- Cell 2:17 2:22 (XmlElem para)
+ |
+ `- Cell 2:17 2:22 (XmlText "text2")
--- /dev/null
+2:7:
+unexpected end of input
+expecting <title> or class=
--- /dev/null
+2:7:
+unexpected end of input
+expecting <title> or class=
--- /dev/null
+2:8:
+unexpected end of input
+expecting <title> or class=
--- /dev/null
+2:8:
+unexpected end of input
+expecting <title> or class=
--- /dev/null
+<!DOCTYPE HTML>
+<html lang="en"><head><meta http-equiv="Content-Type" content="text/html; charset=UTF-8"><title>sec1</title><meta name="generator" content="https://hackage.haskell.org/package/hdoc"><link rel="stylesheet" type="text/css" href="style/dtc-html5.css"></head><body></body></html>
\ No newline at end of file
--- /dev/null
+<?xml-model type="application/relax-ng-compact-syntax" href="./schema/dtc.rnc"?>
+<?xml-stylesheet type="text/xsl" href="./xsl/document.html5.en.xsl"?>
+<?html5-stylesheet type="text/xsl" href="./xsl/document.html5.en.xsl"?>
+<?atom-stylesheet type="text/xsl" href="./xsl/document.atom.en.xsl"?>
+<document>
+ <about>
+ <title>sec1</title>
+ <title>sec11</title>
+ <title>sec12</title>
+ </about>
+</document>
\ No newline at end of file
--- /dev/null
+<!DOCTYPE HTML>
+<html lang="en"><head><meta http-equiv="Content-Type" content="text/html; charset=UTF-8"><title>sec1</title><meta name="generator" content="https://hackage.haskell.org/package/hdoc"><link rel="stylesheet" type="text/css" href="style/dtc-html5.css"></head><body></body></html>
\ No newline at end of file
--- /dev/null
+<?xml-model type="application/relax-ng-compact-syntax" href="./schema/dtc.rnc"?>
+<?xml-stylesheet type="text/xsl" href="./xsl/document.html5.en.xsl"?>
+<?html5-stylesheet type="text/xsl" href="./xsl/document.html5.en.xsl"?>
+<?atom-stylesheet type="text/xsl" href="./xsl/document.atom.en.xsl"?>
+<document>
+ <about>
+ <title>sec1</title>
+ <title>sec11</title>
+ <title>sec12</title>
+ </about>
+</document>
\ No newline at end of file
--- /dev/null
+<!DOCTYPE HTML>
+<html lang="en"><head><meta http-equiv="Content-Type" content="text/html; charset=UTF-8"><title>sec1</title><meta name="generator" content="https://hackage.haskell.org/package/hdoc"><link rel="stylesheet" type="text/css" href="style/dtc-html5.css"></head><body></body></html>
\ No newline at end of file
--- /dev/null
+<?xml-model type="application/relax-ng-compact-syntax" href="./schema/dtc.rnc"?>
+<?xml-stylesheet type="text/xsl" href="./xsl/document.html5.en.xsl"?>
+<?html5-stylesheet type="text/xsl" href="./xsl/document.html5.en.xsl"?>
+<?atom-stylesheet type="text/xsl" href="./xsl/document.atom.en.xsl"?>
+<document>
+ <about>
+ <title>sec1</title>
+ <title>sub11</title>
+ <title>sub12</title>
+ </about>
+</document>
\ No newline at end of file
--- /dev/null
+<!DOCTYPE HTML>
+<html lang="en"><head><meta http-equiv="Content-Type" content="text/html; charset=UTF-8"><title>sec1</title><meta name="generator" content="https://hackage.haskell.org/package/hdoc"><link rel="stylesheet" type="text/css" href="style/dtc-html5.css"></head><body></body></html>
\ No newline at end of file
--- /dev/null
+<?xml-model type="application/relax-ng-compact-syntax" href="./schema/dtc.rnc"?>
+<?xml-stylesheet type="text/xsl" href="./xsl/document.html5.en.xsl"?>
+<?html5-stylesheet type="text/xsl" href="./xsl/document.html5.en.xsl"?>
+<?atom-stylesheet type="text/xsl" href="./xsl/document.atom.en.xsl"?>
+<document>
+ <about>
+ <title>sec1</title>
+ <title>sub11</title>
+ <title>sub12</title>
+ </about>
+</document>
\ No newline at end of file
--- /dev/null
+2:11:
+unexpected end of input
+expecting <title> or class=
--- /dev/null
+2:11:
+unexpected end of input
+expecting <title> or class=
--- /dev/null
+2:7:
+unexpected end of input
+expecting <title> or class=
--- /dev/null
+2:7:
+unexpected end of input
+expecting <title> or class=
--- /dev/null
+2:8:
+unexpected end of input
+expecting <title> or class=
--- /dev/null
+2:8:
+unexpected end of input
+expecting <title> or class=
--- /dev/null
+3:1:
+unexpected <section> at 3:1-3:9
+expecting <title> or class=
--- /dev/null
+3:1:
+unexpected <section> at 3:1-3:9
+expecting <title> or class=
--- /dev/null
+3:1:
+unexpected <section> at 3:1-3:11
+expecting <title> or class=
--- /dev/null
+3:1:
+unexpected <section> at 3:1-3:11
+expecting <title> or class=
--- /dev/null
+2:7:
+unexpected end of input
+expecting <title> or class=
--- /dev/null
+2:7:
+unexpected end of input
+expecting <title> or class=
--- /dev/null
+<!DOCTYPE HTML>
+<html lang="en"><head><meta http-equiv="Content-Type" content="text/html; charset=UTF-8"><title>sec1</title><meta name="generator" content="https://hackage.haskell.org/package/hdoc"><link rel="stylesheet" type="text/css" href="style/dtc-html5.css"></head><body><p class="para" id="para1">text1</p></body></html>
\ No newline at end of file
--- /dev/null
+<?xml-model type="application/relax-ng-compact-syntax" href="./schema/dtc.rnc"?>
+<?xml-stylesheet type="text/xsl" href="./xsl/document.html5.en.xsl"?>
+<?html5-stylesheet type="text/xsl" href="./xsl/document.html5.en.xsl"?>
+<?atom-stylesheet type="text/xsl" href="./xsl/document.atom.en.xsl"?>
+<document>
+ <about>
+ <title>sec1</title>
+ </about>
+ <para>
+ text1
+ </para>
+</document>
\ No newline at end of file
--- /dev/null
+3:7:
+unexpected end of input
+expecting <title> or class=
--- /dev/null
+3:7:
+unexpected end of input
+expecting <title> or class=
--- /dev/null
+5:7:
+unexpected end of input
+expecting <title> or class=
--- /dev/null
+5:7:
+unexpected end of input
+expecting <title> or class=