aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers/Odt
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2017-10-27 23:13:55 -0700
committerJohn MacFarlane <jgm@berkeley.edu>2017-10-27 23:13:55 -0700
commitcbcb9b36c088b3dd1e07f9d0318594b78e5d38f2 (patch)
tree4073e58a0c4ce88f5fb7c48d63b213129ced80fe /src/Text/Pandoc/Readers/Odt
parent84812983573232a1dc25f68268acfa9b28ac5a22 (diff)
downloadpandoc-cbcb9b36c088b3dd1e07f9d0318594b78e5d38f2.tar.gz
hlint suggestions.
Diffstat (limited to 'src/Text/Pandoc/Readers/Odt')
-rw-r--r--src/Text/Pandoc/Readers/Odt/Arrows/State.hs6
-rw-r--r--src/Text/Pandoc/Readers/Odt/Base.hs3
-rw-r--r--src/Text/Pandoc/Readers/Odt/Generic/Fallible.hs4
-rw-r--r--src/Text/Pandoc/Readers/Odt/Generic/Utils.hs4
4 files changed, 8 insertions, 9 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'.
diff --git a/src/Text/Pandoc/Readers/Odt/Base.hs b/src/Text/Pandoc/Readers/Odt/Base.hs
index f8a0b86e7..51c2da788 100644
--- a/src/Text/Pandoc/Readers/Odt/Base.hs
+++ b/src/Text/Pandoc/Readers/Odt/Base.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE PatternGuards #-}
+
{-
Copyright (C) 2015 Martin Linnemann <theCodingMarlin@googlemail.com>
@@ -40,4 +40,3 @@ type OdtConverterState s = XMLConverterState Namespace s
type XMLReader s a b = FallibleXMLConverter Namespace s a b
type XMLReaderSafe s a b = XMLConverter Namespace s a b
-
diff --git a/src/Text/Pandoc/Readers/Odt/Generic/Fallible.hs b/src/Text/Pandoc/Readers/Odt/Generic/Fallible.hs
index 72509e591..f8ea5c605 100644
--- a/src/Text/Pandoc/Readers/Odt/Generic/Fallible.hs
+++ b/src/Text/Pandoc/Readers/Odt/Generic/Fallible.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE GeneralizedNewtypeDeriving #-}
+
{-
Copyright (C) 2015 Martin Linnemann <theCodingMarlin@googlemail.com>
@@ -121,6 +121,6 @@ newtype SuccessList a = SuccessList { collectNonFailing :: [a] }
deriving ( Eq, Ord, Show )
instance ChoiceVector SuccessList where
- spreadChoice = Right . SuccessList . (foldr unTagRight []) . collectNonFailing
+ spreadChoice = Right . SuccessList . foldr unTagRight [] . collectNonFailing
where unTagRight (Right x) = (x:)
unTagRight _ = id
diff --git a/src/Text/Pandoc/Readers/Odt/Generic/Utils.hs b/src/Text/Pandoc/Readers/Odt/Generic/Utils.hs
index f492ec944..556517259 100644
--- a/src/Text/Pandoc/Readers/Odt/Generic/Utils.hs
+++ b/src/Text/Pandoc/Readers/Odt/Generic/Utils.hs
@@ -1,5 +1,5 @@
-{-# LANGUAGE PatternGuards #-}
-{-# LANGUAGE TupleSections #-}
+
+
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE ViewPatterns #-}