diff options
-rw-r--r-- | pandoc.cabal | 4 | ||||
-rw-r--r-- | src/Text/Pandoc/Parsing.hs | 16 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Markdown.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Odt/ContentReader.hs | 6 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Org/DocumentTree.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Org/Inlines.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Vimwiki.hs | 3 | ||||
-rw-r--r-- | stack.lts9.yaml | 1 | ||||
-rw-r--r-- | stack.yaml | 1 |
9 files changed, 26 insertions, 11 deletions
diff --git a/pandoc.cabal b/pandoc.cabal index 240de9a57..9265b01c7 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -370,7 +370,7 @@ library xml >= 1.3.12 && < 1.4, split >= 0.2 && < 0.3, random >= 1 && < 1.2, - pandoc-types >= 1.17.3 && < 1.18, + pandoc-types >= 1.17.4 && < 1.18, aeson >= 0.7 && < 1.4, aeson-pretty >= 0.8.5 && < 0.9, tagsoup >= 0.14.6 && < 0.15, @@ -605,7 +605,7 @@ test-suite test-pandoc hs-source-dirs: test build-depends: base >= 4.2 && < 5, pandoc, - pandoc-types >= 1.17.3 && < 1.18, + pandoc-types >= 1.17.4 && < 1.18, bytestring >= 0.9 && < 0.11, base64-bytestring >= 0.1 && < 1.1, text >= 0.11 && < 1.3, diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs index 82abcb440..d3f1b308f 100644 --- a/src/Text/Pandoc/Parsing.hs +++ b/src/Text/Pandoc/Parsing.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE CPP #-} {-# LANGUAGE ExplicitForAll #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} @@ -202,7 +203,11 @@ import Data.Default import Data.List (intercalate, isSuffixOf, transpose) import qualified Data.Map as M import Data.Maybe (mapMaybe, fromMaybe) +#if MIN_VERSION_base(4,9,0) +import Data.Semigroup (Semigroup, (<>)) +#else import Data.Monoid ((<>)) +#endif import qualified Data.Set as Set import Data.Text (Text) import Text.HTML.TagSoup.Entity (lookupEntity) @@ -250,10 +255,17 @@ returnF = return . return trimInlinesF :: Future s Inlines -> Future s Inlines trimInlinesF = liftM trimInlines +#if MIN_VERSION_base(4,9,0) +instance Semigroup a => Semigroup (Future s a) where + (<>) = liftM2 (<>) +instance (Semigroup a, Monoid a) => Monoid (Future s a) where + mempty = return mempty + mappend = (<>) +#else instance Monoid a => Monoid (Future s a) where mempty = return mempty mappend = liftM2 mappend - mconcat = liftM mconcat . sequence +#endif -- | Parse characters while a predicate is true. takeWhileP :: Monad m @@ -1437,7 +1449,7 @@ token pp pos match = tokenPrim pp (\_ t _ -> pos t) match infixr 5 <+?> (<+?>) :: (Monoid a) => ParserT s st m a -> ParserT s st m a -> ParserT s st m a -a <+?> b = a >>= flip fmap (try b <|> return mempty) . (<>) +a <+?> b = a >>= flip fmap (try b <|> return mempty) . mappend extractIdClass :: Attr -> Attr extractIdClass (ident, cls, kvs) = (ident', cls', kvs') diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index 14cf73de4..7e1b1b95b 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -39,7 +39,7 @@ import qualified Data.HashMap.Strict as H import Data.List (intercalate, sortBy, transpose, elemIndex) import qualified Data.Map as M import Data.Maybe -import Data.Monoid ((<>)) +import Data.Monoid import Data.Ord (comparing) import Data.Scientific (base10Exponent, coefficient) import qualified Data.Set as Set diff --git a/src/Text/Pandoc/Readers/Odt/ContentReader.hs b/src/Text/Pandoc/Readers/Odt/ContentReader.hs index 380f16c66..ad0612ec8 100644 --- a/src/Text/Pandoc/Readers/Odt/ContentReader.hs +++ b/src/Text/Pandoc/Readers/Odt/ContentReader.hs @@ -520,7 +520,7 @@ matchingElement :: (Monoid e) matchingElement ns name reader = (ns, name, asResultAccumulator reader) where asResultAccumulator :: (ArrowChoice a, Monoid m) => a m m -> a m (Fallible m) - asResultAccumulator a = liftAsSuccess $ keepingTheValue a >>% (<>) + asResultAccumulator a = liftAsSuccess $ keepingTheValue a >>% mappend -- matchChildContent' :: (Monoid result) @@ -554,7 +554,7 @@ read_plain_text = fst ^&&& read_plain_text' >>% recover read_plain_text' = ( second ( arr extractText ) >>^ spreadChoice >>?! second text ) - >>?% (<>) + >>?% mappend -- extractText :: XML.Content -> Fallible String extractText (XML.Text cData) = succeedWith (XML.cdData cData) @@ -565,7 +565,7 @@ read_text_seq = matchingElement NsText "sequence" $ matchChildContent [] read_plain_text --- specifically. I honor that, although the current implementation of '(<>)' +-- specifically. I honor that, although the current implementation of 'mappend' -- for 'Inlines' in "Text.Pandoc.Builder" will collapse them again. -- The rational is to be prepared for future modifications. read_spaces :: InlineMatcher diff --git a/src/Text/Pandoc/Readers/Org/DocumentTree.hs b/src/Text/Pandoc/Readers/Org/DocumentTree.hs index f77778ec9..9730854c0 100644 --- a/src/Text/Pandoc/Readers/Org/DocumentTree.hs +++ b/src/Text/Pandoc/Readers/Org/DocumentTree.hs @@ -36,7 +36,7 @@ import Control.Arrow ((***)) import Control.Monad (guard, void) import Data.Char (toLower, toUpper) import Data.List (intersperse) -import Data.Monoid ((<>)) +import Data.Monoid ((<>), mconcat) import Text.Pandoc.Builder (Blocks, Inlines) import Text.Pandoc.Class (PandocMonad) import Text.Pandoc.Definition diff --git a/src/Text/Pandoc/Readers/Org/Inlines.hs b/src/Text/Pandoc/Readers/Org/Inlines.hs index 3a12f38d0..651a069b9 100644 --- a/src/Text/Pandoc/Readers/Org/Inlines.hs +++ b/src/Text/Pandoc/Readers/Org/Inlines.hs @@ -55,7 +55,7 @@ import Data.Char (isAlphaNum, isSpace) import Data.List (intersperse) import qualified Data.Map as M import Data.Maybe (fromMaybe) -import Data.Monoid ((<>)) +import Data.Monoid import Data.Traversable (sequence) import Prelude hiding (sequence) diff --git a/src/Text/Pandoc/Readers/Vimwiki.hs b/src/Text/Pandoc/Readers/Vimwiki.hs index d717a1ba8..74a7e8fd6 100644 --- a/src/Text/Pandoc/Readers/Vimwiki.hs +++ b/src/Text/Pandoc/Readers/Vimwiki.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE CPP #-} {- Copyright (C) 2017-2018 Yuchen Pei <me@ypei.me> @@ -68,7 +69,7 @@ import Control.Monad.Except (throwError) import Data.Default import Data.List (isInfixOf, isPrefixOf) import Data.Maybe -import Data.Monoid ((<>)) +import Data.Monoid import Data.Text (Text, unpack) import Text.Pandoc.Builder (Blocks, Inlines, fromList, toList, trimInlines) import qualified Text.Pandoc.Builder as B (blockQuote, bulletList, code, diff --git a/stack.lts9.yaml b/stack.lts9.yaml index b17a3ebc2..eed6f81f8 100644 --- a/stack.lts9.yaml +++ b/stack.lts9.yaml @@ -27,4 +27,5 @@ extra-deps: - hs-bibutils-6.2.0.1 - pandoc-citeproc-0.14.1.5 - tagsoup-0.14.6 +- pandoc-types-1.17.4 resolver: lts-9.14 diff --git a/stack.yaml b/stack.yaml index 5de035dd6..65033179e 100644 --- a/stack.yaml +++ b/stack.yaml @@ -21,6 +21,7 @@ extra-deps: - tasty-1.0.0.1 - texmath-0.10.1.1 - tagsoup-0.14.6 +- pandoc-types-1.17.4 ghc-options: "$locals": -fhide-source-paths resolver: lts-10.3 |