Move metaValueToInlines
to T.P.W.Shared
This will allow the Powerpoint writer to use it as well.
This commit is contained in:
parent
1d9c2770e3
commit
6d74b35751
2 changed files with 10 additions and 11 deletions
|
@ -1,4 +1,3 @@
|
|||
|
||||
{-# LANGUAGE PatternGuards #-}
|
||||
{-# LANGUAGE RankNTypes #-}
|
||||
{-# LANGUAGE ScopedTypeVariables #-}
|
||||
|
@ -65,7 +64,7 @@ import Text.Pandoc.Readers.Docx.StyleMap
|
|||
import Text.Pandoc.Shared hiding (Element)
|
||||
import Text.Pandoc.Walk
|
||||
import Text.Pandoc.Writers.Math
|
||||
import Text.Pandoc.Writers.Shared (fixDisplayMath)
|
||||
import Text.Pandoc.Writers.Shared (fixDisplayMath, metaValueToInlines)
|
||||
import Text.Printf (printf)
|
||||
import Text.TeXMath
|
||||
import Text.XML.Light as XML
|
||||
|
@ -196,15 +195,6 @@ isValidChar (ord -> c)
|
|||
| 0x10000 <= c && c <= 0x10FFFF = True
|
||||
| otherwise = False
|
||||
|
||||
metaValueToInlines :: MetaValue -> [Inline]
|
||||
metaValueToInlines (MetaString s) = [Str s]
|
||||
metaValueToInlines (MetaInlines ils) = ils
|
||||
metaValueToInlines (MetaBlocks bs) = query return bs
|
||||
metaValueToInlines (MetaBool b) = [Str $ show b]
|
||||
metaValueToInlines _ = []
|
||||
|
||||
|
||||
|
||||
writeDocx :: (PandocMonad m)
|
||||
=> WriterOptions -- ^ Writer options
|
||||
-> Pandoc -- ^ Document to convert
|
||||
|
|
|
@ -40,6 +40,7 @@ module Text.Pandoc.Writers.Shared (
|
|||
, fixDisplayMath
|
||||
, unsmartify
|
||||
, gridTable
|
||||
, metaValueToInlines
|
||||
)
|
||||
where
|
||||
import Control.Monad (zipWithM)
|
||||
|
@ -55,6 +56,7 @@ import qualified Text.Pandoc.Builder as Builder
|
|||
import Text.Pandoc.Definition
|
||||
import Text.Pandoc.Options
|
||||
import Text.Pandoc.Pretty
|
||||
import Text.Pandoc.Walk (query)
|
||||
import Text.Pandoc.UTF8 (toStringLazy)
|
||||
import Text.Pandoc.XML (escapeStringForXML)
|
||||
|
||||
|
@ -308,3 +310,10 @@ gridTable opts blocksToDoc headless aligns widths headers rows = do
|
|||
head'' $$
|
||||
body $$
|
||||
border '-' (repeat AlignDefault) widthsInChars
|
||||
|
||||
metaValueToInlines :: MetaValue -> [Inline]
|
||||
metaValueToInlines (MetaString s) = [Str s]
|
||||
metaValueToInlines (MetaInlines ils) = ils
|
||||
metaValueToInlines (MetaBlocks bs) = query return bs
|
||||
metaValueToInlines (MetaBool b) = [Str $ show b]
|
||||
metaValueToInlines _ = []
|
||||
|
|
Loading…
Add table
Reference in a new issue