summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorHerbert Valerio Riedel <hvr@gnu.org>2017-09-21 23:30:05 +0200
committerHerbert Valerio Riedel <hvr@gnu.org>2017-09-22 00:24:25 +0200
commitfeac0a3bc69fd376231aa3c83d031c131156ddb9 (patch)
treead94a04d30869efe5a9d021f3fe2923269b5bfbd
parent9aa73892e10e90a1799b9277da593e816a827364 (diff)
downloadhaskell-feac0a3bc69fd376231aa3c83d031c131156ddb9.tar.gz
Reexport Semigroup's <> operator from Prelude (#14191)
This completes the 2nd phase of the Semigroup=>Monoid Proposal (SMP) initiated in 8ae263ceb3566a7c82336400b09cb8f381217405. This updates a couple submodules to address <> naming clashes.
-rw-r--r--compiler/utils/GhcPrelude.hs11
-rw-r--r--ghc/GHCi/UI.hs1
-rw-r--r--ghc/GHCi/UI/Info.hs2
-rw-r--r--ghc/GHCi/UI/Monad.hs1
-rw-r--r--ghc/Main.hs2
-rw-r--r--libraries/base/Prelude.hs2
-rw-r--r--libraries/base/changelog.md2
m---------libraries/containers0
m---------libraries/pretty0
-rw-r--r--libraries/template-haskell/Language/Haskell/TH/Ppr.hs1
-rw-r--r--libraries/template-haskell/Language/Haskell/TH/PprLib.hs1
m---------libraries/text0
-rw-r--r--testsuite/tests/ado/ado-optimal.hs4
-rw-r--r--testsuite/tests/ado/ado001.hs4
-rw-r--r--testsuite/tests/callarity/unittest/CallArity1.hs2
-rw-r--r--testsuite/tests/rename/should_fail/T10618.hs2
-rw-r--r--testsuite/tests/rename/should_fail/T10618.stderr6
m---------utils/haddock0
18 files changed, 28 insertions, 13 deletions
diff --git a/compiler/utils/GhcPrelude.hs b/compiler/utils/GhcPrelude.hs
index ed4eacbfb8..8b09bd5b3a 100644
--- a/compiler/utils/GhcPrelude.hs
+++ b/compiler/utils/GhcPrelude.hs
@@ -1,3 +1,5 @@
+{-# LANGUAGE CPP #-}
+
-- | Custom GHC "Prelude"
--
-- This module serves as a replacement for the "Prelude" module
@@ -6,4 +8,13 @@
--
module GhcPrelude (module X) where
+-- We export the 'Semigroup' class but w/o the (<>) operator to avoid
+-- clashing with the (Outputable.<>) operator which is heavily used
+-- through GHC's code-base.
+
+#if MIN_VERSION_base(4,11,0)
+import Prelude as X hiding ((<>))
+#else
import Prelude as X
+import Data.Semigroup as X (Semigroup)
+#endif
diff --git a/ghc/GHCi/UI.hs b/ghc/GHCi/UI.hs
index 6a03b3c365..32e581a10d 100644
--- a/ghc/GHCi/UI.hs
+++ b/ghc/GHCi/UI.hs
@@ -102,6 +102,7 @@ import qualified Data.Map as M
import Data.Time.LocalTime ( getZonedTime )
import Data.Time.Format ( formatTime, defaultTimeLocale )
import Data.Version ( showVersion )
+import Prelude hiding ((<>))
import Exception hiding (catch)
import Foreign hiding (void)
diff --git a/ghc/GHCi/UI/Info.hs b/ghc/GHCi/UI/Info.hs
index c0cb2d1b51..fd8749a3e1 100644
--- a/ghc/GHCi/UI/Info.hs
+++ b/ghc/GHCi/UI/Info.hs
@@ -27,7 +27,7 @@ import Data.Map.Strict (Map)
import qualified Data.Map.Strict as M
import Data.Maybe
import Data.Time
-import Prelude hiding (mod)
+import Prelude hiding (mod,(<>))
import System.Directory
import qualified CoreUtils
diff --git a/ghc/GHCi/UI/Monad.hs b/ghc/GHCi/UI/Monad.hs
index 46f0860ab9..9233beb861 100644
--- a/ghc/GHCi/UI/Monad.hs
+++ b/ghc/GHCi/UI/Monad.hs
@@ -55,6 +55,7 @@ import Data.Time
import System.Environment
import System.IO
import Control.Monad
+import Prelude hiding ((<>))
import System.Console.Haskeline (CompletionFunc, InputT)
import qualified System.Console.Haskeline as Haskeline
diff --git a/ghc/Main.hs b/ghc/Main.hs
index a75aba3e97..7c406e4988 100644
--- a/ghc/Main.hs
+++ b/ghc/Main.hs
@@ -809,7 +809,7 @@ dumpFastStringStats dflags = do
-- the "z-encoded" total.
putMsg dflags msg
where
- x `pcntOf` y = int ((x * 100) `quot` y) <> char '%'
+ x `pcntOf` y = int ((x * 100) `quot` y) Outputable.<> char '%'
countFS :: Int -> Int -> Int -> [[FastString]] -> (Int, Int, Int)
countFS entries longest has_z [] = (entries, longest, has_z)
diff --git a/libraries/base/Prelude.hs b/libraries/base/Prelude.hs
index 75a0d5341d..15e392f271 100644
--- a/libraries/base/Prelude.hs
+++ b/libraries/base/Prelude.hs
@@ -67,7 +67,7 @@ module Prelude (
fromIntegral, realToFrac,
-- ** Semigroups and Monoids
- Semigroup, -- TODO: export (<>)
+ Semigroup((<>)),
Monoid(mempty, mappend, mconcat),
-- ** Monads and functors
diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md
index 6d5543e620..6c15a98993 100644
--- a/libraries/base/changelog.md
+++ b/libraries/base/changelog.md
@@ -11,7 +11,7 @@
* Add `Semigroup` instance for `EventLifetime`.
* Make `Semigroup` a superclass of `Monoid`;
- export `Semigroup` from `Prelude`; remove `Monoid` reexport
+ export `Semigroup((<>))` from `Prelude`; remove `Monoid` reexport
from `Data.Semigroup` (#14191).
* Generalise `instance Monoid a => Monoid (Maybe a)` to
diff --git a/libraries/containers b/libraries/containers
-Subproject 6414704b892a6dc56a1b17e3a530d777b70f56a
+Subproject c07e4848e1b4458265e30cfb6265f9b6bd2bf05
diff --git a/libraries/pretty b/libraries/pretty
-Subproject 56bc78e2c2cfcc850f6fec87fe79743750d4c8b
+Subproject 445e92dd7508978caba5563c1e79b2758dff476
diff --git a/libraries/template-haskell/Language/Haskell/TH/Ppr.hs b/libraries/template-haskell/Language/Haskell/TH/Ppr.hs
index e6c33029ab..bbb73b07c7 100644
--- a/libraries/template-haskell/Language/Haskell/TH/Ppr.hs
+++ b/libraries/template-haskell/Language/Haskell/TH/Ppr.hs
@@ -14,6 +14,7 @@ import Data.Char ( toLower, chr)
import GHC.Show ( showMultiLineString )
import GHC.Lexeme( startsVarSym )
import Data.Ratio ( numerator, denominator )
+import Prelude hiding ((<>))
nestDepth :: Int
nestDepth = 4
diff --git a/libraries/template-haskell/Language/Haskell/TH/PprLib.hs b/libraries/template-haskell/Language/Haskell/TH/PprLib.hs
index 32980ab6cc..7e05d05d83 100644
--- a/libraries/template-haskell/Language/Haskell/TH/PprLib.hs
+++ b/libraries/template-haskell/Language/Haskell/TH/PprLib.hs
@@ -41,6 +41,7 @@ import qualified Text.PrettyPrint as HPJ
import Control.Monad (liftM, liftM2, ap)
import Language.Haskell.TH.Lib.Map ( Map )
import qualified Language.Haskell.TH.Lib.Map as Map ( lookup, insert, empty )
+import Prelude hiding ((<>))
infixl 6 <>
infixl 6 <+>
diff --git a/libraries/text b/libraries/text
-Subproject 1707aa5f2ad5c254c45ac9ffcac749e4d6b67a6
+Subproject 2d88a0a3e8e3bb79260e5c8f61dd6c447f61c5f
diff --git a/testsuite/tests/ado/ado-optimal.hs b/testsuite/tests/ado/ado-optimal.hs
index d67aa4fb1a..5e3266e8c2 100644
--- a/testsuite/tests/ado/ado-optimal.hs
+++ b/testsuite/tests/ado/ado-optimal.hs
@@ -3,7 +3,7 @@
module Main where
import Control.Applicative
-import Text.PrettyPrint
+import Text.PrettyPrint as PP
(a:b:c:d:e:f:g:h:_) = map (\c -> doc [c]) ['a'..]
@@ -64,7 +64,7 @@ instance Monad M where
(Nothing,Nothing) -> (Nothing, b)
(Just d, Nothing) -> (Just d, b)
(Nothing, Just d) -> (Just d, b)
- (Just d1, Just d2) -> (Just (maybeParen p (d1 <> semi <+> d2)), b)
+ (Just d1, Just d2) -> (Just (maybeParen p (d1 PP.<> semi <+> d2)), b)
doc :: String -> M ()
doc d = M $ \_ -> (Just (text d), ())
diff --git a/testsuite/tests/ado/ado001.hs b/testsuite/tests/ado/ado001.hs
index 0d466c5fd1..6abce177e0 100644
--- a/testsuite/tests/ado/ado001.hs
+++ b/testsuite/tests/ado/ado001.hs
@@ -2,7 +2,7 @@
module Main where
import Control.Applicative
-import Text.PrettyPrint
+import Text.PrettyPrint as PP
(a:b:c:d:e:f:g:h:_) = map (\c -> doc [c]) ['a'..]
@@ -175,7 +175,7 @@ instance Monad M where
(Nothing,Nothing) -> (Nothing, b)
(Just d, Nothing) -> (Just d, b)
(Nothing, Just d) -> (Just d, b)
- (Just d1, Just d2) -> (Just (maybeParen p (d1 <> semi <+> d2)), b)
+ (Just d1, Just d2) -> (Just (maybeParen p (d1 PP.<> semi <+> d2)), b)
doc :: String -> M ()
doc d = M $ \_ -> (Just (text d), ())
diff --git a/testsuite/tests/callarity/unittest/CallArity1.hs b/testsuite/tests/callarity/unittest/CallArity1.hs
index 8fd8feb548..1100ff6a8f 100644
--- a/testsuite/tests/callarity/unittest/CallArity1.hs
+++ b/testsuite/tests/callarity/unittest/CallArity1.hs
@@ -172,7 +172,7 @@ main = do
case lintExpr dflags [f,scrutf,scruta] e of
Just msg -> putMsg dflags (msg $$ text "in" <+> text n)
Nothing -> return ()
- putMsg dflags (text n <> char ':')
+ putMsg dflags (text n Outputable.<> char ':')
-- liftIO $ putMsg dflags (ppr e)
let e' = callArityRHS e
let bndrs = nonDetEltsUniqSet (allBoundIds e')
diff --git a/testsuite/tests/rename/should_fail/T10618.hs b/testsuite/tests/rename/should_fail/T10618.hs
index 28b665f6fb..d69cf3d409 100644
--- a/testsuite/tests/rename/should_fail/T10618.hs
+++ b/testsuite/tests/rename/should_fail/T10618.hs
@@ -1,3 +1,3 @@
module T10618 where
-foo = Just $ Nothing <> Nothing
+foo = Just $ Nothing <|> Nothing
diff --git a/testsuite/tests/rename/should_fail/T10618.stderr b/testsuite/tests/rename/should_fail/T10618.stderr
index 8b4dc2c28d..2d478744e1 100644
--- a/testsuite/tests/rename/should_fail/T10618.stderr
+++ b/testsuite/tests/rename/should_fail/T10618.stderr
@@ -1,6 +1,6 @@
T10618.hs:3:22: error:
- • Variable not in scope: (<>) :: Maybe (Maybe a0) -> Maybe a1 -> t
+ • Variable not in scope: (<|>) :: Maybe (Maybe a0) -> Maybe a1 -> t
• Perhaps you meant one of these:
- ‘<$>’ (imported from Prelude), ‘*>’ (imported from Prelude),
- ‘<$’ (imported from Prelude)
+ ‘<$>’ (imported from Prelude), ‘<*>’ (imported from Prelude),
+ ‘<>’ (imported from Prelude)
diff --git a/utils/haddock b/utils/haddock
-Subproject 2f6c11305cca9f50833b99dac729ce76e46aa23
+Subproject 0a64b5cdc051c47b24151b8839ae9067f06d8d0