Tuple tycons have parens around their names
[ghc-base.git] / Data / List.hs
index 8b504f7..1c52b50 100644 (file)
@@ -35,6 +35,7 @@ module Data.List
    , reverse           -- :: [a] -> [a]
 
    , intersperse       -- :: a -> [a] -> [a]
+   , intercalate       -- :: [a] -> [[a]] -> [a]
    , transpose         -- :: [[a]] -> [[a]]
 
    -- * Reducing lists (folds)
@@ -92,6 +93,8 @@ module Data.List
    , span              -- :: (a -> Bool) -> [a] -> ([a], [a])
    , break             -- :: (a -> Bool) -> [a] -> ([a], [a])
 
+   , stripPrefix       -- :: Eq a => [a] -> [a] -> Maybe [a]
+
    , group             -- :: Eq a => [a] -> [[a]]
 
    , inits             -- :: [a] -> [[a]]
@@ -167,6 +170,10 @@ module Data.List
    -- ** The \"@By@\" operations
    -- | By convention, overloaded functions have a non-overloaded
    -- counterpart whose name is suffixed with \`@By@\'.
+   --
+   -- It is often convenient to use these functions together with
+   -- 'Data.Function.on', for instance @'sortBy' ('compare'
+   -- \`on\` 'fst')@.
 
    -- *** User-supplied equality (replacing an @Eq@ context)
    -- | The predicate is assumed to define an equivalence.
@@ -198,7 +205,7 @@ module Data.List
    ) where
 
 #ifdef __NHC__
-import Prelude hiding (Maybe(..))
+import Prelude
 #endif
 
 import Data.Maybe
@@ -216,6 +223,20 @@ infix 5 \\ -- comment to fool cpp
 -- -----------------------------------------------------------------------------
 -- List functions
 
+-- | The 'stripPrefix' function drops the given prefix from a list.
+-- It returns 'Nothing' if the list did not start with the prefix
+-- given, or 'Just' the list after the prefix, if it does.
+--
+-- > stripPrefix "foo" "foobar" -> Just "bar"
+-- > stripPrefix "foo" "foo" -> Just ""
+-- > stripPrefix "foo" "barfoo" -> Nothing
+-- > stripPrefix "foo" "barfoobaz" -> Nothing
+stripPrefix :: Eq a => [a] -> [a] -> Maybe [a]
+stripPrefix [] ys = Just ys
+stripPrefix (x:xs) (y:ys)
+ | x == y = stripPrefix xs ys
+stripPrefix _ _ = Nothing
+
 -- | The 'elemIndex' function returns the index of the first element
 -- in the given list which is equal (by '==') to the query element,
 -- or 'Nothing' if there is no such element.
@@ -276,7 +297,7 @@ isSuffixOf x y          =  reverse x `isPrefixOf` reverse y
 -- >isInfixOf "Haskell" "I really like Haskell." -> True
 -- >isInfixOf "Ial" "I really like Haskell." -> False
 isInfixOf               :: (Eq a) => [a] -> [a] -> Bool
-isInfixOf needle haystack = isJust $ find (isPrefixOf needle) (tails haystack)
+isInfixOf needle haystack = any (isPrefixOf needle) (tails haystack)
 
 -- | The 'nub' function removes duplicate elements from a list.
 -- In particular, it keeps only the first occurrence of each element.
@@ -396,6 +417,12 @@ intersperse _   []      = []
 intersperse _   [x]     = [x]
 intersperse sep (x:xs)  = x : sep : intersperse sep xs
 
+-- | 'intercalate' @xs xss@ is equivalent to @('concat' ('intersperse' xs xss))@.
+-- It inserts the list @xs@ in between the lists in @xss@ and concatenates the
+-- result.
+intercalate :: [a] -> [[a]] -> [a]
+intercalate xs xss = concat (intersperse xs xss)
+
 -- | The 'transpose' function transposes the rows and columns of its argument.
 -- For example,
 --
@@ -844,7 +871,12 @@ rqpart cmp x (y:ys) rle rgt r =
 --
 -- > f' (f x y) = Just (x,y)
 -- > f' z       = Nothing
-
+--
+-- A simple use of unfoldr:
+--
+-- > unfoldr (\b -> if b == 0 then Nothing else Just (b, b-1)) 10
+-- >  [10,9,8,7,6,5,4,3,2,1]
+--
 unfoldr      :: (b -> Maybe (a, b)) -> b -> [a]
 unfoldr f b  =
   case f b of
@@ -855,8 +887,14 @@ unfoldr f b  =
 
 -- | A strict version of 'foldl'.
 foldl'           :: (a -> b -> a) -> a -> [b] -> a
+#ifdef __GLASGOW_HASKELL__
+foldl' f z xs = lgo z xs
+    where lgo z []     = z
+          lgo z (x:xs) = let z' = f z x in z' `seq` lgo z' xs
+#else
 foldl' f a []     = a
 foldl' f a (x:xs) = let a' = f a x in a' `seq` foldl' f a' xs
+#endif
 
 #ifdef __GLASGOW_HASKELL__
 -- | 'foldl1' is a variant of 'foldl' that has no starting value argument,