doc wibble
[ghc-base.git] / GHC / List.lhs
index 5dcf7e0..67c651e 100644 (file)
@@ -108,7 +108,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
@@ -647,7 +647,7 @@ zip _      _      = []
 
 {-# INLINE [0] zipFB #-}
 zipFB :: ((a, b) -> c -> d) -> a -> b -> c -> d
-zipFB c x y r = (x,y) `c` r
+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)
@@ -680,9 +680,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 :: (a -> b -> c) -> (d -> e -> a) -> d -> e -> b -> c
-zipWithFB c f x y r = (x `f` y) `c` r
+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)