{-# 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 forall a. [a] -> Int -> a
!! forall a b. (Integral a, Num b) => a -> b
fromIntegral Position
i
  atIndex :: [a] -> Position -> Elem [a]
atIndex [a]
v Position
i = [a]
v forall a. [a] -> Int -> a
!! 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 = HasCallStack => ByteString -> Int -> Word8
BS.index ByteString
v (forall a b. (Integral a, Num b) => a -> b
fromIntegral Position
i)
  atIndex :: ByteString -> Position -> Elem ByteString
atIndex ByteString
v Position
i = HasCallStack => ByteString -> Int -> Word8
BS.index ByteString
v (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 = forall a. Vector a -> Int -> a
DV.unsafeIndex Vector Word8
v (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 = forall a. Vector a -> Int -> a
DV.unsafeIndex Vector Word8
v (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 = forall a. Vector a -> Int -> a
DV.unsafeIndex Vector Word16
v (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 = forall a. Vector a -> Int -> a
DV.unsafeIndex Vector Word16
v (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 = forall a. Vector a -> Int -> a
DV.unsafeIndex Vector Word32
v (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 = forall a. Vector a -> Int -> a
DV.unsafeIndex Vector Word32
v (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 = forall a. Vector a -> Int -> a
DV.unsafeIndex Vector Word64
v (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 = forall a. Vector a -> Int -> a
DV.unsafeIndex Vector Word64
v (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 = forall a. Storable a => Vector a -> Int -> a
DVS.unsafeIndex Vector Word8
v (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 = forall a. Storable a => Vector a -> Int -> a
DVS.unsafeIndex Vector Word8
v (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 = forall a. Storable a => Vector a -> Int -> a
DVS.unsafeIndex Vector Word16
v (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 = forall a. Storable a => Vector a -> Int -> a
DVS.unsafeIndex Vector Word16
v (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 = forall a. Storable a => Vector a -> Int -> a
DVS.unsafeIndex Vector Word32
v (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 = forall a. Storable a => Vector a -> Int -> a
DVS.unsafeIndex Vector Word32
v (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 = forall a. Storable a => Vector a -> Int -> a
DVS.unsafeIndex Vector Word64
v (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 = forall a. Storable a => Vector a -> Int -> a
DVS.unsafeIndex Vector Word64
v (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 = forall a. Vector a -> Int -> a
DV.unsafeIndex Vector Int8
v (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 = forall a. Vector a -> Int -> a
DV.unsafeIndex Vector Int8
v (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 = forall a. Vector a -> Int -> a
DV.unsafeIndex Vector Int16
v (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 = forall a. Vector a -> Int -> a
DV.unsafeIndex Vector Int16
v (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 = forall a. Vector a -> Int -> a
DV.unsafeIndex Vector Int32
v (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 = forall a. Vector a -> Int -> a
DV.unsafeIndex Vector Int32
v (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 = forall a. Vector a -> Int -> a
DV.unsafeIndex Vector Position
v (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 = forall a. Vector a -> Int -> a
DV.unsafeIndex Vector Position
v (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 = forall a. Storable a => Vector a -> Int -> a
DVS.unsafeIndex Vector Int8
v (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 = forall a. Storable a => Vector a -> Int -> a
DVS.unsafeIndex Vector Int8
v (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 = forall a. Storable a => Vector a -> Int -> a
DVS.unsafeIndex Vector Int16
v (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 = forall a. Storable a => Vector a -> Int -> a
DVS.unsafeIndex Vector Int16
v (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 = forall a. Storable a => Vector a -> Int -> a
DVS.unsafeIndex Vector Int32
v (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 = forall a. Storable a => Vector a -> Int -> a
DVS.unsafeIndex Vector Int32
v (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 = forall a. Storable a => Vector a -> Int -> a
DVS.unsafeIndex Vector Position
v (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 = forall a. Storable a => Vector a -> Int -> a
DVS.unsafeIndex Vector Position
v (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 = forall a. Storable a => Vector a -> Int -> a
DVS.unsafeIndex Vector Int
v (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 = forall a. Storable a => Vector a -> Int -> a
DVS.unsafeIndex Vector Int
v (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 #-}

-- | Get the element of the container at the specified position, but return 'd' if position
-- is out of bounds.
atIndexOr :: AtIndex v => Elem v -> v -> Position -> Elem v
atIndexOr :: forall v. AtIndex v => Elem v -> v -> Position -> Elem v
atIndexOr Elem v
d v
v Position
vi = if Position
vi forall a. Ord a => a -> a -> Bool
>= Position
0 Bool -> Bool -> Bool
&& Position
vi forall a. Ord a => a -> a -> Bool
< forall v. Length v => v -> Position
end v
v
  then v
v forall v. AtIndex v => v -> Position -> Elem v
!!! Position
vi
  else Elem v
d
{-# INLINE atIndexOr #-}

-- | Get the element of the container at the specified position, but return 'before' if position
-- before the first element or 'after' if the position is beyond the last element.
atIndexOrBeforeOrAfter :: AtIndex v => Elem v -> Elem v -> v -> Position -> Elem v
atIndexOrBeforeOrAfter :: forall v. AtIndex v => Elem v -> Elem v -> v -> Position -> Elem v
atIndexOrBeforeOrAfter Elem v
before Elem v
after v
v Position
vi = if Position
vi forall a. Ord a => a -> a -> Bool
< forall v. Length v => v -> Position
end v
v
  then if Position
vi forall a. Ord a => a -> a -> Bool
>= Position
0
    then v
v forall v. AtIndex v => v -> Position -> Elem v
!!! Position
vi
    else Elem v
before
  else Elem v
after
{-# INLINE atIndexOrBeforeOrAfter #-}

-- | Get the element of the container at the specified position, but return the last element
-- if the position is past the end of the container or the default value 'before'' if the position
-- is before the beginning of the vector.
-- In the case when the container is empty, then the default value 'before'' is used.
atIndexOrBeforeOrLast :: (AtIndex v, Length v) => Elem v -> v -> Position -> Elem v
atIndexOrBeforeOrLast :: forall v.
(AtIndex v, Length v) =>
Elem v -> v -> Position -> Elem v
atIndexOrBeforeOrLast Elem v
before v
v Position
vi = if Position
vi forall a. Ord a => a -> a -> Bool
>= Position
0
  then if Position
vi forall a. Ord a => a -> a -> Bool
< forall v. Length v => v -> Position
end v
v
    then v
v forall v. AtIndex v => v -> Position -> Elem v
!!! Position
vi
    else if forall v. Length v => v -> Position
end v
v forall a. Eq a => a -> a -> Bool
/= Position
0
      then v
v forall v. AtIndex v => v -> Position -> Elem v
!!! (forall v. Length v => v -> Position
end v
v forall a. Num a => a -> a -> a
- Position
1)
      else Elem v
before
  else Elem v
before
{-# INLINE atIndexOrBeforeOrLast #-}