diff options
author | John MacFarlane <jgm@berkeley.edu> | 2017-10-27 23:13:55 -0700 |
---|---|---|
committer | John MacFarlane <jgm@berkeley.edu> | 2017-10-27 23:13:55 -0700 |
commit | cbcb9b36c088b3dd1e07f9d0318594b78e5d38f2 (patch) | |
tree | 4073e58a0c4ce88f5fb7c48d63b213129ced80fe /src/Text/Pandoc/Readers/Odt/Arrows | |
parent | 84812983573232a1dc25f68268acfa9b28ac5a22 (diff) | |
download | pandoc-cbcb9b36c088b3dd1e07f9d0318594b78e5d38f2.tar.gz |
hlint suggestions.
Diffstat (limited to 'src/Text/Pandoc/Readers/Odt/Arrows')
-rw-r--r-- | src/Text/Pandoc/Readers/Odt/Arrows/State.hs | 6 |
1 files changed, 3 insertions, 3 deletions
diff --git a/src/Text/Pandoc/Readers/Odt/Arrows/State.hs b/src/Text/Pandoc/Readers/Odt/Arrows/State.hs index 0f7483431..06b2dcaaa 100644 --- a/src/Text/Pandoc/Readers/Odt/Arrows/State.hs +++ b/src/Text/Pandoc/Readers/Odt/Arrows/State.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE Arrows #-} + {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE TupleSections #-} {- @@ -139,7 +139,7 @@ iterateS :: (Foldable f, MonadPlus m) => ArrowState s x y -> ArrowState s (f x) (m y) iterateS a = ArrowState $ \(s,f) -> foldr a' (s,mzero) f - where a' x (s',m) = second ((mplus m).return) $ runArrowState a (s',x) + where a' x (s',m) = second (mplus m.return) $ runArrowState a (s',x) -- | Fold a state arrow through something 'Foldable'. Collect the results in a -- 'MonadPlus'. @@ -147,7 +147,7 @@ iterateSL :: (Foldable f, MonadPlus m) => ArrowState s x y -> ArrowState s (f x) (m y) iterateSL a = ArrowState $ \(s,f) -> foldl a' (s,mzero) f - where a' (s',m) x = second ((mplus m).return) $ runArrowState a (s',x) + where a' (s',m) x = second (mplus m.return) $ runArrowState a (s',x) -- | Fold a fallible state arrow through something 'Foldable'. |