Moved fixDisplayMath from Docx writer to Writer.Shared.
This commit is contained in:
parent
bb0f942463
commit
e3d48da627
2 changed files with 29 additions and 25 deletions
|
@ -30,7 +30,7 @@ Conversion of 'Pandoc' documents to docx.
|
|||
-}
|
||||
module Text.Pandoc.Writers.Docx ( writeDocx ) where
|
||||
import Data.Maybe (fromMaybe)
|
||||
import Data.List ( intercalate, groupBy, isPrefixOf )
|
||||
import Data.List ( intercalate, isPrefixOf )
|
||||
import qualified Data.ByteString as B
|
||||
import qualified Data.ByteString.Lazy as BL
|
||||
import qualified Data.ByteString.Lazy.Char8 as BL8
|
||||
|
@ -43,6 +43,7 @@ import Text.Pandoc.Definition
|
|||
import Text.Pandoc.Generic
|
||||
import Text.Pandoc.ImageSize
|
||||
import Text.Pandoc.Shared hiding (Element)
|
||||
import Text.Pandoc.Writers.Shared (fixDisplayMath)
|
||||
import Text.Pandoc.Options
|
||||
import Text.Pandoc.Readers.TeXMath
|
||||
import Text.Pandoc.Highlighting ( highlight )
|
||||
|
@ -817,27 +818,3 @@ parseXml refArchive relpath =
|
|||
case (findEntryByPath relpath refArchive >>= parseXMLDoc . UTF8.toStringLazy . fromEntry) of
|
||||
Just d -> return d
|
||||
Nothing -> fail $ relpath ++ " missing in reference docx"
|
||||
|
||||
isDisplayMath :: Inline -> Bool
|
||||
isDisplayMath (Math DisplayMath _) = True
|
||||
isDisplayMath _ = False
|
||||
|
||||
stripLeadingTrailingSpace :: [Inline] -> [Inline]
|
||||
stripLeadingTrailingSpace = go . reverse . go . reverse
|
||||
where go (Space:xs) = xs
|
||||
go xs = xs
|
||||
|
||||
fixDisplayMath :: Block -> Block
|
||||
fixDisplayMath (Plain lst)
|
||||
| any isDisplayMath lst && not (all isDisplayMath lst) =
|
||||
-- chop into several paragraphs so each displaymath is its own
|
||||
Div ("",["math"],[]) $ map (Plain . stripLeadingTrailingSpace) $
|
||||
groupBy (\x y -> (isDisplayMath x && isDisplayMath y) ||
|
||||
not (isDisplayMath x || isDisplayMath y)) lst
|
||||
fixDisplayMath (Para lst)
|
||||
| any isDisplayMath lst && not (all isDisplayMath lst) =
|
||||
-- chop into several paragraphs so each displaymath is its own
|
||||
Div ("",["math"],[]) $ map (Para . stripLeadingTrailingSpace) $
|
||||
groupBy (\x y -> (isDisplayMath x && isDisplayMath y) ||
|
||||
not (isDisplayMath x || isDisplayMath y)) lst
|
||||
fixDisplayMath x = x
|
||||
|
|
|
@ -34,6 +34,7 @@ module Text.Pandoc.Writers.Shared (
|
|||
, setField
|
||||
, defField
|
||||
, tagWithAttrs
|
||||
, fixDisplayMath
|
||||
)
|
||||
where
|
||||
import Text.Pandoc.Definition
|
||||
|
@ -46,6 +47,7 @@ import qualified Data.Map as M
|
|||
import qualified Data.Text as T
|
||||
import Data.Aeson (FromJSON(..), fromJSON, ToJSON (..), Value(Object), Result(..))
|
||||
import qualified Data.Traversable as Traversable
|
||||
import Data.List ( groupBy )
|
||||
|
||||
-- | Create JSON value for template from a 'Meta' and an association list
|
||||
-- of variables, specified at the command line or in the writer.
|
||||
|
@ -136,3 +138,28 @@ tagWithAttrs tag (ident,classes,kvs) = hsep
|
|||
,hsep (map (\(k,v) -> text k <> "=" <>
|
||||
doubleQuotes (text (escapeStringForXML v))) kvs)
|
||||
] <> ">"
|
||||
|
||||
isDisplayMath :: Inline -> Bool
|
||||
isDisplayMath (Math DisplayMath _) = True
|
||||
isDisplayMath _ = False
|
||||
|
||||
stripLeadingTrailingSpace :: [Inline] -> [Inline]
|
||||
stripLeadingTrailingSpace = go . reverse . go . reverse
|
||||
where go (Space:xs) = xs
|
||||
go xs = xs
|
||||
|
||||
-- Put display math in its own block (for ODT/DOCX).
|
||||
fixDisplayMath :: Block -> Block
|
||||
fixDisplayMath (Plain lst)
|
||||
| any isDisplayMath lst && not (all isDisplayMath lst) =
|
||||
-- chop into several paragraphs so each displaymath is its own
|
||||
Div ("",["math"],[]) $ map (Plain . stripLeadingTrailingSpace) $
|
||||
groupBy (\x y -> (isDisplayMath x && isDisplayMath y) ||
|
||||
not (isDisplayMath x || isDisplayMath y)) lst
|
||||
fixDisplayMath (Para lst)
|
||||
| any isDisplayMath lst && not (all isDisplayMath lst) =
|
||||
-- chop into several paragraphs so each displaymath is its own
|
||||
Div ("",["math"],[]) $ map (Para . stripLeadingTrailingSpace) $
|
||||
groupBy (\x y -> (isDisplayMath x && isDisplayMath y) ||
|
||||
not (isDisplayMath x || isDisplayMath y)) lst
|
||||
fixDisplayMath x = x
|
||||
|
|
Loading…
Add table
Reference in a new issue