# module Data.List ( # (++), head, last, tail, init, null, length, map, reverse, # intersperse, intercalate, transpose, subsequences, permutations, # foldl, foldl', foldl1, foldl1', foldr, foldr1, concat, concatMap, # and, or, any, all, sum, product, maximum, minimum, scanl, scanl1, # scanr, scanr1, mapAccumL, mapAccumR, iterate, repeat, replicate, # cycle, unfoldr, take, drop, splitAt, takeWhile, dropWhile, span, # break, stripPrefix, group, inits, tails, isPrefixOf, isSuffixOf, # isInfixOf, elem, notElem, lookup, find, filter, partition, (!!), # elemIndex, elemIndices, findIndex, findIndices, zip, zip3, zip4, # zip5, zip6, zip7, zipWith, zipWith3, zipWith4, zipWith5, zipWith6, # zipWith7, unzip, unzip3, unzip4, unzip5, unzip6, unzip7, lines, # words, unlines, unwords, nub, delete, (\\), union, intersect, sort, # insert, nubBy, deleteBy, deleteFirstsBy, unionBy, intersectBy, # groupBy, sortBy, insertBy, maximumBy, minimumBy, genericLength, # genericTake, genericDrop, genericSplitAt, genericIndex, genericReplicate # ) where # list nil = \ c n . n cons = \ x xs c n . c x xs null = \ l . l (\x xs . false) true head = \ l . l (\x xs . x) (error head) tail = \ l . l (\x xs . xs) (error tail) map = \ f l . l (\x xs . cons (f x) (map f xs)) nil append = \ us vs . us (\x xs . cons x (append xs vs)) vs filter = \ p l . l (\x xs . p x (cons x) id (filter p xs)) nil index = \ l n . n (\p . l (\x xs . index xs p) (error index)) (l (\x xs . x) (error index)) reverse = \ l . l (\x xs . append (reverse xs) (cons x nil)) nil foldr = \ f e l . l (\x xs . f x (foldr f e xs)) e length = foldr (const succ) zero ands = foldr and true ors = foldr or false concat = foldr append nil all = \f . compose ands (map f) any = \f . compose ors (map f) concatMap = \f . compose concat (map f) composes = foldr compose id sum = foldr add zero product = foldr mul (succ zero) repeat = \x . cons x (repeat x) cycle = compose concat repeat zipWith = \f l r . l (\x xs . r (\y ys . cons (f x y) (zipWith f xs ys)) nil) nil partition = \p l . l (\x xs . p x first second (cons x) (partition p xs)) (pair nil nil) partitionEithers = \l . l (\e es . e (compose first cons) (compose second cons) (partitionEithers es)) (pair nil nil) take = \n l . n (\p . l (\x xs . cons x (take p xs)) nil) nil drop = \n l . n (\p . l (\x xs . drop p xs) nil) l transpose = \l . l (\xs xss . xs (\y ys . cons (cons y (concatMap (take 1) xss)) (transpose (cons ys (map (drop 1) xss)))) (transpose xss)) nil catMaybes = \l . l (\x xs . maybe id cons x (catMaybes xs)) nil iterate = \f . \x ! cons x (iterate f (f x)) last = \l . l (\x xs . xs (\y ys . last xs) x) (error last) replicate = \n x . take n (repeat x) rotate = \n bs . splitAt n bs \xs ys . append ys xs