{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies #-}
module HaskellWorks.Data.AtIndex
( Container(..)
, AtIndex(..)
, Length(..)
, atIndexOr
, atIndexOrBeforeOrAfter
, atIndexOrBeforeOrLast
) where
import Data.Int
import Data.Word
import HaskellWorks.Data.Length
import HaskellWorks.Data.Positioning
import qualified Data.ByteString as BS
import qualified Data.Vector as DV
import qualified Data.Vector.Storable as DVS
class Length v => AtIndex v where
(!!!) :: v -> Position -> Elem v
atIndex :: v -> Position -> Elem v
instance AtIndex [a] where
!!! :: [a] -> Position -> Elem [a]
(!!!) [a]
v Position
i = [a]
v [a] -> Int -> a
forall a. [a] -> Int -> a
!! Position -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Position
i
atIndex :: [a] -> Position -> Elem [a]
atIndex [a]
v Position
i = [a]
v [a] -> Int -> a
forall a. [a] -> Int -> a
!! Position -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Position
i
{-# INLINE (!!!) #-}
{-# INLINE atIndex #-}
instance AtIndex BS.ByteString where
!!! :: ByteString -> Position -> Elem ByteString
(!!!) ByteString
v Position
i = ByteString -> Int -> Word8
BS.index ByteString
v (Position -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Position
i)
atIndex :: ByteString -> Position -> Elem ByteString
atIndex ByteString
v Position
i = ByteString -> Int -> Word8
BS.index ByteString
v (Position -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Position
i)
{-# INLINE (!!!) #-}
{-# INLINE atIndex #-}
instance AtIndex (DV.Vector Word8) where
#if !defined(BOUNDS_CHECKING_ENABLED)
!!! :: Vector Word8 -> Position -> Elem (Vector Word8)
(!!!) Vector Word8
v Position
i = Vector Word8 -> Int -> Word8
forall a. Vector a -> Int -> a
DV.unsafeIndex Vector Word8
v (Position -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Position
i)
atIndex :: Vector Word8 -> Position -> Elem (Vector Word8)
atIndex Vector Word8
v Position
i = Vector Word8 -> Int -> Word8
forall a. Vector a -> Int -> a
DV.unsafeIndex Vector Word8
v (Position -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Position
i)
#else
(!!!) v i = v DV.! fromIntegral i
atIndex v i = v DV.! fromIntegral i
#endif
{-# INLINE (!!!) #-}
{-# INLINE atIndex #-}
instance AtIndex (DV.Vector Word16) where
#if !defined(BOUNDS_CHECKING_ENABLED)
!!! :: Vector Word16 -> Position -> Elem (Vector Word16)
(!!!) Vector Word16
v Position
i = Vector Word16 -> Int -> Word16
forall a. Vector a -> Int -> a
DV.unsafeIndex Vector Word16
v (Position -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Position
i)
atIndex :: Vector Word16 -> Position -> Elem (Vector Word16)
atIndex Vector Word16
v Position
i = Vector Word16 -> Int -> Word16
forall a. Vector a -> Int -> a
DV.unsafeIndex Vector Word16
v (Position -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Position
i)
#else
(!!!) v i = v DV.! fromIntegral i
atIndex v i = v DV.! fromIntegral i
#endif
{-# INLINE (!!!) #-}
{-# INLINE atIndex #-}
instance AtIndex (DV.Vector Word32) where
#if !defined(BOUNDS_CHECKING_ENABLED)
!!! :: Vector Word32 -> Position -> Elem (Vector Word32)
(!!!) Vector Word32
v Position
i = Vector Word32 -> Int -> Word32
forall a. Vector a -> Int -> a
DV.unsafeIndex Vector Word32
v (Position -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Position
i)
atIndex :: Vector Word32 -> Position -> Elem (Vector Word32)
atIndex Vector Word32
v Position
i = Vector Word32 -> Int -> Word32
forall a. Vector a -> Int -> a
DV.unsafeIndex Vector Word32
v (Position -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Position
i)
#else
(!!!) v i = v DV.! fromIntegral i
atIndex v i = v DV.! fromIntegral i
#endif
{-# INLINE (!!!) #-}
{-# INLINE atIndex #-}
instance AtIndex (DV.Vector Word64) where
#if !defined(BOUNDS_CHECKING_ENABLED)
!!! :: Vector Word64 -> Position -> Elem (Vector Word64)
(!!!) Vector Word64
v Position
i = Vector Word64 -> Int -> Word64
forall a. Vector a -> Int -> a
DV.unsafeIndex Vector Word64
v (Position -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Position
i)
atIndex :: Vector Word64 -> Position -> Elem (Vector Word64)
atIndex Vector Word64
v Position
i = Vector Word64 -> Int -> Word64
forall a. Vector a -> Int -> a
DV.unsafeIndex Vector Word64
v (Position -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Position
i)
#else
(!!!) v i = v DV.! fromIntegral i
atIndex v i = v DV.! fromIntegral i
#endif
{-# INLINE (!!!) #-}
{-# INLINE atIndex #-}
instance AtIndex (DVS.Vector Word8) where
#if !defined(BOUNDS_CHECKING_ENABLED)
!!! :: Vector Word8 -> Position -> Elem (Vector Word8)
(!!!) Vector Word8
v Position
i = Vector Word8 -> Int -> Word8
forall a. Storable a => Vector a -> Int -> a
DVS.unsafeIndex Vector Word8
v (Position -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Position
i)
atIndex :: Vector Word8 -> Position -> Elem (Vector Word8)
atIndex Vector Word8
v Position
i = Vector Word8 -> Int -> Word8
forall a. Storable a => Vector a -> Int -> a
DVS.unsafeIndex Vector Word8
v (Position -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Position
i)
#else
(!!!) v i = v DVS.! fromIntegral i
atIndex v i = v DVS.! fromIntegral i
#endif
{-# INLINE (!!!) #-}
{-# INLINE atIndex #-}
instance AtIndex (DVS.Vector Word16) where
#if !defined(BOUNDS_CHECKING_ENABLED)
!!! :: Vector Word16 -> Position -> Elem (Vector Word16)
(!!!) Vector Word16
v Position
i = Vector Word16 -> Int -> Word16
forall a. Storable a => Vector a -> Int -> a
DVS.unsafeIndex Vector Word16
v (Position -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Position
i)
atIndex :: Vector Word16 -> Position -> Elem (Vector Word16)
atIndex Vector Word16
v Position
i = Vector Word16 -> Int -> Word16
forall a. Storable a => Vector a -> Int -> a
DVS.unsafeIndex Vector Word16
v (Position -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Position
i)
#else
(!!!) v i = v DVS.! fromIntegral i
atIndex v i = v DVS.! fromIntegral i
#endif
{-# INLINE (!!!) #-}
{-# INLINE atIndex #-}
instance AtIndex (DVS.Vector Word32) where
#if !defined(BOUNDS_CHECKING_ENABLED)
!!! :: Vector Word32 -> Position -> Elem (Vector Word32)
(!!!) Vector Word32
v Position
i = Vector Word32 -> Int -> Word32
forall a. Storable a => Vector a -> Int -> a
DVS.unsafeIndex Vector Word32
v (Position -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Position
i)
atIndex :: Vector Word32 -> Position -> Elem (Vector Word32)
atIndex Vector Word32
v Position
i = Vector Word32 -> Int -> Word32
forall a. Storable a => Vector a -> Int -> a
DVS.unsafeIndex Vector Word32
v (Position -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Position
i)
#else
(!!!) v i = v DVS.! fromIntegral i
atIndex v i = v DVS.! fromIntegral i
#endif
{-# INLINE (!!!) #-}
{-# INLINE atIndex #-}
instance AtIndex (DVS.Vector Word64) where
#if !defined(BOUNDS_CHECKING_ENABLED)
!!! :: Vector Word64 -> Position -> Elem (Vector Word64)
(!!!) Vector Word64
v Position
i = Vector Word64 -> Int -> Word64
forall a. Storable a => Vector a -> Int -> a
DVS.unsafeIndex Vector Word64
v (Position -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Position
i)
atIndex :: Vector Word64 -> Position -> Elem (Vector Word64)
atIndex Vector Word64
v Position
i = Vector Word64 -> Int -> Word64
forall a. Storable a => Vector a -> Int -> a
DVS.unsafeIndex Vector Word64
v (Position -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Position
i)
#else
(!!!) v i = v DVS.! fromIntegral i
atIndex v i = v DVS.! fromIntegral i
#endif
{-# INLINE (!!!) #-}
{-# INLINE atIndex #-}
instance AtIndex (DV.Vector Int8) where
#if !defined(BOUNDS_CHECKING_ENABLED)
!!! :: Vector Int8 -> Position -> Elem (Vector Int8)
(!!!) Vector Int8
v Position
i = Vector Int8 -> Int -> Int8
forall a. Vector a -> Int -> a
DV.unsafeIndex Vector Int8
v (Position -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Position
i)
atIndex :: Vector Int8 -> Position -> Elem (Vector Int8)
atIndex Vector Int8
v Position
i = Vector Int8 -> Int -> Int8
forall a. Vector a -> Int -> a
DV.unsafeIndex Vector Int8
v (Position -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Position
i)
#else
(!!!) v i = v DV.! fromIntegral i
atIndex v i = v DV.! fromIntegral i
#endif
{-# INLINE (!!!) #-}
{-# INLINE atIndex #-}
instance AtIndex (DV.Vector Int16) where
#if !defined(BOUNDS_CHECKING_ENABLED)
!!! :: Vector Int16 -> Position -> Elem (Vector Int16)
(!!!) Vector Int16
v Position
i = Vector Int16 -> Int -> Int16
forall a. Vector a -> Int -> a
DV.unsafeIndex Vector Int16
v (Position -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Position
i)
atIndex :: Vector Int16 -> Position -> Elem (Vector Int16)
atIndex Vector Int16
v Position
i = Vector Int16 -> Int -> Int16
forall a. Vector a -> Int -> a
DV.unsafeIndex Vector Int16
v (Position -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Position
i)
#else
(!!!) v i = v DV.! fromIntegral i
atIndex v i = v DV.! fromIntegral i
#endif
{-# INLINE (!!!) #-}
{-# INLINE atIndex #-}
instance AtIndex (DV.Vector Int32) where
#if !defined(BOUNDS_CHECKING_ENABLED)
!!! :: Vector Int32 -> Position -> Elem (Vector Int32)
(!!!) Vector Int32
v Position
i = Vector Int32 -> Int -> Int32
forall a. Vector a -> Int -> a
DV.unsafeIndex Vector Int32
v (Position -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Position
i)
atIndex :: Vector Int32 -> Position -> Elem (Vector Int32)
atIndex Vector Int32
v Position
i = Vector Int32 -> Int -> Int32
forall a. Vector a -> Int -> a
DV.unsafeIndex Vector Int32
v (Position -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Position
i)
#else
(!!!) v i = v DV.! fromIntegral i
atIndex v i = v DV.! fromIntegral i
#endif
{-# INLINE (!!!) #-}
{-# INLINE atIndex #-}
instance AtIndex (DV.Vector Int64) where
#if !defined(BOUNDS_CHECKING_ENABLED)
!!! :: Vector Position -> Position -> Elem (Vector Position)
(!!!) Vector Position
v Position
i = Vector Position -> Int -> Position
forall a. Vector a -> Int -> a
DV.unsafeIndex Vector Position
v (Position -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Position
i)
atIndex :: Vector Position -> Position -> Elem (Vector Position)
atIndex Vector Position
v Position
i = Vector Position -> Int -> Position
forall a. Vector a -> Int -> a
DV.unsafeIndex Vector Position
v (Position -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Position
i)
#else
(!!!) v i = v DV.! fromIntegral i
atIndex v i = v DV.! fromIntegral i
#endif
{-# INLINE (!!!) #-}
{-# INLINE atIndex #-}
instance AtIndex (DVS.Vector Int8) where
#if !defined(BOUNDS_CHECKING_ENABLED)
!!! :: Vector Int8 -> Position -> Elem (Vector Int8)
(!!!) Vector Int8
v Position
i = Vector Int8 -> Int -> Int8
forall a. Storable a => Vector a -> Int -> a
DVS.unsafeIndex Vector Int8
v (Position -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Position
i)
atIndex :: Vector Int8 -> Position -> Elem (Vector Int8)
atIndex Vector Int8
v Position
i = Vector Int8 -> Int -> Int8
forall a. Storable a => Vector a -> Int -> a
DVS.unsafeIndex Vector Int8
v (Position -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Position
i)
#else
(!!!) v i = v DVS.! fromIntegral i
atIndex v i = v DVS.! fromIntegral i
#endif
{-# INLINE (!!!) #-}
{-# INLINE atIndex #-}
instance AtIndex (DVS.Vector Int16) where
#if !defined(BOUNDS_CHECKING_ENABLED)
!!! :: Vector Int16 -> Position -> Elem (Vector Int16)
(!!!) Vector Int16
v Position
i = Vector Int16 -> Int -> Int16
forall a. Storable a => Vector a -> Int -> a
DVS.unsafeIndex Vector Int16
v (Position -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Position
i)
atIndex :: Vector Int16 -> Position -> Elem (Vector Int16)
atIndex Vector Int16
v Position
i = Vector Int16 -> Int -> Int16
forall a. Storable a => Vector a -> Int -> a
DVS.unsafeIndex Vector Int16
v (Position -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Position
i)
#else
(!!!) v i = v DVS.! fromIntegral i
atIndex v i = v DVS.! fromIntegral i
#endif
{-# INLINE (!!!) #-}
{-# INLINE atIndex #-}
instance AtIndex (DVS.Vector Int32) where
#if !defined(BOUNDS_CHECKING_ENABLED)
!!! :: Vector Int32 -> Position -> Elem (Vector Int32)
(!!!) Vector Int32
v Position
i = Vector Int32 -> Int -> Int32
forall a. Storable a => Vector a -> Int -> a
DVS.unsafeIndex Vector Int32
v (Position -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Position
i)
atIndex :: Vector Int32 -> Position -> Elem (Vector Int32)
atIndex Vector Int32
v Position
i = Vector Int32 -> Int -> Int32
forall a. Storable a => Vector a -> Int -> a
DVS.unsafeIndex Vector Int32
v (Position -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Position
i)
#else
(!!!) v i = v DVS.! fromIntegral i
atIndex v i = v DVS.! fromIntegral i
#endif
{-# INLINE (!!!) #-}
{-# INLINE atIndex #-}
instance AtIndex (DVS.Vector Int64) where
#if !defined(BOUNDS_CHECKING_ENABLED)
!!! :: Vector Position -> Position -> Elem (Vector Position)
(!!!) Vector Position
v Position
i = Vector Position -> Int -> Position
forall a. Storable a => Vector a -> Int -> a
DVS.unsafeIndex Vector Position
v (Position -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Position
i)
atIndex :: Vector Position -> Position -> Elem (Vector Position)
atIndex Vector Position
v Position
i = Vector Position -> Int -> Position
forall a. Storable a => Vector a -> Int -> a
DVS.unsafeIndex Vector Position
v (Position -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Position
i)
#else
(!!!) v i = v DVS.! fromIntegral i
atIndex v i = v DVS.! fromIntegral i
#endif
{-# INLINE (!!!) #-}
{-# INLINE atIndex #-}
instance AtIndex (DVS.Vector Int) where
#if !defined(BOUNDS_CHECKING_ENABLED)
!!! :: Vector Int -> Position -> Elem (Vector Int)
(!!!) Vector Int
v Position
i = Vector Int -> Int -> Int
forall a. Storable a => Vector a -> Int -> a
DVS.unsafeIndex Vector Int
v (Position -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Position
i)
atIndex :: Vector Int -> Position -> Elem (Vector Int)
atIndex Vector Int
v Position
i = Vector Int -> Int -> Int
forall a. Storable a => Vector a -> Int -> a
DVS.unsafeIndex Vector Int
v (Position -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Position
i)
#else
(!!!) v i = v DVS.! fromIntegral i
atIndex v i = v DVS.! fromIntegral i
#endif
{-# INLINE (!!!) #-}
{-# INLINE atIndex #-}
atIndexOr :: AtIndex v => Elem v -> v -> Position -> Elem v
atIndexOr :: Elem v -> v -> Position -> Elem v
atIndexOr Elem v
d v
v Position
vi = if Position
vi Position -> Position -> Bool
forall a. Ord a => a -> a -> Bool
>= Position
0 Bool -> Bool -> Bool
&& Position
vi Position -> Position -> Bool
forall a. Ord a => a -> a -> Bool
< v -> Position
forall v. Length v => v -> Position
end v
v
then v
v v -> Position -> Elem v
forall v. AtIndex v => v -> Position -> Elem v
!!! Position
vi
else Elem v
d
{-# INLINE atIndexOr #-}
atIndexOrBeforeOrAfter :: AtIndex v => Elem v -> Elem v -> v -> Position -> Elem v
atIndexOrBeforeOrAfter :: Elem v -> Elem v -> v -> Position -> Elem v
atIndexOrBeforeOrAfter Elem v
before Elem v
after v
v Position
vi = if Position
vi Position -> Position -> Bool
forall a. Ord a => a -> a -> Bool
< v -> Position
forall v. Length v => v -> Position
end v
v
then if Position
vi Position -> Position -> Bool
forall a. Ord a => a -> a -> Bool
>= Position
0
then v
v v -> Position -> Elem v
forall v. AtIndex v => v -> Position -> Elem v
!!! Position
vi
else Elem v
before
else Elem v
after
{-# INLINE atIndexOrBeforeOrAfter #-}
atIndexOrBeforeOrLast :: (AtIndex v, Length v) => Elem v -> v -> Position -> Elem v
atIndexOrBeforeOrLast :: Elem v -> v -> Position -> Elem v
atIndexOrBeforeOrLast Elem v
before v
v Position
vi = if Position
vi Position -> Position -> Bool
forall a. Ord a => a -> a -> Bool
>= Position
0
then if Position
vi Position -> Position -> Bool
forall a. Ord a => a -> a -> Bool
< v -> Position
forall v. Length v => v -> Position
end v
v
then v
v v -> Position -> Elem v
forall v. AtIndex v => v -> Position -> Elem v
!!! Position
vi
else if v -> Position
forall v. Length v => v -> Position
end v
v Position -> Position -> Bool
forall a. Eq a => a -> a -> Bool
/= Position
0
then v
v v -> Position -> Elem v
forall v. AtIndex v => v -> Position -> Elem v
!!! (v -> Position
forall v. Length v => v -> Position
end v
v Position -> Position -> Position
forall a. Num a => a -> a -> a
- Position
1)
else Elem v
before
else Elem v
before
{-# INLINE atIndexOrBeforeOrLast #-}