{-# LANGUAGE CPP, NoImplicitPrelude #-}
{-# LANGUAGE BangPatterns #-}
#if __GLASGOW_HASKELL__ >= 702
{-# LANGUAGE Trustworthy #-}
#endif
module Data.List.Compat (
module Base
#if !(MIN_VERSION_base(4,15,0))
, singleton
#endif
#if !(MIN_VERSION_base(4,11,0))
, iterate'
#endif
#if !(MIN_VERSION_base(4,8,0))
, all
, and
, any
, concat
, concatMap
, elem
, find
, foldl
, foldl'
, foldl1
, foldr
, foldr1
, length
, maximum
, maximumBy
, minimum
, minimumBy
, notElem
, nub
, nubBy
, null
, or
, product
, sum
, union
, unionBy
, mapAccumL
, mapAccumR
, isSubsequenceOf
, sortOn
, uncons
, scanl'
#endif
#if !(MIN_VERSION_base(4,5,0))
, dropWhileEnd
#endif
) where
#if MIN_VERSION_base(4,8,0)
import Data.List as Base
#else
import Data.List as Base hiding (
all
, and
, any
, concat
, concatMap
, elem
, find
, foldl
, foldl'
, foldl1
, foldr
, foldr1
, length
, maximum
, maximumBy
, minimum
, minimumBy
, notElem
, nub
, nubBy
, null
, or
, product
, sum
, union
, unionBy
, mapAccumL
, mapAccumR
)
import Data.Foldable.Compat
import Data.Traversable
import Data.Ord (comparing)
#endif
#if !(MIN_VERSION_base(4,11,0))
import GHC.Exts (build)
import Prelude.Compat hiding (foldr, null)
#endif
#if !(MIN_VERSION_base(4,5,0))
dropWhileEnd :: (a -> Bool) -> [a] -> [a]
dropWhileEnd p = foldr (\x xs -> if p x && null xs then [] else x : xs) []
#endif
#if !(MIN_VERSION_base(4,8,0))
isSubsequenceOf :: (Eq a) => [a] -> [a] -> Bool
isSubsequenceOf [] _ = True
isSubsequenceOf _ [] = False
isSubsequenceOf a@(x:a') (y:b) | x == y = isSubsequenceOf a' b
| otherwise = isSubsequenceOf a b
sortOn :: Ord b => (a -> b) -> [a] -> [a]
sortOn f =
map snd . sortBy (comparing fst) . map (\x -> let y = f x in y `seq` (y, x))
uncons :: [a] -> Maybe (a, [a])
uncons [] = Nothing
uncons (x:xs) = Just (x, xs)
{-# NOINLINE [1] scanl' #-}
scanl' :: (b -> a -> b) -> b -> [a] -> [b]
scanl' = scanlGo'
where
scanlGo' :: (b -> a -> b) -> b -> [a] -> [b]
scanlGo' f !q ls = q : (case ls of
[] -> []
x:xs -> scanlGo' f (f q x) xs)
nub :: (Eq a) => [a] -> [a]
nub = nubBy (==)
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)
elem_by :: (a -> a -> Bool) -> a -> [a] -> Bool
elem_by _ _ [] = False
elem_by eq y (x:xs) = x `eq` y || elem_by eq y xs
union :: (Eq a) => [a] -> [a] -> [a]
union = unionBy (==)
unionBy :: (a -> a -> Bool) -> [a] -> [a] -> [a]
unionBy eq xs ys = xs ++ foldl (flip (deleteBy eq)) (nubBy eq ys) xs
#endif
#if !(MIN_VERSION_base(4,11,0))
{-# NOINLINE [1] iterate' #-}
iterate' :: (a -> a) -> a -> [a]
iterate' f x =
let x' = f x
in x' `seq` (x : iterate' f x')
{-# INLINE [0] iterate'FB #-}
iterate'FB :: (a -> b -> b) -> (a -> a) -> a -> b
iterate'FB c f x0 = go x0
where go x =
let x' = f x
in x' `seq` (x `c` go x')
{-# RULES
"iterate'" [~1] forall f x. iterate' f x = build (\c _n -> iterate'FB c f x)
"iterate'FB" [1] iterate'FB (:) = iterate'
#-}
#endif
#if !(MIN_VERSION_base(4,15,0))
singleton :: a -> [a]
singleton :: a -> [a]
singleton a
x = [a
x]
#endif