{-# LANGUAGE CPP #-}
{-# LANGUAGE Rank2Types #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE MultiParamTypeClasses #-}
#ifdef TRUSTWORTHY
{-# LANGUAGE Trustworthy #-}
#endif
-------------------------------------------------------------------------------
-- |
-- Module      :  Data.Vector.Lens
-- Copyright   :  (C) 2012-16 Edward Kmett
-- License     :  BSD-style (see the file LICENSE)
-- Maintainer  :  Edward Kmett <ekmett@gmail.com>
-- Stability   :  provisional
-- Portability :  non-portable
--
-- This module provides lenses and traversals for working with generic
-- vectors.
-------------------------------------------------------------------------------
module Data.Vector.Lens
  ( toVectorOf
  -- * Isomorphisms
  , vector
  , forced
  -- * Lenses
  , sliced
  -- * Traversal of individual indices
  , 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)

-- $setup
-- >>> import qualified Data.Vector as Vector
-- >>> import Control.Lens

-- | @sliced i n@ provides a t'Lens' that edits the @n@ elements starting
-- at index @i@ from a t'Lens'.
--
-- This is only a valid t'Lens' if you do not change the length of the
-- resulting 'Vector'.
--
-- Attempting to return a longer or shorter vector will result in
-- violations of the t'Lens' laws.
--
-- >>> Vector.fromList [1..10] ^. sliced 2 5 == Vector.fromList [3,4,5,6,7]
-- True
--
-- >>> (Vector.fromList [1..10] & sliced 2 5 . mapped .~ 0) == Vector.fromList [1,2,0,0,0,0,0,8,9,10]
-- True
sliced :: Int -- ^ @i@ starting index
       -> Int -- ^ @n@ length
       -> 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 (forall a. Int -> Int -> Vector a -> Vector a
V.slice Int
i Int
n Vector a
v) forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \ Vector a
v0 -> Vector a
v forall a. Vector a -> [(Int, a)] -> Vector a
V.// forall a b. [a] -> [b] -> [(a, b)]
zip [Int
i..Int
iforall a. Num a => a -> a -> a
+Int
nforall a. Num a => a -> a -> a
-Int
1] (forall a. Vector a -> [a]
V.toList Vector a
v0)
{-# INLINE sliced #-}

-- | Similar to 'toListOf', but returning a 'Vector'.
--
-- >>> toVectorOf both (8,15) == Vector.fromList [8,15]
-- True
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 = forall a. [a] -> Vector a
V.fromList (forall a s. Getting (Endo [a]) s a -> s -> [a]
toListOf Getting (Endo [a]) s a
l s
s)
{-# INLINE toVectorOf #-}

-- | Convert a list to a 'Vector' (or back)
--
-- >>> [1,2,3] ^. vector == Vector.fromList [1,2,3]
-- True
--
-- >>> [1,2,3] ^. vector . from vector
-- [1,2,3]
--
-- >>> Vector.fromList [0,8,15] ^. from vector . vector == Vector.fromList [0,8,15]
-- True
vector :: Iso [a] [b] (Vector a) (Vector b)
vector :: forall a b. Iso [a] [b] (Vector a) (Vector b)
vector = forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso forall a. [a] -> Vector a
V.fromList forall a. Vector a -> [a]
V.toList
{-# INLINE vector #-}

-- | Convert a 'Vector' to a version that doesn't retain any extra
-- memory.
forced :: Iso (Vector a) (Vector b) (Vector a) (Vector b)
forced :: forall a b. Iso (Vector a) (Vector b) (Vector a) (Vector b)
forced = forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso forall a. Vector a -> Vector a
V.force forall a. Vector a -> Vector a
V.force
{-# INLINE forced #-}

-- | This t'Traversal' will ignore any duplicates in the supplied list
-- of indices.
--
-- >>> toListOf (ordinals [1,3,2,5,9,10]) $ Vector.fromList [2,4..40]
-- [4,8,6,12,20,22]
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 = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Vector a
v forall a. Vector a -> [(Int, a)] -> Vector a
V.//) forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (\Int
i -> (,) Int
i forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f 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 forall a. Vector a -> Int -> a
V.! Int
i)) forall a b. (a -> b) -> a -> b
$ Int -> [Int] -> [Int]
ordinalNub (forall (t :: * -> *) a. Foldable t => t a -> Int
length Vector a
v) [Int]
is
{-# INLINE ordinals #-}