{-# LANGUAGE CPP #-}
{-# LANGUAGE Rank2Types #-}
{-# LANGUAGE FlexibleContexts #-}
#ifdef TRUSTWORTHY
{-# LANGUAGE Trustworthy #-}
#endif
#ifndef MIN_VERSION_vector
#define MIN_VERSION_vector(x,y,z) 1
#endif
module Data.Vector.Generic.Lens
( toVectorOf
, forced
, vector
, asStream
, asStreamR
, cloned
, converted
, sliced
, ordinals
, vectorIx
, vectorTraverse
) where
import Control.Applicative
import Control.Lens.Type
import Control.Lens.Lens
import Control.Lens.Getter
import Control.Lens.Fold
import Control.Lens.Iso
import Control.Lens.Indexed
import Control.Lens.Setter
import Control.Lens.Traversal
import Control.Lens.Internal.List (ordinalNub)
import Data.Monoid
import Data.Vector.Generic as V hiding (zip, filter, indexed)
import Data.Vector.Generic.New (New)
import Prelude hiding ((++), length, null, head, tail, init, last, map, reverse)
#if MIN_VERSION_vector(0,11,0)
import Data.Vector.Fusion.Bundle (Bundle)
#else
import Data.Vector.Fusion.Stream (Stream)
#endif
sliced :: Vector v a
=> Int
-> Int
-> Lens' (v a) (v a)
sliced i n f v = f (slice i n v) <&> \ v0 -> v // zip [i..i+n-1] (V.toList v0)
{-# INLINE sliced #-}
toVectorOf :: Vector v a => Getting (Endo [a]) s a -> s -> v a
toVectorOf l s = fromList (toListOf l s)
{-# INLINE toVectorOf #-}
vector :: (Vector v a, Vector v b) => Iso [a] [b] (v a) (v b)
vector = iso fromList V.toList
{-# INLINE vector #-}
#if MIN_VERSION_vector(0,11,0)
asStream :: (Vector v a, Vector v b) => Iso (v a) (v b) (Bundle v a) (Bundle v b)
#else
asStream :: (Vector v a, Vector v b) => Iso (v a) (v b) (Stream a) (Stream b)
#endif
asStream = iso stream unstream
{-# INLINE asStream #-}
#if MIN_VERSION_vector(0,11,0)
asStreamR :: (Vector v a, Vector v b) => Iso (v a) (v b) (Bundle v a) (Bundle v b)
#else
asStreamR :: (Vector v a, Vector v b) => Iso (v a) (v b) (Stream a) (Stream b)
#endif
asStreamR = iso streamR unstreamR
{-# INLINE asStreamR #-}
cloned :: Vector v a => Iso' (v a) (New v a)
cloned = iso clone new
{-# INLINE cloned #-}
forced :: Vector v a => Iso' (v a) (v a)
forced = involuted force
{-# INLINE forced #-}
ordinals :: Vector v a => [Int] -> IndexedTraversal' Int (v a) a
ordinals is f v = fmap (v //) $ traverse (\i -> (,) i <$> indexed f i (v ! i)) $ ordinalNub (length v) is
{-# INLINE ordinals #-}
vectorIx :: V.Vector v a => Int -> Traversal' (v a) a
vectorIx i f v
| 0 <= i && i < V.length v = f (v V.! i) <&> \a -> v V.// [(i, a)]
| otherwise = pure v
{-# INLINE vectorIx #-}
vectorTraverse :: (V.Vector v a, V.Vector w b) => IndexedTraversal Int (v a) (w b) a b
vectorTraverse f v = V.fromListN (V.length v) <$> traversed f (V.toList v)
{-# INLINE [0] vectorTraverse #-}
{-# RULES
"vectorTraverse -> mapped" vectorTraverse = sets V.map :: (V.Vector v a, V.Vector v b) => ASetter (v a) (v b) a b;
"vectorTraverse -> imapped" vectorTraverse = isets V.imap :: (V.Vector v a, V.Vector v b) => AnIndexedSetter Int (v a) (v b) a b;
"vectorTraverse -> foldr" vectorTraverse = foldring V.foldr :: V.Vector v a => Getting (Endo r) (v a) a;
"vectorTraverse -> ifoldr" vectorTraverse = ifoldring V.ifoldr :: V.Vector v a => IndexedGetting Int (Endo r) (v a) a;
#-}
converted :: (Vector v a, Vector w a, Vector v b, Vector w b) => Iso (v a) (v b) (w a) (w b)
converted = iso convert convert