aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers/Odt
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Readers/Odt')
-rw-r--r--src/Text/Pandoc/Readers/Odt/ContentReader.hs5
-rw-r--r--src/Text/Pandoc/Readers/Odt/Generic/Utils.hs1
2 files changed, 3 insertions, 3 deletions
diff --git a/src/Text/Pandoc/Readers/Odt/ContentReader.hs b/src/Text/Pandoc/Readers/Odt/ContentReader.hs
index 24391dbf0..43c44e7e9 100644
--- a/src/Text/Pandoc/Readers/Odt/ContentReader.hs
+++ b/src/Text/Pandoc/Readers/Odt/ContentReader.hs
@@ -25,6 +25,7 @@ module Text.Pandoc.Readers.Odt.ContentReader
import Control.Applicative hiding (liftA, liftA2, liftA3)
import Control.Arrow
+import Control.Monad ((<=<))
import qualified Data.ByteString.Lazy as B
import Data.Foldable (fold)
@@ -352,11 +353,11 @@ modifierFromStyleDiff propertyTriple =
lookupPreviousValue f = lookupPreviousStyleValue (fmap f . textProperties)
- lookupPreviousValueM f = lookupPreviousStyleValue ((f =<<).textProperties)
+ lookupPreviousValueM f = lookupPreviousStyleValue (f <=< textProperties)
lookupPreviousStyleValue f (ReaderState{..},_,mFamily)
= findBy f (extendedStylePropertyChain styleTrace styleSet)
- <|> ( f =<< fmap (lookupDefaultStyle' styleSet) mFamily )
+ <|> (f . lookupDefaultStyle' styleSet =<< mFamily)
type ParaModifier = Blocks -> Blocks
diff --git a/src/Text/Pandoc/Readers/Odt/Generic/Utils.hs b/src/Text/Pandoc/Readers/Odt/Generic/Utils.hs
index 146f35319..6dc56a0d9 100644
--- a/src/Text/Pandoc/Readers/Odt/Generic/Utils.hs
+++ b/src/Text/Pandoc/Readers/Odt/Generic/Utils.hs
@@ -1,4 +1,3 @@
-{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE ViewPatterns #-}
{- |
Module : Text.Pandoc.Reader.Odt.Generic.Utils