Added skeleton of basic docbook reader.
This commit is contained in:
parent
e37c4526b2
commit
d339b29967
4 changed files with 40 additions and 1 deletions
|
@ -246,6 +246,7 @@ Library
|
|||
Text.Pandoc.Readers.LaTeX,
|
||||
Text.Pandoc.Readers.Markdown,
|
||||
Text.Pandoc.Readers.RST,
|
||||
Text.Pandoc.Readers.DocBook,
|
||||
Text.Pandoc.Readers.TeXMath,
|
||||
Text.Pandoc.Readers.Textile,
|
||||
Text.Pandoc.Readers.Native,
|
||||
|
|
|
@ -119,6 +119,7 @@ import Text.Pandoc.Definition
|
|||
import Text.Pandoc.Generic
|
||||
import Text.Pandoc.Readers.Markdown
|
||||
import Text.Pandoc.Readers.RST
|
||||
import Text.Pandoc.Readers.DocBook
|
||||
import Text.Pandoc.Readers.LaTeX
|
||||
import Text.Pandoc.Readers.HTML
|
||||
import Text.Pandoc.Readers.Textile
|
||||
|
@ -162,6 +163,7 @@ readers = [("native" , \_ -> readNative)
|
|||
,("rst" , readRST)
|
||||
,("rst+lhs" , \st ->
|
||||
readRST st{ stateLiterateHaskell = True})
|
||||
,("docbook" , readDocBook)
|
||||
,("textile" , readTextile) -- TODO : textile+lhs
|
||||
,("html" , readHtml)
|
||||
,("latex" , readLaTeX)
|
||||
|
|
|
@ -1,4 +1,4 @@
|
|||
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
||||
{-# LANGUAGE GeneralizedNewtypeDeriving, DatatypeContexts #-}
|
||||
{-
|
||||
Copyright (C) 2010 John MacFarlane <jgm@berkeley.edu>
|
||||
|
||||
|
|
36
src/Text/Pandoc/Readers/DocBook.hs
Normal file
36
src/Text/Pandoc/Readers/DocBook.hs
Normal file
|
@ -0,0 +1,36 @@
|
|||
module Text.Pandoc.Readers.DocBook ( readDocBook ) where
|
||||
import Text.Pandoc.Parsing (ParserState(..), defaultParserState)
|
||||
import Text.Pandoc.Definition
|
||||
import Text.Pandoc.Builder
|
||||
import Text.XML.Light
|
||||
import Data.Monoid
|
||||
import Data.Char (isSpace)
|
||||
|
||||
readDocBook :: ParserState -> String -> Pandoc
|
||||
readDocBook st inp = Pandoc (Meta [] [] []) $ toList blocks
|
||||
where blocks = mconcat $ map (parseBlock st) $ parseXML inp
|
||||
|
||||
parseBlock :: ParserState -> Content -> Blocks
|
||||
parseBlock st (Text (CData _ s _)) = if all isSpace s
|
||||
then mempty
|
||||
else plain $ text s
|
||||
parseBlock st (Elem e) =
|
||||
case qName (elName e) of
|
||||
"para" -> para $ trimInlines $ mconcat
|
||||
$ map (parseInline st) $ elContent e
|
||||
_ -> mconcat $ map (parseBlock st) $ elContent e
|
||||
parseBlock st (CRef _) = mempty
|
||||
|
||||
parseInline :: ParserState -> Content -> Inlines
|
||||
parseInline st (Text (CData _ s _)) = text s
|
||||
parseInline st (Elem e) =
|
||||
case qName (elName e) of
|
||||
"emphasis" -> case lookupAttrBy (\attr -> qName attr == "role")
|
||||
(elAttribs e) of
|
||||
Just "strong" -> strong innerInlines
|
||||
_ -> emph innerInlines
|
||||
_ -> innerInlines
|
||||
where innerInlines = trimInlines . mconcat . map (parseInline st)
|
||||
$ elContent e
|
||||
parseInline st (CRef _) = mempty
|
||||
|
Loading…
Reference in a new issue