aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers
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 /src/Text/Pandoc/Readers
parentbb2530caa414234f00e7c89ef18a538708b2297c (diff)
downloadpandoc-105a50569be6d2c1b37cc290abcbfbae1cd0fd1e.tar.gz
Allow compilation with base 4.15
Diffstat (limited to 'src/Text/Pandoc/Readers')
-rw-r--r--src/Text/Pandoc/Readers/Docx/Combine.hs6
-rw-r--r--src/Text/Pandoc/Readers/Odt/ContentReader.hs11
2 files changed, 8 insertions, 9 deletions
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)