{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables,TypeFamilies,FlexibleInstances,MultiParamTypeClasses #-} -- | Functor-lazy vectors are like boxed vectors, but support mapping a function onto all elements in constant time. All vector operations (except slicing) are fully supported. See for more details. module Data.Vector.FunctorLazy ( -- * Functor-lazy vectors Vector, MVector, -- * Accessors -- ** Length information VG.length, VG.null, -- ** Indexing (VG.!), (VG.!?), VG.head, VG.last, VG.unsafeIndex, VG.unsafeHead, VG.unsafeLast, -- ** Monadic indexing VG.indexM, VG.headM, VG.lastM, VG.unsafeIndexM, VG.unsafeHeadM, VG.unsafeLastM, -- -- ** Extracting subvectors (slicing) -- slice, init, tail, take, drop, splitAt, -- unsafeSlice, unsafeInit, unsafeTail, unsafeTake, unsafeDrop, -- * Construction -- ** Initialisation VG.empty, VG.singleton, VG.replicate, VG.generate, VG.iterateN, -- ** Monadic initialisation VG.replicateM, VG.generateM, VG.create, -- ** Unfolding VG.unfoldr, VG.unfoldrN, VG.constructN, VG.constructrN, -- ** Enumeration VG.enumFromN, VG.enumFromStepN, VG.enumFromTo, VG.enumFromThenTo, -- ** Concatenation VG.cons, VG.snoc, (VG.++), VG.concat, -- ** Restricting memory usage VG.force, -- * Modifying vectors -- ** Bulk updates (VG.//), VG.update, VG.update_, VG.unsafeUpd, VG.unsafeUpdate, VG.unsafeUpdate_, -- ** Accumulations VG.accum, VG.accumulate, VG.accumulate_, VG.unsafeAccum, VG.unsafeAccumulate, VG.unsafeAccumulate_, -- ** Permutations VG.reverse, VG.backpermute, VG.unsafeBackpermute, -- ** Safe destructive updates VG.modify, -- * Elementwise operations -- ** Indexing VG.indexed, -- -- ** Mapping -- map, imap, concatMap, -- -- ** Monadic mapping -- mapM, mapM_, forM, forM_, -- ** Zipping VG.zipWith, VG.zipWith3, VG.zipWith4, VG.zipWith5, VG.zipWith6, VG.izipWith, VG.izipWith3, VG.izipWith4, VG.izipWith5, VG.izipWith6, VG.zip, VG.zip3, VG.zip4, VG.zip5, VG.zip6, -- ** Monadic zipping VG.zipWithM, VG.zipWithM_, -- ** Unzipping VG.unzip, VG.unzip3, VG.unzip4, VG.unzip5, VG.unzip6, -- * Working with predicates -- ** Filtering VG.filter, VG.ifilter, VG.filterM, VG.takeWhile, VG.dropWhile, -- -- ** Partitioning -- VG.partition, VG.unstablePartition, VG.span, VG.break, -- ** Searching VG.elem, VG.notElem, VG.find, VG.findIndex, VG.findIndices, VG.elemIndex, VG.elemIndices, -- * Folding VG.foldl, VG.foldl1, VG.foldl', VG.foldl1', VG.foldr, VG.foldr1, VG.foldr', VG.foldr1', VG.ifoldl, VG.ifoldl', VG.ifoldr, VG.ifoldr', -- ** Specialised folds VG.all, VG.any, VG.and, VG.or, VG.sum, VG.product, VG.maximum, VG.maximumBy, VG.minimum, VG.minimumBy, VG.minIndex, VG.minIndexBy, VG.maxIndex, VG.maxIndexBy, -- ** Monadic folds VG.foldM, VG.foldM', VG.fold1M, VG.fold1M', VG.foldM_, VG.foldM'_, VG.fold1M_, VG.fold1M'_, -- ** Monadic sequencing VG.sequence, VG.sequence_, -- * Prefix sums (scans) VG.prescanl, VG.prescanl', VG.postscanl, VG.postscanl', VG.scanl, VG.scanl', VG.scanl1, VG.scanl1', VG.prescanr, VG.prescanr', VG.postscanr, VG.postscanr', VG.scanr, VG.scanr', VG.scanr1, VG.scanr1', -- * Conversions -- ** Lists VG.toList, VG.fromList, VG.fromListN, -- ** Other vector types VG.convert, -- ** Mutable vectors VG.freeze, VG.thaw, VG.copy, VG.unsafeFreeze, VG.unsafeThaw, VG.unsafeCopy ) where import Data.Monoid hiding (Any) import qualified Data.Vector as V import qualified Data.Vector.Mutable as VM import qualified Data.Vector.Unboxed as VU import qualified Data.Vector.Generic as VG import qualified Data.Vector.Generic.Mutable as VGM import qualified Data.Vector.Unboxed.Mutable as VUM import Data.Vector.Unboxed.Deriving import Data.Primitive.Array import Data.Primitive.ByteArray import Control.Monad.ST import Control.Monad.Primitive import Unsafe.Coerce import System.IO.Unsafe import GHC.Prim import Data.Vector.FunctorLazy.Common import Data.Vector.FunctorLazy.Mutable ------------------------------------------------------------------------------- -- data types data Vector a = Vector { vecAny :: !(Array Any) , vecInt :: !(ByteArray) , len :: !Int , control :: !LazyController } instance (Show a) => Show (Vector a) where show v = "fromList [" ++ go (VG.length v-1) where go (-1) = "" go i = go (i-1) ++ show (v VG.! i) ++ "," instance Functor Vector where {-# INLINE fmap #-} fmap f v = v { control = LazyController { funcL = (unsafeCoerce f):(funcL $ control v) , funcC = 1+(funcC $ control v) }} ------------------------------------------------------------------------------- -- vector instances type instance VG.Mutable Vector = MVector instance VG.Vector Vector a where {-# INLINE basicUnsafeFreeze #-} basicUnsafeFreeze v = do frozenAny <- unsafeFreezeArray (mvecAny v) frozenInt <- unsafeFreezeByteArray (mvecInt v) return $ Vector frozenAny frozenInt (mlen v) (mcontrol v) {-# INLINE basicUnsafeThaw #-} basicUnsafeThaw v = do thawedAny <- unsafeThawArray (vecAny v) thawedInt <- unsafeThawByteArray (vecInt v) return $ MVector thawedAny thawedInt (len v) (control v) {-# INLINE basicLength #-} basicLength = len {-# INLINE basicUnsafeIndexM #-} basicUnsafeIndexM (Vector va vi len (LazyController fl fc)) i = do any <- indexArrayM va i let count = indexByteArray vi i let any' = unsafeCoerce any return $ appList any' (take (fc - count) fl) {-# INLINE basicUnsafeSlice #-} basicUnsafeSlice s len v = error "Data.Vector.FunctorLazy.Vector: slicing not supported"