{-# LANGUAGE TypeFamilies         #-}
{-# LANGUAGE BangPatterns         #-}
{-# LANGUAGE FlexibleContexts     #-}
{-# LANGUAGE FlexibleInstances    #-}
{-# LANGUAGE OverlappingInstances #-}

-- |
-- Module      : Data.Adaptive.List
-- Copyright   : (c) Duncan Coutts 2007
--               (c) Don Stewart   2007 .. 2009
-- License     : BSD-style
-- Maintainer  : dons@galois.com
-- Stability   : experimental
--
-- Self adapting polymorphic lists.
--
-- This library statically specializes the polymorphic container
-- representation of lists to specific, more efficient representations,
-- when instantiated with particular monomorphic types. It does this via
-- an associated more efficient data type for each pair of elements you
-- wish to store in your container.
--
-- The resulting list structures use less space, and functions on them tend to
-- be faster, than regular lists.
--
-- Instead of representing '[1..5] :: [Int]' as:
--
-- >      (:) 
-- >     /   \
-- >    /     \
-- > I# 1#    (:)
-- >         /   \
-- >        /     \
-- >     I# 2#    (:)
-- >             /   \
-- >            /     \
-- >         I# 3#    []
--
-- The compiler will select an associated data type that packs better,
-- via the class instances, resulting in:
--
-- >   ConsInt 1#
-- >    |
-- >   ConsInt 2#
-- >    |
-- >   ConsInt 3#
-- >    |
-- >    []
--
-- The user however, still sees a polymorphic list type.
--
-- This list type currently doesn't fuse.
--
module Data.Adaptive.List where

import Data.Adaptive.Tuple

import qualified Prelude
import Prelude (Eq(..),Ord(..),Ordering(..), (.)
               ,Int,Char,Float,Double,Integer,Bool(..),otherwise,(-))
import Data.Int
import Data.Word

-- * The adaptive list class-associated type
--
-- | Representation-improving polymorphic lists.
--
class AdaptList a where

    data List a

    -- | The empty list
    empty   :: List a

    -- | Prepend a value onto a list
    cons    :: a -> List a -> List a

    -- | Is the list empty?
    null    :: List a -> Bool

    -- | The first element of the list
    head    :: List a -> a

    -- | The tail of the list
    tail    :: List a -> List a

------------------------------------------------------------------------
-- * Basic Interface

infixr 5 ++
infixr 5 :
-- infix  5 \\ -- comment to fool cpp
-- infixl 9 !!
infix  4 `elem`, `notElem`

-- | /O(n)/, convert an adaptive list to a regular list
toList :: AdaptList a => List a -> [a]
toList xs
    | null xs   = []
    | otherwise = head xs : toList (tail xs)

-- | /O(n)/, convert an adaptive list to a regular list
fromList :: AdaptList a => [a] -> List a
fromList []     = empty
fromList (x:xs) = x `cons` fromList xs

-- | /O(n)/, construct a list by enumerating a range
enumFromToList :: (AdaptList a, Ord a, Prelude.Enum a) => a -> a ->List a
enumFromToList x0 y
            | x0 > y    = empty
            | otherwise = go x0
               where
                 go x = x `cons` if x == y then empty else go (Prelude.succ x)
{-# INLINE enumFromToList #-}

-- | /O(1)/, uncons, take apart a list into the head and tail.
--
uncons :: AdaptList a => List a -> Prelude.Maybe (a, List a)
uncons xs | null xs   = Prelude.Nothing
          | otherwise = Prelude.Just (head xs, tail xs)

-- | /O(n)/, Append two lists, i.e.,
--
-- > [x1, ..., xm] ++ [y1, ..., yn] == [x1, ..., xm, y1, ..., yn]
-- > [x1, ..., xm] ++ [y1, ...] == [x1, ..., xm, y1, ...]
--
-- If the first list is not finite, the result is the first list.
-- The spine of the first list argument must be copied.
--
(++) :: AdaptList a => List a -> List a -> List a
(++) xs ys
    | null xs   = ys
    | otherwise = head xs `cons` tail xs ++ ys

-- | /O(n)/, Extract the last element of a list, which must be finite
-- and non-empty.
last :: AdaptList a => List a -> a
last xs
    | null xs   = errorEmptyList "last"
    | otherwise = go (head xs) (tail xs)
  where
    go y z
        | null z    = y
        | otherwise = go (head z) (tail z)
{-# INLINE last #-}

-- | /O(n)/. Return all the elements of a list except the last one.
-- The list must be finite and non-empty.
init :: AdaptList a => List a -> List a
init xs
    | null xs   = errorEmptyList "init"
    | otherwise = go (head xs) (tail xs)
  where
    go y z
        | null z    = empty
        | otherwise = y `cons` go (head z) (tail z)
{-# INLINE init #-}

-- | /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 :: AdaptList a => List a -> Int
length xs0 = go xs0 0
  where
    go :: AdaptList a => List a -> Int -> Int
    go xs !a
        | null xs   = a
        | otherwise = go (tail xs) (a Prelude.+ 1)
{-# INLINE length #-}

-- ---------------------------------------------------------------------
-- * List transformations

-- | /O(n)/. 'map' @f xs@ is the list obtained by applying @f@ to each element
-- of @xs@, i.e.,
--
-- > map f [x1, x2, ..., xn] == [f x1, f x2, ..., f xn]
-- > map f [x1, x2, ...] == [f x1, f x2, ...]
--
-- Properties:
--
-- > map f . map g         = map (f . g)
-- > map f (repeat x)      = repeat (f x)
-- > map f (replicate n x) = replicate n (f x)

map :: (AdaptList a, AdaptList b) => (a -> b) -> List a -> List b
map f as = go as
  where
    go xs
        | null xs   = empty
        | otherwise = f (head xs) `cons` go (tail xs)
{-# INLINE map #-}

-- | /O(n)/. 'reverse' @xs@ returns the elements of @xs@ in reverse order.
-- @xs@ must be finite. Will fuse as a consumer only.
reverse :: AdaptList a => List a -> List a
reverse = foldl (Prelude.flip cons) empty
{-# INLINE reverse #-}

-- | /O(n)/. The 'intersperse' function takes an element and a list and
-- \`intersperses\' that element between the elements of the list.
-- For example,
--
-- > intersperse ',' "abcde" == "a,b,c,d,e"
--
intersperse :: AdaptList a => a -> List a -> List a
intersperse sep zs
    | null zs   = empty
    | otherwise = head zs `cons` go (tail zs)
  where
    go xs
        | null xs   = empty
        | otherwise = sep `cons` (head xs `cons` go (tail xs))
{-# INLINE intersperse #-}

-- | /O(n)/. '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 = concat . intersperse
--
intercalate :: (AdaptList (List a), AdaptList a)
            => List a -> List (List a) -> List a
intercalate sep xss = go (intersperse sep xss)
  where
    go ys
        | null ys   = empty
        | otherwise = head ys ++ go (tail ys)
{-# INLINE intercalate #-}

-- ---------------------------------------------------------------------
-- * Reducing lists (folds)

-- | /O(n)/. 'foldl', applied to a binary operator, a starting value (typically
-- the left-identity of the operator), and a list, reduces the list
-- using the binary operator, from left to right:
--
-- > foldl f z [x1, x2, ..., xn] == (...((z `f` x1) `f` x2) `f`...) `f` xn
--
-- The list must be finite. The accumulator is whnf strict.
--
foldl :: AdaptList b => (a -> b -> a) -> a -> List b -> a
foldl f z0 xs0 = go z0 xs0
  where
    go !z xs
        | null xs   = z
        | otherwise = go (f z (head xs)) (tail xs)
{-# INLINE foldl #-}

-- | /O(n)/. 'foldl1' is a variant of 'foldl' that has no starting value argument,
-- and thus must be applied to non-empty lists.
foldl1 :: AdaptList a => (a -> a -> a) -> List a -> a
foldl1 f zs
    | null zs   = errorEmptyList "foldl1"
    | otherwise = go (head zs) (tail zs)
  where
    go !z xs
        | null xs     = z
        | otherwise   = go (f z (head xs)) (tail xs)
{-# INLINE foldl1 #-}

-- | /O(n)/. 'foldr', applied to a binary operator, a starting value (typically
-- the right-identity of the operator), and a list, reduces the list
-- using the binary operator, from right to left:
--
-- > foldr f z [x1, x2, ..., xn] == x1 `f` (x2 `f` ... (xn `f` z)...)
--
foldr :: AdaptList a => (a -> b -> b) -> b -> List a -> b
foldr k z xs = go xs
  where
    go ys
        | null xs   = z
        | otherwise = head ys `k` go (tail ys)
{-# INLINE foldr #-}

-- | /O(n)/. 'foldr1' is a variant of 'foldr' that has no starting value argument,
-- and thus must be applied to non-empty lists.
foldr1 :: AdaptList a => (a -> a -> a) -> List a -> a
foldr1 k xs
    | null xs   = errorEmptyList "foldr1"
    | otherwise = go (head xs) (tail xs)
  where
    go z ys
        | null ys   = z
        | otherwise = z `k` go (head ys) (tail ys)
{-# INLINE foldr1 #-}

-- ---------------------------------------------------------------------
-- * Special folds

-- | /O(n)/. Concatenate a list of lists.
-- concat :: [[a]] -> [a]
concat :: (AdaptList (List a), AdaptList a)
       => List (List a) -> List a
concat xss0 = to xss0
  where
    go xs xss
        | null xs   = to xss
        | otherwise = head xs `cons` go (tail xs) xss
    to xs
        | null xs   = empty
        | otherwise = go (head xs) (tail xs)
{-# INLINE concat #-}

-- | /O(n)/, /fusion/. Map a function over a list and concatenate the results.
concatMap :: (AdaptList a1, AdaptList a)
          => (a -> List a1) -> List a -> List a1
concatMap f = foldr (\x y -> f x ++ y) empty
{-# INLINE concatMap #-}

-- | /O(n)/. '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'
-- value at a finite index of a finite or infinite list.
--
and :: List Bool -> Bool
and xs
    | null xs               = True
    | Prelude.not (head xs) = False
    | otherwise             = and (tail xs)
{-# INLINE and #-}

-- | /O(n)/. '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'
-- value at a finite index of a finite or infinite list.
or :: List Bool -> Bool
or xs
    | null xs   = False
    | head xs   = True
    | otherwise = or (tail xs)
{-# INLINE or #-}

-- | /O(n)/. Applied to a predicate and a list, 'any' determines if any element
-- of the list satisfies the predicate.
any :: AdaptList a => (a -> Bool) -> List a -> Bool
any p xs0 = go xs0
  where
    go xs
        | null xs   = False
        | otherwise = case p (head xs) of
                        True -> True
                        _    -> go (tail xs)
{-# INLINE any #-}

-- | Applied to a predicate and a list, 'all' determines if all elements
-- of the list satisfy the predicate.
all :: AdaptList a => (a -> Bool) -> List a -> Bool
all p xs0 = go xs0
  where
    go xs
        | null xs   = True
        | otherwise = case p (head xs) of
                        True -> go (tail xs)
                        _    -> False
{-# INLINE all #-}

-- | /O(n)/, /fusion/. The 'sum' function computes the sum of a finite list of numbers.
sum :: (AdaptList a, Prelude.Num a) => List a -> a
sum l = go l 0
  where
    go xs !a
        | null xs   = a
        | otherwise = go (tail xs) (a Prelude.+ head xs)
{-# INLINE sum #-}

-- | /O(n)/,/fusion/. The 'product' function computes the product of a finite list of numbers.
product :: (AdaptList a, Prelude.Num a) => List a -> a
product l = go l 1
  where
    go xs !a
        | null xs   = a
        | otherwise = go (tail xs) (a Prelude.* head xs)
{-# INLINE product #-}

-- | /O(n)/. 'maximum' returns the maximum value from a list,
-- which must be non-empty, finite, and of an ordered type.
-- It is a special case of 'Data.List.maximumBy', which allows the
-- programmer to supply their own comparison function.
maximum :: (AdaptList a, Prelude.Ord a) => List a -> a
maximum xs
    | null xs   = errorEmptyList "maximum"
    | otherwise = foldl1 Prelude.max xs
{-# INLINE maximum #-}

-- | /O(n)/. 'minimum' returns the minimum value from a list,
-- which must be non-empty, finite, and of an ordered type.
-- It is a special case of 'Data.List.minimumBy', which allows the
-- programmer to supply their own comparison function.
minimum :: (AdaptList a, Prelude.Ord a) => List a -> a
minimum xs
    | null xs   = errorEmptyList "minimum"
    | otherwise = foldl1 Prelude.min xs
{-# INLINE minimum #-}

-- ---------------------------------------------------------------------
-- * Building lists
-- ** Scans

-- | /O(n)/. 'scanl' is similar to 'foldl', but returns a list of successive
-- reduced values from the left:
--
-- > scanl f z [x1, x2, ...] == [z, z `f` x1, (z `f` x1) `f` x2, ...]
--
-- Properties:
--
-- > last (scanl f z xs) == foldl f z x
--
scanl :: (AdaptList b, AdaptList a) => (a -> b -> a) -> a -> List b -> List a
scanl f q ls = q `cons` if null ls
                          then empty
                          else scanl f (f q (head ls)) (tail ls)
{-# INLINE scanl #-}

-- | /O(n)/. 'scanl1' is a variant of 'scanl' that has no starting value argument:
--
-- > scanl1 f [x1, x2, ...] == [x1, x1 `f` x2, ...]
--
scanl1 :: AdaptList a => (a -> a -> a) -> List a -> List a
scanl1 f xs
    | null xs   = empty
    | otherwise = scanl f (head xs) (tail xs)
{-# INLINE scanl1 #-}

-- | /O(n)/. 'scanr' is the right-to-left dual of 'scanl'.
-- Properties:
--
-- > head (scanr f z xs) == foldr f z xs
--
scanr :: (AdaptList a, AdaptList b) => (a -> b -> b) -> b -> List a -> List b
scanr f q0 xs
    | null xs    = cons q0 empty
    | otherwise  = f (head xs) (head qs) `cons` qs
                    where qs = scanr f q0 (tail xs)
{-# INLINE scanr #-}

-- | 'scanr1' is a variant of 'scanr' that has no starting value argument.
scanr1 :: AdaptList a => (a -> a -> a) -> List a -> List a
scanr1 f xs
    | null xs        = empty
    | null (tail xs) = xs
    | otherwise      = f (head xs) (head qs) `cons` qs
                  where qs = scanr1 f (tail xs)

------------------------------------------------------------------------
-- ** Infinite lists

-- | /O(n)/, 'iterate' @f x@ returns an infinite list of repeated applications
-- of @f@ to @x@:
--
-- > iterate f x == [x, f x, f (f x), ...]
iterate :: AdaptList a => (a -> a) -> a -> List a
iterate f x = go x
    where go z = z `cons` go (f z)
{-# INLINE iterate #-}

-- | /O(n)/. 'repeat' @x@ is an infinite list, with @x@ the value of every element.
repeat :: AdaptList a => a -> List a
repeat x = xs where xs = x `cons` xs
{-# INLINE repeat #-}

-- | /O(n)/. 'replicate' @n x@ is a list of length @n@ with @x@ the value of
-- every element.
-- It is an instance of the more general 'Data.List.genericReplicate',
-- in which @n@ may be of any integral type.
--
replicate :: AdaptList a => Int -> a -> List a
replicate n0 _ | n0 <= 0 = empty
replicate n0 x           = go n0
  where
    go 0 = empty
    go n = x `cons` go (n-1)
{-# INLINE replicate #-}

-- | /fusion/. 'cycle' ties a finite list into a circular one, or equivalently,
-- the infinite repetition of the original list.  It is the identity
-- on infinite lists.
--
cycle :: AdaptList a => List a -> List a
cycle xs0
    | null xs0  = errorEmptyList "cycle"
    | otherwise = go xs0
  where
    go xs
        | null xs   = go xs0
        | otherwise = head xs `cons` go (tail xs)
{-# INLINE cycle #-}

-- ---------------------------------------------------------------------
-- ** Unfolding

-- | The 'unfoldr' function is a \`dual\' to 'foldr': while 'foldr'
-- reduces a list to a summary value, 'unfoldr' builds a list from
-- a seed value.  The function takes the element and returns 'Nothing'
-- if it is done producing the list or returns 'Just' @(a,b)@, in which
-- case, @a@ is a prepended to the list and @b@ is used as the next
-- element in a recursive call.  For example,
--
-- > iterate f == unfoldr (\x -> Just (x, f x))
--
-- In some cases, 'unfoldr' can undo a 'foldr' operation:
--
-- > unfoldr f' (foldr f z xs) == xs
--
-- if the following holds:
--
-- > 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]
--
-- /TODO/: AdaptPair state.
--
unfoldr :: AdaptList a => (b -> Prelude.Maybe (a, b)) -> b -> List a
unfoldr f b0 = unfold b0
  where
    unfold b = case f b of
      Prelude.Just (a,b') -> a `cons` unfold b'
      Prelude.Nothing     -> empty
{-# INLINE unfoldr #-}

------------------------------------------------------------------------
-- * Sublists
-- ** Extracting sublists

-- | /O(n)/. 'take' @n@, applied to a list @xs@, returns the prefix of @xs@
-- of length @n@, or @xs@ itself if @n > 'length' xs@:
--
-- > take 5 "Hello World!" == "Hello"
-- > take 3 [1,2,3,4,5] == [1,2,3]
-- > take 3 [1,2] == [1,2]
-- > take 3 [] == []
-- > take (-1) [1,2] == []
-- > take 0 [1,2] == []
--
-- It is an instance of the more general 'Data.List.genericTake',
-- in which @n@ may be of any integral type.
--
take :: AdaptList a => Int -> List a -> List a
take i _ | i <= 0 = empty
take i ls = go i ls
  where
    go :: AdaptList a => Int -> List a -> List a
    go 0 _  = empty
    go n xs
        | null xs   = empty
        | otherwise = (head xs) `cons` go (n-1) (tail xs)
{-# INLINE take #-}

-- | /O(n)/. 'drop' @n xs@ returns the suffix of @xs@
-- after the first @n@ elements, or @[]@ if @n > 'length' xs@:
--
-- > drop 6 "Hello World!" == "World!"
-- > drop 3 [1,2,3,4,5] == [4,5]
-- > drop 3 [1,2] == []
-- > drop 3 [] == []
-- > drop (-1) [1,2] == [1,2]
-- > drop 0 [1,2] == [1,2]
--
-- It is an instance of the more general 'Data.List.genericDrop',
-- in which @n@ may be of any integral type.
--
drop :: AdaptList a => Int -> List a -> List a
drop n ls
  | n Prelude.< 0 = ls
  | otherwise     = go n ls
  where
    go :: AdaptList a => Int -> List a -> List a
    go 0 xs      = xs
    go m xs
        | null xs   = empty
        | otherwise = go (m-1) (tail xs)
{-# INLINE drop #-}

-- | 'splitAt' @n xs@ returns a tuple where first element is @xs@ prefix of
-- length @n@ and second element is the remainder of the list:
--
-- > splitAt 6 "Hello World!" == ("Hello ","World!")
-- > splitAt 3 [1,2,3,4,5] == ([1,2,3],[4,5])
-- > splitAt 1 [1,2,3] == ([1],[2,3])
-- > splitAt 3 [1,2,3] == ([1,2,3],[])
-- > splitAt 4 [1,2,3] == ([1,2,3],[])
-- > splitAt 0 [1,2,3] == ([],[1,2,3])
-- > splitAt (-1) [1,2,3] == ([],[1,2,3])
--
-- It is equivalent to @('take' n xs, 'drop' n xs)@.
-- 'splitAt' is an instance of the more general 'Data.List.genericSplitAt',
-- in which @n@ may be of any integral type.
--
splitAt :: AdaptList a => Int -> List a -> (List a, List a)
splitAt n ls
  | n Prelude.< 0  = (empty, ls)
  | otherwise      = go n ls
  where
    go :: AdaptList a => Int -> List a -> (List a, List a)
    go 0 xs     = (empty, xs)
    go m xs
        | null xs   = (empty, empty)
        | otherwise = (head xs `cons` xs', xs'')
      where
        (xs', xs'') = go (m-1) (tail xs)
{-# INLINE splitAt #-}

-- ---------------------------------------------------------------------
-- * Searching lists
-- ** Searching by equality

-- | /O(n)/. 'elem' is the list membership predicate, usually written
-- in infix form, e.g., @x `elem` xs@.
--
elem :: (AdaptList a, Prelude.Eq a) => a -> List a -> Bool
elem x ys
    | null ys              = False
    | x Prelude.== head ys = True
    | otherwise            = elem x (tail ys)
{-# INLINE elem #-}

-- | /O(n)/. 'notElem' is the negation of 'elem'.
notElem :: (AdaptList a, Prelude.Eq a) => a -> List a -> Bool
notElem x xs = Prelude.not (elem x xs)
{-# INLINE notElem #-}

-- | /O(n)/. 'filter', applied to a predicate and a list, returns the list of
-- those elements that satisfy the predicate; i.e.,
--
-- > filter p xs = [ x | x <- xs, p x]
--
-- Properties:
--
-- > filter p (filter q s) = filter (\x -> q x && p x) s
--
filter :: AdaptList a => (a -> Bool) -> List a -> List a
filter p xs0
    | null xs0  = empty
    | otherwise = go xs0
  where
    go xs
        | null xs     = empty
        | p x         = x `cons` go ys
        | otherwise   =          go ys
            where x  = head xs
                  ys = tail xs
{-# INLINE filter #-}

------------------------------------------------------------------------
-- * Zipping and unzipping lists

-- | /O(n)/,/fusion/. 'zip' takes two lists and returns a list of
-- corresponding pairs. If one input list is short, excess elements of
-- the longer list are discarded.
--
-- Properties:
--
-- > zip a b = zipWith (,) a b
--
zip :: (AdaptPair a b, AdaptList a , AdaptList b, AdaptList (Pair a b))
    => List a -> List b -> List (Pair a b)
zip as bs
    | null as   = empty
    | null bs   = empty
    | otherwise = pair (head as) (head bs) `cons` zip (tail as) (tail bs)
{-# INLINE zip #-}

------------------------------------------------------------------------

{-


-- -----------------------------------------------------------------------------

{-
-- ---------------------------------------------------------------------
-- ** Accumulating maps

-- | The 'mapAccumL' function behaves like a combination of 'map' and
-- 'foldl'; it applies a function to each element of a list, passing
-- an accumulating parameter from left to right, and returning a final
-- value of this accumulator together with the new list.
--
mapAccumL :: (acc -> x -> (acc, y)) -> acc -> [x] -> (acc, [y])
mapAccumL _ s []     = (s, [])
mapAccumL f s (x:xs) = (s'',y:ys)
                       where (s', y ) = f s x
                             (s'',ys) = mapAccumL f s' xs

-- TODO fuse

-- | The 'mapAccumR' function behaves like a combination of 'map' and
-- 'foldr'; it applies a function to each element of a list, passing
-- an accumulating parameter from right to left, and returning a final
-- value of this accumulator together with the new list.
--
mapAccumR :: (acc -> x -> (acc, y)) -> acc -> [x] -> (acc, [y])
mapAccumR _ s []     = (s, [])
mapAccumR f s (x:xs) = (s'', y:ys)
                       where (s'',y ) = f s' x
                             (s', ys) = mapAccumR f s xs

-- TODO fuse
-}

-- | /O(n)/,/fusion/. 'takeWhile', applied to a predicate @p@ and a list @xs@, returns the
-- longest prefix (possibly empty) of @xs@ of elements that satisfy @p@:
--
-- > takeWhile (< 3) [1,2,3,4,1,2,3,4] == [1,2]
-- > takeWhile (< 9) [1,2,3] == [1,2,3]
-- > takeWhile (< 0) [1,2,3] == []
--
takeWhile :: (a -> Bool) -> [a] -> [a]
takeWhile _ []    = []
takeWhile p xs0   = go xs0
  where
    go []         = []
    go (x:xs)
      | p x       = x : go xs
      | otherwise = []
{-# NOINLINE [1] takeWhile #-}

{-# RULES
"takeWhile -> fusible" [~1] forall f xs.
    takeWhile f xs = unstream (Stream.takeWhile f (stream xs))
--"takeWhile -> unfused" [1] forall f xs.
--    unstream (Stream.takeWhile f (stream xs)) = takeWhile f xs
  #-}

-- | /O(n)/,/fusion/. 'dropWhile' @p xs@ returns the suffix remaining after 'takeWhile' @p xs@:
--
-- > dropWhile (< 3) [1,2,3,4,5,1,2,3] == [3,4,5,1,2,3]
-- > dropWhile (< 9) [1,2,3] == []
-- > dropWhile (< 0) [1,2,3] == [1,2,3]
--
dropWhile :: (a -> Bool) -> [a] -> [a]
dropWhile _ []    = []
dropWhile p xs0   = go xs0
  where
    go []         = []
    go xs@(x:xs')
      | p x       = go xs'
      | otherwise = xs
{-# NOINLINE [1] dropWhile #-}

{-# RULES
"dropWhile -> fusible" [~1] forall f xs.
    dropWhile f xs = unstream (Stream.dropWhile f (stream xs))
--"dropWhile -> unfused" [1] forall f xs.
--    unstream (Stream.dropWhile f (stream xs)) = dropWhile f xs
  #-}

-- | 'span', applied to a predicate @p@ and a list @xs@, returns a tuple where
-- first element is longest prefix (possibly empty) of @xs@ of elements that
-- satisfy @p@ and second element is the remainder of the list:
-- 
-- > span (< 3) [1,2,3,4,1,2,3,4] == ([1,2],[3,4,1,2,3,4])
-- > span (< 9) [1,2,3] == ([1,2,3],[])
-- > span (< 0) [1,2,3] == ([],[1,2,3])
-- 
-- 'span' @p xs@ is equivalent to @('takeWhile' p xs, 'dropWhile' p xs)@
span :: (a -> Bool) -> [a] -> ([a], [a])
span _ []         = ([], [])
span p xs0        = go xs0
  where
    go []         = ([], [])
    go xs@(x:xs')
      | p x       = let (ys,zs) = go xs'
                     in (x:ys,zs)
      | otherwise = ([],xs)

-- TODO fuse
-- Hmm, these do a lot of sharing, but is it worth it?

-- | 'break', applied to a predicate @p@ and a list @xs@, returns a tuple where
-- first element is longest prefix (possibly empty) of @xs@ of elements that
-- /do not satisfy/ @p@ and second element is the remainder of the list:
-- 
-- > break (> 3) [1,2,3,4,1,2,3,4] == ([1,2,3],[4,1,2,3,4])
-- > break (< 9) [1,2,3] == ([],[1,2,3])
-- > break (> 9) [1,2,3] == ([1,2,3],[])
--
-- 'break' @p@ is equivalent to @'span' ('not' . p)@.
--
break :: (a -> Bool) -> [a] -> ([a], [a])
break _ []        = ([], [])
break p xs0       = go xs0
  where
    go []         = ([], [])
    go xs@(x:xs')
      | p x       = ([],xs)
      | otherwise = let (ys,zs) = go xs'
                    in (x:ys,zs)

-- TODO fuse

-- | The 'group' function takes a list and returns a list of lists such
-- that the concatenation of the result is equal to the argument.  Moreover,
-- each sublist in the result contains only equal elements.  For example,
--
-- > group "Mississippi" = ["M","i","ss","i","ss","i","pp","i"]
--
-- It is a special case of 'groupBy', which allows the programmer to supply
-- their own equality test.
group :: Eq a => [a] -> [[a]]
group []     = []
group (x:xs) = (x:ys) : group zs
               where (ys,zs) = span (x ==) xs

-- TODO fuse

-- | The 'inits' function returns all initial segments of the argument,
-- shortest first.  For example,
--
-- > inits "abc" == ["","a","ab","abc"]
--
inits :: [a] -> [[a]]
inits []     = [] : []
inits (x:xs) = [] : map (x:) (inits xs)

-- TODO fuse

-- | The 'tails' function returns all final segments of the argument,
-- longest first.  For example,
--
-- > tails "abc" == ["abc", "bc", "c",""]
--
tails :: [a] -> [[a]]
tails []         = []  : []
tails xxs@(_:xs) = xxs : tails xs

-- TODO fuse

------------------------------------------------------------------------
-- * Predicates

-- | /O(n)/,/fusion/. The 'isPrefixOf' function takes two lists and
-- returns 'True' iff the first list is a prefix of the second.
--
isPrefixOf :: Eq a => [a] -> [a] -> Bool
isPrefixOf [] _                      = True
isPrefixOf _  []                     = False
isPrefixOf (x:xs) (y:ys) | x == y    = isPrefixOf xs ys
                         | otherwise = False
{-# NOINLINE [1] isPrefixOf #-}

{-# RULES
"isPrefixOf -> fusible" [~1] forall xs ys.
    isPrefixOf xs ys = Stream.isPrefixOf (stream xs) (stream ys)
--"isPrefixOf -> unfused" [1]  forall xs ys.
--    Stream.isPrefixOf (stream xs) (stream ys) = isPrefixOf xs ys
  #-}

-- | The 'isSuffixOf' function takes two lists and returns 'True'
-- iff the first list is a suffix of the second.
-- Both lists must be finite.
isSuffixOf :: Eq a => [a] -> [a] -> Bool
isSuffixOf x y = reverse x `isPrefixOf` reverse y

-- TODO fuse

-- | The 'isInfixOf' function takes two lists and returns 'True'
-- iff the first list is contained, wholly and intact,
-- anywhere within the second.
--
-- Example:
--
-- > isInfixOf "Haskell" "I really like Haskell." -> True
-- > isInfixOf "Ial" "I really like Haskell." -> False
--
isInfixOf :: Eq a => [a] -> [a] -> Bool
isInfixOf needle haystack = any (isPrefixOf needle) (tails haystack)

-- TODO fuse

-- ---------------------------------------------------------------------

-- | /O(n)/,/fusion/. 'lookup' @key assocs@ looks up a key in an association list.
lookup :: Eq a => a -> [(a, b)] -> Maybe b
lookup _   []       = Nothing
lookup key xys0     = go xys0
  where
    go []           = Nothing
    go ((x,y):xys)
      | key == x    = Just y
      | otherwise   = lookup key xys
{-# NOINLINE [1] lookup #-}

------------------------------------------------------------------------
-- ** Searching with a predicate

-- | /O(n)/,/fusion/. The 'find' function takes a predicate and a list and returns the
-- first element in the list matching the predicate, or 'Nothing' if
-- there is no such element.
find :: (a -> Bool) -> [a] -> Maybe a
find _ []       = Nothing
find p xs0      = go xs0
  where
    go []                 = Nothing
    go (x:xs) | p x       = Just x
              | otherwise = go xs
{-# NOINLINE [1] find #-}

{-# RULES
"find -> fusible" [~1] forall f xs.
    find f xs = Stream.find f (stream xs)
--"find -> unfused" [1] forall f xs.
--    Stream.find f (stream xs) = find f xs
  #-}

-- | The 'partition' function takes a predicate a list and returns
-- the pair of lists of elements which do and do not satisfy the
-- predicate, respectively; i.e.,
--
-- > partition p xs == (filter p xs, filter (not . p) xs)
partition :: (a -> Bool) -> [a] -> ([a], [a])
partition p xs = foldr (select p) ([],[]) xs
{-# INLINE partition #-}

-- TODO fuse

select :: (a -> Bool) -> a -> ([a], [a]) -> ([a], [a])
select p x ~(ts,fs) | p x       = (x:ts,fs)
                    | otherwise = (ts, x:fs)

------------------------------------------------------------------------
-- * Indexing lists

-- | /O(n)/,/fusion/. List index (subscript) operator, starting from 0.
-- It is an instance of the more general 'Data.List.genericIndex',
-- which takes an index of any integral type.
(!!) :: [a] -> Int -> a
xs0 !! n0
  | n0 < 0    = error "Prelude.(!!): negative index"
  | otherwise = index xs0 n0
#ifndef __HADDOCK__
  where
    index []     _ = error "Prelude.(!!): index too large"
    index (y:ys) n = if n == 0 then y else index ys (n-1)
#endif
{-# NOINLINE [1] (!!) #-}

{-# RULES
"!! -> fusible" [~1] forall xs n.
    xs !! n = Stream.index (stream xs) n
-- "!! -> unfused" [1] forall  xs n.
--     Stream.index (stream xs) n = xs !! n
  #-}

-- | 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.
-- 
-- Properties:
--
-- > elemIndex x xs = listToMaybe [ n | (n,a) <- zip [0..] xs, a == x ]
-- > elemIndex x xs = findIndex (x==) xs
--
elemIndex	:: Eq a => a -> [a] -> Maybe Int
elemIndex x     = findIndex (x==)
{-# INLINE elemIndex #-}
{-
elemIndex :: Eq a => a -> [a] -> Maybe Int
elemIndex y xs0 = loop_elemIndex xs0 0
#ifndef __HADDOCK__
  where
    loop_elemIndex []     !_ = Nothing
    loop_elemIndex (x:xs) !n
      | p x       = Just n
      | otherwise = loop_elemIndex xs (n + 1)
    p = (y ==)
#endif
{-# NOINLINE [1] elemIndex #-}
-}
{- RULES
"elemIndex -> fusible" [~1] forall x xs.
    elemIndex x xs = Stream.elemIndex x (stream xs)
"elemIndex -> unfused" [1] forall x xs.
    Stream.elemIndex x (stream xs) = elemIndex x xs
  -}

-- | /O(n)/,/fusion/. The 'elemIndices' function extends 'elemIndex', by
-- returning the indices of all elements equal to the query element, in
-- ascending order.
--
-- Properties:
--
-- > length (filter (==a) xs) = length (elemIndices a xs)
--
elemIndices     :: Eq a => a -> [a] -> [Int]
elemIndices x   = findIndices (x==)
{-# INLINE elemIndices #-}

{-
elemIndices :: Eq a => a -> [a] -> [Int]
elemIndices y xs0 = loop_elemIndices xs0 0
#ifndef __HADDOCK__
  where
    loop_elemIndices []     !_  = []
    loop_elemIndices (x:xs) !n
      | p x       = n : loop_elemIndices xs (n + 1)
      | otherwise =     loop_elemIndices xs (n + 1)
    p = (y ==)
#endif
{-# NOINLINE [1] elemIndices #-}
-}
{- RULES
"elemIndices -> fusible" [~1] forall x xs.
    elemIndices x xs = unstream (Stream.elemIndices x (stream xs))
"elemIndices -> unfused" [1] forall x xs.
    unstream (Stream.elemIndices x (stream xs)) = elemIndices x xs
  -}

-- | The 'findIndex' function takes a predicate and a list and returns
-- the index of the first element in the list satisfying the predicate,
-- or 'Nothing' if there is no such element.
--
-- Properties:
--
-- > findIndex p xs = listToMaybe [ n | (n,x) <- zip [0..] xs, p x ]
--
findIndex :: (a -> Bool) -> [a] -> Maybe Int
findIndex p ls    = loop_findIndex ls 0#
  where
    loop_findIndex []   _ = Nothing
    loop_findIndex (x:xs) n
      | p x       = Just (I# n)
      | otherwise = loop_findIndex xs (n +# 1#)
{-# NOINLINE [1] findIndex #-}

{-# RULES
"findIndex -> fusible" [~1] forall f xs.
    findIndex f xs = Stream.findIndex f (stream xs)
-- "findIndex -> unfused" [1] forall f xs.
--     Stream.findIndex f (stream xs) = findIndex f xs
  #-}

-- | /O(n)/,/fusion/. The 'findIndices' function extends 'findIndex', by
-- returning the indices of all elements satisfying the predicate, in
-- ascending order.
--
-- Properties:
--
-- > length (filter p xs) = length (findIndices p xs)
--
findIndices :: (a -> Bool) -> [a] -> [Int]
findIndices p ls  = loop_findIndices ls 0#
  where
    loop_findIndices []     _ = []
    loop_findIndices (x:xs) n
      | p x       = I# n : loop_findIndices xs (n +# 1#)
      | otherwise =        loop_findIndices xs (n +# 1#)
{-# NOINLINE [1] findIndices #-}

-- | /O(n)/,/fusion/. 'zip3' takes three lists and returns a list of
-- triples, analogous to 'zip'.
--
-- Properties:
--
-- > zip3 a b c = zipWith (,,) a b c
--
zip3 :: [a] -> [b] -> [c] -> [(a, b, c)]
zip3 (a:as) (b:bs) (c:cs) = (a,b,c) : zip3 as bs cs
zip3 _      _      _      = []
{-# NOINLINE [1] zip3 #-}

{-# RULES
"zip3 -> fusible" [~1] forall xs ys zs.
    zip3 xs ys zs = unstream (Stream.zipWith3 (,,) (stream xs) (stream ys) (stream zs))
-- "zip3 -> unfused" [1]  forall xs ys zs.
--     unstream (Stream.zipWith3 (,,) (stream xs) (stream ys) (stream zs)) = zip3 xs ys zs
  #-}

-- | /O(n)/,/fusion/. The 'zip4' function takes four lists and returns a list of
-- quadruples, analogous to 'zip'.
zip4 :: [a] -> [b] -> [c] -> [d] -> [(a, b, c, d)]
zip4 = zipWith4 (,,,)
{-# INLINE zip4 #-}

-- | The 'zip5' function takes five lists and returns a list of
-- five-tuples, analogous to 'zip'.
zip5 :: [a] -> [b] -> [c] -> [d] -> [e] -> [(a, b, c, d, e)]
zip5 = zipWith5 (,,,,)

-- | The 'zip6' function takes six lists and returns a list of six-tuples,
-- analogous to 'zip'.
zip6 :: [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [(a, b, c, d, e, f)]
zip6 = zipWith6 (,,,,,)

-- | The 'zip7' function takes seven lists and returns a list of
-- seven-tuples, analogous to 'zip'.
zip7 :: [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -> [(a, b, c, d, e, f, g)]
zip7 = zipWith7 (,,,,,,)

-- | /O(n)/,/fusion/. 'zipWith' generalises 'zip' by zipping with the
-- function given as the first argument, instead of a tupling function.
-- For example, @'zipWith' (+)@ is applied to two lists to produce the
-- list of corresponding sums.
-- Properties:
--
-- > zipWith (,) = zip
--
zipWith :: (a -> b -> c) -> [a] -> [b] -> [c]
zipWith f (a:as) (b:bs) = f a b : zipWith f as bs
zipWith _ _      _      = []
{-# INLINE [1] zipWith #-}

--FIXME: If we change the above INLINE to NOINLINE then ghc goes into
--       a loop, why? Do we have some dodgy recursive rules somewhere?

{-# RULES
"zipWith -> fusible" [~1] forall f xs ys.
    zipWith f xs ys = unstream (Stream.zipWith f (stream xs) (stream ys))
-- "zipWith -> unfused" [1]  forall f xs ys.
--     unstream (Stream.zipWith f (stream xs) (stream ys)) = zipWith f xs ys
  #-}

-- | /O(n)/,/fusion/. The 'zipWith3' function takes a function which
-- combines three elements, as well as three lists and returns a list of
-- their point-wise combination, analogous to 'zipWith'.
--
-- Properties:
--
-- > zipWith3 (,,) = zip3
--
zipWith3 :: (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d]
zipWith3 z (a:as) (b:bs) (c:cs) = z a b c : zipWith3 z as bs cs
zipWith3 _ _ _ _                = []
{-# NOINLINE [1] zipWith3 #-}

{-# RULES
"zipWith3 -> fusible" [~1] forall f xs ys zs.
    zipWith3 f xs ys zs = unstream (Stream.zipWith3 f (stream xs) (stream ys) (stream zs))
-- "zipWith3 -> unfused" [1]  forall f xs ys zs.
--     unstream (Stream.zipWith3 f (stream xs) (stream ys) (stream zs)) = zipWith3 f xs ys zs
  #-}

-- | /O(n)/,/fusion/. The 'zipWith4' function takes a function which combines four
-- elements, as well as four lists and returns a list of their point-wise
-- combination, analogous to 'zipWith'.
zipWith4 :: (a -> b -> c -> d -> e) -> [a] -> [b] -> [c] -> [d] -> [e]
zipWith4 z (a:as) (b:bs) (c:cs) (d:ds)
                        = z a b c d : zipWith4 z as bs cs ds
zipWith4 _ _ _ _ _      = []
{-# NOINLINE [1] zipWith4 #-}

{-# RULES
"zipWith4 -> fusible" [~1] forall f ws xs ys zs.
    zipWith4 f ws xs ys zs = unstream (Stream.zipWith4 f (stream ws) (stream xs) (stream ys) (stream zs))
-- "zipWith4 -> unfused" [1]  forall f ws xs ys zs.
--     unstream (Stream.zipWith4 f (stream ws) (stream xs) (stream ys) (stream zs)) = zipWith4 f ws xs ys zs
  #-}

-- | The 'zipWith5' function takes a function which combines five
-- elements, as well as five lists and returns a list of their point-wise
-- combination, analogous to 'zipWith'.
zipWith5 :: (a -> b -> c -> d -> e -> f)
         -> [a] -> [b] -> [c] -> [d] -> [e] -> [f]
zipWith5 z (a:as) (b:bs) (c:cs) (d:ds) (e:es)
                        = z a b c d e : zipWith5 z as bs cs ds es
zipWith5 _ _ _ _ _ _    = []

-- TODO fuse

-- | The 'zipWith6' function takes a function which combines six
-- elements, as well as six lists and returns a list of their point-wise
-- combination, analogous to 'zipWith'.
zipWith6 :: (a -> b -> c -> d -> e -> f -> g)
         -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g]
zipWith6 z (a:as) (b:bs) (c:cs) (d:ds) (e:es) (f:fs)
                        = z a b c d e f : zipWith6 z as bs cs ds es fs
zipWith6 _ _ _ _ _ _ _  = []

-- TODO fuse

-- | The 'zipWith7' function takes a function which combines seven
-- elements, as well as seven lists and returns a list of their point-wise
-- combination, analogous to 'zipWith'.
zipWith7 :: (a -> b -> c -> d -> e -> f -> g -> h)
         -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -> [h]
zipWith7 z (a:as) (b:bs) (c:cs) (d:ds) (e:es) (f:fs) (g:gs)
                         = z a b c d e f g : zipWith7 z as bs cs ds es fs gs
zipWith7 _ _ _ _ _ _ _ _ = []

-- TODO fuse

------------------------------------------------------------------------
-- unzips

-- | 'unzip' transforms a list of pairs into a list of first components
-- and a list of second components.
unzip :: [(a, b)] -> ([a], [b])
unzip = foldr (\(a,b) ~(as,bs) -> (a:as,b:bs)) ([],[])

-- TODO fuse

-- | The 'unzip3' function takes a list of triples and returns three
-- lists, analogous to 'unzip'.
unzip3 :: [(a, b, c)] -> ([a], [b], [c])
unzip3 = foldr (\(a,b,c) ~(as,bs,cs) -> (a:as,b:bs,c:cs)) ([],[],[])

-- TODO fuse

-- | The 'unzip4' function takes a list of quadruples and returns four
-- lists, analogous to 'unzip'.
unzip4 :: [(a, b, c, d)] -> ([a], [b], [c], [d])
unzip4 = foldr (\(a,b,c,d) ~(as,bs,cs,ds) ->
                      (a:as,b:bs,c:cs,d:ds))
               ([],[],[],[])

-- TODO fuse

-- | The 'unzip5' function takes a list of five-tuples and returns five
-- lists, analogous to 'unzip'.
unzip5 :: [(a, b, c, d, e)] -> ([a], [b], [c], [d], [e])
unzip5 = foldr (\(a,b,c,d,e) ~(as,bs,cs,ds,es) ->
                      (a:as,b:bs,c:cs,d:ds,e:es))
               ([],[],[],[],[])

-- TODO fuse

-- | The 'unzip6' function takes a list of six-tuples and returns six
-- lists, analogous to 'unzip'.
unzip6 :: [(a, b, c, d, e, f)] -> ([a], [b], [c], [d], [e], [f])
unzip6 = foldr (\(a,b,c,d,e,f) ~(as,bs,cs,ds,es,fs) ->
                      (a:as,b:bs,c:cs,d:ds,e:es,f:fs))
               ([],[],[],[],[],[])

-- TODO fuse

-- | The 'unzip7' function takes a list of seven-tuples and returns
-- seven lists, analogous to 'unzip'.
unzip7 :: [(a, b, c, d, e, f, g)] -> ([a], [b], [c], [d], [e], [f], [g])
unzip7 = foldr (\(a,b,c,d,e,f,g) ~(as,bs,cs,ds,es,fs,gs) ->
                      (a:as,b:bs,c:cs,d:ds,e:es,f:fs,g:gs))
               ([],[],[],[],[],[],[])

-- TODO fuse

------------------------------------------------------------------------
-- * Special lists
-- ** Functions on strings

-- | /O(O)/,/fusion/. 'lines' breaks a string up into a list of strings
-- at newline characters. The resulting strings do not contain
-- newlines.
lines :: String -> [String]
lines [] = []
lines s  = let (l, s') = break (== '\n') s
            in l : case s' of
                     []      -> []
                     (_:s'') -> lines s''
--TODO: can we do better than this and preserve the same strictness?

{-
-- This implementation is fast but too strict :-(
-- it doesn't yield each line until it has seen the ending '\n'

lines :: String -> [String]
lines []  = []
lines cs0 = go [] cs0
  where
    go l []        = reverse l : []
    go l ('\n':cs) = reverse l : case cs of
                                   [] -> []
                                   _  -> go [] cs
    go l (  c :cs) = go (c:l) cs
-}
{-# INLINE [1] lines #-}

{- RULES
"lines -> fusible" [~1] forall xs.
    lines xs = unstream (Stream.lines (stream xs))
"lines -> unfused" [1]  forall xs.
    unstream (Stream.lines (stream xs)) = lines xs
  -}

-- | 'words' breaks a string up into a list of words, which were delimited
-- by white space.
words :: String -> [String]
words s = case dropWhile isSpace s of
            "" -> []
            s' -> w : words s''
                  where (w, s'') = break isSpace s'
-- TODO fuse
--TODO: can we do better than this and preserve the same strictness?

{-
-- This implementation is fast but too strict :-(
-- it doesn't yield each word until it has seen the ending space

words cs0 = dropSpaces cs0
  where
    dropSpaces :: String -> [String]
    dropSpaces []         = []
    dropSpaces (c:cs)
         | isSpace c = dropSpaces cs
         | otherwise      = munchWord [c] cs

    munchWord :: String -> String -> [String]
    munchWord w []     = reverse w : []
    munchWord w (c:cs)
      | isSpace c = reverse w : dropSpaces cs
      | otherwise      = munchWord (c:w) cs
-}

-- | /O(n)/,/fusion/. 'unlines' is an inverse operation to 'lines'.
-- It joins lines, after appending a terminating newline to each.
--
-- > unlines xs = concatMap (++"\n")
--
unlines :: [String] -> String
unlines css0 = to css0
  where go []     css = '\n' : to css
        go (c:cs) css =   c  : go cs css

        to []       = []
        to (cs:css) = go cs css
{-# NOINLINE [1] unlines #-}

--
-- fuse via:
--      unlines xs = concatMap (snoc xs '\n')
--
{- RULES
"unlines -> fusible" [~1] forall xs.
    unlines xs = unstream (Stream.concatMap (\x -> Stream.snoc (stream x) '\n') (stream xs))
"unlines -> unfused" [1]  forall xs.
    unstream (Stream.concatMap (\x -> Stream.snoc (stream x) '\n') (stream xs)) = unlines xs
  -}

-- | 'unwords' is an inverse operation to 'words'.
-- It joins words with separating spaces.
unwords :: [String] -> String
unwords []         = []
unwords (cs0:css0) = go cs0 css0
  where go []     css = to css
        go (c:cs) css = c : go cs css

        to []       = []
        to (cs:ccs) = ' ' : go cs ccs

-- TODO fuse

------------------------------------------------------------------------
-- ** \"Set\" operations

-- | The 'nub' function removes duplicate elements from a list.
-- In particular, it keeps only the first occurrence of each element.
-- (The name 'nub' means \`essence\'.)
-- It is a special case of 'nubBy', which allows the programmer to supply
-- their own equality test.
--
nub :: Eq a => [a] -> [a]
nub l               = nub' l []
  where
    nub' [] _       = []
    nub' (x:xs) ls
      | x `elem` ls = nub' xs ls
      | otherwise   = x : nub' xs (x:ls)

{- RULES
-- ndm's optimisation
"sort/nub" forall xs.  sort (nub xs) = map head (group (sort xs))
  -}

-- TODO fuse

-- | 'delete' @x@ removes the first occurrence of @x@ from its list argument.
-- For example,
--
-- > delete 'a' "banana" == "bnana"
--
-- It is a special case of 'deleteBy', which allows the programmer to
-- supply their own equality test.
--
delete :: Eq a => a -> [a] -> [a]
delete = deleteBy (==)

-- TODO fuse

-- | The '\\' function is list difference ((non-associative).
-- In the result of @xs@ '\\' @ys@, the first occurrence of each element of
-- @ys@ in turn (if any) has been removed from @xs@.  Thus
--
-- > (xs ++ ys) \\ xs == ys.
--
-- It is a special case of 'deleteFirstsBy', which allows the programmer
-- to supply their own equality test.
(\\) :: Eq a => [a] -> [a] -> [a]
(\\) = foldl (flip delete)

-- | The 'union' function returns the list union of the two lists.
-- For example,
--
-- > "dog" `union` "cow" == "dogcw"
--
-- Duplicates, and elements of the first list, are removed from the
-- the second list, but if the first list contains duplicates, so will
-- the result.
-- It is a special case of 'unionBy', which allows the programmer to supply
-- their own equality test.
--
union :: Eq a => [a] -> [a] -> [a]
union = unionBy (==)

-- TODO fuse

-- | The 'intersect' function takes the list intersection of two lists.
-- For example,
--
-- > [1,2,3,4] `intersect` [2,4,6,8] == [2,4]
--
-- If the first list contains duplicates, so will the result.
-- It is a special case of 'intersectBy', which allows the programmer to
-- supply their own equality test.
--
intersect :: Eq a => [a] -> [a] -> [a]
intersect = intersectBy (==)

-- TODO fuse

------------------------------------------------------------------------
-- ** Ordered lists 

-- TODO stuff in Ord can use Map/IntMap
-- TODO Hooray, an Ord constraint! we could use a better structure.

-- | The 'sort' function implements a stable sorting algorithm.
-- It is a special case of 'sortBy', which allows the programmer to supply
-- their own comparison function.
--
-- Properties:
--
-- > not (null x) ==> (head . sort) x = minimum x
-- > not (null x) ==> (last . sort) x = maximum x
--
sort :: Ord a => [a] -> [a]
sort l = mergesort compare l

-- TODO fuse, we have an Ord constraint!

-- | /O(n)/,/fusion/. The 'insert' function takes an element and a list and inserts the
-- element into the list at the last position where it is still less
-- than or equal to the next element.  In particular, if the list
-- is sorted before the call, the result will also be sorted.
-- It is a special case of 'insertBy', which allows the programmer to
-- supply their own comparison function.
--
insert :: Ord a => a -> [a] -> [a]
insert e ls = insertBy (compare) e ls
{-# INLINE insert #-}

------------------------------------------------------------------------
-- * Generalized functions
-- ** The \"By\" operations
-- *** User-supplied equality (replacing an Eq context)

-- | The 'nubBy' function behaves just like 'nub', except it uses a
-- user-supplied equality predicate instead of the overloaded '=='
-- function.
nubBy :: (a -> a -> Bool) -> [a] -> [a]
nubBy eq l              = nubBy' l []
  where
    nubBy' [] _         = []
    nubBy' (y:ys) xs
      | elem_by eq y xs = nubBy' ys xs
      | otherwise       = y : nubBy' ys (y:xs)

-- TODO fuse

-- Not exported:
-- Note that we keep the call to `eq` with arguments in the
-- same order as in the reference implementation
-- 'xs' is the list of things we've seen so far, 
-- 'y' is the potential new element
--
elem_by :: (a -> a -> Bool) -> a -> [a] -> Bool
elem_by _  _ []         = False
elem_by eq y (x:xs)     = if x `eq` y then True else elem_by eq y xs

-- | The 'deleteBy' function behaves like 'delete', but takes a
-- user-supplied equality predicate.
deleteBy :: (a -> a -> Bool) -> a -> [a] -> [a]
deleteBy _  _ []        = []
deleteBy eq x (y:ys)    = if x `eq` y then ys else y : deleteBy eq x ys

-- TODO fuse

deleteFirstsBy :: (a -> a -> Bool) -> [a] -> [a] -> [a]
deleteFirstsBy eq       = foldl (flip (deleteBy eq))


-- | The 'unionBy' function is the non-overloaded version of 'union'.
unionBy :: (a -> a -> Bool) -> [a] -> [a] -> [a]
unionBy eq xs ys        = xs ++ foldl (flip (deleteBy eq)) (nubBy eq ys) xs

-- TODO fuse

-- | The 'intersectBy' function is the non-overloaded version of 'intersect'.
intersectBy :: (a -> a -> Bool) -> [a] -> [a] -> [a]
intersectBy eq xs ys    = [x | x <- xs, any (eq x) ys]

-- TODO fuse

-- | The 'groupBy' function is the non-overloaded version of 'group'.
groupBy :: (a -> a -> Bool) -> [a] -> [[a]]
groupBy _  []     = []
groupBy eq (x:xs) = (x:ys) : groupBy eq zs
                    where (ys,zs) = span (eq x) xs

-- TODO fuse

------------------------------------------------------------------------
-- *** User-supplied comparison (replacing an Ord context)

-- | The 'sortBy' function is the non-overloaded version of 'sort'.
sortBy :: (a -> a -> Ordering) -> [a] -> [a]
sortBy cmp l = mergesort cmp l

-- TODO fuse

mergesort :: (a -> a -> Ordering) -> [a] -> [a]
mergesort cmp xs = mergesort' cmp (map wrap xs)

mergesort' :: (a -> a -> Ordering) -> [[a]] -> [a]
mergesort' _ []    = []
mergesort' _ [xs]  = xs
mergesort' cmp xss = mergesort' cmp (merge_pairs cmp xss)

merge_pairs :: (a -> a -> Ordering) -> [[a]] -> [[a]]
merge_pairs _   []          = []
merge_pairs _   [xs]        = [xs]
merge_pairs cmp (xs:ys:xss) = merge cmp xs ys : merge_pairs cmp xss

merge :: (a -> a -> Ordering) -> [a] -> [a] -> [a]
merge _   xs [] = xs
merge _   [] ys = ys
merge cmp (x:xs) (y:ys)
 = case x `cmp` y of
        GT -> y : merge cmp (x:xs)   ys
        _  -> x : merge cmp    xs (y:ys)

wrap :: a -> [a]
wrap x = [x]

-- | /O(n)/,/fusion/. The non-overloaded version of 'insert'.
insertBy :: (a -> a -> Ordering) -> a -> [a] -> [a]
insertBy _   x [] = [x]
insertBy cmp x ys@(y:ys')
    = case cmp x y of
        GT -> y : insertBy cmp x ys'
        _  -> x : ys
{-# NOINLINE [1] insertBy #-}

{-# RULES
"insertBy -> fusible" [~1] forall f x xs.
    insertBy f x xs = unstream (Stream.insertBy f x (stream xs))
-- "insertBy -> unfused" [1]  forall f x xs.
--     unstream (Stream.insertBy f x (stream xs)) = insertBy f x xs
  #-}

-- | /O(n)/,/fusion/. The 'maximumBy' function takes a comparison function and a list
-- and returns the greatest element of the list by the comparison function.
-- The list must be finite and non-empty.
--
maximumBy :: (a -> a -> Ordering) -> [a] -> a
maximumBy _ []   = error "List.maximumBy: empty list"
maximumBy cmp xs = foldl1 max' xs
    where
       max' x y = case cmp x y of
                    GT -> x
                    _  -> y
{-# NOINLINE [1] maximumBy #-}

{-# RULES
"maximumBy -> fused"  [~1] forall p xs.
    maximumBy p xs = Stream.maximumBy p (stream xs)
-- "maximumBy -> unfused" [1] forall p xs.
--     Stream.maximumBy p (stream xs) = maximumBy p xs
  #-}

-- | /O(n)/,/fusion/. The 'minimumBy' function takes a comparison function and a list
-- and returns the least element of the list by the comparison function.
-- The list must be finite and non-empty.
minimumBy :: (a -> a -> Ordering) -> [a] -> a
minimumBy _ []   = error "List.minimumBy: empty list"
minimumBy cmp xs = foldl1 min' xs
    where
        min' x y = case cmp x y of
                        GT -> y
                        _  -> x
{-# NOINLINE [1] minimumBy #-}

{-# RULES
"minimumBy -> fused"  [~1] forall p xs.
    minimumBy p xs = Stream.minimumBy p (stream xs)
-- "minimumBy -> unfused" [1] forall p xs.
--     Stream.minimumBy p (stream xs) = minimumBy p xs
  #-}

------------------------------------------------------------------------
-- * The \"generic\" operations

-- | The 'genericLength' function is an overloaded version of 'length'.  In
-- particular, instead of returning an 'Int', it returns any type which is
-- an instance of 'Num'.  It is, however, less efficient than 'length'.
--
genericLength :: Num i => [b] -> i
genericLength []    = 0
genericLength (_:l) = 1 + genericLength l
{-# NOINLINE [1] genericLength #-}

{-# RULES
"genericLength -> fusible" [~1] forall xs.
    genericLength xs = Stream.genericLength (stream xs)
-- "genericLength -> unfused" [1] forall xs.
--     Stream.genericLength (stream xs) = genericLength xs
  #-}

{-# RULES
"genericLength -> length/Int" genericLength = length :: [a] -> Int
  #-}

-- | /O(n)/,/fusion/. The 'genericTake' function is an overloaded version of 'take', which
-- accepts any 'Integral' value as the number of elements to take.
genericTake :: Integral i => i -> [a] -> [a]
genericTake 0 _      = []
genericTake _ []     = []
genericTake n (x:xs)
             | n > 0 = x : genericTake (n-1) xs
             | otherwise = error "List.genericTake: negative argument"
{-# NOINLINE [1] genericTake #-}

{-# RULES
"genericTake -> fusible" [~1] forall xs n.
    genericTake n xs = unstream (Stream.genericTake n (stream xs))
-- "genericTake -> unfused" [1]  forall xs n.
--     unstream (Stream.genericTake n (stream xs)) = genericTake n xs
  #-}

{-# RULES
"genericTake -> take/Int" genericTake = take :: Int -> [a] -> [a]
  #-}

-- | /O(n)/,/fusion/. The 'genericDrop' function is an overloaded version of 'drop', which
-- accepts any 'Integral' value as the number of elements to drop.
genericDrop :: Integral i => i -> [a] -> [a]
genericDrop 0 xs        = xs
genericDrop _ []        = []
genericDrop n (_:xs) | n > 0  = genericDrop (n-1) xs
genericDrop _ _         = error "List.genericDrop: negative argument"
{-# NOINLINE [1] genericDrop #-}

{-# RULES
"genericDrop -> fusible" [~1] forall xs n.
    genericDrop n xs = unstream (Stream.genericDrop n (stream xs))
-- "genericDrop -> unfused" [1]  forall xs n.
--     unstream (Stream.genericDrop n (stream xs)) = genericDrop n xs
  #-}

{-# RULES
"genericDrop -> drop/Int" genericDrop = drop :: Int -> [a] -> [a]
  #-}

-- | /O(n)/,/fusion/. The 'genericIndex' function is an overloaded version of '!!', which
-- accepts any 'Integral' value as the index.
genericIndex :: Integral a => [b] -> a -> b
genericIndex (x:_)  0 = x
genericIndex (_:xs) n
    | n > 0           = genericIndex xs (n-1)
    | otherwise       = error "List.genericIndex: negative argument."
genericIndex _ _      = error "List.genericIndex: index too large."
{-# NOINLINE [1] genericIndex #-}


-- can we pull the n > 0 test out and do it just once?
-- probably not since we don't know what n-1 does!!
-- can only specialise it for sane Integral instances :-(

{-# RULES
"genericIndex -> fusible" [~1] forall xs n.
    genericIndex xs n = Stream.genericIndex (stream xs) n
-- "genericIndex -> unfused" [1]  forall xs n.
--     Stream.genericIndex (stream xs) n = genericIndex n xs
  #-}

{-# RULES
"genericIndex -> index/Int" genericIndex = (!!) :: [a] -> Int -> a
  #-}

-- | /O(n)/,/fusion/. The 'genericSplitAt' function is an overloaded
-- version of 'splitAt', which accepts any 'Integral' value as the
-- position at which to split.
--
genericSplitAt :: Integral i => i -> [a] -> ([a], [a])
genericSplitAt 0 xs     = ([],xs)
genericSplitAt _ []     = ([],[])
genericSplitAt n (x:xs) | n > 0  = (x:xs',xs'')
    where (xs',xs'') = genericSplitAt (n-1) xs
genericSplitAt _ _      = error "List.genericSplitAt: negative argument"

{-# RULES
"genericSplitAt -> fusible" [~1] forall xs n.
    genericSplitAt n xs = Stream.genericSplitAt n (stream xs)
-- "genericSplitAt -> unfused" [1]  forall xs n.
--     Stream.genericSplitAt n (stream xs) = genericSplitAt n xs
  #-}

{-# RULES
"genericSplitAt -> splitAt/Int" genericSplitAt = splitAt :: Int -> [a] -> ([a], [a])
  #-}

-- | /O(n)/,/fusion/. The 'genericReplicate' function is an overloaded version of 'replicate',
-- which accepts any 'Integral' value as the number of repetitions to make.
--
genericReplicate :: Integral i => i -> a -> [a]
genericReplicate n x = genericTake n (repeat x)
{-# INLINE genericReplicate #-}

{-# RULES
"genericReplicate -> replicate/Int" genericReplicate = replicate :: Int -> a -> [a]
  #-}
-}

-- ---------------------------------------------------------------------
-- Internal utilities

-- Common up near identical calls to `error' to reduce the number
-- constant strings created when compiled:
errorEmptyList :: Prelude.String -> a
errorEmptyList fun = moduleError fun "empty list"
{-# NOINLINE errorEmptyList #-}

moduleError :: Prelude.String -> Prelude.String -> a
moduleError fun msg = Prelude.error ("Data.Adaptive.List." Prelude.++ fun Prelude.++ ':':' ':msg)
{-# NOINLINE moduleError #-}

bottom :: a
bottom = Prelude.error "Data.List.Stream: bottom"
{-# NOINLINE bottom #-}

------------------------------------------------------------------------
-- Instances

instance (AdaptList a, Prelude.Eq a) => Prelude.Eq (List a) where
    xs == ys
        | null xs Prelude.&& null ys = True
        | null xs                    = False
        | null ys                    = False
        | otherwise                  = (head xs Prelude.== head ys)
                            Prelude.&& (tail xs Prelude.== tail ys)

instance (AdaptList a, Prelude.Ord a) => Prelude.Ord (List a) where
    compare xs ys
        | null xs Prelude.&& null ys = EQ
        | null xs                    = LT
        | null ys                    = GT
        | otherwise                  = case compare (head xs) (head ys) of
                                            EQ    -> compare (tail xs) (tail ys)
                                            other -> other

instance (AdaptList a, Prelude.Show a) => Prelude.Show (List a) where
    showsPrec _         = Prelude.showList . toList

------------------------------------------------------------------------

-- Generic adaptive pair: won't flatten!

{-
Data/Adaptive/List.hs:1687:9:
    Conflicting family instance declarations:
      data instance List (Pair a b)
        -- Defined at Data/Adaptive/List.hs:1687:9-12
      data instance List (Pair Int Int)
        -- Defined at Data/Adaptive/List.hs:1699:9-12
-}

{-
    -- looks illegal?
instance AdaptPair a b => AdaptList (Pair a b) where
    data List (Pair a b) = EmptyPair | ConsPair {-# UNPACK #-}!(Pair a b) (List (Pair a b))
    empty                = EmptyPair
    cons x xs            = ConsPair x xs
    null EmptyPair       = True
    null _               = False
    head EmptyPair       = errorEmptyList "head"
    head (ConsPair x _)  = x
    tail EmptyPair       = errorEmptyList "tail"
    tail (ConsPair _ xs) = xs
-}

-- Monomorphic, but we have to flatten ourselves. GHC is doing something wrong.
instance AdaptList (Pair Int Int) where
    data List (Pair Int Int)
        = EmptyPairIntInt
--      | ConsPairIntInt {-# UNPACK #-}!(Pair Int Int) (List (Pair Int Int))
                                      -- this isn't unpacking 
        | ConsPairIntInt {-# UNPACK #-}!Int {-# UNPACK #-}!Int (List (Pair Int Int))

    empty                = EmptyPairIntInt
    cons x xs            = ConsPairIntInt (fst x) (snd x) xs

    null EmptyPairIntInt = True
    null _               = False

    head EmptyPairIntInt         = errorEmptyList "head"
    head (ConsPairIntInt x y _)  = pair x y
    tail EmptyPairIntInt         = errorEmptyList "tail"
    tail (ConsPairIntInt _ _ xs) = xs

------------------------------------------------------------------------

-- | We can unpack bools!
instance AdaptList Bool where
    data List Bool = EmptyBool | ConsBool {-# UNPACK #-}!Int (List Bool)

    empty                = EmptyBool
    cons x xs            = ConsBool (Prelude.fromEnum x) xs -- pack
    null EmptyBool       = True
    null _               = False

    head EmptyBool       = errorEmptyList "head"
    head (ConsBool x _)  = Prelude.toEnum x

    tail EmptyBool       = errorEmptyList "tail"
    tail (ConsBool _ xs) = xs

------------------------------------------------------------------------
-- Generated by scripts/derive-list.hs

instance AdaptList Int where
    data List Int = EmptyInt | ConsInt {-# UNPACK #-}!Int (List Int)
    empty = EmptyInt
    cons = ConsInt
    null EmptyInt = True
    null _ = False
    head EmptyInt = errorEmptyList "head"
    head (ConsInt x _) = x
    tail EmptyInt = errorEmptyList "tail"
    tail (ConsInt _ x) = x

instance AdaptList Integer where
    data List Integer = EmptyInteger | ConsInteger {-# UNPACK #-}!Integer (List Integer)
    empty = EmptyInteger
    cons = ConsInteger
    null EmptyInteger = True
    null _ = False
    head EmptyInteger = errorEmptyList "head"
    head (ConsInteger x _) = x
    tail EmptyInteger = errorEmptyList "tail"
    tail (ConsInteger _ x) = x

instance AdaptList Int8 where
    data List Int8 = EmptyInt8 | ConsInt8 {-# UNPACK #-}!Int8 (List Int8)
    empty = EmptyInt8
    cons = ConsInt8
    null EmptyInt8 = True
    null _ = False
    head EmptyInt8 = errorEmptyList "head"
    head (ConsInt8 x _) = x
    tail EmptyInt8 = errorEmptyList "tail"
    tail (ConsInt8 _ x) = x

instance AdaptList Int16 where
    data List Int16 = EmptyInt16 | ConsInt16 {-# UNPACK #-}!Int16 (List Int16)
    empty = EmptyInt16
    cons = ConsInt16
    null EmptyInt16 = True
    null _ = False
    head EmptyInt16 = errorEmptyList "head"
    head (ConsInt16 x _) = x
    tail EmptyInt16 = errorEmptyList "tail"
    tail (ConsInt16 _ x) = x

instance AdaptList Int32 where
    data List Int32 = EmptyInt32 | ConsInt32 {-# UNPACK #-}!Int32 (List Int32)
    empty = EmptyInt32
    cons = ConsInt32
    null EmptyInt32 = True
    null _ = False
    head EmptyInt32 = errorEmptyList "head"
    head (ConsInt32 x _) = x
    tail EmptyInt32 = errorEmptyList "tail"
    tail (ConsInt32 _ x) = x

instance AdaptList Int64 where
    data List Int64 = EmptyInt64 | ConsInt64 {-# UNPACK #-}!Int64 (List Int64)
    empty = EmptyInt64
    cons = ConsInt64
    null EmptyInt64 = True
    null _ = False
    head EmptyInt64 = errorEmptyList "head"
    head (ConsInt64 x _) = x
    tail EmptyInt64 = errorEmptyList "tail"
    tail (ConsInt64 _ x) = x

instance AdaptList Word where
    data List Word = EmptyWord | ConsWord {-# UNPACK #-}!Word (List Word)
    empty = EmptyWord
    cons = ConsWord
    null EmptyWord = True
    null _ = False
    head EmptyWord = errorEmptyList "head"
    head (ConsWord x _) = x
    tail EmptyWord = errorEmptyList "tail"
    tail (ConsWord _ x) = x

instance AdaptList Word8 where
    data List Word8 = EmptyWord8 | ConsWord8 {-# UNPACK #-}!Word8 (List Word8)
    empty = EmptyWord8
    cons = ConsWord8
    null EmptyWord8 = True
    null _ = False
    head EmptyWord8 = errorEmptyList "head"
    head (ConsWord8 x _) = x
    tail EmptyWord8 = errorEmptyList "tail"
    tail (ConsWord8 _ x) = x

instance AdaptList Word16 where
    data List Word16 = EmptyWord16 | ConsWord16 {-# UNPACK #-}!Word16 (List Word16)
    empty = EmptyWord16
    cons = ConsWord16
    null EmptyWord16 = True
    null _ = False
    head EmptyWord16 = errorEmptyList "head"
    head (ConsWord16 x _) = x
    tail EmptyWord16 = errorEmptyList "tail"
    tail (ConsWord16 _ x) = x

instance AdaptList Word32 where
    data List Word32 = EmptyWord32 | ConsWord32 {-# UNPACK #-}!Word32 (List Word32)
    empty = EmptyWord32
    cons = ConsWord32
    null EmptyWord32 = True
    null _ = False
    head EmptyWord32 = errorEmptyList "head"
    head (ConsWord32 x _) = x
    tail EmptyWord32 = errorEmptyList "tail"
    tail (ConsWord32 _ x) = x

instance AdaptList Word64 where
    data List Word64 = EmptyWord64 | ConsWord64 {-# UNPACK #-}!Word64 (List Word64)
    empty = EmptyWord64
    cons = ConsWord64
    null EmptyWord64 = True
    null _ = False
    head EmptyWord64 = errorEmptyList "head"
    head (ConsWord64 x _) = x
    tail EmptyWord64 = errorEmptyList "tail"
    tail (ConsWord64 _ x) = x

instance AdaptList Double where
    data List Double = EmptyDouble | ConsDouble {-# UNPACK #-}!Double (List Double)
    empty = EmptyDouble
    cons = ConsDouble
    null EmptyDouble = True
    null _ = False
    head EmptyDouble = errorEmptyList "head"
    head (ConsDouble x _) = x
    tail EmptyDouble = errorEmptyList "tail"
    tail (ConsDouble _ x) = x

instance AdaptList Float where
    data List Float = EmptyFloat | ConsFloat {-# UNPACK #-}!Float (List Float)
    empty = EmptyFloat
    cons = ConsFloat
    null EmptyFloat = True
    null _ = False
    head EmptyFloat = errorEmptyList "head"
    head (ConsFloat x _) = x
    tail EmptyFloat = errorEmptyList "tail"
    tail (ConsFloat _ x) = x

instance AdaptList Char where
    data List Char = EmptyChar | ConsChar {-# UNPACK #-}!Char (List Char)
    empty = EmptyChar
    cons = ConsChar
    null EmptyChar = True
    null _ = False
    head EmptyChar = errorEmptyList "head"
    head (ConsChar x _) = x
    tail EmptyChar = errorEmptyList "tail"
    tail (ConsChar _ x) = x