Use explicit language extensions & remove extension fields from base.cabal
[ghc-base.git] / GHC / List.lhs
index a52a1d4..ff8593c 100644 (file)
@@ -1,6 +1,7 @@
 \begin{code}
-{-# OPTIONS_GHC -fno-implicit-prelude #-}
+{-# LANGUAGE CPP, NoImplicitPrelude, MagicHash #-}
 {-# OPTIONS_HADDOCK hide #-}
+
 -----------------------------------------------------------------------------
 -- |
 -- Module      :  GHC.List
@@ -38,7 +39,6 @@ module GHC.List (
 
  ) where
 
-import Data.Tuple()     -- Instances
 import Data.Maybe
 import GHC.Base
 
@@ -58,6 +58,7 @@ head                    :: [a] -> a
 head (x:_)              =  x
 head []                 =  badHead
 
+badHead :: a
 badHead = errorEmptyList "head"
 
 -- This rule is useful in cases like 
@@ -89,7 +90,7 @@ last (x:xs)             =  last' x xs
 #endif
 
 -- | Return all the elements of a list except the last one.
--- The list must be finite and non-empty.
+-- The list must be non-empty.
 init                    :: [a] -> [a]
 #ifdef USE_REPORT_PRELUDE
 init [x]                =  []
@@ -108,7 +109,7 @@ null                    :: [a] -> Bool
 null []                 =  True
 null (_:_)              =  False
 
--- | 'length' returns the length of a finite list as an 'Int'.
+-- | /O(n)/. 'length' returns the length of a finite list as an 'Int'.
 -- It is an instance of the more general 'Data.List.genericLength',
 -- the result type of which may be any kind of number.
 length                  :: [a] -> Int
@@ -130,6 +131,7 @@ filter pred (x:xs)
   | otherwise      = filter pred xs
 
 {-# NOINLINE [0] filterFB #-}
+filterFB :: (a -> b -> b) -> (a -> Bool) -> a -> b -> b
 filterFB c p x r | p x       = x `c` r
                  | otherwise = r
 
@@ -162,7 +164,7 @@ filterFB c p x r | p x       = x `c` r
 -- and hence the classic space leak on foldl (+) 0 xs
 
 foldl        :: (a -> b -> a) -> a -> [b] -> a
-foldl f z xs = lgo z xs
+foldl f z0 xs0 = lgo z0 xs0
              where
                 lgo z []     =  z
                 lgo z (x:xs) = lgo (f z x) xs
@@ -213,8 +215,8 @@ scanr f q0 (x:xs)       =  f x q : qs
 -- | 'scanr1' is a variant of 'scanr' that has no starting value argument.
 
 scanr1                  :: (a -> a -> a) -> [a] -> [a]
-scanr1 f []             =  []
-scanr1 f [x]            =  [x]
+scanr1 _ []             =  []
+scanr1 _ [x]            =  [x]
 scanr1 f (x:xs)         =  f x q : qs
                            where qs@(q:_) = scanr1 f xs 
 
@@ -226,6 +228,7 @@ scanr1 f (x:xs)         =  f x q : qs
 iterate :: (a -> a) -> a -> [a]
 iterate f x =  x : iterate f (f x)
 
+iterateFB :: (a -> b -> b) -> (a -> a) -> a -> b
 iterateFB c f x = x `c` iterateFB c f (f x)
 
 
@@ -242,6 +245,7 @@ repeat :: a -> [a]
 repeat x = xs where xs = x : xs
 
 {-# INLINE [0] repeatFB #-}     -- ditto
+repeatFB :: (a -> b -> b) -> a -> b
 repeatFB c x = xs where xs = x `c` xs
 
 
@@ -500,11 +504,15 @@ or (x:xs)       =  x || or xs
 #endif
 
 -- | Applied to a predicate and a list, 'any' determines if any element
--- of the list satisfies the predicate.
+-- of the list satisfies the predicate.  For the result to be
+-- 'False', the list must be finite; 'True', however, results from a 'True'
+-- value for the predicate applied to an element at a finite index of a finite or infinite list.
 any                     :: (a -> Bool) -> [a] -> Bool
 
 -- | Applied to a predicate and a list, 'all' determines if all elements
--- of the list satisfy the predicate.
+-- of the list satisfy the predicate. For the result to be
+-- 'True', the list must be finite; 'False', however, results from a 'False'
+-- value for the predicate applied to an element at a finite index of a finite or infinite list.
 all                     :: (a -> Bool) -> [a] -> Bool
 #ifdef USE_REPORT_PRELUDE
 any p                   =  or . map p
@@ -524,7 +532,8 @@ all p (x:xs)    =  p x && all p xs
 #endif
 
 -- | 'elem' is the list membership predicate, usually written in infix form,
--- e.g., @x \`elem\` xs@.
+-- e.g., @x \`elem\` xs@.  For the result to be
+-- 'False', the list must be finite; 'True', however, results from an element equal to @x@ found at a finite index of a finite or infinite list.
 elem                    :: (Eq a) => a -> [a] -> Bool
 
 -- | 'notElem' is the negation of 'elem'.
@@ -578,8 +587,8 @@ xs     !! n | n < 0 =  error "Prelude.!!: negative index"
 -- The semantics is not quite the same for error conditions
 -- in the more efficient version.
 --
-xs !! (I# n) | n <# 0#   =  error "Prelude.(!!): negative index\n"
-             | otherwise =  sub xs n
+xs !! (I# n0) | n0 <# 0#   =  error "Prelude.(!!): negative index\n"
+               | otherwise =  sub xs n0
                          where
                             sub :: [a] -> Int# -> a
                             sub []     _ = error "Prelude.(!!): index too large\n"
@@ -597,13 +606,16 @@ xs !! (I# n) | n <# 0#   =  error "Prelude.(!!): negative index\n"
 %*********************************************************
 
 \begin{code}
+foldr2 :: (a -> b -> c -> c) -> c -> [a] -> [b] -> c
 foldr2 _k z []    _ys    = z
 foldr2 _k z _xs   []     = z
 foldr2 k z (x:xs) (y:ys) = k x y (foldr2 k z xs ys)
 
+foldr2_left :: (a -> b -> c -> d) -> d -> a -> ([b] -> c) -> [b] -> d
 foldr2_left _k  z _x _r []     = z
 foldr2_left  k _z  x  r (y:ys) = k x y (r ys)
 
+foldr2_right :: (a -> b -> c -> d) -> d -> b -> ([a] -> c) -> [a] -> d
 foldr2_right _k z  _y _r []     = z
 foldr2_right  k _z  y  r (x:xs) = k x y (r xs)
 
@@ -640,7 +652,8 @@ zip (a:as) (b:bs) = (a,b) : zip as bs
 zip _      _      = []
 
 {-# INLINE [0] zipFB #-}
-zipFB c x y r = (x,y) `c` r
+zipFB :: ((a, b) -> c -> d) -> a -> b -> c -> d
+zipFB c = \x y r -> (x,y) `c` r
 
 {-# RULES
 "zip"      [~1] forall xs ys. zip xs ys = build (\c n -> foldr2 (zipFB c) n xs ys)
@@ -673,8 +686,11 @@ zipWith :: (a->b->c) -> [a]->[b]->[c]
 zipWith f (a:as) (b:bs) = f a b : zipWith f as bs
 zipWith _ _      _      = []
 
+-- zipWithFB must have arity 2 since it gets two arguments in the "zipWith"
+-- rule; it might not get inlined otherwise
 {-# INLINE [0] zipWithFB #-}
-zipWithFB c f x y r = (x `f` y) `c` r
+zipWithFB :: (a -> b -> c) -> (d -> e -> a) -> d -> e -> b -> c
+zipWithFB c f = \x y r -> (x `f` y) `c` r
 
 {-# RULES
 "zipWith"       [~1] forall f xs ys.    zipWith f xs ys = build (\c n -> foldr2 (zipWithFB c f) n xs ys)