Skip to content

Commit 2d62b97

Browse files
mpilgremMarge Bot
authored andcommitted
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-

0 commit comments

Comments
 (0)