module NoSlow.Backend.List ( module Prelude, cons, imap, enumFromTo_Int, index, append, slice, prescanl', prescanr', backpermute, update, update_, minIndex, maxIndex, unstablePartition, pair, from2, triple, from3 ) where import NoSlow.Util.Base import Data.List imap :: (Int -> a -> b) -> [a] -> [b] {-# INLINE imap #-} imap f = zipWith f [0..] enumFromTo_Int :: Int -> Int -> [Int] {-# INLINE enumFromTo_Int #-} enumFromTo_Int = enumFromTo cons :: a -> [a] -> [a] {-# INLINE cons #-} cons = (:) index :: [a] -> Int -> a {-# INLINE index #-} index = (!!) append :: [a] -> [a] -> [a] {-# INLINE append #-} append = (++) slice :: [a] -> Int -> Int -> [a] {-# INLINE slice #-} slice xs i n = take n (drop i xs) prescanl' :: (a -> b -> a) -> a -> [b] -> [a] {-# INLINE prescanl' #-} prescanl' f z xs = init (scanl f z xs) prescanr' :: (a -> b -> b) -> b -> [a] -> [b] {-# INLINE prescanr' #-} prescanr' f z xs = tail (scanr f z xs) backpermute = Unsupported update = Unsupported update_ = Unsupported minIndex = Unsupported maxIndex = Unsupported unstablePartition :: (a -> Bool) -> [a] -> ([a],[a]) {-# INLINE unstablePartition #-} unstablePartition = partition pair :: a -> b -> (a,b) pair = (,) from2 :: (a,b) -> (a,b) from2 = id triple :: a -> b -> c -> (a,b,c) triple = (,,) from3 :: (a,b,c) -> (a,b,c) from3 = id