{-# LANGUAGE NoImplicitPrelude #-} module Precursor.Data.List ( -- * Basic functions uncons -- * List transformations , init , tail , reverse , intersperse , intercalate , transpose , subsequences , permutations , nub -- * Building lists , fromList -- ** Scans , scanl , scanl' , scanl1 , scanr , scanr1 -- ** Infinite lists , iterate , repeat , replicate , cycle -- ** Unfolding , unfoldr , unfoldl -- * Sublists -- ** Extracting sublists , take , drop , splitAt , takeWhile , dropWhile , group , inits , tails -- * Searching with a predicate , filter , partition -- * Zipping and unzipping lists , zip , zipWith , unzip , zip3 , zipWith3 , unzip3 -- * Ordered lists , sort , sortOn -- * Generalized functions -- | The predicate is assumed to define an equivalence. , groupBy -- | The function is assumed to define a total ordering. , sortBy ) where import Data.List hiding (init, insert, nub, tail) import GHC.Exts (fromList) import Precursor.Algebra.Monoid import Precursor.Algebra.Ord import Precursor.Control.Applicative import Precursor.Control.Category import Precursor.Control.State import Precursor.Data.Bool import Precursor.Data.Maybe import Precursor.Data.Set import Precursor.Data.Tuple import Precursor.Function -- $setup -- >>> import Precursor.Control.Alternative -- >>> import Precursor.Control.Functor -- >>> import Precursor.Numeric.Integral -- | 'unfoldl' is the dual of 'foldl', similar to 'unfoldr'. It can be -- quite useful as a kind of lightweight state-thing: -- -- >>> let toDigs b = unfoldl (ensure (>0) >-> flip divMod b) -- >>> toDigs 10 123 -- [1,2,3] -- >>> toDigs 2 5 -- [1,0,1] unfoldl :: (b -> Maybe (b, a)) -> b -> [a] unfoldl f = r [] where r a = maybe a ((uncurry.flip) (r . (:a))) . f -- | Extract the elements after the head of a list. If the given list is -- empty, returns an empty list. -- -- >>> tail [1,2,3] -- [2,3] -- >>> tail [] -- [] tail :: [a] -> [a] tail (_:xs) = xs tail xs = xs -- | Return all the elements of a list except the last one. -- If the given list is empty, returns an empty list. -- -- >>> init [1,2,3] -- [1,2] -- >>> init [] -- [] init :: [a] -> [a] init [] = [] init (x:xs) = init' x xs where init' _ [] = [] init' y (z:zs) = y : init' z zs -- | /O(n*log n)/. 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\'.) -- -- >>> nub [1,2,3,2,3,4,1,2,5,2,3] -- [1,2,3,4,5] -- >>> take 5 (nub [1..]) -- [1,2,3,4,5] -- >>> take 5 (nub [10,9..]) -- [10,9,8,7,6] nub :: Ord a => [a] -> [a] nub = flip evalState mempty . filterA (\x -> gets (not . member x) <* modify' (add x))