Removed redundant import.
This commit is contained in:
parent
07e0981316
commit
94d64a63f2
1 changed files with 1 additions and 3 deletions
|
@ -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'.
|
||||
|
|
Loading…
Add table
Reference in a new issue