{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE NoImplicitPrelude #-}
module Data.Vector.NonEmpty.Mutable
(
NonEmptyMVector
, NonEmptyIOVector
, NonEmptySTVector
, length
, slice, init, tail, take, drop, splitAt
, unsafeSlice, unsafeTake, unsafeDrop
, overlaps
, fromMVector, toMVector, unsafeFromMVector
, new, new1, unsafeNew
, replicate, replicate1
, replicateM, replicate1M
, clone
, grow, unsafeGrow
, clear
, read, write, modify, swap
, unsafeRead, unsafeWrite, unsafeModify, unsafeSwap
, nextPermutation
, set, copy, move, unsafeCopy, unsafeMove
) where
import Prelude (Bool, Int, Ord, (.), max)
import Control.Monad.Primitive
import Data.Functor
import Data.Maybe (Maybe(..))
import Data.Typeable (Typeable)
import Data.Vector.Mutable (MVector)
import qualified Data.Vector.Mutable as M
newtype NonEmptyMVector s a = NonEmptyMVector
{ _nemVec :: MVector s a }
deriving (Typeable)
type NonEmptyIOVector = NonEmptyMVector RealWorld
type NonEmptySTVector s = NonEmptyMVector s
length :: NonEmptyMVector s a -> Int
length = M.length . _nemVec
{-# INLINE length #-}
slice :: Int -> Int -> NonEmptyMVector s a -> MVector s a
slice n m = M.slice n m . _nemVec
{-# INLINE slice #-}
take :: Int -> NonEmptyMVector s a -> MVector s a
take n = M.take n . _nemVec
{-# INLINE take #-}
drop :: Int -> NonEmptyMVector s a -> MVector s a
drop n = M.drop n . _nemVec
{-# INLINE drop #-}
splitAt :: Int -> NonEmptyMVector s a -> (MVector s a, MVector s a)
splitAt n = M.splitAt n . _nemVec
{-# INLINE splitAt #-}
init :: NonEmptyMVector s a -> MVector s a
init = M.unsafeInit . _nemVec
{-# INLINE init #-}
tail :: NonEmptyMVector s a -> MVector s a
tail = M.unsafeTail . _nemVec
{-# INLINE tail #-}
unsafeSlice
:: Int
-> Int
-> NonEmptyMVector s a
-> MVector s a
unsafeSlice n m = M.unsafeSlice n m . _nemVec
{-# INLINE unsafeSlice #-}
unsafeTake :: Int -> NonEmptyMVector s a -> MVector s a
unsafeTake n = M.unsafeTake n . _nemVec
{-# INLINE unsafeTake #-}
unsafeDrop :: Int -> NonEmptyMVector s a -> MVector s a
unsafeDrop n = M.unsafeDrop n . _nemVec
{-# INLINE unsafeDrop #-}
overlaps :: NonEmptyMVector s a -> NonEmptyMVector s a -> Bool
overlaps (NonEmptyMVector v) (NonEmptyMVector u) = M.overlaps v u
{-# INLINE overlaps #-}
fromMVector :: MVector s a -> Maybe (NonEmptyMVector s a)
fromMVector v = if M.null v then Nothing else Just (NonEmptyMVector v)
toMVector :: NonEmptyMVector s a -> MVector s a
toMVector = _nemVec
unsafeFromMVector :: MVector s a -> NonEmptyMVector s a
unsafeFromMVector = NonEmptyMVector
{-# INLINE unsafeFromMVector #-}
new
:: PrimMonad m
=> Int
-> m (Maybe (NonEmptyMVector (PrimState m) a))
new = fmap fromMVector . M.new
{-# INLINE new #-}
new1
:: PrimMonad m
=> Int
-> m (NonEmptyMVector (PrimState m) a)
new1 n = fmap unsafeFromMVector (M.new (max n 1))
{-# INLINE new1 #-}
unsafeNew
:: PrimMonad m
=> Int
-> m (Maybe (NonEmptyMVector (PrimState m) a))
unsafeNew = fmap fromMVector . M.unsafeNew
{-# INLINE unsafeNew #-}
replicate
:: PrimMonad m
=> Int
-> a
-> m (Maybe (NonEmptyMVector (PrimState m) a))
replicate n a = fmap fromMVector (M.replicate n a)
{-# INLINE replicate #-}
replicate1
:: PrimMonad m
=> Int
-> a
-> m (NonEmptyMVector (PrimState m) a)
replicate1 n a = fmap unsafeFromMVector (M.replicate (max n 1) a)
{-# INLINE replicate1 #-}
replicateM
:: PrimMonad m
=> Int
-> m a
-> m (Maybe (NonEmptyMVector (PrimState m) a))
replicateM n a = fmap fromMVector (M.replicateM n a)
{-# INLINE replicateM #-}
replicate1M
:: PrimMonad m
=> Int
-> m a
-> m (Maybe (NonEmptyMVector (PrimState m) a))
replicate1M n a = fmap fromMVector (M.replicateM (max n 1) a)
{-# INLINE replicate1M #-}
clone
:: PrimMonad m
=> NonEmptyMVector (PrimState m) a
-> m (NonEmptyMVector (PrimState m) a)
clone (NonEmptyMVector v) = fmap NonEmptyMVector (M.clone v)
{-# INLINE clone #-}
grow
:: PrimMonad m
=> NonEmptyMVector (PrimState m) a
-> Int
-> m (NonEmptyMVector (PrimState m) a)
grow (NonEmptyMVector v) n = fmap NonEmptyMVector (M.grow v n)
{-# INLINE grow #-}
unsafeGrow
:: PrimMonad m
=> NonEmptyMVector (PrimState m) a
-> Int
-> m (NonEmptyMVector (PrimState m) a)
unsafeGrow (NonEmptyMVector v) n = fmap NonEmptyMVector (M.unsafeGrow v n)
{-# INLINE unsafeGrow #-}
clear :: PrimMonad m => NonEmptyMVector (PrimState m) a -> m ()
clear = M.clear . _nemVec
{-# INLINE clear #-}
read
:: PrimMonad m
=> NonEmptyMVector (PrimState m) a
-> Int
-> m a
read (NonEmptyMVector v) n = M.read v n
{-# INLINE read #-}
write
:: PrimMonad m
=> NonEmptyMVector (PrimState m) a
-> Int
-> a
-> m ()
write (NonEmptyMVector v) n a = M.write v n a
{-# INLINE write #-}
modify
:: PrimMonad m
=> NonEmptyMVector (PrimState m) a
-> (a -> a)
-> Int
-> m ()
modify (NonEmptyMVector v) f n = M.modify v f n
{-# INLINE modify #-}
swap
:: PrimMonad m
=> NonEmptyMVector (PrimState m) a
-> Int
-> Int
-> m ()
swap (NonEmptyMVector v) n m = M.swap v n m
{-# INLINE swap #-}
unsafeRead
:: PrimMonad m
=> NonEmptyMVector (PrimState m) a
-> Int
-> m a
unsafeRead (NonEmptyMVector v) n = M.unsafeRead v n
{-# INLINE unsafeRead #-}
unsafeWrite
:: PrimMonad m
=> NonEmptyMVector (PrimState m) a
-> Int
-> a
-> m ()
unsafeWrite (NonEmptyMVector v) n a = M.unsafeWrite v n a
{-# INLINE unsafeWrite #-}
unsafeModify
:: PrimMonad m
=> NonEmptyMVector (PrimState m) a
-> (a -> a)
-> Int
-> m ()
unsafeModify (NonEmptyMVector v) f n = M.unsafeModify v f n
{-# INLINE unsafeModify #-}
unsafeSwap :: PrimMonad m => NonEmptyMVector (PrimState m) a -> Int -> Int -> m ()
unsafeSwap (NonEmptyMVector v) n m = M.unsafeSwap v n m
{-# INLINE unsafeSwap #-}
set :: PrimMonad m => NonEmptyMVector (PrimState m) a -> a -> m ()
set (NonEmptyMVector v) a = M.set v a
{-# INLINE set #-}
copy
:: PrimMonad m
=> NonEmptyMVector (PrimState m) a
-> NonEmptyMVector (PrimState m) a
-> m ()
copy (NonEmptyMVector v) (NonEmptyMVector v') = M.copy v v'
{-# INLINE copy #-}
unsafeCopy
:: PrimMonad m
=> NonEmptyMVector (PrimState m) a
-> NonEmptyMVector (PrimState m) a
-> m ()
unsafeCopy (NonEmptyMVector v) (NonEmptyMVector v') = M.unsafeCopy v v'
{-# INLINE unsafeCopy #-}
move
:: PrimMonad m
=> NonEmptyMVector (PrimState m) a
-> NonEmptyMVector (PrimState m) a -> m ()
move (NonEmptyMVector v) (NonEmptyMVector v') = M.move v v'
{-# INLINE move #-}
unsafeMove
:: PrimMonad m
=> NonEmptyMVector (PrimState m) a
-> NonEmptyMVector (PrimState m) a
-> m ()
unsafeMove (NonEmptyMVector v) (NonEmptyMVector v') = M.unsafeMove v v'
{-# INLINE unsafeMove #-}
nextPermutation
:: (PrimMonad m,Ord e)
=> NonEmptyMVector (PrimState m) e
-> m Bool
nextPermutation = M.nextPermutation . _nemVec
{-# INLINE nextPermutation #-}