[Git][ghc/ghc][master] 5 commits: Export liftA2 from Prelude

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Thu Sep 8 21:49:27 UTC 2022



Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
77209ab3 by Georgi Lyubenov at 2022-09-08T17:14:36+03:00
Export liftA2 from Prelude

Changes:
In order to be warning free and compatible, we hide Applicative(..)
from Prelude in a few places and instead import it directly from
Control.Applicative.
Please see the migration guide at
https://github.com/haskell/core-libraries-committee/blob/main/guides/export-lifta2-prelude.md
for more details.

This means that Applicative is now exported in its entirety from
Prelude.

Motivation:

This change is motivated by a few things:
* liftA2 is an often used function, even more so than (<*>) for some
  people.
* When implementing Applicative, the compiler will prompt you for either
  an implementation of (<*>) or of liftA2, but trying to use the latter
  ends with an error, without further imports. This could be confusing
  for newbies.
* For teaching, it is often times easier to introduce liftA2 first,
  as it is a natural generalisation of fmap.
* This change seems to have been unanimously and enthusiastically
  accepted by the CLC members, possibly indicating a lot of love for it.
* This change causes very limited breakage, see the linked issue below
  for an investigation on this.

See https://github.com/haskell/core-libraries-committee/issues/50
for the surrounding discussion and more details.

- - - - -
442a94e8 by Georgi Lyubenov at 2022-09-08T17:14:36+03:00
Add changelog entry for liftA2 export from Prelude

- - - - -
fb968680 by Georgi Lyubenov at 2022-09-08T17:14:36+03:00
Bump submodule containers to one with liftA2 warnings fixed

- - - - -
f54ff818 by Georgi Lyubenov at 2022-09-08T17:14:36+03:00
Bump submodule Cabal to one with liftA2 warnings fixed

- - - - -
a4b34808 by Georgi Lyubenov at 2022-09-08T17:14:36+03:00
Isolate some Applicative hidings to GHC.Prelude

By reexporting the entirety of Applicative from GHC.Prelude, we can save
ourselves some `hiding` and importing of `Applicative` in consumers of GHC.Prelude.
This also has the benefit of isolating this type of change to
GHC.Prelude, so that people in the future don't have to think about it.

- - - - -


15 changed files:

- compiler/GHC/Hs/Doc.hs
- compiler/GHC/Prelude.hs
- compiler/GHC/Types/SrcLoc.hs
- compiler/GHC/Utils/Misc.hs
- compiler/GHC/Utils/Monad.hs
- libraries/Cabal
- libraries/base/Data/Complex.hs
- libraries/base/Data/List/NonEmpty.hs
- libraries/base/Data/Semigroup.hs
- libraries/base/Prelude.hs
- libraries/base/changelog.md
- libraries/containers
- libraries/template-haskell/Language/Haskell/TH/Lib.hs
- libraries/template-haskell/Language/Haskell/TH/Lib/Internal.hs
- libraries/template-haskell/Language/Haskell/TH/Syntax.hs


Changes:

=====================================
compiler/GHC/Hs/Doc.hs
=====================================
@@ -38,7 +38,6 @@ import GHC.Types.Avail
 import GHC.Types.Name.Set
 import GHC.Driver.Flags
 
-import Control.Applicative (liftA2)
 import Data.Data
 import Data.IntMap (IntMap)
 import qualified Data.IntMap as IntMap


=====================================
compiler/GHC/Prelude.hs
=====================================
@@ -14,6 +14,7 @@
 
 module GHC.Prelude
   (module X
+  ,Applicative (..)
   ,module Bits
   ,shiftL, shiftR
   ) where
@@ -47,7 +48,8 @@ NoImplicitPrelude. There are two motivations for this:
     extensions.
 -}
 
-import Prelude as X hiding ((<>))
+import Prelude as X hiding ((<>), Applicative(..))
+import Control.Applicative (Applicative(..))
 import Data.Foldable as X (foldl')
 
 #if MIN_VERSION_base(4,16,0)


=====================================
compiler/GHC/Types/SrcLoc.hs
=====================================
@@ -125,7 +125,6 @@ import GHC.Data.FastString
 import qualified GHC.Data.Strict as Strict
 
 import Control.DeepSeq
-import Control.Applicative (liftA2)
 import Data.Data
 import Data.List (sortBy, intercalate)
 import Data.Function (on)


=====================================
compiler/GHC/Utils/Misc.hs
=====================================
@@ -141,7 +141,6 @@ import Data.List.NonEmpty  ( NonEmpty(..) )
 import GHC.Exts
 import GHC.Stack (HasCallStack)
 
-import Control.Applicative ( liftA2 )
 import Control.Monad    ( liftM, guard )
 import Control.Monad.IO.Class ( MonadIO, liftIO )
 import System.IO.Error as IO ( isDoesNotExistError )


=====================================
compiler/GHC/Utils/Monad.hs
=====================================
@@ -29,7 +29,6 @@ module GHC.Utils.Monad
 
 import GHC.Prelude
 
-import Control.Applicative
 import Control.Monad
 import Control.Monad.Fix
 import Control.Monad.IO.Class


=====================================
libraries/Cabal
=====================================
@@ -1 +1 @@
-Subproject commit 5d18b763356dca719f5286a52328cb41b9fa4192
+Subproject commit dac10555299fa0d750838529a67598821264e5e3


=====================================
libraries/base/Data/Complex.hs
=====================================
@@ -35,6 +35,7 @@ module Data.Complex
 
         )  where
 
