{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE ScopedTypeVariables #-}
module DSV.Vector
( Vector
, vectorIndexInt, vectorIndexNat, vectorIndexInteger, nthVectorElement
, vectorLookup
, vectorZip, vectorZipWith
, listToVector, vectorToList
, emptyVector
) where
import DSV.Numbers
import DSV.Prelude
import Control.Monad ((>=>))
import qualified Data.Vector as Vector
type Vector = Vector.Vector
vectorIndexInt :: forall a . Vector a -> Int -> Maybe a
vectorIndexInt = (Vector.!?)
vectorIndexNat :: forall a. Vector a -> Natural -> Maybe a
vectorIndexNat xs n = vectorIndexInt xs (fromIntegral n)
vectorIndexInteger ::
forall a .
Vector a -> Integer -> Maybe a
vectorIndexInteger xs =
fromIntegerMaybe >=> vectorIndexInt xs
vectorZip ::
forall a b .
Vector a -> Vector b -> Vector (a, b)
vectorZip = Vector.zip
vectorZipWith ::
forall a b c .
(a -> b -> c) -> Vector a -> Vector b -> Vector c
vectorZipWith = Vector.zipWith
nthVectorElement :: forall a . Integer -> Vector a -> Maybe a
nthVectorElement n xs = vectorIndexInteger xs (n - 1)
vectorLookup ::
forall name value .
(name -> Bool)
-> Vector (name, value)
-> Maybe value
vectorLookup f xs =
case filter (\(n, _) -> f n) (toList xs) of
[(_, v)] -> Just v
_ -> Nothing
listToVector :: forall a . [a] -> Vector a
listToVector = Vector.fromList
vectorToList :: forall a . Vector a -> [a]
vectorToList = toList
emptyVector :: forall a . Vector a
emptyVector = Vector.empty