{-# LANGUAGE NoImplicitPrelude #-}
module NumericPrelude.List.Checked
(take, drop, splitAt, (!!), zipWith,
) where
import qualified Algebra.ToInteger as ToInteger
import Algebra.Ring (one, )
import Algebra.Additive (zero, (-), )
import Data.Tuple.HT (mapFst, )
import qualified NumericPrelude.List as NPList
import NumericPrelude.Base hiding (take, drop, splitAt, length, replicate, (!!), zipWith, )
moduleError :: String -> String -> a
moduleError name msg =
error $ "NumericPrelude.List.Left." ++ name ++ ": " ++ msg
take :: (ToInteger.C n) => n -> [a] -> [a]
take n =
if n<=zero
then const []
else \xt ->
case xt of
[] -> moduleError "take" "index out of range"
(x:xs) -> x : take (n-one) xs
drop :: (ToInteger.C n) => n -> [a] -> [a]
drop n =
if n<=zero
then id
else \xt ->
case xt of
[] -> moduleError "drop" "index out of range"
(_:xs) -> drop (n-one) xs
splitAt :: (ToInteger.C n) => n -> [a] -> ([a], [a])
splitAt n xt =
if n<=zero
then ([], xt)
else
case xt of
[] -> moduleError "splitAt" "index out of range"
(x:xs) -> mapFst (x:) $ splitAt (n-one) xs
(!!) :: (ToInteger.C n) => [a] -> n -> a
(!!) [] _ = moduleError "(!!)" "index out of range"
(!!) (x:xs) n =
if n<=zero
then x
else (!!) xs (n-one)
zipWith
:: (a -> b -> c)
-> [a]
-> [b]
-> [c]
zipWith = NPList.zipWithChecked