aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers/Haddock.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Readers/Haddock.hs')
-rw-r--r--src/Text/Pandoc/Readers/Haddock.hs22
1 files changed, 20 insertions, 2 deletions
diff --git a/src/Text/Pandoc/Readers/Haddock.hs b/src/Text/Pandoc/Readers/Haddock.hs
index e98c79ed8..967037e4e 100644
--- a/src/Text/Pandoc/Readers/Haddock.hs
+++ b/src/Text/Pandoc/Readers/Haddock.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE CPP #-}
{- |
Module : Text.Pandoc.Readers.Haddock
@@ -14,13 +15,13 @@ module Text.Pandoc.Readers.Haddock
( readHaddock
) where
+import Prelude
import Control.Monad.Except (throwError)
import Data.List (intersperse, stripPrefix)
import Data.Maybe (fromMaybe)
-import Data.Monoid ((<>))
import Data.Text (Text, unpack)
import Documentation.Haddock.Parser
-import Documentation.Haddock.Types
+import Documentation.Haddock.Types as H
import Text.Pandoc.Builder (Blocks, Inlines)
import qualified Text.Pandoc.Builder as B
import Text.Pandoc.Class (PandocMonad)
@@ -86,6 +87,20 @@ docHToBlocks d' =
DocProperty s -> B.codeBlockWith ("",["property","haskell"],[]) (trim s)
DocExamples es -> mconcat $ map (\e ->
makeExample ">>>" (exampleExpression e) (exampleResult e)) es
+#if MIN_VERSION_haddock_library(1,5,0)
+ DocTable H.Table{ tableHeaderRows = headerRows
+ , tableBodyRows = bodyRows
+ }
+ -> let toCells = map (docHToBlocks . tableCellContents) . tableRowCells
+ (header, body) =
+ if null headerRows
+ then ([], map toCells bodyRows)
+ else (toCells (head headerRows),
+ map toCells (tail headerRows ++ bodyRows))
+ colspecs = replicate (maximum (map length body))
+ (AlignDefault, 0.0)
+ in B.table mempty colspecs header body
+#endif
where inlineFallback = B.plain $ docHToInlines False d'
consolidatePlains = B.fromList . consolidatePlains' . B.toList
@@ -134,6 +149,9 @@ docHToInlines isCode d' =
DocAName s -> B.spanWith (s,["anchor"],[]) mempty
DocProperty _ -> mempty
DocExamples _ -> mempty
+#if MIN_VERSION_haddock_library(1,5,0)
+ DocTable _ -> mempty
+#endif
-- | Create an 'Example', stripping superfluous characters as appropriate
makeExample :: String -> String -> [String] -> Blocks