Skip to content
Snippets Groups Projects
Commit 5aa5aac3 authored by Cheng Shao's avatar Cheng Shao
Browse files

Remove unused USE_REPORT_PRELUDE code paths from the tree

This patch removes unused `USE_REPORT_PRELUDE` code paths from the
tree. They have been present since the first git revision
4fb94ae5, and might have been useful
for debugging purposes many years ago, but these code paths are never
actually built. Removing these ease maintenance of relevant modules in
the future, and also allows us to get rid of `CPP` extension in those
modules as a nice byproduct.

(cherry picked from commit 573cad4b)
parent d492ae38
No related branches found
No related tags found
No related merge requests found
{-# LANGUAGE Trustworthy #-} {-# LANGUAGE Trustworthy #-}
{-# LANGUAGE CPP, NoImplicitPrelude, ScopedTypeVariables, {-# LANGUAGE NoImplicitPrelude, ScopedTypeVariables,
MagicHash, BangPatterns #-} MagicHash, BangPatterns #-}
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
...@@ -370,9 +370,6 @@ findIndex p = listToMaybe . findIndices p ...@@ -370,9 +370,6 @@ findIndex p = listToMaybe . findIndices p
-- >>> findIndices (\l -> length l > 3) ["a", "bcde", "fgh", "ijklmnop"] -- >>> findIndices (\l -> length l > 3) ["a", "bcde", "fgh", "ijklmnop"]
-- [1,3] -- [1,3]
findIndices :: (a -> Bool) -> [a] -> [Int] findIndices :: (a -> Bool) -> [a] -> [Int]
#if defined(USE_REPORT_PRELUDE)
findIndices p xs = [ i | (x,i) <- zip xs [0..], p x]
#else
-- Efficient definition, adapted from Data.Sequence -- Efficient definition, adapted from Data.Sequence
-- (Note that making this INLINABLE instead of INLINE allows -- (Note that making this INLINABLE instead of INLINE allows
-- 'findIndex' to fuse, fixing #15426.) -- 'findIndex' to fuse, fixing #15426.)
...@@ -381,7 +378,6 @@ findIndices p ls = build $ \c n -> ...@@ -381,7 +378,6 @@ findIndices p ls = build $ \c n ->
let go x r k | p x = I# k `c` r (k +# 1#) let go x r k | p x = I# k `c` r (k +# 1#)
| otherwise = r (k +# 1#) | otherwise = r (k +# 1#)
in foldr go (\_ -> n) ls 0# in foldr go (\_ -> n) ls 0#
#endif /* USE_REPORT_PRELUDE */
-- | \(\mathcal{O}(\min(m,n))\). The 'isPrefixOf' function takes two lists and -- | \(\mathcal{O}(\min(m,n))\). The 'isPrefixOf' function takes two lists and
-- returns 'True' iff the first list is a prefix of the second. -- returns 'True' iff the first list is a prefix of the second.
...@@ -540,10 +536,6 @@ nub = nubBy (==) ...@@ -540,10 +536,6 @@ nub = nubBy (==)
-- >>> nubBy (>) [1, 2, 3, 2, 1, 5, 4, 5, 3, 2] -- >>> nubBy (>) [1, 2, 3, 2, 1, 5, 4, 5, 3, 2]
-- [1,2,3,5,5] -- [1,2,3,5,5]
nubBy :: (a -> a -> Bool) -> [a] -> [a] nubBy :: (a -> a -> Bool) -> [a] -> [a]
#if defined(USE_REPORT_PRELUDE)
nubBy eq [] = []
nubBy eq (x:xs) = x : nubBy eq (filter (\ y -> not (eq x y)) xs)
#else
-- stolen from HBC -- stolen from HBC
nubBy eq l = nubBy' l [] nubBy eq l = nubBy' l []
where where
...@@ -562,7 +554,6 @@ nubBy eq l = nubBy' l [] ...@@ -562,7 +554,6 @@ nubBy eq l = nubBy' l []
elem_by :: (a -> a -> Bool) -> a -> [a] -> Bool elem_by :: (a -> a -> Bool) -> a -> [a] -> Bool
elem_by _ _ [] = False elem_by _ _ [] = False
elem_by eq y (x:xs) = x `eq` y || elem_by eq y xs elem_by eq y (x:xs) = x `eq` y || elem_by eq y xs
#endif
-- | \(\mathcal{O}(n)\). 'delete' @x@ removes the first occurrence of @x@ from -- | \(\mathcal{O}(n)\). 'delete' @x@ removes the first occurrence of @x@ from
...@@ -1620,10 +1611,6 @@ sort :: (Ord a) => [a] -> [a] ...@@ -1620,10 +1611,6 @@ sort :: (Ord a) => [a] -> [a]
-- [(1,"Hello"),(2,"world"),(4,"!")] -- [(1,"Hello"),(2,"world"),(4,"!")]
sortBy :: (a -> a -> Ordering) -> [a] -> [a] sortBy :: (a -> a -> Ordering) -> [a] -> [a]
#if defined(USE_REPORT_PRELUDE)
sort = sortBy compare
sortBy cmp = foldr (insertBy cmp) []
#else
{- {-
GHC's mergesort replaced by a better implementation, 24/12/2009. GHC's mergesort replaced by a better implementation, 24/12/2009.
...@@ -1772,8 +1759,6 @@ rqpart cmp x (y:ys) rle rgt r = ...@@ -1772,8 +1759,6 @@ rqpart cmp x (y:ys) rle rgt r =
_ -> rqpart cmp x ys (y:rle) rgt r _ -> rqpart cmp x ys (y:rle) rgt r
-} -}
#endif /* USE_REPORT_PRELUDE */
-- | Sort a list by comparing the results of a key function applied to each -- | Sort a list by comparing the results of a key function applied to each
-- element. @'sortOn' f@ is equivalent to @'sortBy' ('comparing' f)@, but has the -- element. @'sortOn' f@ is equivalent to @'sortBy' ('comparing' f)@, but has the
-- performance advantage of only evaluating @f@ once for each element in the -- performance advantage of only evaluating @f@ once for each element in the
...@@ -1943,14 +1928,10 @@ lines s = cons (case break (== '\n') s of ...@@ -1943,14 +1928,10 @@ lines s = cons (case break (== '\n') s of
-- >>> unlines . lines $ "foo\nbar" -- >>> unlines . lines $ "foo\nbar"
-- "foo\nbar\n" -- "foo\nbar\n"
unlines :: [String] -> String unlines :: [String] -> String
#if defined(USE_REPORT_PRELUDE)
unlines = concatMap (++ "\n")
#else
-- HBC version (stolen) -- HBC version (stolen)
-- here's a more efficient version -- here's a more efficient version
unlines [] = [] unlines [] = []
unlines (l:ls) = l ++ '\n' : unlines ls unlines (l:ls) = l ++ '\n' : unlines ls
#endif
-- | 'words' breaks a string up into a list of words, which were delimited -- | 'words' breaks a string up into a list of words, which were delimited
-- by white space (as defined by 'isSpace'). This function trims any white spaces -- by white space (as defined by 'isSpace'). This function trims any white spaces
...@@ -2001,10 +1982,6 @@ wordsFB c n = go ...@@ -2001,10 +1982,6 @@ wordsFB c n = go
-- >>> unwords ["foo", "bar", "", "baz"] -- >>> unwords ["foo", "bar", "", "baz"]
-- "foo bar baz" -- "foo bar baz"
unwords :: [String] -> String unwords :: [String] -> String
#if defined(USE_REPORT_PRELUDE)
unwords [] = ""
unwords ws = foldr1 (\w s -> w ++ ' ':s) ws
#else
-- Here's a lazier version that can get the last element of a -- Here's a lazier version that can get the last element of a
-- _|_-terminated list. -- _|_-terminated list.
{-# NOINLINE [1] unwords #-} {-# NOINLINE [1] unwords #-}
...@@ -2034,7 +2011,6 @@ tailUnwords (_:xs) = xs ...@@ -2034,7 +2011,6 @@ tailUnwords (_:xs) = xs
{-# INLINE [0] unwordsFB #-} {-# INLINE [0] unwordsFB #-}
unwordsFB :: String -> String -> String unwordsFB :: String -> String -> String
unwordsFB w r = ' ' : w ++ r unwordsFB w r = ' ' : w ++ r
#endif
{- A "SnocBuilder" is a version of Chris Okasaki's banker's queue that supports {- A "SnocBuilder" is a version of Chris Okasaki's banker's queue that supports
toListSB instead of uncons. In single-threaded use, its performance toListSB instead of uncons. In single-threaded use, its performance
......
{-# LANGUAGE Trustworthy #-} {-# LANGUAGE Trustworthy #-}
{-# LANGUAGE CPP, NoImplicitPrelude, ScopedTypeVariables #-} {-# LANGUAGE NoImplicitPrelude, ScopedTypeVariables #-}
{-# LANGUAGE BangPatterns #-} {-# LANGUAGE BangPatterns #-}
{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} {-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}
...@@ -196,11 +196,6 @@ tail [] = errorEmptyList "tail" ...@@ -196,11 +196,6 @@ tail [] = errorEmptyList "tail"
-- >>> last [] -- >>> last []
-- *** Exception: Prelude.last: empty list -- *** Exception: Prelude.last: empty list
last :: HasCallStack => [a] -> a last :: HasCallStack => [a] -> a
#if defined(USE_REPORT_PRELUDE)
last [x] = x
last (_:xs) = last xs
last [] = errorEmptyList "last"
#else
-- Use foldl to make last a good consumer. -- Use foldl to make last a good consumer.
-- This will compile to good code for the actual GHC.List.last. -- This will compile to good code for the actual GHC.List.last.
-- (At least as long it is eta-expanded, otherwise it does not, #10260.) -- (At least as long it is eta-expanded, otherwise it does not, #10260.)
...@@ -210,7 +205,6 @@ last xs = foldl (\_ x -> x) lastError xs ...@@ -210,7 +205,6 @@ last xs = foldl (\_ x -> x) lastError xs
-- foldl. -- foldl.
lastError :: HasCallStack => a lastError :: HasCallStack => a
lastError = errorEmptyList "last" lastError = errorEmptyList "last"
#endif
-- | \(\mathcal{O}(n)\). Return all the elements of a list except the last one. -- | \(\mathcal{O}(n)\). Return all the elements of a list except the last one.
-- The list must be non-empty. -- The list must be non-empty.
...@@ -228,17 +222,11 @@ lastError = errorEmptyList "last" ...@@ -228,17 +222,11 @@ lastError = errorEmptyList "last"
-- >>> init [] -- >>> init []
-- *** Exception: Prelude.init: empty list -- *** Exception: Prelude.init: empty list
init :: HasCallStack => [a] -> [a] init :: HasCallStack => [a] -> [a]
#if defined(USE_REPORT_PRELUDE)
init [x] = []
init (x:xs) = x : init xs
init [] = errorEmptyList "init"
#else
-- eliminate repeated cases -- eliminate repeated cases
init [] = errorEmptyList "init" init [] = errorEmptyList "init"
init (x:xs) = init' x xs init (x:xs) = init' x xs
where init' _ [] = [] where init' _ [] = []
init' y (z:zs) = y : init' z zs init' y (z:zs) = y : init' z zs
#endif
-- | \(\mathcal{O}(1)\). Test whether a list is empty. -- | \(\mathcal{O}(1)\). Test whether a list is empty.
-- --
...@@ -1073,11 +1061,6 @@ dropWhile p xs@(x:xs') ...@@ -1073,11 +1061,6 @@ dropWhile p xs@(x:xs')
-- >>> take 0 [1,2] -- >>> take 0 [1,2]
-- [] -- []
take :: Int -> [a] -> [a] take :: Int -> [a] -> [a]
#if defined(USE_REPORT_PRELUDE)
take n _ | n <= 0 = []
take _ [] = []
take n (x:xs) = x : take (n-1) xs
#else
{- We always want to inline this to take advantage of a known length argument {- We always want to inline this to take advantage of a known length argument
sign. Note, however, that it's important for the RULES to grab take, rather sign. Note, however, that it's important for the RULES to grab take, rather
...@@ -1123,7 +1106,6 @@ takeFB c n x xs ...@@ -1123,7 +1106,6 @@ takeFB c n x xs
= \ m -> case m of = \ m -> case m of
1 -> x `c` n 1 -> x `c` n
_ -> x `c` xs (m - 1) _ -> x `c` xs (m - 1)
#endif
-- | 'drop' @n xs@ returns the suffix of @xs@ -- | 'drop' @n xs@ returns the suffix of @xs@
-- after the first @n@ elements, or @[]@ if @n >= 'length' xs@. -- after the first @n@ elements, or @[]@ if @n >= 'length' xs@.
...@@ -1151,11 +1133,6 @@ takeFB c n x xs ...@@ -1151,11 +1133,6 @@ takeFB c n x xs
-- >>> drop 0 [1,2] -- >>> drop 0 [1,2]
-- [1,2] -- [1,2]
drop :: Int -> [a] -> [a] drop :: Int -> [a] -> [a]
#if defined(USE_REPORT_PRELUDE)
drop n xs | n <= 0 = xs
drop _ [] = []
drop n (_:xs) = drop (n-1) xs
#else /* hack away */
{-# INLINE drop #-} {-# INLINE drop #-}
drop n ls drop n ls
| n <= 0 = ls | n <= 0 = ls
...@@ -1167,7 +1144,6 @@ drop n ls ...@@ -1167,7 +1144,6 @@ drop n ls
unsafeDrop !_ [] = [] unsafeDrop !_ [] = []
unsafeDrop 1 (_:xs) = xs unsafeDrop 1 (_:xs) = xs
unsafeDrop m (_:xs) = unsafeDrop (m - 1) xs unsafeDrop m (_:xs) = unsafeDrop (m - 1) xs
#endif
-- | 'splitAt' @n xs@ returns a tuple where first element is @xs@ prefix of -- | 'splitAt' @n xs@ returns a tuple where first element is @xs@ prefix of
-- length @n@ and second element is the remainder of the list: -- length @n@ and second element is the remainder of the list:
...@@ -1213,9 +1189,6 @@ drop n ls ...@@ -1213,9 +1189,6 @@ drop n ls
-- ([],[1,2,3]) -- ([],[1,2,3])
splitAt :: Int -> [a] -> ([a],[a]) splitAt :: Int -> [a] -> ([a],[a])
#if defined(USE_REPORT_PRELUDE)
splitAt n xs = (take n xs, drop n xs)
#else
splitAt n ls splitAt n ls
| n <= 0 = ([], ls) | n <= 0 = ([], ls)
| otherwise = splitAt' n ls | otherwise = splitAt' n ls
...@@ -1226,7 +1199,6 @@ splitAt n ls ...@@ -1226,7 +1199,6 @@ splitAt n ls
splitAt' m (x:xs) = (x:xs', xs'') splitAt' m (x:xs) = (x:xs', xs'')
where where
(xs', xs'') = splitAt' (m - 1) xs (xs', xs'') = splitAt' (m - 1) xs
#endif /* USE_REPORT_PRELUDE */
-- | 'span', applied to a predicate @p@ and a list @xs@, returns a tuple where -- | 'span', applied to a predicate @p@ and a list @xs@, returns a tuple where
-- first element is the longest prefix (possibly empty) of @xs@ of elements that -- first element is the longest prefix (possibly empty) of @xs@ of elements that
...@@ -1304,15 +1276,11 @@ span p xs@(x:xs') ...@@ -1304,15 +1276,11 @@ span p xs@(x:xs')
-- >>> break (> 9) [1,2,3] -- >>> break (> 9) [1,2,3]
-- ([1,2,3],[]) -- ([1,2,3],[])
break :: (a -> Bool) -> [a] -> ([a],[a]) break :: (a -> Bool) -> [a] -> ([a],[a])
#if defined(USE_REPORT_PRELUDE)
break p = span (not . p)
#else
-- HBC version (stolen) -- HBC version (stolen)
break _ xs@[] = (xs, xs) break _ xs@[] = (xs, xs)
break p xs@(x:xs') break p xs@(x:xs')
| p x = ([],xs) | p x = ([],xs)
| otherwise = let (ys,zs) = break p xs' in (x:ys,zs) | otherwise = let (ys,zs) = break p xs' in (x:ys,zs)
#endif
-- | \(\mathcal{O}(n)\). 'reverse' @xs@ returns the elements of @xs@ in reverse order. -- | \(\mathcal{O}(n)\). 'reverse' @xs@ returns the elements of @xs@ in reverse order.
-- @xs@ must be finite. -- @xs@ must be finite.
...@@ -1341,14 +1309,10 @@ break p xs@(x:xs') ...@@ -1341,14 +1309,10 @@ break p xs@(x:xs')
-- >>> reverse [1..] -- >>> reverse [1..]
-- * Hangs forever * -- * Hangs forever *
reverse :: [a] -> [a] reverse :: [a] -> [a]
#if defined(USE_REPORT_PRELUDE)
reverse = foldl (flip (:)) []
#else
reverse l = rev l [] reverse l = rev l []
where where
rev [] a = a rev [] a = a
rev (x:xs) a = rev xs (x:a) rev (x:xs) a = rev xs (x:a)
#endif
-- | 'and' returns the conjunction of a Boolean list. For the result to be -- | 'and' returns the conjunction of a Boolean list. For the result to be
-- 'True', the list must be finite; 'False', however, results from a 'False' -- 'True', the list must be finite; 'False', however, results from a 'False'
...@@ -1374,9 +1338,6 @@ reverse l = rev l [] ...@@ -1374,9 +1338,6 @@ reverse l = rev l []
-- >>> and (repeat True) -- >>> and (repeat True)
-- * Hangs forever * -- * Hangs forever *
and :: [Bool] -> Bool and :: [Bool] -> Bool
#if defined(USE_REPORT_PRELUDE)
and = foldr (&&) True
#else
and [] = True and [] = True
and (x:xs) = x && and xs and (x:xs) = x && and xs
{-# NOINLINE [1] and #-} {-# NOINLINE [1] and #-}
...@@ -1385,7 +1346,6 @@ and (x:xs) = x && and xs ...@@ -1385,7 +1346,6 @@ and (x:xs) = x && and xs
"and/build" forall (g::forall b.(Bool->b->b)->b->b) . "and/build" forall (g::forall b.(Bool->b->b)->b->b) .
and (build g) = g (&&) True and (build g) = g (&&) True
#-} #-}
#endif
-- | 'or' returns the disjunction of a Boolean list. For the result to be -- | 'or' returns the disjunction of a Boolean list. For the result to be
-- 'False', the list must be finite; 'True', however, results from a 'True' -- 'False', the list must be finite; 'True', however, results from a 'True'
...@@ -1411,9 +1371,6 @@ and (x:xs) = x && and xs ...@@ -1411,9 +1371,6 @@ and (x:xs) = x && and xs
-- >>> or (repeat False) -- >>> or (repeat False)
-- * Hangs forever * -- * Hangs forever *
or :: [Bool] -> Bool or :: [Bool] -> Bool
#if defined(USE_REPORT_PRELUDE)
or = foldr (||) False
#else
or [] = False or [] = False
or (x:xs) = x || or xs or (x:xs) = x || or xs
{-# NOINLINE [1] or #-} {-# NOINLINE [1] or #-}
...@@ -1422,7 +1379,6 @@ or (x:xs) = x || or xs ...@@ -1422,7 +1379,6 @@ or (x:xs) = x || or xs
"or/build" forall (g::forall b.(Bool->b->b)->b->b) . "or/build" forall (g::forall b.(Bool->b->b)->b->b) .
or (build g) = g (||) False or (build g) = g (||) False
#-} #-}
#endif
-- | Applied to a predicate and a list, 'any' determines if any element -- | Applied to a predicate and a list, 'any' determines if any element
-- of the list satisfies the predicate. For the result to be -- of the list satisfies the predicate. For the result to be
...@@ -1447,9 +1403,6 @@ or (x:xs) = x || or xs ...@@ -1447,9 +1403,6 @@ or (x:xs) = x || or xs
-- >>> any (> 3) [0, -1..] -- >>> any (> 3) [0, -1..]
-- * Hangs forever * -- * Hangs forever *
any :: (a -> Bool) -> [a] -> Bool any :: (a -> Bool) -> [a] -> Bool
#if defined(USE_REPORT_PRELUDE)
any p = or . map p
#else
any _ [] = False any _ [] = False
any p (x:xs) = p x || any p xs any p (x:xs) = p x || any p xs
...@@ -1459,7 +1412,6 @@ any p (x:xs) = p x || any p xs ...@@ -1459,7 +1412,6 @@ any p (x:xs) = p x || any p xs
"any/build" forall p (g::forall b.(a->b->b)->b->b) . "any/build" forall p (g::forall b.(a->b->b)->b->b) .
any p (build g) = g ((||) . p) False any p (build g) = g ((||) . p) False
#-} #-}
#endif
-- | Applied to a predicate and a list, 'all' determines if all elements -- | Applied to a predicate and a list, 'all' determines if all elements
-- of the list satisfy the predicate. For the result to be -- of the list satisfy the predicate. For the result to be
...@@ -1484,9 +1436,6 @@ any p (x:xs) = p x || any p xs ...@@ -1484,9 +1436,6 @@ any p (x:xs) = p x || any p xs
-- >>> all (> 3) [4..] -- >>> all (> 3) [4..]
-- * Hangs forever * -- * Hangs forever *
all :: (a -> Bool) -> [a] -> Bool all :: (a -> Bool) -> [a] -> Bool
#if defined(USE_REPORT_PRELUDE)
all p = and . map p
#else
all _ [] = True all _ [] = True
all p (x:xs) = p x && all p xs all p (x:xs) = p x && all p xs
...@@ -1496,7 +1445,6 @@ all p (x:xs) = p x && all p xs ...@@ -1496,7 +1445,6 @@ all p (x:xs) = p x && all p xs
"all/build" forall p (g::forall b.(a->b->b)->b->b) . "all/build" forall p (g::forall b.(a->b->b)->b->b) .
all p (build g) = g ((&&) . p) True all p (build g) = g ((&&) . p) True
#-} #-}
#endif
-- | 'elem' is the list membership predicate, usually written in infix form, -- | 'elem' is the list membership predicate, usually written in infix form,
-- e.g., @x \`elem\` xs@. For the result to be -- e.g., @x \`elem\` xs@. For the result to be
...@@ -1520,9 +1468,6 @@ all p (x:xs) = p x && all p xs ...@@ -1520,9 +1468,6 @@ all p (x:xs) = p x && all p xs
-- >>> 3 `elem` [4..] -- >>> 3 `elem` [4..]
-- * Hangs forever * -- * Hangs forever *
elem :: (Eq a) => a -> [a] -> Bool elem :: (Eq a) => a -> [a] -> Bool
#if defined(USE_REPORT_PRELUDE)
elem x = any (== x)
#else
elem _ [] = False elem _ [] = False
elem x (y:ys) = x==y || elem x ys elem x (y:ys) = x==y || elem x ys
{-# NOINLINE [1] elem #-} {-# NOINLINE [1] elem #-}
...@@ -1530,7 +1475,6 @@ elem x (y:ys) = x==y || elem x ys ...@@ -1530,7 +1475,6 @@ elem x (y:ys) = x==y || elem x ys
"elem/build" forall x (g :: forall b . (a -> b -> b) -> b -> b) "elem/build" forall x (g :: forall b . (a -> b -> b) -> b -> b)
. elem x (build g) = g (\ y r -> (x == y) || r) False . elem x (build g) = g (\ y r -> (x == y) || r) False
#-} #-}
#endif
-- | 'notElem' is the negation of 'elem'. -- | 'notElem' is the negation of 'elem'.
-- --
...@@ -1551,9 +1495,6 @@ elem x (y:ys) = x==y || elem x ys ...@@ -1551,9 +1495,6 @@ elem x (y:ys) = x==y || elem x ys
-- >>> 3 `notElem` [4..] -- >>> 3 `notElem` [4..]
-- * Hangs forever * -- * Hangs forever *
notElem :: (Eq a) => a -> [a] -> Bool notElem :: (Eq a) => a -> [a] -> Bool
#if defined(USE_REPORT_PRELUDE)
notElem x = all (/= x)
#else
notElem _ [] = True notElem _ [] = True
notElem x (y:ys)= x /= y && notElem x ys notElem x (y:ys)= x /= y && notElem x ys
{-# NOINLINE [1] notElem #-} {-# NOINLINE [1] notElem #-}
...@@ -1561,7 +1502,6 @@ notElem x (y:ys)= x /= y && notElem x ys ...@@ -1561,7 +1502,6 @@ notElem x (y:ys)= x /= y && notElem x ys
"notElem/build" forall x (g :: forall b . (a -> b -> b) -> b -> b) "notElem/build" forall x (g :: forall b . (a -> b -> b) -> b -> b)
. notElem x (build g) = g (\ y r -> (x /= y) && r) True . notElem x (build g) = g (\ y r -> (x /= y) && r) True
#-} #-}
#endif
-- | \(\mathcal{O}(n)\). 'lookup' @key assocs@ looks up a key in an association -- | \(\mathcal{O}(n)\). 'lookup' @key assocs@ looks up a key in an association
-- list. -- list.
...@@ -1654,14 +1594,6 @@ concat = foldr (++) [] ...@@ -1654,14 +1594,6 @@ concat = foldr (++) []
-- --
-- >>> ['a', 'b', 'c'] !! (-1) -- >>> ['a', 'b', 'c'] !! (-1)
-- *** Exception: Prelude.!!: negative index -- *** Exception: Prelude.!!: negative index
#if defined(USE_REPORT_PRELUDE)
(!!) :: [a] -> Int -> a
xs !! n | n < 0 = errorWithoutStackTrace "Prelude.!!: negative index"
[] !! _ = errorWithoutStackTrace "Prelude.!!: index too large"
(x:_) !! 0 = x
(_:xs) !! n = xs !! (n-1)
-- Prelude version is without HasCallStack to avoid building linear one
#else
(!!) :: HasCallStack => [a] -> Int -> a (!!) :: HasCallStack => [a] -> Int -> a
-- We don't really want the errors to inline with (!!). -- We don't really want the errors to inline with (!!).
...@@ -1680,7 +1612,6 @@ xs !! n ...@@ -1680,7 +1612,6 @@ xs !! n
| otherwise = foldr (\x r k -> case k of | otherwise = foldr (\x r k -> case k of
0 -> x 0 -> x
_ -> r (k-1)) tooLarge xs n _ -> r (k-1)) tooLarge xs n
#endif
-- | List index (subscript) operator, starting from 0. Returns 'Nothing' -- | List index (subscript) operator, starting from 0. Returns 'Nothing'
-- if the index is out of bounds -- if the index is out of bounds
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment