aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorAlbert Krewinkel <albert@zeitkraut.de>2021-05-25 17:49:48 +0200
committerJohn MacFarlane <jgm@berkeley.edu>2021-05-25 11:52:49 -0700
commit105a50569be6d2c1b37cc290abcbfbae1cd0fd1e (patch)
tree1f34ec197a2f9936bf546e88918edd64f19ed33f
parentbb2530caa414234f00e7c89ef18a538708b2297c (diff)
downloadpandoc-105a50569be6d2c1b37cc290abcbfbae1cd0fd1e.tar.gz
Allow compilation with base 4.15
-rw-r--r--src/Text/Pandoc/Options.hs34
-rw-r--r--src/Text/Pandoc/Readers/Docx/Combine.hs6
-rw-r--r--src/Text/Pandoc/Readers/Odt/ContentReader.hs11
-rw-r--r--src/Text/Pandoc/Writers/OpenDocument.hs98
4 files changed, 72 insertions, 77 deletions
diff --git a/src/Text/Pandoc/Options.hs b/src/Text/Pandoc/Options.hs
index 92bda36b2..85d9aa103 100644
--- a/src/Text/Pandoc/Options.hs
+++ b/src/Text/Pandoc/Options.hs
@@ -316,6 +316,23 @@ defaultKaTeXURL :: Text
defaultKaTeXURL = "https://cdnjs.cloudflare.com/ajax/libs/KaTeX/0.11.1/"
-- Update documentation in doc/filters.md if this is changed.
+$(deriveJSON defaultOptions{ constructorTagModifier =
+ camelCaseStrToHyphenated
+ } ''TrackChanges)
+
+$(deriveJSON defaultOptions{ constructorTagModifier =
+ camelCaseStrToHyphenated
+ } ''WrapOption)
+
+$(deriveJSON defaultOptions{ constructorTagModifier =
+ camelCaseStrToHyphenated . drop 8
+ } ''TopLevelDivision)
+
+$(deriveJSON defaultOptions{ constructorTagModifier =
+ camelCaseStrToHyphenated
+ } ''ReferenceLocation)
+
+-- Update documentation in doc/filters.md if this is changed.
$(deriveJSON defaultOptions ''ReaderOptions)
$(deriveJSON defaultOptions{
@@ -338,20 +355,3 @@ $(deriveJSON defaultOptions{ constructorTagModifier =
} ''ObfuscationMethod)
$(deriveJSON defaultOptions ''HTMLSlideVariant)
-
--- Update documentation in doc/filters.md if this is changed.
-$(deriveJSON defaultOptions{ constructorTagModifier =
- camelCaseStrToHyphenated
- } ''TrackChanges)
-
-$(deriveJSON defaultOptions{ constructorTagModifier =
- camelCaseStrToHyphenated
- } ''WrapOption)
-
-$(deriveJSON defaultOptions{ constructorTagModifier =
- camelCaseStrToHyphenated . drop 8
- } ''TopLevelDivision)
-
-$(deriveJSON defaultOptions{ constructorTagModifier =
- camelCaseStrToHyphenated
- } ''ReferenceLocation)
diff --git a/src/Text/Pandoc/Readers/Docx/Combine.hs b/src/Text/Pandoc/Readers/Docx/Combine.hs
index 7c6d01769..6e4faa639 100644
--- a/src/Text/Pandoc/Readers/Docx/Combine.hs
+++ b/src/Text/Pandoc/Readers/Docx/Combine.hs
@@ -61,7 +61,7 @@ import Data.List
import Data.Bifunctor
import Data.Sequence ( ViewL (..), ViewR (..), viewl, viewr, spanr, spanl
, (><), (|>) )
-import Text.Pandoc.Builder
+import Text.Pandoc.Builder as B
data Modifier a = Modifier (a -> a)
| AttrModifier (Attr -> a -> a) Attr
@@ -116,12 +116,12 @@ ilModifierAndInnards ils = case viewl $ unMany ils of
inlinesL :: Inlines -> (Inlines, Inlines)
inlinesL ils = case viewl $ unMany ils of
- (s :< sq) -> (singleton s, Many sq)
+ (s :< sq) -> (B.singleton s, Many sq)
_ -> (mempty, ils)
inlinesR :: Inlines -> (Inlines, Inlines)
inlinesR ils = case viewr $ unMany ils of
- (sq :> s) -> (Many sq, singleton s)
+ (sq :> s) -> (Many sq, B.singleton s)
_ -> (ils, mempty)
combineInlines :: Inlines -> Inlines -> Inlines
diff --git a/src/Text/Pandoc/Readers/Odt/ContentReader.hs b/src/Text/Pandoc/Readers/Odt/ContentReader.hs
index c4220b0db..5520d039f 100644
--- a/src/Text/Pandoc/Readers/Odt/ContentReader.hs
+++ b/src/Text/Pandoc/Readers/Odt/ContentReader.hs
@@ -1,4 +1,5 @@
{-# LANGUAGE Arrows #-}
+{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveFoldable #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE PatternGuards #-}
@@ -33,7 +34,7 @@ import Data.List (find)
import qualified Data.Map as M
import qualified Data.Text as T
import Data.Maybe
-import Data.Semigroup (First(..), Option(..))
+import Data.Monoid (Alt (..))
import Text.TeXMath (readMathML, writeTeX)
import qualified Text.Pandoc.XML.Light as XML
@@ -505,13 +506,11 @@ type InlineMatcher = ElementMatcher Inlines
type BlockMatcher = ElementMatcher Blocks
-
-newtype FirstMatch a = FirstMatch (Option (First a))
- deriving (Foldable, Monoid, Semigroup)
+newtype FirstMatch a = FirstMatch (Alt Maybe a)
+ deriving (Foldable, Monoid, Semigroup)
firstMatch :: a -> FirstMatch a
-firstMatch = FirstMatch . Option . Just . First
-
+firstMatch = FirstMatch . Alt . Just
--
matchingElement :: (Monoid e)
diff --git a/src/Text/Pandoc/Writers/OpenDocument.hs b/src/Text/Pandoc/Writers/OpenDocument.hs
index 34a3a4aa5..5f3224c2f 100644
--- a/src/Text/Pandoc/Writers/OpenDocument.hs
+++ b/src/Text/Pandoc/Writers/OpenDocument.hs
@@ -1,4 +1,5 @@
{-# LANGUAGE FlexibleContexts #-}
+{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE ViewPatterns #-}
@@ -372,36 +373,32 @@ blocksToOpenDocument o b = vcat <$> mapM (blockToOpenDocument o) b
-- | Convert a Pandoc block element to OpenDocument.
blockToOpenDocument :: PandocMonad m => WriterOptions -> Block -> OD m (Doc Text)
-blockToOpenDocument o bs
- | Plain b <- bs = if null b
- then return empty
- else inParagraphTags =<< inlinesToOpenDocument o b
- | Para [Image attr c (s,T.stripPrefix "fig:" -> Just t)] <- bs
- = figure attr c s t
- | Para b <- bs = if null b &&
- not (isEnabled Ext_empty_paragraphs o)
- then return empty
- else inParagraphTags =<< inlinesToOpenDocument o b
- | LineBlock b <- bs = blockToOpenDocument o $ linesToPara b
- | Div attr xs <- bs = mkDiv attr xs
- | Header i (ident,_,_) b
- <- bs = setFirstPara >> (inHeaderTags i ident
- =<< inlinesToOpenDocument o b)
- | BlockQuote b <- bs = setFirstPara >> mkBlockQuote b
- | DefinitionList b <- bs = setFirstPara >> defList b
- | BulletList b <- bs = setFirstPara >> bulletListToOpenDocument o b
- | OrderedList a b <- bs = setFirstPara >> orderedList a b
- | CodeBlock _ s <- bs = setFirstPara >> preformatted s
- | Table a bc s th tb tf <- bs = setFirstPara >> table (Ann.toTable a bc s th tb tf)
- | HorizontalRule <- bs = setFirstPara >> return (selfClosingTag "text:p"
- [ ("text:style-name", "Horizontal_20_Line") ])
- | RawBlock f s <- bs = if f == Format "opendocument"
- then return $ text $ T.unpack s
- else do
- report $ BlockNotRendered bs
- return empty
- | Null <- bs = return empty
- | otherwise = return empty
+blockToOpenDocument o = \case
+ Plain b -> if null b
+ then return empty
+ else inParagraphTags =<< inlinesToOpenDocument o b
+ Para [Image attr c (s,T.stripPrefix "fig:" -> Just t)] -> figure attr c s t
+ Para b -> if null b &&
+ not (isEnabled Ext_empty_paragraphs o)
+ then return empty
+ else inParagraphTags =<< inlinesToOpenDocument o b
+ LineBlock b -> blockToOpenDocument o $ linesToPara b
+ Div attr xs -> mkDiv attr xs
+ Header i (ident,_,_) b -> do
+ setFirstPara
+ inHeaderTags i ident =<< inlinesToOpenDocument o b
+ BlockQuote b -> setFirstPara >> mkBlockQuote b
+ DefinitionList b -> setFirstPara >> defList b
+ BulletList b -> setFirstPara >> bulletListToOpenDocument o b
+ OrderedList a b -> setFirstPara >> orderedList a b
+ CodeBlock _ s -> setFirstPara >> preformatted s
+ Table a bc s th tb tf -> setFirstPara >> table (Ann.toTable a bc s th tb tf)
+ HorizontalRule -> setFirstPara >> return (selfClosingTag "text:p"
+ [ ("text:style-name", "Horizontal_20_Line") ])
+ b@(RawBlock f s) -> if f == Format "opendocument"
+ then return $ text $ T.unpack s
+ else empty <$ report (BlockNotRendered b)
+ Null -> return empty
where
defList b = do setInDefinitionList True
r <- vcat <$> mapM (deflistItemToOpenDocument o) b
@@ -874,27 +871,26 @@ data TextStyle = Italic
textStyleAttr :: Map.Map Text Text
-> TextStyle
-> Map.Map Text Text
-textStyleAttr m s
- | Italic <- s = Map.insert "fo:font-style" "italic" .
- Map.insert "style:font-style-asian" "italic" .
- Map.insert "style:font-style-complex" "italic" $ m
- | Bold <- s = Map.insert "fo:font-weight" "bold" .
- Map.insert "style:font-weight-asian" "bold" .
- Map.insert "style:font-weight-complex" "bold" $ m
- | Under <- s = Map.insert "style:text-underline-style" "solid" .
- Map.insert "style:text-underline-width" "auto" .
- Map.insert "style:text-underline-color" "font-color" $ m
- | Strike <- s = Map.insert "style:text-line-through-style" "solid" m
- | Sub <- s = Map.insert "style:text-position" "sub 58%" m
- | Sup <- s = Map.insert "style:text-position" "super 58%" m
- | SmallC <- s = Map.insert "fo:font-variant" "small-caps" m
- | Pre <- s = Map.insert "style:font-name" "Courier New" .
- Map.insert "style:font-name-asian" "Courier New" .
- Map.insert "style:font-name-complex" "Courier New" $ m
- | Language lang <- s
- = Map.insert "fo:language" (langLanguage lang) .
- maybe id (Map.insert "fo:country") (langRegion lang) $ m
- | otherwise = m
+textStyleAttr m = \case
+ Italic -> Map.insert "fo:font-style" "italic" .
+ Map.insert "style:font-style-asian" "italic" .
+ Map.insert "style:font-style-complex" "italic" $ m
+ Bold -> Map.insert "fo:font-weight" "bold" .
+ Map.insert "style:font-weight-asian" "bold" .
+ Map.insert "style:font-weight-complex" "bold" $ m
+ Under -> Map.insert "style:text-underline-style" "solid" .
+ Map.insert "style:text-underline-width" "auto" .
+ Map.insert "style:text-underline-color" "font-color" $ m
+ Strike -> Map.insert "style:text-line-through-style" "solid" m
+ Sub -> Map.insert "style:text-position" "sub 58%" m
+ Sup -> Map.insert "style:text-position" "super 58%" m
+ SmallC -> Map.insert "fo:font-variant" "small-caps" m
+ Pre -> Map.insert "style:font-name" "Courier New" .
+ Map.insert "style:font-name-asian" "Courier New" .
+ Map.insert "style:font-name-complex" "Courier New" $ m
+ Language lang ->
+ Map.insert "fo:language" (langLanguage lang) .
+ maybe id (Map.insert "fo:country") (langRegion lang) $ m
withLangFromAttr :: PandocMonad m => Attr -> OD m a -> OD m a
withLangFromAttr (_,_,kvs) action =