From 94d64a63f2fb463bc260cf2f0bae1eff2116ce28 Mon Sep 17 00:00:00 2001
From: John MacFarlane <jgm@berkeley.edu>
Date: Fri, 16 Mar 2018 08:15:09 -0700
Subject: Removed redundant import.

---
 src/Text/Pandoc/Readers/Odt/Arrows/State.hs | 4 +---
 1 file changed, 1 insertion(+), 3 deletions(-)

(limited to 'src')

diff --git a/src/Text/Pandoc/Readers/Odt/Arrows/State.hs b/src/Text/Pandoc/Readers/Odt/Arrows/State.hs
index 73bed545e..202118669 100644
--- a/src/Text/Pandoc/Readers/Odt/Arrows/State.hs
+++ b/src/Text/Pandoc/Readers/Odt/Arrows/State.hs
@@ -1,4 +1,3 @@
-
 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE TupleSections     #-}
 {-
@@ -45,7 +44,6 @@ import qualified Control.Category as Cat
 import Control.Monad
 
 import Data.Foldable
-import Data.Monoid
 
 import Text.Pandoc.Readers.Odt.Arrows.Utils
 import Text.Pandoc.Readers.Odt.Generic.Fallible
@@ -131,7 +129,7 @@ withSubStateF' unlift a = ArrowState go
 -- and one with any function.
 foldS :: (Foldable f, Monoid m) => ArrowState s x m -> ArrowState s (f x) m
 foldS a = ArrowState $ \(s,f) -> foldr a' (s,mempty) f
-  where a' x (s',m) = second (m <>)  $ runArrowState a (s',x)
+  where a' x (s',m) = second (mappend m)  $ runArrowState a (s',x)
 
 -- | Fold a state arrow through something 'Foldable'. Collect the results in a
 -- 'MonadPlus'.
-- 
cgit v1.2.3