{-# Language GADTs, DataKinds, TypeOperators, BangPatterns #-}
{-# Language PatternGuards #-}
{-# Language TypeApplications, ScopedTypeVariables #-}
{-# Language Rank2Types, RoleAnnotations #-}
{-# Language CPP #-}
#if __GLASGOW_HASKELL__ >= 805
{-# Language NoStarIsType #-}
#endif
module Data.Parameterized.Vector
( Vector
, fromList
, toList
, length
, nonEmpty
, lengthInt
, elemAt
, elemAtMaybe
, elemAtUnsafe
, insertAt
, insertAtMaybe
, uncons
, slice
, Data.Parameterized.Vector.take
, replace
, mapAt
, mapAtM
, zipWith
, zipWithM
, zipWithM_
, interleave
, shuffle
, reverse
, rotateL
, rotateR
, shiftL
, shiftR
, singleton
, cons
, snoc
, generate
, generateM
, joinWithM
, joinWith
, splitWith
, splitWithA
, split
, join
, append
) where
import qualified Data.Vector as Vector
import Data.Functor.Compose
import Data.Coerce
import Data.Vector.Mutable (MVector)
import qualified Data.Vector.Mutable as MVector
import Control.Monad.ST
import Data.Functor.Identity
import Data.Parameterized.NatRepr
import Data.Parameterized.NatRepr.Internal
import Data.Proxy
import Prelude hiding (length,reverse,zipWith)
import Numeric.Natural
import Data.Parameterized.Utils.Endian
data Vector n a where
Vector :: (1 <= n) => !(Vector.Vector a) -> Vector n a
type role Vector nominal representational
instance Eq a => Eq (Vector n a) where
(Vector Vector a
x) == :: Vector n a -> Vector n a -> Bool
== (Vector Vector a
y) = Vector a
x Vector a -> Vector a -> Bool
forall a. Eq a => a -> a -> Bool
== Vector a
y
instance Show a => Show (Vector n a) where
show :: Vector n a -> String
show (Vector Vector a
x) = Vector a -> String
forall a. Show a => a -> String
show Vector a
x
toList :: Vector n a -> [a]
toList :: Vector n a -> [a]
toList (Vector Vector a
v) = Vector a -> [a]
forall a. Vector a -> [a]
Vector.toList Vector a
v
{-# Inline toList #-}
length :: Vector n a -> NatRepr n
length :: Vector n a -> NatRepr n
length (Vector Vector a
xs) = Natural -> NatRepr n
forall (n :: Nat). Natural -> NatRepr n
NatRepr (Int -> Natural
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector a -> Int
forall a. Vector a -> Int
Vector.length Vector a
xs) :: Natural)
{-# INLINE length #-}
lengthInt :: Vector n a -> Int
lengthInt :: Vector n a -> Int
lengthInt (Vector Vector a
xs) = Vector a -> Int
forall a. Vector a -> Int
Vector.length Vector a
xs
{-# Inline lengthInt #-}
elemAt :: ((i+1) <= n) => NatRepr i -> Vector n a -> a
elemAt :: NatRepr i -> Vector n a -> a
elemAt NatRepr i
n (Vector Vector a
xs) = Vector a
xs Vector a -> Int -> a
forall a. Vector a -> Int -> a
Vector.! NatRepr i -> Int
forall (n :: Nat). NatRepr n -> Int
widthVal NatRepr i
n
elemAtMaybe :: Int -> Vector n a -> Maybe a
elemAtMaybe :: Int -> Vector n a -> Maybe a
elemAtMaybe Int
n (Vector Vector a
xs) = Vector a
xs Vector a -> Int -> Maybe a
forall a. Vector a -> Int -> Maybe a
Vector.!? Int
n
{-# INLINE elemAt #-}
elemAtUnsafe :: Int -> Vector n a -> a
elemAtUnsafe :: Int -> Vector n a -> a
elemAtUnsafe Int
n (Vector Vector a
xs) = Vector a
xs Vector a -> Int -> a
forall a. Vector a -> Int -> a
Vector.! Int
n
{-# INLINE elemAtUnsafe #-}
insertAt :: ((i + 1) <= n) => NatRepr i -> a -> Vector n a -> Vector n a
insertAt :: NatRepr i -> a -> Vector n a -> Vector n a
insertAt NatRepr i
n a
a (Vector Vector a
xs) = Vector a -> Vector n a
forall (n :: Nat) a. (1 <= n) => Vector a -> Vector n a
Vector (Vector a -> [(Int, a)] -> Vector a
forall a. Vector a -> [(Int, a)] -> Vector a
Vector.unsafeUpd Vector a
xs [(NatRepr i -> Int
forall (n :: Nat). NatRepr n -> Int
widthVal NatRepr i
n,a
a)])
insertAtMaybe :: Int -> a -> Vector n a -> Maybe (Vector n a)
insertAtMaybe :: Int -> a -> Vector n a -> Maybe (Vector n a)
insertAtMaybe Int
n a
a (Vector Vector a
xs)
| Int
0 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
n Bool -> Bool -> Bool
&& Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Vector a -> Int
forall a. Vector a -> Int
Vector.length Vector a
xs = Vector n a -> Maybe (Vector n a)
forall a. a -> Maybe a
Just (Vector a -> Vector n a
forall (n :: Nat) a. (1 <= n) => Vector a -> Vector n a
Vector (Vector a -> [(Int, a)] -> Vector a
forall a. Vector a -> [(Int, a)] -> Vector a
Vector.unsafeUpd Vector a
xs [(Int
n,a
a)]))
| Bool
otherwise = Maybe (Vector n a)
forall a. Maybe a
Nothing
nonEmpty :: Vector n a -> LeqProof 1 n
nonEmpty :: Vector n a -> LeqProof 1 n
nonEmpty (Vector Vector a
_) = LeqProof 1 n
forall (m :: Nat) (n :: Nat). (m <= n) => LeqProof m n
LeqProof
{-# Inline nonEmpty #-}
uncons :: forall n a. Vector n a -> (a, Either (n :~: 1) (Vector (n-1) a))
uncons :: Vector n a -> (a, Either (n :~: 1) (Vector (n - 1) a))
uncons v :: Vector n a
v@(Vector Vector a
xs) = (Vector a -> a
forall a. Vector a -> a
Vector.head Vector a
xs, Either (n :~: 1) (Vector (n - 1) a)
mbTail)
where
mbTail :: Either (n :~: 1) (Vector (n - 1) a)
mbTail :: Either (n :~: 1) (Vector (n - 1) a)
mbTail = case NatRepr 1 -> NatRepr n -> Either (LeqProof (1 + 1) n) (1 :~: n)
forall (m :: Nat) (n :: Nat).
(m <= n) =>
NatRepr m -> NatRepr n -> Either (LeqProof (m + 1) n) (m :~: n)
testStrictLeq (KnownNat 1 => NatRepr 1
forall (n :: Nat). KnownNat n => NatRepr n
knownNat @1) (Vector n a -> NatRepr n
forall (n :: Nat) a. Vector n a -> NatRepr n
length Vector n a
v) of
Left LeqProof (1 + 1) n
n2_leq_n ->
do LeqProof 1 (n - 1)
LeqProof <- LeqProof 1 (n - 1) -> Either (n :~: 1) (LeqProof 1 (n - 1))
forall (m :: Type -> Type) a. Monad m => a -> m a
return (LeqProof 2 n -> LeqProof 1 1 -> LeqProof (2 - 1) (n - 1)
forall (x_l :: Nat) (x_h :: Nat) (y_l :: Nat) (y_h :: Nat).
LeqProof x_l x_h
-> LeqProof y_l y_h -> LeqProof (x_l - y_h) (x_h - y_l)
leqSub2 LeqProof 2 n
LeqProof (1 + 1) n
n2_leq_n (NatRepr 1 -> LeqProof 1 1
forall (f :: Nat -> Type) (n :: Nat). f n -> LeqProof n n
leqRefl (KnownNat 1 => NatRepr 1
forall (n :: Nat). KnownNat n => NatRepr n
knownNat @1)))
Vector (n - 1) a -> Either (n :~: 1) (Vector (n - 1) a)
forall (m :: Type -> Type) a. Monad m => a -> m a
return (Vector a -> Vector (n - 1) a
forall (n :: Nat) a. (1 <= n) => Vector a -> Vector n a
Vector (Vector a -> Vector a
forall a. Vector a -> Vector a
Vector.tail Vector a
xs))
Right 1 :~: n
Refl -> (n :~: n) -> Either (n :~: n) (Vector 0 a)
forall a b. a -> Either a b
Left n :~: n
forall k (a :: k). a :~: a
Refl
{-# Inline uncons #-}
fromList :: (1 <= n) => NatRepr n -> [a] -> Maybe (Vector n a)
fromList :: NatRepr n -> [a] -> Maybe (Vector n a)
fromList NatRepr n
n [a]
xs
| NatRepr n -> Int
forall (n :: Nat). NatRepr n -> Int
widthVal NatRepr n
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Vector a -> Int
forall a. Vector a -> Int
Vector.length Vector a
v = Vector n a -> Maybe (Vector n a)
forall a. a -> Maybe a
Just (Vector a -> Vector n a
forall (n :: Nat) a. (1 <= n) => Vector a -> Vector n a
Vector Vector a
v)
| Bool
otherwise = Maybe (Vector n a)
forall a. Maybe a
Nothing
where
v :: Vector a
v = [a] -> Vector a
forall a. [a] -> Vector a
Vector.fromList [a]
xs
{-# INLINE fromList #-}
slice :: (i + w <= n, 1 <= w) =>
NatRepr i ->
NatRepr w ->
Vector n a -> Vector w a
slice :: NatRepr i -> NatRepr w -> Vector n a -> Vector w a
slice NatRepr i
i NatRepr w
w (Vector Vector a
xs) = Vector a -> Vector w a
forall (n :: Nat) a. (1 <= n) => Vector a -> Vector n a
Vector (Int -> Int -> Vector a -> Vector a
forall a. Int -> Int -> Vector a -> Vector a
Vector.slice (NatRepr i -> Int
forall (n :: Nat). NatRepr n -> Int
widthVal NatRepr i
i) (NatRepr w -> Int
forall (n :: Nat). NatRepr n -> Int
widthVal NatRepr w
w) Vector a
xs)
{-# INLINE slice #-}
take :: forall n x a. (1 <= n) => NatRepr n -> Vector (n + x) a -> Vector n a
take :: NatRepr n -> Vector (n + x) a -> Vector n a
take | LeqProof n (n + x)
LeqProof <- LeqProof n (n + x)
prf = NatRepr 0 -> NatRepr n -> Vector (n + x) a -> Vector n a
forall (i :: Nat) (w :: Nat) (n :: Nat) a.
((i + w) <= n, 1 <= w) =>
NatRepr i -> NatRepr w -> Vector n a -> Vector w a
slice (KnownNat 0 => NatRepr 0
forall (n :: Nat). KnownNat n => NatRepr n
knownNat @0)
where
prf :: LeqProof n (n + x)
prf = LeqProof n n -> Proxy x -> LeqProof n (n + x)
forall (f :: Nat -> Type) (m :: Nat) (n :: Nat) (p :: Nat).
LeqProof m n -> f p -> LeqProof m (n + p)
leqAdd (Proxy n -> LeqProof n n
forall (f :: Nat -> Type) (n :: Nat). f n -> LeqProof n n
leqRefl (Proxy n
forall k (t :: k). Proxy t
Proxy @n)) (Proxy x
forall k (t :: k). Proxy t
Proxy @x)
mapAtM :: Monad m => (i + w <= n, 1 <= w) =>
NatRepr i ->
NatRepr w ->
(Vector w a -> m (Vector w a)) ->
Vector n a -> m (Vector n a)
mapAtM :: NatRepr i
-> NatRepr w
-> (Vector w a -> m (Vector w a))
-> Vector n a
-> m (Vector n a)
mapAtM NatRepr i
i NatRepr w
w Vector w a -> m (Vector w a)
f (Vector Vector a
vn) =
let
(Vector a
vhead, Vector a
vtail) = Int -> Vector a -> (Vector a, Vector a)
forall a. Int -> Vector a -> (Vector a, Vector a)
Vector.splitAt (NatRepr i -> Int
forall (n :: Nat). NatRepr n -> Int
widthVal NatRepr i
i) Vector a
vn
(Vector a
vsect, Vector a
vend) = Int -> Vector a -> (Vector a, Vector a)
forall a. Int -> Vector a -> (Vector a, Vector a)
Vector.splitAt (NatRepr w -> Int
forall (n :: Nat). NatRepr n -> Int
widthVal NatRepr w
w) Vector a
vtail
in do
Vector Vector a
vsect' <- Vector w a -> m (Vector w a)
f (Vector a -> Vector w a
forall (n :: Nat) a. (1 <= n) => Vector a -> Vector n a
Vector Vector a
vsect)
Vector n a -> m (Vector n a)
forall (m :: Type -> Type) a. Monad m => a -> m a
return (Vector n a -> m (Vector n a)) -> Vector n a -> m (Vector n a)
forall a b. (a -> b) -> a -> b
$ Vector a -> Vector n a
forall (n :: Nat) a. (1 <= n) => Vector a -> Vector n a
Vector (Vector a -> Vector n a) -> Vector a -> Vector n a
forall a b. (a -> b) -> a -> b
$ Vector a
vhead Vector a -> Vector a -> Vector a
forall a. Vector a -> Vector a -> Vector a
Vector.++ Vector a
vsect' Vector a -> Vector a -> Vector a
forall a. Vector a -> Vector a -> Vector a
Vector.++ Vector a
vend
mapAt :: (i + w <= n, 1 <= w) =>
NatRepr i ->
NatRepr w ->
(Vector w a -> Vector w a) ->
Vector n a -> Vector n a
mapAt :: NatRepr i
-> NatRepr w
-> (Vector w a -> Vector w a)
-> Vector n a
-> Vector n a
mapAt NatRepr i
i NatRepr w
w Vector w a -> Vector w a
f Vector n a
vn = Identity (Vector n a) -> Vector n a
forall a. Identity a -> a
runIdentity (Identity (Vector n a) -> Vector n a)
-> Identity (Vector n a) -> Vector n a
forall a b. (a -> b) -> a -> b
$ NatRepr i
-> NatRepr w
-> (Vector w a -> Identity (Vector w a))
-> Vector n a
-> Identity (Vector n a)
forall (m :: Type -> Type) (i :: Nat) (w :: Nat) (n :: Nat) a.
(Monad m, (i + w) <= n, 1 <= w) =>
NatRepr i
-> NatRepr w
-> (Vector w a -> m (Vector w a))
-> Vector n a
-> m (Vector n a)
mapAtM NatRepr i
i NatRepr w
w (Vector w a -> Identity (Vector w a)
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure (Vector w a -> Identity (Vector w a))
-> (Vector w a -> Vector w a)
-> Vector w a
-> Identity (Vector w a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vector w a -> Vector w a
f) Vector n a
vn
replace :: (i + w <= n, 1 <= w) =>
NatRepr i ->
Vector w a ->
Vector n a -> Vector n a
replace :: NatRepr i -> Vector w a -> Vector n a -> Vector n a
replace NatRepr i
i Vector w a
vw Vector n a
vn = NatRepr i
-> NatRepr w
-> (Vector w a -> Vector w a)
-> Vector n a
-> Vector n a
forall (i :: Nat) (w :: Nat) (n :: Nat) a.
((i + w) <= n, 1 <= w) =>
NatRepr i
-> NatRepr w
-> (Vector w a -> Vector w a)
-> Vector n a
-> Vector n a
mapAt NatRepr i
i (Vector w a -> NatRepr w
forall (n :: Nat) a. Vector n a -> NatRepr n
length Vector w a
vw) (Vector w a -> Vector w a -> Vector w a
forall a b. a -> b -> a
const Vector w a
vw) Vector n a
vn
instance Functor (Vector n) where
fmap :: (a -> b) -> Vector n a -> Vector n b
fmap a -> b
f (Vector Vector a
xs) = Vector b -> Vector n b
forall (n :: Nat) a. (1 <= n) => Vector a -> Vector n a
Vector ((a -> b) -> Vector a -> Vector b
forall a b. (a -> b) -> Vector a -> Vector b
Vector.map a -> b
f Vector a
xs)
{-# Inline fmap #-}
instance Foldable (Vector n) where
foldMap :: (a -> m) -> Vector n a -> m
foldMap a -> m
f (Vector Vector a
xs) = (a -> m) -> Vector a -> m
forall (t :: Type -> Type) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap a -> m
f Vector a
xs
instance Traversable (Vector n) where
traverse :: (a -> f b) -> Vector n a -> f (Vector n b)
traverse a -> f b
f (Vector Vector a
xs) = Vector b -> Vector n b
forall (n :: Nat) a. (1 <= n) => Vector a -> Vector n a
Vector (Vector b -> Vector n b) -> f (Vector b) -> f (Vector n b)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (a -> f b) -> Vector a -> f (Vector b)
forall (t :: Type -> Type) (f :: Type -> Type) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse a -> f b
f Vector a
xs
{-# Inline traverse #-}
zipWith :: (a -> b -> c) -> Vector n a -> Vector n b -> Vector n c
zipWith :: (a -> b -> c) -> Vector n a -> Vector n b -> Vector n c
zipWith a -> b -> c
f (Vector Vector a
xs) (Vector Vector b
ys) = Vector c -> Vector n c
forall (n :: Nat) a. (1 <= n) => Vector a -> Vector n a
Vector ((a -> b -> c) -> Vector a -> Vector b -> Vector c
forall a b c. (a -> b -> c) -> Vector a -> Vector b -> Vector c
Vector.zipWith a -> b -> c
f Vector a
xs Vector b
ys)
{-# Inline zipWith #-}
zipWithM :: Monad m => (a -> b -> m c) ->
Vector n a -> Vector n b -> m (Vector n c)
zipWithM :: (a -> b -> m c) -> Vector n a -> Vector n b -> m (Vector n c)
zipWithM a -> b -> m c
f (Vector Vector a
xs) (Vector Vector b
ys) = Vector c -> Vector n c
forall (n :: Nat) a. (1 <= n) => Vector a -> Vector n a
Vector (Vector c -> Vector n c) -> m (Vector c) -> m (Vector n c)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (a -> b -> m c) -> Vector a -> Vector b -> m (Vector c)
forall (m :: Type -> Type) a b c.
Monad m =>
(a -> b -> m c) -> Vector a -> Vector b -> m (Vector c)
Vector.zipWithM a -> b -> m c
f Vector a
xs Vector b
ys
{-# Inline zipWithM #-}
zipWithM_ :: Monad m => (a -> b -> m ()) -> Vector n a -> Vector n b -> m ()
zipWithM_ :: (a -> b -> m ()) -> Vector n a -> Vector n b -> m ()
zipWithM_ a -> b -> m ()
f (Vector Vector a
xs) (Vector Vector b
ys) = (a -> b -> m ()) -> Vector a -> Vector b -> m ()
forall (m :: Type -> Type) a b c.
Monad m =>
(a -> b -> m c) -> Vector a -> Vector b -> m ()
Vector.zipWithM_ a -> b -> m ()
f Vector a
xs Vector b
ys
{-# Inline zipWithM_ #-}
interleave ::
forall n a. (1 <= n) => Vector n a -> Vector n a -> Vector (2 * n) a
interleave :: Vector n a -> Vector n a -> Vector (2 * n) a
interleave (Vector Vector a
xs) (Vector Vector a
ys)
| LeqProof 1 (2 * n)
LeqProof <- Proxy 2 -> Proxy n -> LeqProof 1 (2 * n)
forall (p :: Nat -> Type) (q :: Nat -> Type) (x :: Nat) (y :: Nat).
(1 <= x, 1 <= y) =>
p x -> q y -> LeqProof 1 (x * y)
leqMulPos (Proxy 2
forall k (t :: k). Proxy t
Proxy @2) (Proxy n
forall k (t :: k). Proxy t
Proxy @n) = Vector a -> Vector (2 * n) a
forall (n :: Nat) a. (1 <= n) => Vector a -> Vector n a
Vector Vector a
zs
where
len :: Int
len = Vector a -> Int
forall a. Vector a -> Int
Vector.length Vector a
xs Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Vector a -> Int
forall a. Vector a -> Int
Vector.length Vector a
ys
zs :: Vector a
zs = Int -> (Int -> a) -> Vector a
forall a. Int -> (Int -> a) -> Vector a
Vector.generate Int
len (\Int
i -> let v :: Vector a
v = if Int -> Bool
forall a. Integral a => a -> Bool
even Int
i then Vector a
xs else Vector a
ys
in Vector a
v Vector a -> Int -> a
forall a. Vector a -> Int -> a
Vector.! (Int
i Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Int
2))
shuffle :: (Int -> Int) -> Vector n a -> Vector n a
shuffle :: (Int -> Int) -> Vector n a -> Vector n a
shuffle Int -> Int
f (Vector Vector a
xs) = Vector a -> Vector n a
forall (n :: Nat) a. (1 <= n) => Vector a -> Vector n a
Vector Vector a
ys
where
ys :: Vector a
ys = Int -> (Int -> a) -> Vector a
forall a. Int -> (Int -> a) -> Vector a
Vector.generate (Vector a -> Int
forall a. Vector a -> Int
Vector.length Vector a
xs) (\Int
i -> Vector a
xs Vector a -> Int -> a
forall a. Vector a -> Int -> a
Vector.! Int -> Int
f Int
i)
{-# Inline shuffle #-}
reverse :: forall a n. (1 <= n) => Vector n a -> Vector n a
reverse :: Vector n a -> Vector n a
reverse Vector n a
x = (Int -> Int) -> Vector n a -> Vector n a
forall (n :: Nat) a. (Int -> Int) -> Vector n a -> Vector n a
shuffle (\Int
i -> Vector n a -> Int
forall (n :: Nat) a. Vector n a -> Int
lengthInt Vector n a
x Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) Vector n a
x
rotateL :: Int -> Vector n a -> Vector n a
rotateL :: Int -> Vector n a -> Vector n a
rotateL !Int
n Vector n a
xs = (Int -> Int) -> Vector n a -> Vector n a
forall (n :: Nat) a. (Int -> Int) -> Vector n a -> Vector n a
shuffle Int -> Int
rotL Vector n a
xs
where
!len :: Int
len = Vector n a -> Int
forall (n :: Nat) a. Vector n a -> Int
lengthInt Vector n a
xs
rotL :: Int -> Int
rotL Int
i = (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
n) Int -> Int -> Int
forall a. Integral a => a -> a -> a
`mod` Int
len
{-# Inline rotateL #-}
rotateR :: Int -> Vector n a -> Vector n a
rotateR :: Int -> Vector n a -> Vector n a
rotateR !Int
n Vector n a
xs = (Int -> Int) -> Vector n a -> Vector n a
forall (n :: Nat) a. (Int -> Int) -> Vector n a -> Vector n a
shuffle Int -> Int
rotR Vector n a
xs
where
!len :: Int
len = Vector n a -> Int
forall (n :: Nat) a. Vector n a -> Int
lengthInt Vector n a
xs
rotR :: Int -> Int
rotR Int
i = (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
n) Int -> Int -> Int
forall a. Integral a => a -> a -> a
`mod` Int
len
{-# Inline rotateR #-}
shiftL :: Int -> a -> Vector n a -> Vector n a
shiftL :: Int -> a -> Vector n a -> Vector n a
shiftL !Int
x a
a (Vector Vector a
xs) = Vector a -> Vector n a
forall (n :: Nat) a. (1 <= n) => Vector a -> Vector n a
Vector Vector a
ys
where
!len :: Int
len = Vector a -> Int
forall a. Vector a -> Int
Vector.length Vector a
xs
ys :: Vector a
ys = Int -> (Int -> a) -> Vector a
forall a. Int -> (Int -> a) -> Vector a
Vector.generate Int
len (\Int
i -> let j :: Int
j = Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
x
in if Int
j Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
len then a
a else Vector a
xs Vector a -> Int -> a
forall a. Vector a -> Int -> a
Vector.! Int
j)
{-# Inline shiftL #-}
shiftR :: Int -> a -> Vector n a -> Vector n a
shiftR :: Int -> a -> Vector n a -> Vector n a
shiftR !Int
x a
a (Vector Vector a
xs) = Vector a -> Vector n a
forall (n :: Nat) a. (1 <= n) => Vector a -> Vector n a
Vector Vector a
ys
where
!len :: Int
len = Vector a -> Int
forall a. Vector a -> Int
Vector.length Vector a
xs
ys :: Vector a
ys = Int -> (Int -> a) -> Vector a
forall a. Int -> (Int -> a) -> Vector a
Vector.generate Int
len (\Int
i -> let j :: Int
j = Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
x
in if Int
j Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 then a
a else Vector a
xs Vector a -> Int -> a
forall a. Vector a -> Int -> a
Vector.! Int
j)
{-# Inline shiftR #-}
append :: Vector m a -> Vector n a -> Vector (m + n) a
append :: Vector m a -> Vector n a -> Vector (m + n) a
append v1 :: Vector m a
v1@(Vector Vector a
xs) v2 :: Vector n a
v2@(Vector Vector a
ys) =
case NatRepr m -> NatRepr n -> LeqProof 1 (m + n)
forall (m :: Nat) (n :: Nat) (p :: Nat -> Type) (q :: Nat -> Type).
(1 <= m, 1 <= n) =>
p m -> q n -> LeqProof 1 (m + n)
leqAddPos (Vector m a -> NatRepr m
forall (n :: Nat) a. Vector n a -> NatRepr n
length Vector m a
v1) (Vector n a -> NatRepr n
forall (n :: Nat) a. Vector n a -> NatRepr n
length Vector n a
v2) of { LeqProof 1 (m + n)
LeqProof ->
Vector a -> Vector (m + n) a
forall (n :: Nat) a. (1 <= n) => Vector a -> Vector n a
Vector (Vector a
xs Vector a -> Vector a -> Vector a
forall a. Vector a -> Vector a -> Vector a
Vector.++ Vector a
ys)
}
{-# Inline append #-}
singleton :: forall a. a -> Vector 1 a
singleton :: a -> Vector 1 a
singleton a
a = Vector a -> Vector 1 a
forall (n :: Nat) a. (1 <= n) => Vector a -> Vector n a
Vector (a -> Vector a
forall a. a -> Vector a
Vector.singleton a
a)
leqLen :: forall n a. Vector n a -> LeqProof 1 (n + 1)
leqLen :: Vector n a -> LeqProof 1 (n + 1)
leqLen Vector n a
v =
let leqSucc :: forall f z. f z -> LeqProof z (z + 1)
leqSucc :: f z -> LeqProof z (z + 1)
leqSucc f z
fz = LeqProof z z -> NatRepr 1 -> LeqProof z (z + 1)
forall (f :: Nat -> Type) (m :: Nat) (n :: Nat) (p :: Nat).
LeqProof m n -> f p -> LeqProof m (n + p)
leqAdd (f z -> LeqProof z z
forall (f :: Nat -> Type) (n :: Nat). f n -> LeqProof n n
leqRefl f z
fz :: LeqProof z z) (KnownNat 1 => NatRepr 1
forall (n :: Nat). KnownNat n => NatRepr n
knownNat @1)
in LeqProof 1 n -> LeqProof n (n + 1) -> LeqProof 1 (n + 1)
forall (m :: Nat) (n :: Nat) (p :: Nat).
LeqProof m n -> LeqProof n p -> LeqProof m p
leqTrans (Vector n a -> LeqProof 1 n
forall (n :: Nat) a. Vector n a -> LeqProof 1 n
nonEmpty Vector n a
v :: LeqProof 1 n) (NatRepr n -> LeqProof n (n + 1)
forall (f :: Nat -> Type) (z :: Nat). f z -> LeqProof z (z + 1)
leqSucc (Vector n a -> NatRepr n
forall (n :: Nat) a. Vector n a -> NatRepr n
length Vector n a
v))
cons :: forall n a. a -> Vector n a -> Vector (n+1) a
cons :: a -> Vector n a -> Vector (n + 1) a
cons a
a v :: Vector n a
v@(Vector Vector a
x) = case Vector n a -> LeqProof 1 (n + 1)
forall (n :: Nat) a. Vector n a -> LeqProof 1 (n + 1)
leqLen Vector n a
v of LeqProof 1 (n + 1)
LeqProof -> (Vector a -> Vector (n + 1) a
forall (n :: Nat) a. (1 <= n) => Vector a -> Vector n a
Vector (a -> Vector a -> Vector a
forall a. a -> Vector a -> Vector a
Vector.cons a
a Vector a
x))
snoc :: forall n a. Vector n a -> a -> Vector (n+1) a
snoc :: Vector n a -> a -> Vector (n + 1) a
snoc v :: Vector n a
v@(Vector Vector a
x) a
a = case Vector n a -> LeqProof 1 (n + 1)
forall (n :: Nat) a. Vector n a -> LeqProof 1 (n + 1)
leqLen Vector n a
v of LeqProof 1 (n + 1)
LeqProof -> (Vector a -> Vector (n + 1) a
forall (n :: Nat) a. (1 <= n) => Vector a -> Vector n a
Vector (Vector a -> a -> Vector a
forall a. Vector a -> a -> Vector a
Vector.snoc Vector a
x a
a))
newtype Vector' a n = MkVector' (Vector (n+1) a)
unVector' :: Vector' a n -> Vector (n+1) a
unVector' :: Vector' a n -> Vector (n + 1) a
unVector' (MkVector' Vector (n + 1) a
v) = Vector (n + 1) a
v
snoc' :: forall a m. Vector' a m -> a -> Vector' a (m+1)
snoc' :: Vector' a m -> a -> Vector' a (m + 1)
snoc' Vector' a m
v = Vector ((m + 1) + 1) a -> Vector' a (m + 1)
forall a (n :: Nat). Vector (n + 1) a -> Vector' a n
MkVector' (Vector ((m + 1) + 1) a -> Vector' a (m + 1))
-> (a -> Vector ((m + 1) + 1) a) -> a -> Vector' a (m + 1)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vector (m + 1) a -> a -> Vector ((m + 1) + 1) a
forall (n :: Nat) a. Vector n a -> a -> Vector (n + 1) a
snoc (Vector' a m -> Vector (m + 1) a
forall a (n :: Nat). Vector' a n -> Vector (n + 1) a
unVector' Vector' a m
v)
generate' :: forall h a
. NatRepr h
-> (forall n. (n <= h) => NatRepr n -> a)
-> Vector' a h
generate' :: NatRepr h
-> (forall (n :: Nat). (n <= h) => NatRepr n -> a) -> Vector' a h
generate' NatRepr h
h forall (n :: Nat). (n <= h) => NatRepr n -> a
gen =
case NatRepr h -> Either (h :~: 0) (LeqProof 1 h)
forall (n :: Nat). NatRepr n -> Either (n :~: 0) (LeqProof 1 n)
isZeroOrGT1 NatRepr h
h of
Left h :~: 0
Refl -> Vector' a h
Vector' a 0
base
Right LeqProof 1 h
LeqProof ->
case (NatRepr h -> NatRepr 1 -> ((h - 1) + 1) :~: h
forall (f :: Nat -> Type) (m :: Nat) (g :: Nat -> Type) (n :: Nat).
(n <= m) =>
f m -> g n -> ((m - n) + n) :~: m
minusPlusCancel NatRepr h
h (KnownNat 1 => NatRepr 1
forall (n :: Nat). KnownNat n => NatRepr n
knownNat @1) :: h - 1 + 1 :~: h) of { ((h - 1) + 1) :~: h
Refl ->
NatRepr (h - 1)
-> NatRepr (h - 1)
-> Vector' a 0
-> (forall (n :: Nat).
(n <= (h - 1)) =>
NatRepr n -> Vector' a n -> Vector' a (n + 1))
-> Vector' a ((h - 1) + 1)
forall (m :: Nat) (h :: Nat) (f :: Nat -> Type).
(m <= h) =>
NatRepr m
-> NatRepr h
-> f 0
-> (forall (n :: Nat). (n <= h) => NatRepr n -> f n -> f (n + 1))
-> f (m + 1)
natRecBounded (NatRepr h -> NatRepr (h - 1)
forall (n :: Nat). (1 <= n) => NatRepr n -> NatRepr (n - 1)
decNat NatRepr h
h) (NatRepr h -> NatRepr (h - 1)
forall (n :: Nat). (1 <= n) => NatRepr n -> NatRepr (n - 1)
decNat NatRepr h
h) Vector' a 0
base forall (n :: Nat).
(n <= (h - 1)) =>
NatRepr n -> Vector' a n -> Vector' a (n + 1)
forall (m :: Nat).
(1 <= h, m <= (h - 1)) =>
NatRepr m -> Vector' a m -> Vector' a (m + 1)
step
}
where base :: Vector' a 0
base :: Vector' a 0
base = Vector (0 + 1) a -> Vector' a 0
forall a (n :: Nat). Vector (n + 1) a -> Vector' a n
MkVector' (Vector (0 + 1) a -> Vector' a 0)
-> Vector (0 + 1) a -> Vector' a 0
forall a b. (a -> b) -> a -> b
$ a -> Vector 1 a
forall a. a -> Vector 1 a
singleton (NatRepr 0 -> a
forall (n :: Nat). (n <= h) => NatRepr n -> a
gen (KnownNat 0 => NatRepr 0
forall (n :: Nat). KnownNat n => NatRepr n
knownNat @0))
step :: forall m. (1 <= h, m <= h - 1)
=> NatRepr m -> Vector' a m -> Vector' a (m + 1)
step :: NatRepr m -> Vector' a m -> Vector' a (m + 1)
step NatRepr m
m Vector' a m
v =
case NatRepr h -> NatRepr 1 -> ((h - 1) + 1) :~: h
forall (f :: Nat -> Type) (m :: Nat) (g :: Nat -> Type) (n :: Nat).
(n <= m) =>
f m -> g n -> ((m - n) + n) :~: m
minusPlusCancel NatRepr h
h (KnownNat 1 => NatRepr 1
forall (n :: Nat). KnownNat n => NatRepr n
knownNat @1) :: h - 1 + 1 :~: h of { ((h - 1) + 1) :~: h
Refl ->
case (LeqProof m (h - 1)
-> LeqProof 1 1 -> LeqProof (m + 1) ((h - 1) + 1)
forall (x_l :: Nat) (x_h :: Nat) (y_l :: Nat) (y_h :: Nat).
LeqProof x_l x_h
-> LeqProof y_l y_h -> LeqProof (x_l + y_l) (x_h + y_h)
leqAdd2 (LeqProof m (h - 1)
forall (m :: Nat) (n :: Nat). (m <= n) => LeqProof m n
LeqProof :: LeqProof m (h-1))
(LeqProof 1 1
forall (m :: Nat) (n :: Nat). (m <= n) => LeqProof m n
LeqProof :: LeqProof 1 1) :: LeqProof (m+1) h) of { LeqProof (m + 1) h
LeqProof ->
Vector' a m -> a -> Vector' a (m + 1)
forall a (m :: Nat). Vector' a m -> a -> Vector' a (m + 1)
snoc' Vector' a m
v (NatRepr (m + 1) -> a
forall (n :: Nat). (n <= h) => NatRepr n -> a
gen (NatRepr m -> NatRepr (m + 1)
forall (n :: Nat). NatRepr n -> NatRepr (n + 1)
incNat NatRepr m
m))
}}
generate :: forall h a
. NatRepr h
-> (forall n. (n <= h) => NatRepr n -> a)
-> Vector (h + 1) a
generate :: NatRepr h
-> (forall (n :: Nat). (n <= h) => NatRepr n -> a)
-> Vector (h + 1) a
generate NatRepr h
h forall (n :: Nat). (n <= h) => NatRepr n -> a
gen = Vector' a h -> Vector (h + 1) a
forall a (n :: Nat). Vector' a n -> Vector (n + 1) a
unVector' (NatRepr h
-> (forall (n :: Nat). (n <= h) => NatRepr n -> a) -> Vector' a h
forall (h :: Nat) a.
NatRepr h
-> (forall (n :: Nat). (n <= h) => NatRepr n -> a) -> Vector' a h
generate' NatRepr h
h forall (n :: Nat). (n <= h) => NatRepr n -> a
gen)
generateM :: forall m h a. (Monad m)
=> NatRepr h
-> (forall n. (n <= h) => NatRepr n -> m a)
-> m (Vector (h + 1) a)
generateM :: NatRepr h
-> (forall (n :: Nat). (n <= h) => NatRepr n -> m a)
-> m (Vector (h + 1) a)
generateM NatRepr h
h forall (n :: Nat). (n <= h) => NatRepr n -> m a
gen = Vector (h + 1) (m a) -> m (Vector (h + 1) a)
forall (t :: Type -> Type) (m :: Type -> Type) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence (Vector (h + 1) (m a) -> m (Vector (h + 1) a))
-> Vector (h + 1) (m a) -> m (Vector (h + 1) a)
forall a b. (a -> b) -> a -> b
$ NatRepr h
-> (forall (n :: Nat). (n <= h) => NatRepr n -> m a)
-> Vector (h + 1) (m a)
forall (h :: Nat) a.
NatRepr h
-> (forall (n :: Nat). (n <= h) => NatRepr n -> a)
-> Vector (h + 1) a
generate NatRepr h
h forall (n :: Nat). (n <= h) => NatRepr n -> m a
gen
coerceVec :: Coercible a b => Vector n a -> Vector n b
coerceVec :: Vector n a -> Vector n b
coerceVec = Vector n a -> Vector n b
coerce
joinWithM ::
forall m f n w.
(1 <= w, Monad m) =>
(forall l. (1 <= l) => NatRepr l -> f w -> f l -> m (f (w + l)))
-> NatRepr w
-> Vector n (f w)
-> m (f (n * w))
joinWithM :: (forall (l :: Nat).
(1 <= l) =>
NatRepr l -> f w -> f l -> m (f (w + l)))
-> NatRepr w -> Vector n (f w) -> m (f (n * w))
joinWithM forall (l :: Nat).
(1 <= l) =>
NatRepr l -> f w -> f l -> m (f (w + l))
jn NatRepr w
w = ((f (n * w), NatRepr (n * w)) -> f (n * w))
-> m (f (n * w), NatRepr (n * w)) -> m (f (n * w))
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap (f (n * w), NatRepr (n * w)) -> f (n * w)
forall a b. (a, b) -> a
fst (m (f (n * w), NatRepr (n * w)) -> m (f (n * w)))
-> (Vector n (f w) -> m (f (n * w), NatRepr (n * w)))
-> Vector n (f w)
-> m (f (n * w))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vector n (f w) -> m (f (n * w), NatRepr (n * w))
forall (l :: Nat). Vector l (f w) -> m (f (l * w), NatRepr (l * w))
go
where
go :: forall l. Vector l (f w) -> m (f (l * w), NatRepr (l * w))
go :: Vector l (f w) -> m (f (l * w), NatRepr (l * w))
go Vector l (f w)
exprs =
case Vector l (f w) -> (f w, Either (l :~: 1) (Vector (l - 1) (f w)))
forall (n :: Nat) a.
Vector n a -> (a, Either (n :~: 1) (Vector (n - 1) a))
uncons Vector l (f w)
exprs of
(f w
a, Left l :~: 1
Refl) -> (f w, NatRepr w) -> m (f w, NatRepr w)
forall (m :: Type -> Type) a. Monad m => a -> m a
return (f w
a, NatRepr w
w)
(f w
a, Right Vector (l - 1) (f w)
rest) ->
case Vector (l - 1) (f w) -> LeqProof 1 (l - 1)
forall (n :: Nat) a. Vector n a -> LeqProof 1 n
nonEmpty Vector (l - 1) (f w)
rest of { LeqProof 1 (l - 1)
LeqProof ->
case NatRepr (l - 1) -> NatRepr w -> LeqProof 1 ((l - 1) * w)
forall (p :: Nat -> Type) (q :: Nat -> Type) (x :: Nat) (y :: Nat).
(1 <= x, 1 <= y) =>
p x -> q y -> LeqProof 1 (x * y)
leqMulPos (Vector (l - 1) (f w) -> NatRepr (l - 1)
forall (n :: Nat) a. Vector n a -> NatRepr n
length Vector (l - 1) (f w)
rest) NatRepr w
w of { LeqProof 1 ((l - 1) * w)
LeqProof ->
case Vector l (f w) -> LeqProof 1 l
forall (n :: Nat) a. Vector n a -> LeqProof 1 n
nonEmpty Vector l (f w)
exprs of { LeqProof 1 l
LeqProof ->
case NatRepr w -> NatRepr l -> (w + ((l - 1) * w)) :~: (l * w)
forall (n :: Nat) (p :: Nat -> Type) (w :: Nat) (q :: Nat -> Type).
(1 <= n) =>
p w -> q n -> (w + ((n - 1) * w)) :~: (n * w)
lemmaMul NatRepr w
w (Vector l (f w) -> NatRepr l
forall (n :: Nat) a. Vector n a -> NatRepr n
length Vector l (f w)
exprs) of { (w + ((l - 1) * w)) :~: (l * w)
Refl -> do
(f ((l - 1) * w)
res, NatRepr ((l - 1) * w)
sz) <- Vector (l - 1) (f w) -> m (f ((l - 1) * w), NatRepr ((l - 1) * w))
forall (l :: Nat). Vector l (f w) -> m (f (l * w), NatRepr (l * w))
go Vector (l - 1) (f w)
rest
f (w + ((l - 1) * w))
joined <- NatRepr ((l - 1) * w)
-> f w -> f ((l - 1) * w) -> m (f (w + ((l - 1) * w)))
forall (l :: Nat).
(1 <= l) =>
NatRepr l -> f w -> f l -> m (f (w + l))
jn NatRepr ((l - 1) * w)
sz f w
a f ((l - 1) * w)
res
(f (w + ((l - 1) * w)), NatRepr (w + ((l - 1) * w)))
-> m (f (w + ((l - 1) * w)), NatRepr (w + ((l - 1) * w)))
forall (m :: Type -> Type) a. Monad m => a -> m a
return (f (w + ((l - 1) * w))
joined, NatRepr w -> NatRepr ((l - 1) * w) -> NatRepr (w + ((l - 1) * w))
forall (m :: Nat) (n :: Nat).
NatRepr m -> NatRepr n -> NatRepr (m + n)
addNat NatRepr w
w NatRepr ((l - 1) * w)
sz)
}}}}
joinWith ::
forall f n w.
(1 <= w) =>
(forall l. (1 <= l) => NatRepr l -> f w -> f l -> f (w + l))
-> NatRepr w
-> Vector n (f w)
-> f (n * w)
joinWith :: (forall (l :: Nat).
(1 <= l) =>
NatRepr l -> f w -> f l -> f (w + l))
-> NatRepr w -> Vector n (f w) -> f (n * w)
joinWith forall (l :: Nat). (1 <= l) => NatRepr l -> f w -> f l -> f (w + l)
jn NatRepr w
w Vector n (f w)
v = Identity (f (n * w)) -> f (n * w)
forall a. Identity a -> a
runIdentity (Identity (f (n * w)) -> f (n * w))
-> Identity (f (n * w)) -> f (n * w)
forall a b. (a -> b) -> a -> b
$ (forall (l :: Nat).
(1 <= l) =>
NatRepr l -> f w -> f l -> Identity (f (w + l)))
-> NatRepr w -> Vector n (f w) -> Identity (f (n * w))
forall (m :: Type -> Type) (f :: Nat -> Type) (n :: Nat)
(w :: Nat).
(1 <= w, Monad m) =>
(forall (l :: Nat).
(1 <= l) =>
NatRepr l -> f w -> f l -> m (f (w + l)))
-> NatRepr w -> Vector n (f w) -> m (f (n * w))
joinWithM (\NatRepr l
n f w
x -> f (w + l) -> Identity (f (w + l))
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure (f (w + l) -> Identity (f (w + l)))
-> (f l -> f (w + l)) -> f l -> Identity (f (w + l))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (NatRepr l -> f w -> f l -> f (w + l)
forall (l :: Nat). (1 <= l) => NatRepr l -> f w -> f l -> f (w + l)
jn NatRepr l
n f w
x)) NatRepr w
w Vector n (f w)
v
{-# Inline joinWith #-}
splitWith :: forall f w n.
(1 <= w, 1 <= n) =>
Endian ->
(forall i. (i + w <= n * w) =>
NatRepr (n * w) -> NatRepr i -> f (n * w) -> f w)
->
NatRepr n -> NatRepr w -> f (n * w) -> Vector n (f w)
splitWith :: Endian
-> (forall (i :: Nat).
((i + w) <= (n * w)) =>
NatRepr (n * w) -> NatRepr i -> f (n * w) -> f w)
-> NatRepr n
-> NatRepr w
-> f (n * w)
-> Vector n (f w)
splitWith Endian
endian forall (i :: Nat).
((i + w) <= (n * w)) =>
NatRepr (n * w) -> NatRepr i -> f (n * w) -> f w
select NatRepr n
n NatRepr w
w f (n * w)
val = Vector (f w) -> Vector n (f w)
forall (n :: Nat) a. (1 <= n) => Vector a -> Vector n a
Vector ((forall s. ST s (MVector s (f w))) -> Vector (f w)
forall a. (forall s. ST s (MVector s a)) -> Vector a
Vector.create forall s. ST s (MVector s (f w))
initializer)
where
len :: Int
len = NatRepr n -> Int
forall (n :: Nat). NatRepr n -> Int
widthVal NatRepr n
n
start :: Int
next :: Int -> Int
(Int
start,Int -> Int
next) = case Endian
endian of
Endian
LittleEndian -> (Int
0, Int -> Int
forall a. Enum a => a -> a
succ)
Endian
BigEndian -> (Int
len Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1, Int -> Int
forall a. Enum a => a -> a
pred)
initializer :: forall s. ST s (MVector s (f w))
initializer :: ST s (MVector s (f w))
initializer =
do LeqProof 1 (n * w)
LeqProof <- LeqProof 1 (n * w) -> ST s (LeqProof 1 (n * w))
forall (m :: Type -> Type) a. Monad m => a -> m a
return (NatRepr n -> NatRepr w -> LeqProof 1 (n * w)
forall (p :: Nat -> Type) (q :: Nat -> Type) (x :: Nat) (y :: Nat).
(1 <= x, 1 <= y) =>
p x -> q y -> LeqProof 1 (x * y)
leqMulPos NatRepr n
n NatRepr w
w)
LeqProof w (n * w)
LeqProof <- LeqProof w (n * w) -> ST s (LeqProof w (n * w))
forall (m :: Type -> Type) a. Monad m => a -> m a
return (NatRepr n -> NatRepr w -> LeqProof w (n * w)
forall (x :: Nat) (p :: Nat -> Type) (q :: Nat -> Type) (y :: Nat).
(1 <= x) =>
p x -> q y -> LeqProof y (x * y)
leqMulMono NatRepr n
n NatRepr w
w)
MVector s (f w)
v <- Int -> ST s (MVector (PrimState (ST s)) (f w))
forall (m :: Type -> Type) a.
PrimMonad m =>
Int -> m (MVector (PrimState m) a)
MVector.new Int
len
let fill :: Int -> NatRepr i -> ST s ()
fill :: Int -> NatRepr i -> ST s ()
fill Int
loc NatRepr i
i =
let end :: NatRepr (i + w)
end = NatRepr i -> NatRepr w -> NatRepr (i + w)
forall (m :: Nat) (n :: Nat).
NatRepr m -> NatRepr n -> NatRepr (m + n)
addNat NatRepr i
i NatRepr w
w in
case NatRepr (i + w)
-> NatRepr (n * w) -> Maybe (LeqProof (i + w) (n * w))
forall (m :: Nat) (n :: Nat).
NatRepr m -> NatRepr n -> Maybe (LeqProof m n)
testLeq NatRepr (i + w)
end NatRepr (n * w)
inLen of
Just LeqProof (i + w) (n * w)
LeqProof ->
do MVector (PrimState (ST s)) (f w) -> Int -> f w -> ST s ()
forall (m :: Type -> Type) a.
PrimMonad m =>
MVector (PrimState m) a -> Int -> a -> m ()
MVector.write MVector s (f w)
MVector (PrimState (ST s)) (f w)
v Int
loc (NatRepr (n * w) -> NatRepr i -> f (n * w) -> f w
forall (i :: Nat).
((i + w) <= (n * w)) =>
NatRepr (n * w) -> NatRepr i -> f (n * w) -> f w
select NatRepr (n * w)
inLen NatRepr i
i f (n * w)
val)
Int -> NatRepr (i + w) -> ST s ()
forall (i :: Nat). Int -> NatRepr i -> ST s ()
fill (Int -> Int
next Int
loc) NatRepr (i + w)
end
Maybe (LeqProof (i + w) (n * w))
Nothing -> () -> ST s ()
forall (m :: Type -> Type) a. Monad m => a -> m a
return ()
Int -> NatRepr 0 -> ST s ()
forall (i :: Nat). Int -> NatRepr i -> ST s ()
fill Int
start (KnownNat 0 => NatRepr 0
forall (n :: Nat). KnownNat n => NatRepr n
knownNat @0)
MVector s (f w) -> ST s (MVector s (f w))
forall (m :: Type -> Type) a. Monad m => a -> m a
return MVector s (f w)
v
inLen :: NatRepr (n * w)
inLen :: NatRepr (n * w)
inLen = NatRepr n -> NatRepr w -> NatRepr (n * w)
forall (n :: Nat) (m :: Nat).
NatRepr n -> NatRepr m -> NatRepr (n * m)
natMultiply NatRepr n
n NatRepr w
w
{-# Inline splitWith #-}
splitWithA :: forall f g w n. (Applicative f, 1 <= w, 1 <= n) =>
Endian ->
(forall i. (i + w <= n * w) =>
NatRepr (n * w) -> NatRepr i -> g (n * w) -> f (g w))
->
NatRepr n -> NatRepr w -> g (n * w) -> f (Vector n (g w))
splitWithA :: Endian
-> (forall (i :: Nat).
((i + w) <= (n * w)) =>
NatRepr (n * w) -> NatRepr i -> g (n * w) -> f (g w))
-> NatRepr n
-> NatRepr w
-> g (n * w)
-> f (Vector n (g w))
splitWithA Endian
e forall (i :: Nat).
((i + w) <= (n * w)) =>
NatRepr (n * w) -> NatRepr i -> g (n * w) -> f (g w)
select NatRepr n
n NatRepr w
w g (n * w)
val = (Compose f g w -> f (g w))
-> Vector n (Compose f g w) -> f (Vector n (g w))
forall (t :: Type -> Type) (f :: Type -> Type) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse Compose f g w -> f (g w)
forall k1 (f :: k1 -> Type) k2 (g :: k2 -> k1) (a :: k2).
Compose f g a -> f (g a)
getCompose (Vector n (Compose f g w) -> f (Vector n (g w)))
-> Vector n (Compose f g w) -> f (Vector n (g w))
forall a b. (a -> b) -> a -> b
$
Endian
-> (forall (i :: Nat).
((i + w) <= (n * w)) =>
NatRepr (n * w)
-> NatRepr i -> Compose f g (n * w) -> Compose f g w)
-> NatRepr n
-> NatRepr w
-> Compose f g (n * w)
-> Vector n (Compose f g w)
forall (f :: Nat -> Type) (w :: Nat) (n :: Nat).
(1 <= w, 1 <= n) =>
Endian
-> (forall (i :: Nat).
((i + w) <= (n * w)) =>
NatRepr (n * w) -> NatRepr i -> f (n * w) -> f w)
-> NatRepr n
-> NatRepr w
-> f (n * w)
-> Vector n (f w)
splitWith @(Compose f g) Endian
e forall (i :: Nat).
((i + w) <= (n * w)) =>
NatRepr (n * w)
-> NatRepr i -> Compose f g (n * w) -> Compose f g w
select' NatRepr n
n NatRepr w
w (Compose f g (n * w) -> Vector n (Compose f g w))
-> Compose f g (n * w) -> Vector n (Compose f g w)
forall a b. (a -> b) -> a -> b
$ f (g (n * w)) -> Compose f g (n * w)
forall k k1 (f :: k -> Type) (g :: k1 -> k) (a :: k1).
f (g a) -> Compose f g a
Compose (g (n * w) -> f (g (n * w))
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure g (n * w)
val)
where
select' :: (forall i. (i + w <= n * w)
=> NatRepr (n * w) -> NatRepr i -> Compose f g (n * w) -> Compose f g w)
select' :: NatRepr (n * w)
-> NatRepr i -> Compose f g (n * w) -> Compose f g w
select' NatRepr (n * w)
nw NatRepr i
i Compose f g (n * w)
_ = f (g w) -> Compose f g w
forall k k1 (f :: k -> Type) (g :: k1 -> k) (a :: k1).
f (g a) -> Compose f g a
Compose (f (g w) -> Compose f g w) -> f (g w) -> Compose f g w
forall a b. (a -> b) -> a -> b
$ NatRepr (n * w) -> NatRepr i -> g (n * w) -> f (g w)
forall (i :: Nat).
((i + w) <= (n * w)) =>
NatRepr (n * w) -> NatRepr i -> g (n * w) -> f (g w)
select NatRepr (n * w)
nw NatRepr i
i g (n * w)
val
newtype Vec a n = Vec (Vector n a)
vSlice :: (i + w <= l, 1 <= w) =>
NatRepr w -> NatRepr l -> NatRepr i -> Vec a l -> Vec a w
vSlice :: NatRepr w -> NatRepr l -> NatRepr i -> Vec a l -> Vec a w
vSlice NatRepr w
w NatRepr l
_ NatRepr i
i (Vec Vector l a
xs) = Vector w a -> Vec a w
forall a (n :: Nat). Vector n a -> Vec a n
Vec (NatRepr i -> NatRepr w -> Vector l a -> Vector w a
forall (i :: Nat) (w :: Nat) (n :: Nat) a.
((i + w) <= n, 1 <= w) =>
NatRepr i -> NatRepr w -> Vector n a -> Vector w a
slice NatRepr i
i NatRepr w
w Vector l a
xs)
{-# Inline vSlice #-}
vAppend :: NatRepr n -> Vec a m -> Vec a n -> Vec a (m + n)
vAppend :: NatRepr n -> Vec a m -> Vec a n -> Vec a (m + n)
vAppend NatRepr n
_ (Vec Vector m a
xs) (Vec Vector n a
ys) = Vector (m + n) a -> Vec a (m + n)
forall a (n :: Nat). Vector n a -> Vec a n
Vec (Vector m a -> Vector n a -> Vector (m + n) a
forall (m :: Nat) a (n :: Nat).
Vector m a -> Vector n a -> Vector (m + n) a
append Vector m a
xs Vector n a
ys)
{-# Inline vAppend #-}
split :: (1 <= w, 1 <= n) =>
NatRepr n
-> NatRepr w
-> Vector (n * w) a
-> Vector n (Vector w a)
split :: NatRepr n -> NatRepr w -> Vector (n * w) a -> Vector n (Vector w a)
split NatRepr n
n NatRepr w
w Vector (n * w) a
xs = Vector n (Vec a w) -> Vector n (Vector w a)
forall a b (n :: Nat). Coercible a b => Vector n a -> Vector n b
coerceVec (Endian
-> (forall (i :: Nat).
((i + w) <= (n * w)) =>
NatRepr (n * w) -> NatRepr i -> Vec a (n * w) -> Vec a w)
-> NatRepr n
-> NatRepr w
-> Vec a (n * w)
-> Vector n (Vec a w)
forall (f :: Nat -> Type) (w :: Nat) (n :: Nat).
(1 <= w, 1 <= n) =>
Endian
-> (forall (i :: Nat).
((i + w) <= (n * w)) =>
NatRepr (n * w) -> NatRepr i -> f (n * w) -> f w)
-> NatRepr n
-> NatRepr w
-> f (n * w)
-> Vector n (f w)
splitWith Endian
LittleEndian (NatRepr w
-> NatRepr (n * w) -> NatRepr i -> Vec a (n * w) -> Vec a w
forall (i :: Nat) (w :: Nat) (l :: Nat) a.
((i + w) <= l, 1 <= w) =>
NatRepr w -> NatRepr l -> NatRepr i -> Vec a l -> Vec a w
vSlice NatRepr w
w) NatRepr n
n NatRepr w
w (Vector (n * w) a -> Vec a (n * w)
forall a (n :: Nat). Vector n a -> Vec a n
Vec Vector (n * w) a
xs))
{-# Inline split #-}
join :: (1 <= w) => NatRepr w -> Vector n (Vector w a) -> Vector (n * w) a
join :: NatRepr w -> Vector n (Vector w a) -> Vector (n * w) a
join NatRepr w
w Vector n (Vector w a)
xs = Vector (n * w) a
ys
where Vec Vector (n * w) a
ys = (forall (l :: Nat).
(1 <= l) =>
NatRepr l -> Vec a w -> Vec a l -> Vec a (w + l))
-> NatRepr w -> Vector n (Vec a w) -> Vec a (n * w)
forall (f :: Nat -> Type) (n :: Nat) (w :: Nat).
(1 <= w) =>
(forall (l :: Nat).
(1 <= l) =>
NatRepr l -> f w -> f l -> f (w + l))
-> NatRepr w -> Vector n (f w) -> f (n * w)
joinWith forall (l :: Nat).
(1 <= l) =>
NatRepr l -> Vec a w -> Vec a l -> Vec a (w + l)
forall (n :: Nat) a (m :: Nat).
NatRepr n -> Vec a m -> Vec a n -> Vec a (m + n)
vAppend NatRepr w
w (Vector n (Vector w a) -> Vector n (Vec a w)
forall a b (n :: Nat). Coercible a b => Vector n a -> Vector n b
coerceVec Vector n (Vector w a)
xs)
{-# Inline join #-}