aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc
diff options
context:
space:
mode:
authorJohn MacFarlane <fiddlosopher@gmail.com>2012-04-14 16:44:21 -0700
committerJohn MacFarlane <fiddlosopher@gmail.com>2012-04-14 16:44:21 -0700
commitd339b29967878f64d5fe45d03d214476e9d88f7e (patch)
tree94f18785f2fbdc606e5d732d505dff6f5f8ba085 /src/Text/Pandoc
parente37c4526b2ae9d52a2f43d83c00f6f720637ce5c (diff)
downloadpandoc-d339b29967878f64d5fe45d03d214476e9d88f7e.tar.gz
Added skeleton of basic docbook reader.
Diffstat (limited to 'src/Text/Pandoc')
-rw-r--r--src/Text/Pandoc/Pretty.hs2
-rw-r--r--src/Text/Pandoc/Readers/DocBook.hs36
2 files changed, 37 insertions, 1 deletions
diff --git a/src/Text/Pandoc/Pretty.hs b/src/Text/Pandoc/Pretty.hs
index bf78b2594..3cabcb75b 100644
--- a/src/Text/Pandoc/Pretty.hs
+++ b/src/Text/Pandoc/Pretty.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE GeneralizedNewtypeDeriving #-}
+{-# LANGUAGE GeneralizedNewtypeDeriving, DatatypeContexts #-}
{-
Copyright (C) 2010 John MacFarlane <jgm@berkeley.edu>
diff --git a/src/Text/Pandoc/Readers/DocBook.hs b/src/Text/Pandoc/Readers/DocBook.hs
new file mode 100644
index 000000000..73a2e6abc
--- /dev/null
+++ b/src/Text/Pandoc/Readers/DocBook.hs
@@ -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
+