+import Prelude hiding (Applicative(..))
 import GHC.Base (Applicative (..))
 import GHC.Generics (Generic, Generic1)
 import GHC.Float (Floating(..))


=====================================
libraries/base/Data/List/NonEmpty.hs
=====================================
@@ -102,7 +102,7 @@ import           Prelude             hiding (break, cycle, drop, dropWhile,
                                       last, length, map, repeat, reverse,
                                       scanl, scanl1, scanr, scanr1, span,
                                       splitAt, tail, take, takeWhile,
-                                      unzip, zip, zipWith, (!!))
+                                      unzip, zip, zipWith, (!!), Applicative(..))
 import qualified Prelude
 
 import           Control.Applicative (Applicative (..), Alternative (many))


=====================================
libraries/base/Data/Semigroup.hs
=====================================
@@ -98,7 +98,7 @@ module Data.Semigroup (
   , ArgMax
   ) where
 
-import           Prelude             hiding (foldr1)
+import           Prelude             hiding (foldr1, Applicative(..))
 
 import GHC.Base (Semigroup(..))
 


=====================================
libraries/base/Prelude.hs
=====================================
@@ -73,7 +73,7 @@ module Prelude (
 
     -- ** Monads and functors
     Functor(fmap, (<$)), (<$>),
-    Applicative(pure, (<*>), (*>), (<*)),
+    Applicative(pure, (<*>), (*>), (<*), liftA2),
     Monad((>>=), (>>), return),
     MonadFail(fail),
     mapM_, sequence_, (=<<),


=====================================
libraries/base/changelog.md
=====================================
@@ -25,6 +25,10 @@
   * Change default `Ord` implementation of `(>=)`, `(>)`, and `(<)` to use
     `(<=)` instead of `compare` per
     [Core Libraries proposal](https://github.com/haskell/core-libraries-committee/issues/24).
+  * Export `liftA2` from `Prelude`. This means that the entirety of `Applicative`
+    is now exported from `Prelude`. See [CLC #50](https://github.com/haskell/core-libraries-committee/issues/50)
+    for the related discussion,
+    as well as [the migration guide](https://github.com/haskell/core-libraries-committee/blob/main/guides/export-lifta2-prelude.md)
 
 ## 4.17.0.0 *August 2022*
 


=====================================
libraries/containers
=====================================
@@ -1 +1 @@
-Subproject commit 50175b72dc781f82a419bddafba1bdd758fbee4b
+Subproject commit 5e338df84454b56d649360a57d2c186785aff2b4


=====================================
libraries/template-haskell/Language/Haskell/TH/Lib.hs
=====================================
@@ -178,10 +178,10 @@ import Language.Haskell.TH.Lib.Internal hiding
 import qualified Language.Haskell.TH.Lib.Internal as Internal
 import Language.Haskell.TH.Syntax
 
-import Control.Applicative ( liftA2 )
+import Control.Applicative (Applicative(..))
 import Foreign.ForeignPtr
 import Data.Word
-import Prelude
+import Prelude hiding (Applicative(..))
 
 -- All definitions below represent the "old" API, since their definitions are
 -- different in Language.Haskell.TH.Lib.Internal. Please think carefully before


=====================================
libraries/template-haskell/Language/Haskell/TH/Lib/Internal.hs
=====================================
@@ -20,12 +20,12 @@ module Language.Haskell.TH.Lib.Internal where
 
 import Language.Haskell.TH.Syntax hiding (Role, InjectivityAnn)
 import qualified Language.Haskell.TH.Syntax as TH
-import Control.Applicative(liftA, liftA2)
+import Control.Applicative(liftA, Applicative(..))
 import qualified Data.Kind as Kind (Type)
 import Data.Word( Word8 )
 import Data.List.NonEmpty ( NonEmpty(..) )
 import GHC.Exts (TYPE)
-import Prelude
+import Prelude hiding (Applicative(..))
 
 ----------------------------------------------------------
 -- * Type synonyms


=====================================
libraries/template-haskell/Language/Haskell/TH/Syntax.hs
=====================================
@@ -39,7 +39,7 @@ import GHC.IO.Unsafe    ( unsafeDupableInterleaveIO )
 import Control.Monad (liftM)
 import Control.Monad.IO.Class (MonadIO (..))
 import Control.Monad.Fix (MonadFix (..))
-import Control.Applicative (liftA2)
+import Control.Applicative (Applicative(..))
 import Control.Exception (BlockedIndefinitelyOnMVar (..), catch, throwIO)
 import Control.Exception.Base (FixIOException (..))
 import Control.Concurrent.MVar (newEmptyMVar, readMVar, putMVar)
@@ -60,7 +60,7 @@ import GHC.Lexeme       ( startsVarSym, startsVarId )
 import GHC.ForeignSrcLang.Type
 import Language.Haskell.TH.LanguageExtensions
 import Numeric.Natural
-import Prelude
+import Prelude hiding (Applicative(..))
 import Foreign.ForeignPtr
 import Foreign.C.String
 import Foreign.C.Types



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7918265d53db963bfd3dd529b1063fb844549733...a4b34808720e93b434b4fcf18db114bc1f0599aa

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7918265d53db963bfd3dd529b1063fb844549733...a4b34808720e93b434b4fcf18db114bc1f0599aa
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20220908/093c728c/attachment-0001.html>


More information about the ghc-commits mailing list