summaryrefslogtreecommitdiff
path: root/libraries
diff options
context:
space:
mode:
authorHerbert Valerio Riedel <hvr@gnu.org>2014-09-18 23:05:47 +0200
committerHerbert Valerio Riedel <hvr@gnu.org>2014-09-18 23:13:02 +0200
commitaf22696b8f6d8b677c33f70537a5999ad94266cd (patch)
treeb42bdce024635772b58fe55e72a649eb1f2ea67e /libraries
parentfbf1e3065bf32317db8e87afe8a58ceee2c02241 (diff)
downloadhaskell-af22696b8f6d8b677c33f70537a5999ad94266cd.tar.gz
Invert module-dep between Control.Monad and Data.Foldable
This is the last preparation needed before generalizing entities in Control.Monad conflicting with those from Data.Foldable (re #9586) Reviewed By: ekmett, austin Differential Revision: https://phabricator.haskell.org/D225
Diffstat (limited to 'libraries')
-rw-r--r--libraries/base/Control/Applicative.hs4
-rw-r--r--libraries/base/Control/Monad.hs1
-rw-r--r--libraries/base/Data/Foldable.hs4
-rw-r--r--libraries/base/Text/ParserCombinators/ReadP.hs5
-rw-r--r--libraries/base/Text/Read/Lex.hs8
5 files changed, 16 insertions, 6 deletions
diff --git a/libraries/base/Control/Applicative.hs b/libraries/base/Control/Applicative.hs
index accf58f561..d6157b3d69 100644
--- a/libraries/base/Control/Applicative.hs
+++ b/libraries/base/Control/Applicative.hs
@@ -53,6 +53,7 @@ import Data.Maybe
import Data.Tuple
import Data.Eq
import Data.Ord
+import Data.Foldable (Foldable(..))
import Data.Functor ((<$>))
import GHC.Base hiding ((.), id)
@@ -64,6 +65,9 @@ import GHC.Show (Show)
newtype Const a b = Const { getConst :: a }
deriving (Generic, Generic1)
+instance Foldable (Const m) where
+ foldMap _ _ = mempty
+
instance Functor (Const m) where
fmap _ (Const v) = Const v
diff --git a/libraries/base/Control/Monad.hs b/libraries/base/Control/Monad.hs
index 0597055da9..3487a09c65 100644
--- a/libraries/base/Control/Monad.hs
+++ b/libraries/base/Control/Monad.hs
@@ -76,6 +76,7 @@ module Control.Monad
, (<$!>)
) where
+import Data.Foldable ()
import Data.Functor ( void )
import Data.Maybe
diff --git a/libraries/base/Data/Foldable.hs b/libraries/base/Data/Foldable.hs
index 0e655de573..f6f787b628 100644
--- a/libraries/base/Data/Foldable.hs
+++ b/libraries/base/Data/Foldable.hs
@@ -58,7 +58,6 @@ module Data.Foldable (
find
) where
-import Control.Applicative ( Const )
import Data.Bool
import Data.Either
import Data.Eq
@@ -202,9 +201,6 @@ instance Foldable Proxy where
foldr1 _ _ = error "foldr1: Proxy"
{-# INLINE foldr1 #-}
-instance Foldable (Const m) where
- foldMap _ _ = mempty
-
-- | Monadic fold over the elements of a structure,
-- associating to the right, i.e. from right to left.
foldrM :: (Foldable t, Monad m) => (a -> b -> m b) -> b -> t a -> m b
diff --git a/libraries/base/Text/ParserCombinators/ReadP.hs b/libraries/base/Text/ParserCombinators/ReadP.hs
index 3d2b39c57e..0139e7733d 100644
--- a/libraries/base/Text/ParserCombinators/ReadP.hs
+++ b/libraries/base/Text/ParserCombinators/ReadP.hs
@@ -72,7 +72,6 @@ module Text.ParserCombinators.ReadP
)
where
-import Control.Monad ( sequence )
import {-# SOURCE #-} GHC.Unicode ( isSpace )
import GHC.List ( replicate, null )
import GHC.Base hiding ( many )
@@ -311,6 +310,10 @@ count :: Int -> ReadP a -> ReadP [a]
-- ^ @count n p@ parses @n@ occurrences of @p@ in sequence. A list of
-- results is returned.
count n p = sequence (replicate n p)
+ where -- local 'sequence' to avoid import-cycle
+ sequence ms = foldr k (return []) ms
+ where
+ k m m' = do { x <- m; xs <- m'; return (x:xs) }
between :: ReadP open -> ReadP close -> ReadP a -> ReadP a
-- ^ @between open close p@ parses @open@, followed by @p@ and finally
diff --git a/libraries/base/Text/Read/Lex.hs b/libraries/base/Text/Read/Lex.hs
index 557637d896..39ca46a33f 100644
--- a/libraries/base/Text/Read/Lex.hs
+++ b/libraries/base/Text/Read/Lex.hs
@@ -45,7 +45,13 @@ import GHC.Real( Rational, (%), fromIntegral,
import GHC.List
import GHC.Enum( minBound, maxBound )
import Data.Maybe
-import Control.Monad
+
+-- local copy to break import-cycle
+-- | @'guard' b@ is @'return' ()@ if @b@ is 'True',
+-- and 'mzero' if @b@ is 'False'.
+guard :: (MonadPlus m) => Bool -> m ()
+guard True = return ()
+guard False = mzero
-- -----------------------------------------------------------------------------
-- Lexing types