{-# LANGUAGE CPP #-}
{-# LANGUAGE Rank2Types #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE MultiParamTypeClasses #-}
#ifdef TRUSTWORTHY
{-# LANGUAGE Trustworthy #-}
#endif
module Data.Vector.Lens
  ( toVectorOf
  
  , vector
  , forced
  
  , sliced
  
  , ordinals
  ) where
import Prelude ()
import Control.Lens
import Control.Lens.Internal.List (ordinalNub)
import Control.Lens.Internal.Prelude
import qualified Data.Vector as V
import Data.Vector (Vector)
sliced :: Int 
       -> Int 
       -> Lens' (Vector a) (Vector a)
sliced :: forall a. Int -> Int -> Lens' (Vector a) (Vector a)
sliced Int
i Int
n Vector a -> f (Vector a)
f Vector a
v = Vector a -> f (Vector a)
f (Int -> Int -> Vector a -> Vector a
forall a. Int -> Int -> Vector a -> Vector a
V.slice Int
i Int
n Vector a
v) f (Vector a) -> (Vector a -> Vector a) -> f (Vector a)
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \ Vector a
v0 -> Vector a
v Vector a -> [(Int, a)] -> Vector a
forall a. Vector a -> [(Int, a)] -> Vector a
V.// [Int] -> [a] -> [(Int, a)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Int
i..Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1] (Vector a -> [a]
forall a. Vector a -> [a]
V.toList Vector a
v0)
{-# INLINE sliced #-}
toVectorOf :: Getting (Endo [a]) s a -> s -> Vector a
toVectorOf :: forall a s. Getting (Endo [a]) s a -> s -> Vector a
toVectorOf Getting (Endo [a]) s a
l s
s = [a] -> Vector a
forall a. [a] -> Vector a
V.fromList (Getting (Endo [a]) s a -> s -> [a]
forall a s. Getting (Endo [a]) s a -> s -> [a]
toListOf Getting (Endo [a]) s a
l s
s)
{-# INLINE toVectorOf #-}
vector :: Iso [a] [b] (Vector a) (Vector b)
vector :: forall a b (p :: * -> * -> *) (f :: * -> *).
(Profunctor p, Functor f) =>
p (Vector a) (f (Vector b)) -> p [a] (f [b])
vector = ([a] -> Vector a)
-> (Vector b -> [b]) -> Iso [a] [b] (Vector a) (Vector b)
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso [a] -> Vector a
forall a. [a] -> Vector a
V.fromList Vector b -> [b]
forall a. Vector a -> [a]
V.toList
{-# INLINE vector #-}
forced :: Iso (Vector a) (Vector b) (Vector a) (Vector b)
forced :: forall a b (p :: * -> * -> *) (f :: * -> *).
(Profunctor p, Functor f) =>
p (Vector a) (f (Vector b)) -> p (Vector a) (f (Vector b))
forced = (Vector a -> Vector a)
-> (Vector b -> Vector b)
-> Iso (Vector a) (Vector b) (Vector a) (Vector b)
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso Vector a -> Vector a
forall a. Vector a -> Vector a
V.force Vector b -> Vector b
forall a. Vector a -> Vector a
V.force
{-# INLINE forced #-}
ordinals :: [Int] -> IndexedTraversal' Int (Vector a) a
ordinals :: forall a. [Int] -> IndexedTraversal' Int (Vector a) a
ordinals [Int]
is p a (f a)
f Vector a
v = ([(Int, a)] -> Vector a) -> f [(Int, a)] -> f (Vector a)
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Vector a
v Vector a -> [(Int, a)] -> Vector a
forall a. Vector a -> [(Int, a)] -> Vector a
V.//) (f [(Int, a)] -> f (Vector a)) -> f [(Int, a)] -> f (Vector a)
forall a b. (a -> b) -> a -> b
$ (Int -> f (Int, a)) -> [Int] -> f [(Int, a)]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse (\Int
i -> (,) Int
i (a -> (Int, a)) -> f a -> f (Int, a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> p a (f a) -> Int -> a -> f a
forall a b. p a b -> Int -> a -> b
forall i (p :: * -> * -> *) a b.
Indexable i p =>
p a b -> i -> a -> b
indexed p a (f a)
f Int
i (Vector a
v Vector a -> Int -> a
forall a. Vector a -> Int -> a
V.! Int
i)) ([Int] -> f [(Int, a)]) -> [Int] -> f [(Int, a)]
forall a b. (a -> b) -> a -> b
$ Int -> [Int] -> [Int]
ordinalNub (Vector a -> Int
forall a. Vector a -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length Vector a
v) [Int]
is
{-# INLINE ordinals #-}