[commit: ghc] master: Remove Data.List.NonEmpty.{words, unwords, lines, unlines} (8f02baa)
git at git.haskell.org
git at git.haskell.org
Sat Oct 31 21:28:55 UTC 2015
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/8f02baac9ea3d8cf8dfbadd2bc3af799ddbc0367/ghc
>---------------------------------------------------------------
commit 8f02baac9ea3d8cf8dfbadd2bc3af799ddbc0367
Author: Herbert Valerio Riedel <hvr at gnu.org>
Date: Sat Oct 31 21:55:26 2015 +0100
Remove Data.List.NonEmpty.{words,unwords,lines,unlines}
This change mirrors the change that occured for the recent
`semigroups-0.18` release, i.e.
https://github.com/ekmett/semigroups/commit/7a000212847b0d309892f34e4754a25ddec7100b
This removal addresses concerns raised in #10365
>---------------------------------------------------------------
8f02baac9ea3d8cf8dfbadd2bc3af799ddbc0367
libraries/base/Data/List/NonEmpty.hs | 37 +++---------------------------------
1 file changed, 3 insertions(+), 34 deletions(-)
diff --git a/libraries/base/Data/List/NonEmpty.hs b/libraries/base/Data/List/NonEmpty.hs
index d8bad07..9bcdcbf 100644
--- a/libraries/base/Data/List/NonEmpty.hs
+++ b/libraries/base/Data/List/NonEmpty.hs
@@ -85,11 +85,6 @@ module Data.List.NonEmpty (
, zip -- :: NonEmpty a -> NonEmpty b -> NonEmpty (a,b)
, zipWith -- :: (a -> b -> c) -> NonEmpty a -> NonEmpty b -> NonEmpty c
, unzip -- :: NonEmpty (a, b) -> (NonEmpty a, NonEmpty b)
- -- * Functions on streams of characters
- , words -- :: NonEmpty Char -> NonEmpty String
- , unwords -- :: NonEmpty String -> NonEmpty Char
- , lines -- :: NonEmpty Char -> NonEmpty String
- , unlines -- :: NonEmpty String -> NonEmpty Char
-- * Converting to and from a list
, fromList -- :: [a] -> NonEmpty a
, toList -- :: NonEmpty a -> [a]
@@ -100,10 +95,10 @@ module Data.List.NonEmpty (
import Prelude hiding (break, cycle, drop, dropWhile,
filter, foldl, foldr, head, init, iterate,
- last, length, lines, map, repeat, reverse,
+ last, length, map, repeat, reverse,
scanl, scanl1, scanr, scanr1, span,
- splitAt, tail, take, takeWhile, unlines,
- unwords, unzip, words, zip, zipWith, (!!))
+ splitAt, tail, take, takeWhile,
+ unzip, zip, zipWith, (!!))
import qualified Prelude
import Control.Applicative (Alternative, many)
@@ -462,32 +457,6 @@ zipWith f ~(x :| xs) ~(y :| ys) = f x y :| List.zipWith f xs ys
unzip :: Functor f => f (a,b) -> (f a, f b)
unzip xs = (fst <$> xs, snd <$> xs)
--- | The 'words' function breaks a stream of characters into a
--- stream of words, which were delimited by white space.
---
--- /Beware/: if the input contains no words (i.e. is entirely
--- whitespace), this will cause an error.
-words :: NonEmpty Char -> NonEmpty String
-words = lift List.words
-
--- | The 'unwords' function is an inverse operation to 'words'. It
--- joins words with separating spaces.
---
--- /Beware/: the input @(\"\" :| [])@ will cause an error.
-unwords :: NonEmpty String -> NonEmpty Char
-unwords = lift List.unwords
-
--- | The 'lines' function breaks a stream of characters into a stream
--- of strings at newline characters. The resulting strings do not
--- contain newlines.
-lines :: NonEmpty Char -> NonEmpty String
-lines = lift List.lines
-
--- | The 'unlines' function is an inverse operation to 'lines'. It
--- joins lines, after appending a terminating newline to each.
-unlines :: NonEmpty String -> NonEmpty Char
-unlines = lift List.unlines
-
-- | The 'nub' function removes duplicate elements from a list. In
-- particular, it keeps only the first occurence of each element.
-- (The name 'nub' means \'essence\'.)
More information about the ghc-commits
mailing list