{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE BangPatterns #-}
module Haskus.Utils.List
( at
, unsafeAt
, checkLength
, (++)
, replicate
, drop
, length
, take
, chunksOf
, pick1
, enumList
, zipLeftWith
, zipRightWith
, L.partition
, L.nub
, L.sort
, L.intersperse
, L.foldl'
, L.head
, L.tail
, L.zipWith
, L.repeat
, L.nubOn
, L.nubBy
, L.sortOn
, L.sortBy
, L.split
, L.splitOn
, L.groupOn
, L.groupBy
, L.transpose
, (L.\\)
, L.intersect
, L.find
, L.zip3
, L.zip4
, L.zip5
, L.zip6
, L.zip7
, L.stripPrefix
, L.isPrefixOf
, L.deleteBy
, L.isSuffixOf
, L.elem
, L.notElem
)
where
import Prelude hiding (replicate, length, drop, take)
import qualified Data.List as L
import qualified Data.List.Extra as L
at :: [a] -> Word -> Maybe a
{-# INLINABLE at #-}
at = go
where
go [] _ = Nothing
go (x:_xs) 0 = Just x
go (_x:xs) !n = go xs (n-1)
unsafeAt :: [a] -> Word -> a
{-# INLINABLE unsafeAt #-}
unsafeAt vs k = go vs k
where
go [] _ = error ("Unsafe list index too large: " ++ show k)
go (x:_xs) 0 = x
go (_x:xs) !n = go xs (n-1)
checkLength :: Word -> [a] -> Bool
checkLength 0 [] = True
checkLength 0 _ = False
checkLength _ [] = False
checkLength i (_:xs) = checkLength (i-1) xs
replicate :: Word -> a -> [a]
replicate n a = L.replicate (fromIntegral n) a
take :: Word -> [a] -> [a]
take n = L.take (fromIntegral n)
length :: Foldable t => t a -> Word
length = fromIntegral . L.length
drop :: Word -> [a] -> [a]
drop n = L.drop (fromIntegral n)
chunksOf :: Word -> [a] -> [[a]]
chunksOf n = L.chunksOf (fromIntegral n)
pick1 :: [a] -> [(a,[a])]
pick1 = go []
where
go _ [] = []
go ys (x:xs) = (x,reverse ys++xs) : go (x:ys) xs
enumList :: forall a. (Bounded a,Enum a) => [a]
enumList = enumFrom minBound
zipLeftWith :: (a -> b) -> [a] -> [(b,a)]
zipLeftWith f xs = fmap f xs `zip` xs
zipRightWith :: (a -> b) -> [a] -> [(a,b)]
zipRightWith f xs = xs `zip` fmap f xs