Skip to content

Commit 2d62b97

Browse files
mpilgremMarge Bot
authored and
Marge Bot
committed
Re CLC #300 - Specify fmap for NonEmpty as map
See: * haskell/core-libraries-committee#300 Seeks to: * move existing instances for NonEmpty (except of Eq and Ord) out of GHC.Internal.Base into new GHC.Internal.Data.NonEmpty (to avoid otherwise unavoidable cycles in the module graph); * move map out of Data.List.NonEmpty (base package) into GHC.Internal.Data.NonEmpty; * define fmap as map for NonEmpty instance of Functor, avoiding code duplication; * re-export map from existing GHC.Internal.Data.List.NonEmpty; and * re-export map from Data.List.NonEmpty (base package); without breaking anything in the GHC repository. Various tests *.stdout and *.stderr files are amended also.
1 parent 2e7bf44 commit 2d62b97

30 files changed

+104
-76
lines changed

libraries/base/changelog.md

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -8,6 +8,7 @@
88
([GHC #25066](https://gitlab.haskell.org/ghc/ghc/-/issues/25066), [CLC proposal #290](https://github.com/haskell/core-libraries-committee/issues/290))
99
* `Data.List.NonEmpty.{init,last,tails1}` are now defined using only total functions (rather than partial ones). ([CLC proposal #293](https://github.com/haskell/core-libraries-committee/issues/293))
1010
* `Data.List.NonEmpty` functions now have the same laziness as their `Data.List` counterparts (i.e. make them more strict than they currently are) ([CLC proposal #107](https://github.com/haskell/core-libraries-committee/issues/107))
11+
* `instance Functor NonEmpty` is now specified using `map` (rather than duplicating code). ([CLC proposal #300](https://github.com/haskell/core-libraries-committee/issues/300))
1112

1213
## 4.21.0.0 *TBA*
1314
* Introduce `Data.Bounded` module exporting the `Bounded` typeclass (finishing [CLC proposal #208](https://github.com/haskell/core-libraries-committee/issues/208))

libraries/base/src/Data/List/NonEmpty.hs

Lines changed: 1 addition & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -123,7 +123,7 @@ import qualified GHC.Internal.Data.Foldable as Foldable
123123
import GHC.Internal.Data.Function (on)
124124
import GHC.Internal.Data.Ord (comparing)
125125
import GHC.Internal.Stack.Types (HasCallStack)
126-
import GHC.Internal.Data.List.NonEmpty
126+
import GHC.Internal.Data.List.NonEmpty (NonEmpty (..), map, zip, zipWith)
127127

128128
infixr 5 <|
129129

@@ -290,10 +290,6 @@ toList (a :| as) = a : as
290290
lift :: Foldable f => ([a] -> [b]) -> f a -> NonEmpty b
291291
lift f = fromList . f . Foldable.toList
292292

293-
-- | Map a function over a 'NonEmpty' stream.
294-
map :: (a -> b) -> NonEmpty a -> NonEmpty b
295-
map f (a :| as) = f a :| fmap f as
296-
297293
-- | The 'inits' function takes a stream @xs@ and returns all the
298294
-- finite prefixes of @xs@, starting with the shortest. The result is
299295
-- 'NonEmpty' because the result always contains the empty list as the first

libraries/base/src/Data/Semigroup.hs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -105,7 +105,7 @@ module Data.Semigroup (
105105
, ArgMax
106106
) where
107107

108-
import GHC.Internal.Base hiding (Any)
108+
import GHC.Internal.Base hiding (Any, NonEmpty(..))
109109
import GHC.Internal.Enum
110110
import GHC.Internal.Show
111111
import GHC.Internal.Read
@@ -116,6 +116,7 @@ import Data.Bifoldable
116116
import Data.Bifunctor
117117
import Data.Bitraversable
118118
import GHC.Internal.Data.Foldable
119+
import GHC.Internal.Data.NonEmpty (NonEmpty(..))
119120
import GHC.Internal.Data.Traversable
120121
import GHC.Internal.Data.Semigroup.Internal
121122
import GHC.Internal.Control.Monad.Fix

libraries/base/src/GHC/Base.hs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -138,7 +138,8 @@ module GHC.Base
138138
, divModInt#, divModInt8#, divModInt16#, divModInt32#
139139
) where
140140

141-
import GHC.Internal.Base
141+
import GHC.Internal.Base hiding ( NonEmpty(..) )
142+
import GHC.Internal.Data.NonEmpty ( NonEmpty(..) )
142143
import GHC.Prim hiding
143144
(
144145
-- Hide dataToTag# ops because they are expected to break for

libraries/ghc-internal/ghc-internal.cabal.in

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -152,6 +152,7 @@ Library
152152
GHC.Internal.Data.List.NonEmpty
153153
GHC.Internal.Data.Maybe
154154
GHC.Internal.Data.Monoid
155+
GHC.Internal.Data.NonEmpty
155156
GHC.Internal.Data.OldList
156157
GHC.Internal.Data.Ord
157158
GHC.Internal.Data.Proxy

libraries/ghc-internal/src/GHC/Internal/Base.hs

Lines changed: 8 additions & 28 deletions
Original file line numberDiff line numberDiff line change
@@ -17,7 +17,7 @@ GHC.Prim Has no implementation. It defines built-in things, and
1717
copied to make GHC.Prim.hi
1818
1919
GHC.Internal.Base Classes: Eq, Ord, Functor, Monad
20-
Types: List, (), Int, Bool, Ordering, Char, String
20+
Types: List, (), Int, Bool, Ordering, Char, String, NonEmpty
2121
2222
GHC.Internal.Data.Tuple Types: tuples, plus instances for GHC.Internal.Base classes
2323
@@ -29,6 +29,13 @@ GHC.Internal.Data.Maybe Type: Maybe, plus instances for GHC.Internal.Base c
2929
3030
GHC.Internal.List List functions
3131
32+
GHC.Internal.Data.NonEmpty Orphan instances for GHC.Internal.Base.NonEmpty of
33+
GHC.Internal.Base classes (other than Eq and Ord)
34+
plus function map
35+
36+
GHC.Internal.Data.List.NonEmpty Re-export GHC.Internal.Data.NonEmpty plus
37+
functions zip and zipWith
38+
3239
GHC.Internal.Num Class: Num, plus instances for Int
3340
Type: Integer, plus instances for all classes so far (Eq, Ord, Num, Show)
3441
@@ -753,12 +760,6 @@ needed to make foldr/build forms efficient are turned off, we'll get reasonably
753760
efficient translations anyway.
754761
-}
755762

756-
-- | @since base-4.9.0.0
757-
instance Semigroup (NonEmpty a) where
758-
(a :| as) <> bs = a :| (as ++ toList bs)
759-
where
760-
toList (c :| cs) = c : cs
761-
762763
-- | @since base-4.9.0.0
763764
instance Semigroup b => Semigroup (a -> b) where
764765
f <> g = \x -> f x <> g x
@@ -1709,27 +1710,6 @@ data NonEmpty a = a :| [a]
17091710
, Ord -- ^ @since base-4.9.0.0
17101711
)
17111712

1712-
-- | @since base-4.9.0.0
1713-
instance Functor NonEmpty where
1714-
fmap f (a :| as) = f a :| fmap f as
1715-
b <$ (_ :| as) = b :| (b <$ as)
1716-
1717-
-- | @since base-4.9.0.0
1718-
instance Applicative NonEmpty where
1719-
pure a = a :| []
1720-
(<*>) = ap
1721-
liftA2 = liftM2
1722-
1723-
-- | @since base-4.9.0.0
1724-
instance Monad NonEmpty where
1725-
(a :| as) >>= f =
1726-
case f a of
1727-
b :| bs -> b :| (bs ++ bs')
1728-
where
1729-
bs' = as >>= toList . f
1730-
toList (c :| cs) = c : cs
1731-
1732-
17331713
----------------------------------------------
17341714
-- The list type
17351715

libraries/ghc-internal/src/GHC/Internal/Control/Monad/Fix.hs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -32,9 +32,10 @@ import GHC.Internal.Data.Function ( fix )
3232
import GHC.Internal.Data.Maybe
3333
import GHC.Internal.Data.Monoid ( Monoid, Dual(..), Sum(..), Product(..)
3434
, First(..), Last(..), Alt(..), Ap(..) )
35+
import GHC.Internal.Data.NonEmpty ( NonEmpty(..) )
3536
import GHC.Internal.Data.Ord ( Down(..) )
3637
import GHC.Internal.Data.Tuple ( Solo(..), snd )
37-
import GHC.Internal.Base ( Monad, NonEmpty(..), errorWithoutStackTrace, (.) )
38+
import GHC.Internal.Base ( Monad, errorWithoutStackTrace, (.) )
3839
import GHC.Internal.Generics
3940
import GHC.Internal.List ( head, drop )
4041
import GHC.Internal.Control.Monad.ST.Imp

libraries/ghc-internal/src/GHC/Internal/Control/Monad/Zip.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -22,9 +22,9 @@ import GHC.Internal.Control.Monad (liftM, liftM2, Monad(..))
2222
import GHC.Internal.Data.Functor.Identity
2323
import qualified GHC.Internal.Data.Functor
2424
import GHC.Internal.Data.Monoid
25+
import GHC.Internal.Data.NonEmpty ( NonEmpty(..) )
2526
import GHC.Internal.Data.Ord ( Down(..) )
2627
import GHC.Internal.Data.Proxy
27-
import GHC.Internal.Base (NonEmpty(..))
2828
--import qualified Data.List.NonEmpty as NE
2929
import GHC.Internal.Generics
3030
import qualified GHC.Internal.Data.List.NonEmpty as NE

libraries/ghc-internal/src/GHC/Internal/Data/Data.hs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -115,11 +115,12 @@ import GHC.Internal.Data.Either
115115
import GHC.Internal.Data.Eq
116116
import GHC.Internal.Data.Maybe
117117
import GHC.Internal.Data.Monoid
118+
import GHC.Internal.Data.NonEmpty ( NonEmpty(..) )
118119
import GHC.Internal.Data.Ord
119120
import GHC.Internal.Data.List (findIndex)
120121
import GHC.Internal.Data.Typeable
121122
import GHC.Internal.Data.Version( Version(..) )
122-
import GHC.Internal.Base hiding (Any, IntRep, FloatRep)
123+
import GHC.Internal.Base hiding (Any, IntRep, FloatRep, NonEmpty(..))
123124
import GHC.Internal.List
124125
import GHC.Internal.Num
125126
import GHC.Internal.Read

libraries/ghc-internal/src/GHC/Internal/Data/Foldable.hs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1529,4 +1529,3 @@ the number of elements combined). The `mconcat` implementations for `Text` and
15291529
`ByteString` preallocate the required storage, and then combine all the list
15301530
elements in a single pass.
15311531
-}
1532-

libraries/ghc-internal/src/GHC/Internal/Data/List/NonEmpty.hs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -4,9 +4,10 @@ module GHC.Internal.Data.List.NonEmpty
44
( NonEmpty(..)
55
, zip
66
, zipWith
7+
, map
78
) where
89

9-
import GHC.Internal.Base
10+
import GHC.Internal.Data.NonEmpty (NonEmpty (..), map)
1011
import qualified GHC.Internal.Data.List as List
1112

1213
-- | The 'zip' function takes two streams and returns a stream of
Lines changed: 48 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,48 @@
1+
{-# LANGUAGE Trustworthy #-}
2+
{-# OPTIONS_GHC -Wno-orphans #-}
3+
4+
module GHC.Internal.Data.NonEmpty
5+
( NonEmpty (..)
6+
, map
7+
) where
8+
9+
import GHC.Internal.Base
10+
( Applicative (..), Functor (..), Monad (..), NonEmpty (..)
11+
, Semigroup (..), (++), (.), ap, liftM2
12+
)
13+
14+
-- The following were moved here from module Data.List.NonEmpty of the base
15+
-- package: map.
16+
17+
-- | Map a function over a 'NonEmpty' stream.
18+
map :: (a -> b) -> NonEmpty a -> NonEmpty b
19+
map f (a :| as) = f a :| fmap f as
20+
21+
-- The following orphan instances were moved here from module GHC.Internal.Base:
22+
-- Semigroup, Functor, Applicative and Monad.
23+
24+
-- | @since base-4.9.0.0
25+
instance Semigroup (NonEmpty a) where
26+
(a :| as) <> bs = a :| (as ++ toList bs)
27+
where
28+
toList (c :| cs) = c : cs
29+
30+
-- | @since base-4.9.0.0
31+
instance Functor NonEmpty where
32+
fmap = map
33+
b <$ (_ :| as) = b :| (b <$ as)
34+
35+
-- | @since base-4.9.0.0
36+
instance Applicative NonEmpty where
37+
pure a = a :| []
38+
(<*>) = ap
39+
liftA2 = liftM2
40+
41+
-- | @since base-4.9.0.0
42+
instance Monad NonEmpty where
43+
(a :| as) >>= f =
44+
case f a of
45+
b :| bs -> b :| (bs ++ bs')
46+
where
47+
bs' = as >>= toList . f
48+
toList (c :| cs) = c : cs

libraries/ghc-internal/src/GHC/Internal/Data/Traversable.hs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -486,4 +486,3 @@ foldMapDefault :: forall t m a . (Traversable t, Monoid m)
486486
{-# INLINE foldMapDefault #-}
487487
-- See Note [Function coercion] in Data.Functor.Utils.
488488
foldMapDefault = coerce (traverse @t @(Const m) @a @())
489-

libraries/ghc-internal/src/GHC/Internal/Generics.hs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1879,4 +1879,3 @@ instance SingKind DecidedStrictness where
18791879
fromSing SDecidedLazy = DecidedLazy
18801880
fromSing SDecidedStrict = DecidedStrict
18811881
fromSing SDecidedUnpack = DecidedUnpack
1882-

libraries/ghc-internal/src/GHC/Internal/TH/Lib.hs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -30,10 +30,11 @@ import Data.List.NonEmpty ( NonEmpty(..) )
3030
import GHC.Exts (TYPE)
3131
import Prelude hiding (Applicative(..))
3232
#else
33-
import GHC.Internal.Base hiding (Type, Module, inline)
33+
import GHC.Internal.Base hiding (NonEmpty (..), Type, Module, inline)
3434
import GHC.Internal.Data.Foldable
3535
import GHC.Internal.Data.Functor
3636
import GHC.Internal.Data.Maybe
37+
import GHC.Internal.Data.NonEmpty (NonEmpty(..))
3738
import GHC.Internal.Data.Traversable (traverse, sequenceA)
3839
import GHC.Internal.Integer
3940
import GHC.Internal.List (zip)

libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -50,8 +50,9 @@ import GHC.Internal.Lexeme ( startsVarSym, startsVarId )
5050
import GHC.Internal.Data.Either
5151
import GHC.Internal.Type.Reflection
5252
import GHC.Internal.Data.Bool
53-
import GHC.Internal.Base hiding (Type, Module, inline)
53+
import GHC.Internal.Base hiding (NonEmpty(..), Type, Module, inline)
5454
import GHC.Internal.Data.Foldable
55+
import GHC.Internal.Data.NonEmpty (NonEmpty(..))
5556
import GHC.Internal.Integer
5657
import GHC.Internal.Real
5758
import GHC.Internal.Word

libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -50,8 +50,9 @@ import Foreign.C.String
5050
import Foreign.C.Types
5151
import GHC.Types (TYPE, RuntimeRep(..))
5252
#else
53-
import GHC.Internal.Base hiding (Type, Module, sequence)
53+
import GHC.Internal.Base hiding (NonEmpty(..),Type, Module, sequence)
5454
import GHC.Internal.Data.Data hiding (Fixity(..))
55+
import GHC.Internal.Data.NonEmpty (NonEmpty(..))
5556
import GHC.Internal.Data.Traversable
5657
import GHC.Internal.Word
5758
import GHC.Internal.Generics (Generic)

libraries/ghc-internal/src/GHC/Internal/Text/ParserCombinators/ReadP.hs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -74,7 +74,8 @@ module GHC.Internal.Text.ParserCombinators.ReadP
7474

7575
import GHC.Internal.Unicode ( isSpace )
7676
import GHC.Internal.List ( replicate, null )
77-
import GHC.Internal.Base hiding ( many )
77+
import GHC.Internal.Base hiding ( NonEmpty (..), many )
78+
import GHC.Internal.Data.NonEmpty ( NonEmpty (..) )
7879

7980
import GHC.Internal.Control.Monad.Fail
8081

testsuite/tests/interface-stability/base-exports.stdout

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -11052,7 +11052,6 @@ instance forall (m :: * -> *). GHC.Internal.Base.Monad m => GHC.Internal.Base.Ap
1105211052
instance GHC.Internal.Base.Applicative GHC.Types.IO -- Defined in ‘GHC.Internal.Base’
1105311053
instance GHC.Internal.Base.Applicative [] -- Defined in ‘GHC.Internal.Base’
1105411054
instance GHC.Internal.Base.Applicative GHC.Internal.Maybe.Maybe -- Defined in ‘GHC.Internal.Base’
11055-
instance GHC.Internal.Base.Applicative GHC.Internal.Base.NonEmpty -- Defined in ‘GHC.Internal.Base’
1105611055
instance GHC.Internal.Base.Applicative Solo -- Defined in ‘GHC.Internal.Base’
1105711056
instance forall a. GHC.Internal.Base.Monoid a => GHC.Internal.Base.Applicative ((,) a) -- Defined in ‘GHC.Internal.Base’
1105811057
instance forall a b. (GHC.Internal.Base.Monoid a, GHC.Internal.Base.Monoid b) => GHC.Internal.Base.Applicative ((,,) a b) -- Defined in ‘GHC.Internal.Base’
@@ -11066,6 +11065,7 @@ instance forall s. GHC.Internal.Base.Applicative (GHC.Internal.Control.Monad.ST.
1106611065
instance GHC.Internal.Base.Applicative Data.Complex.Complex -- Defined in ‘Data.Complex’
1106711066
instance forall e. GHC.Internal.Base.Applicative (GHC.Internal.Data.Either.Either e) -- Defined in ‘GHC.Internal.Data.Either’
1106811067
instance GHC.Internal.Base.Applicative GHC.Internal.Data.Functor.Identity.Identity -- Defined in ‘GHC.Internal.Data.Functor.Identity’
11068+
instance GHC.Internal.Base.Applicative GHC.Internal.Base.NonEmpty -- Defined in ‘GHC.Internal.Data.NonEmpty’
1106911069
instance GHC.Internal.Base.Applicative GHC.Internal.Data.Semigroup.Internal.Dual -- Defined in ‘GHC.Internal.Data.Semigroup.Internal’
1107011070
instance GHC.Internal.Base.Applicative GHC.Internal.Data.Semigroup.Internal.Product -- Defined in ‘GHC.Internal.Data.Semigroup.Internal’
1107111071
instance GHC.Internal.Base.Applicative GHC.Internal.Data.Semigroup.Internal.Sum -- Defined in ‘GHC.Internal.Data.Semigroup.Internal’
@@ -11086,7 +11086,6 @@ instance forall (m :: * -> *). GHC.Internal.Base.Monad m => GHC.Internal.Base.Fu
1108611086
instance GHC.Internal.Base.Functor GHC.Types.IO -- Defined in ‘GHC.Internal.Base’
1108711087
instance GHC.Internal.Base.Functor [] -- Defined in ‘GHC.Internal.Base’
1108811088
instance GHC.Internal.Base.Functor GHC.Internal.Maybe.Maybe -- Defined in ‘GHC.Internal.Base’
11089-
instance GHC.Internal.Base.Functor GHC.Internal.Base.NonEmpty -- Defined in ‘GHC.Internal.Base’
1109011089
instance GHC.Internal.Base.Functor Solo -- Defined in ‘GHC.Internal.Base’
1109111090
instance forall a. GHC.Internal.Base.Functor ((,) a) -- Defined in ‘GHC.Internal.Base’
1109211091
instance forall a b. GHC.Internal.Base.Functor ((,,) a b) -- Defined in ‘GHC.Internal.Base’
@@ -11104,6 +11103,7 @@ instance forall s. GHC.Internal.Base.Functor (GHC.Internal.Control.Monad.ST.Lazy
1110411103
instance GHC.Internal.Base.Functor Data.Complex.Complex -- Defined in ‘Data.Complex’
1110511104
instance forall a. GHC.Internal.Base.Functor (GHC.Internal.Data.Either.Either a) -- Defined in ‘GHC.Internal.Data.Either’
1110611105
instance GHC.Internal.Base.Functor GHC.Internal.Data.Functor.Identity.Identity -- Defined in ‘GHC.Internal.Data.Functor.Identity’
11106+
instance GHC.Internal.Base.Functor GHC.Internal.Base.NonEmpty -- Defined in ‘GHC.Internal.Data.NonEmpty’
1110711107
instance GHC.Internal.Base.Functor GHC.Internal.Data.Semigroup.Internal.Dual -- Defined in ‘GHC.Internal.Data.Semigroup.Internal’
1110811108
instance GHC.Internal.Base.Functor GHC.Internal.Data.Semigroup.Internal.Product -- Defined in ‘GHC.Internal.Data.Semigroup.Internal’
1110911109
instance GHC.Internal.Base.Functor GHC.Internal.Data.Semigroup.Internal.Sum -- Defined in ‘GHC.Internal.Data.Semigroup.Internal’
@@ -11128,7 +11128,6 @@ instance forall (m :: * -> *). GHC.Internal.Base.Monad m => GHC.Internal.Base.Mo
1112811128
instance GHC.Internal.Base.Monad GHC.Types.IO -- Defined in ‘GHC.Internal.Base’
1112911129
instance GHC.Internal.Base.Monad [] -- Defined in ‘GHC.Internal.Base’
1113011130
instance GHC.Internal.Base.Monad GHC.Internal.Maybe.Maybe -- Defined in ‘GHC.Internal.Base’
11131-
instance GHC.Internal.Base.Monad GHC.Internal.Base.NonEmpty -- Defined in ‘GHC.Internal.Base’
1113211131
instance GHC.Internal.Base.Monad Solo -- Defined in ‘GHC.Internal.Base’
1113311132
instance forall a. GHC.Internal.Base.Monoid a => GHC.Internal.Base.Monad ((,) a) -- Defined in ‘GHC.Internal.Base’
1113411133
instance forall a b. (GHC.Internal.Base.Monoid a, GHC.Internal.Base.Monoid b) => GHC.Internal.Base.Monad ((,,) a b) -- Defined in ‘GHC.Internal.Base’
@@ -11141,6 +11140,7 @@ instance forall s. GHC.Internal.Base.Monad (GHC.Internal.Control.Monad.ST.Lazy.I
1114111140
instance GHC.Internal.Base.Monad Data.Complex.Complex -- Defined in ‘Data.Complex’
1114211141
instance forall e. GHC.Internal.Base.Monad (GHC.Internal.Data.Either.Either e) -- Defined in ‘GHC.Internal.Data.Either’
1114311142
instance GHC.Internal.Base.Monad GHC.Internal.Data.Functor.Identity.Identity -- Defined in ‘GHC.Internal.Data.Functor.Identity’
11143+
instance GHC.Internal.Base.Monad GHC.Internal.Base.NonEmpty -- Defined in ‘GHC.Internal.Data.NonEmpty’
1114411144
instance GHC.Internal.Base.Monad GHC.Internal.Data.Semigroup.Internal.Dual -- Defined in ‘GHC.Internal.Data.Semigroup.Internal’
1114511145
instance GHC.Internal.Base.Monad GHC.Internal.Data.Semigroup.Internal.Product -- Defined in ‘GHC.Internal.Data.Semigroup.Internal’
1114611146
instance GHC.Internal.Base.Monad GHC.Internal.Data.Semigroup.Internal.Sum -- Defined in ‘GHC.Internal.Data.Semigroup.Internal’
@@ -11218,7 +11218,6 @@ instance forall k (p :: k). GHC.Internal.Base.Monoid (GHC.Internal.Generics.U1 p
1121811218
instance forall a. GHC.Internal.Base.Semigroup a => GHC.Internal.Base.Semigroup (GHC.Types.IO a) -- Defined in ‘GHC.Internal.Base’
1121911219
instance forall a. GHC.Internal.Base.Semigroup [a] -- Defined in ‘GHC.Internal.Base’
1122011220
instance forall a. GHC.Internal.Base.Semigroup a => GHC.Internal.Base.Semigroup (GHC.Internal.Maybe.Maybe a) -- Defined in ‘GHC.Internal.Base’
11221-
instance forall a. GHC.Internal.Base.Semigroup (GHC.Internal.Base.NonEmpty a) -- Defined in ‘GHC.Internal.Base’
1122211221
instance GHC.Internal.Base.Semigroup GHC.Types.Ordering -- Defined in ‘GHC.Internal.Base’
1122311222
instance forall a. GHC.Internal.Base.Semigroup a => GHC.Internal.Base.Semigroup (Solo a) -- Defined in ‘GHC.Internal.Base’
1122411223
instance forall a b. (GHC.Internal.Base.Semigroup a, GHC.Internal.Base.Semigroup b) => GHC.Internal.Base.Semigroup (a, b) -- Defined in ‘GHC.Internal.Base’
@@ -11248,6 +11247,7 @@ instance forall a b. GHC.Internal.Base.Semigroup a => GHC.Internal.Base.Semigrou
1124811247
instance forall a. GHC.Internal.Base.Semigroup (Data.Functor.Contravariant.Predicate a) -- Defined in ‘Data.Functor.Contravariant’
1124911248
instance forall a. GHC.Internal.Base.Semigroup a => GHC.Internal.Base.Semigroup (GHC.Internal.Data.Functor.Identity.Identity a) -- Defined in ‘GHC.Internal.Data.Functor.Identity’
1125011249
instance [safe] forall k (f :: k -> *) (a :: k) (g :: k -> *). (GHC.Internal.Base.Semigroup (f a), GHC.Internal.Base.Semigroup (g a)) => GHC.Internal.Base.Semigroup (Data.Functor.Product.Product f g a) -- Defined in ‘Data.Functor.Product’
11250+
instance forall a. GHC.Internal.Base.Semigroup (GHC.Internal.Base.NonEmpty a) -- Defined in ‘GHC.Internal.Data.NonEmpty’
1125111251
instance GHC.Internal.Base.Semigroup GHC.Internal.Data.Semigroup.Internal.All -- Defined in ‘GHC.Internal.Data.Semigroup.Internal’
1125211252
instance GHC.Internal.Base.Semigroup GHC.Internal.Data.Semigroup.Internal.Any -- Defined in ‘GHC.Internal.Data.Semigroup.Internal’
1125311253
instance forall a. GHC.Internal.Base.Semigroup a => GHC.Internal.Base.Semigroup (GHC.Internal.Data.Semigroup.Internal.Dual a) -- Defined in ‘GHC.Internal.Data.Semigroup.Internal’

0 commit comments

Comments
 (0)