{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE Trustworthy #-}
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.Vector.Mutable (MVector)
import qualified Data.Vector.Mutable as M
import Data.Vector.NonEmpty.Internal
length :: NonEmptyMVector s a -> Int
length :: NonEmptyMVector s a -> Int
length = MVector s a -> Int
forall s a. MVector s a -> Int
M.length (MVector s a -> Int)
-> (NonEmptyMVector s a -> MVector s a)
-> NonEmptyMVector s a
-> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonEmptyMVector s a -> MVector s a
forall s a. NonEmptyMVector s a -> MVector s a
_nemVec
{-# INLINE length #-}
slice :: Int -> Int -> NonEmptyMVector s a -> MVector s a
slice :: Int -> Int -> NonEmptyMVector s a -> MVector s a
slice Int
n Int
m = Int -> Int -> MVector s a -> MVector s a
forall s a. Int -> Int -> MVector s a -> MVector s a
M.slice Int
n Int
m (MVector s a -> MVector s a)
-> (NonEmptyMVector s a -> MVector s a)
-> NonEmptyMVector s a
-> MVector s a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonEmptyMVector s a -> MVector s a
forall s a. NonEmptyMVector s a -> MVector s a
_nemVec
{-# INLINE slice #-}
take :: Int -> NonEmptyMVector s a -> MVector s a
take :: Int -> NonEmptyMVector s a -> MVector s a
take Int
n = Int -> MVector s a -> MVector s a
forall s a. Int -> MVector s a -> MVector s a
M.take Int
n (MVector s a -> MVector s a)
-> (NonEmptyMVector s a -> MVector s a)
-> NonEmptyMVector s a
-> MVector s a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonEmptyMVector s a -> MVector s a
forall s a. NonEmptyMVector s a -> MVector s a
_nemVec
{-# INLINE take #-}
drop :: Int -> NonEmptyMVector s a -> MVector s a
drop :: Int -> NonEmptyMVector s a -> MVector s a
drop Int
n = Int -> MVector s a -> MVector s a
forall s a. Int -> MVector s a -> MVector s a
M.drop Int
n (MVector s a -> MVector s a)
-> (NonEmptyMVector s a -> MVector s a)
-> NonEmptyMVector s a
-> MVector s a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonEmptyMVector s a -> MVector s a
forall s a. NonEmptyMVector s a -> MVector s a
_nemVec
{-# INLINE drop #-}
splitAt :: Int -> NonEmptyMVector s a -> (MVector s a, MVector s a)
splitAt :: Int -> NonEmptyMVector s a -> (MVector s a, MVector s a)
splitAt Int
n = Int -> MVector s a -> (MVector s a, MVector s a)
forall s a. Int -> MVector s a -> (MVector s a, MVector s a)
M.splitAt Int
n (MVector s a -> (MVector s a, MVector s a))
-> (NonEmptyMVector s a -> MVector s a)
-> NonEmptyMVector s a
-> (MVector s a, MVector s a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonEmptyMVector s a -> MVector s a
forall s a. NonEmptyMVector s a -> MVector s a
_nemVec
{-# INLINE splitAt #-}
init :: NonEmptyMVector s a -> MVector s a
init :: NonEmptyMVector s a -> MVector s a
init = MVector s a -> MVector s a
forall s a. MVector s a -> MVector s a
M.unsafeInit (MVector s a -> MVector s a)
-> (NonEmptyMVector s a -> MVector s a)
-> NonEmptyMVector s a
-> MVector s a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonEmptyMVector s a -> MVector s a
forall s a. NonEmptyMVector s a -> MVector s a
_nemVec
{-# INLINE init #-}
tail :: NonEmptyMVector s a -> MVector s a
tail :: NonEmptyMVector s a -> MVector s a
tail = MVector s a -> MVector s a
forall s a. MVector s a -> MVector s a
M.unsafeTail (MVector s a -> MVector s a)
-> (NonEmptyMVector s a -> MVector s a)
-> NonEmptyMVector s a
-> MVector s a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonEmptyMVector s a -> MVector s a
forall s a. NonEmptyMVector s a -> MVector s a
_nemVec
{-# INLINE tail #-}
unsafeSlice
    :: Int
      
    -> Int
      
    -> NonEmptyMVector s a
    -> MVector s a
unsafeSlice :: Int -> Int -> NonEmptyMVector s a -> MVector s a
unsafeSlice Int
n Int
m = Int -> Int -> MVector s a -> MVector s a
forall s a. Int -> Int -> MVector s a -> MVector s a
M.unsafeSlice Int
n Int
m (MVector s a -> MVector s a)
-> (NonEmptyMVector s a -> MVector s a)
-> NonEmptyMVector s a
-> MVector s a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonEmptyMVector s a -> MVector s a
forall s a. NonEmptyMVector s a -> MVector s a
_nemVec
{-# INLINE unsafeSlice #-}
unsafeTake :: Int -> NonEmptyMVector s a -> MVector s a
unsafeTake :: Int -> NonEmptyMVector s a -> MVector s a
unsafeTake Int
n = Int -> MVector s a -> MVector s a
forall s a. Int -> MVector s a -> MVector s a
M.unsafeTake Int
n (MVector s a -> MVector s a)
-> (NonEmptyMVector s a -> MVector s a)
-> NonEmptyMVector s a
-> MVector s a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonEmptyMVector s a -> MVector s a
forall s a. NonEmptyMVector s a -> MVector s a
_nemVec
{-# INLINE unsafeTake #-}
unsafeDrop :: Int -> NonEmptyMVector s a -> MVector s a
unsafeDrop :: Int -> NonEmptyMVector s a -> MVector s a
unsafeDrop Int
n = Int -> MVector s a -> MVector s a
forall s a. Int -> MVector s a -> MVector s a
M.unsafeDrop Int
n (MVector s a -> MVector s a)
-> (NonEmptyMVector s a -> MVector s a)
-> NonEmptyMVector s a
-> MVector s a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonEmptyMVector s a -> MVector s a
forall s a. NonEmptyMVector s a -> MVector s a
_nemVec
{-# INLINE unsafeDrop #-}
overlaps :: NonEmptyMVector s a -> NonEmptyMVector s a -> Bool
overlaps :: NonEmptyMVector s a -> NonEmptyMVector s a -> Bool
overlaps (NonEmptyMVector MVector s a
v) (NonEmptyMVector MVector s a
u) = MVector s a -> MVector s a -> Bool
forall s a. MVector s a -> MVector s a -> Bool
M.overlaps MVector s a
v MVector s a
u
{-# INLINE overlaps #-}
fromMVector :: MVector s a -> Maybe (NonEmptyMVector s a)
fromMVector :: MVector s a -> Maybe (NonEmptyMVector s a)
fromMVector MVector s a
v = if MVector s a -> Bool
forall s a. MVector s a -> Bool
M.null MVector s a
v then Maybe (NonEmptyMVector s a)
forall a. Maybe a
Nothing else NonEmptyMVector s a -> Maybe (NonEmptyMVector s a)
forall a. a -> Maybe a
Just (MVector s a -> NonEmptyMVector s a
forall s a. MVector s a -> NonEmptyMVector s a
NonEmptyMVector MVector s a
v)
toMVector :: NonEmptyMVector s a -> MVector s a
toMVector :: NonEmptyMVector s a -> MVector s a
toMVector = NonEmptyMVector s a -> MVector s a
forall s a. NonEmptyMVector s a -> MVector s a
_nemVec
unsafeFromMVector :: MVector s a -> NonEmptyMVector s a
unsafeFromMVector :: MVector s a -> NonEmptyMVector s a
unsafeFromMVector = MVector s a -> NonEmptyMVector s a
forall s a. MVector s a -> NonEmptyMVector s a
NonEmptyMVector
{-# INLINE unsafeFromMVector #-}
new
    :: PrimMonad m
    => Int
    -> m (Maybe (NonEmptyMVector (PrimState m) a))
new :: Int -> m (Maybe (NonEmptyMVector (PrimState m) a))
new = (MVector (PrimState m) a
 -> Maybe (NonEmptyMVector (PrimState m) a))
-> m (MVector (PrimState m) a)
-> m (Maybe (NonEmptyMVector (PrimState m) a))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap MVector (PrimState m) a -> Maybe (NonEmptyMVector (PrimState m) a)
forall s a. MVector s a -> Maybe (NonEmptyMVector s a)
fromMVector (m (MVector (PrimState m) a)
 -> m (Maybe (NonEmptyMVector (PrimState m) a)))
-> (Int -> m (MVector (PrimState m) a))
-> Int
-> m (Maybe (NonEmptyMVector (PrimState m) a))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> m (MVector (PrimState m) a)
forall (m :: * -> *) a.
PrimMonad m =>
Int -> m (MVector (PrimState m) a)
M.new
{-# INLINE new #-}
new1
    :: PrimMonad m
    => Int
    -> m (NonEmptyMVector (PrimState m) a)
new1 :: Int -> m (NonEmptyMVector (PrimState m) a)
new1 Int
n = (MVector (PrimState m) a -> NonEmptyMVector (PrimState m) a)
-> m (MVector (PrimState m) a)
-> m (NonEmptyMVector (PrimState m) a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap MVector (PrimState m) a -> NonEmptyMVector (PrimState m) a
forall s a. MVector s a -> NonEmptyMVector s a
unsafeFromMVector (Int -> m (MVector (PrimState m) a)
forall (m :: * -> *) a.
PrimMonad m =>
Int -> m (MVector (PrimState m) a)
M.new (Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
n Int
1))
{-# INLINE new1 #-}
unsafeNew
    :: PrimMonad m
    => Int
    -> m (Maybe (NonEmptyMVector (PrimState m) a))
unsafeNew :: Int -> m (Maybe (NonEmptyMVector (PrimState m) a))
unsafeNew = (MVector (PrimState m) a
 -> Maybe (NonEmptyMVector (PrimState m) a))
-> m (MVector (PrimState m) a)
-> m (Maybe (NonEmptyMVector (PrimState m) a))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap MVector (PrimState m) a -> Maybe (NonEmptyMVector (PrimState m) a)
forall s a. MVector s a -> Maybe (NonEmptyMVector s a)
fromMVector (m (MVector (PrimState m) a)
 -> m (Maybe (NonEmptyMVector (PrimState m) a)))
-> (Int -> m (MVector (PrimState m) a))
-> Int
-> m (Maybe (NonEmptyMVector (PrimState m) a))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> m (MVector (PrimState m) a)
forall (m :: * -> *) a.
PrimMonad m =>
Int -> m (MVector (PrimState m) a)
M.unsafeNew
{-# INLINE unsafeNew #-}
replicate
    :: PrimMonad m
    => Int
    -> a
    -> m (Maybe (NonEmptyMVector (PrimState m) a))
replicate :: Int -> a -> m (Maybe (NonEmptyMVector (PrimState m) a))
replicate Int
n a
a = (MVector (PrimState m) a
 -> Maybe (NonEmptyMVector (PrimState m) a))
-> m (MVector (PrimState m) a)
-> m (Maybe (NonEmptyMVector (PrimState m) a))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap MVector (PrimState m) a -> Maybe (NonEmptyMVector (PrimState m) a)
forall s a. MVector s a -> Maybe (NonEmptyMVector s a)
fromMVector (Int -> a -> m (MVector (PrimState m) a)
forall (m :: * -> *) a.
PrimMonad m =>
Int -> a -> m (MVector (PrimState m) a)
M.replicate Int
n a
a)
{-# INLINE replicate #-}
replicate1
    :: PrimMonad m
    => Int
    -> a
    -> m (NonEmptyMVector (PrimState m) a)
replicate1 :: Int -> a -> m (NonEmptyMVector (PrimState m) a)
replicate1 Int
n a
a = (MVector (PrimState m) a -> NonEmptyMVector (PrimState m) a)
-> m (MVector (PrimState m) a)
-> m (NonEmptyMVector (PrimState m) a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap MVector (PrimState m) a -> NonEmptyMVector (PrimState m) a
forall s a. MVector s a -> NonEmptyMVector s a
unsafeFromMVector (Int -> a -> m (MVector (PrimState m) a)
forall (m :: * -> *) a.
PrimMonad m =>
Int -> a -> m (MVector (PrimState m) a)
M.replicate (Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
n Int
1) a
a)
{-# INLINE replicate1 #-}
replicateM
    :: PrimMonad m
    => Int
    -> m a
    -> m (Maybe (NonEmptyMVector (PrimState m) a))
replicateM :: Int -> m a -> m (Maybe (NonEmptyMVector (PrimState m) a))
replicateM  Int
n m a
a = (MVector (PrimState m) a
 -> Maybe (NonEmptyMVector (PrimState m) a))
-> m (MVector (PrimState m) a)
-> m (Maybe (NonEmptyMVector (PrimState m) a))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap MVector (PrimState m) a -> Maybe (NonEmptyMVector (PrimState m) a)
forall s a. MVector s a -> Maybe (NonEmptyMVector s a)
fromMVector (Int -> m a -> m (MVector (PrimState m) a)
forall (m :: * -> *) a.
PrimMonad m =>
Int -> m a -> m (MVector (PrimState m) a)
M.replicateM Int
n m a
a)
{-# INLINE replicateM #-}
replicate1M
    :: PrimMonad m
    => Int
    -> m a
    -> m (Maybe (NonEmptyMVector (PrimState m) a))
replicate1M :: Int -> m a -> m (Maybe (NonEmptyMVector (PrimState m) a))
replicate1M Int
n m a
a = (MVector (PrimState m) a
 -> Maybe (NonEmptyMVector (PrimState m) a))
-> m (MVector (PrimState m) a)
-> m (Maybe (NonEmptyMVector (PrimState m) a))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap MVector (PrimState m) a -> Maybe (NonEmptyMVector (PrimState m) a)
forall s a. MVector s a -> Maybe (NonEmptyMVector s a)
fromMVector (Int -> m a -> m (MVector (PrimState m) a)
forall (m :: * -> *) a.
PrimMonad m =>
Int -> m a -> m (MVector (PrimState m) a)
M.replicateM (Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
n Int
1) m a
a)
{-# INLINE replicate1M #-}
clone
    :: PrimMonad m
    => NonEmptyMVector (PrimState m) a
    -> m (NonEmptyMVector (PrimState m) a)
clone :: NonEmptyMVector (PrimState m) a
-> m (NonEmptyMVector (PrimState m) a)
clone (NonEmptyMVector MVector (PrimState m) a
v) = (MVector (PrimState m) a -> NonEmptyMVector (PrimState m) a)
-> m (MVector (PrimState m) a)
-> m (NonEmptyMVector (PrimState m) a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap MVector (PrimState m) a -> NonEmptyMVector (PrimState m) a
forall s a. MVector s a -> NonEmptyMVector s a
NonEmptyMVector (MVector (PrimState m) a -> m (MVector (PrimState m) a)
forall (m :: * -> *) a.
PrimMonad m =>
MVector (PrimState m) a -> m (MVector (PrimState m) a)
M.clone MVector (PrimState m) a
v)
{-# INLINE clone #-}
grow
    :: PrimMonad m
    => NonEmptyMVector (PrimState m) a
    -> Int
    -> m (NonEmptyMVector (PrimState m) a)
grow :: NonEmptyMVector (PrimState m) a
-> Int -> m (NonEmptyMVector (PrimState m) a)
grow (NonEmptyMVector MVector (PrimState m) a
v) Int
n = (MVector (PrimState m) a -> NonEmptyMVector (PrimState m) a)
-> m (MVector (PrimState m) a)
-> m (NonEmptyMVector (PrimState m) a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap MVector (PrimState m) a -> NonEmptyMVector (PrimState m) a
forall s a. MVector s a -> NonEmptyMVector s a
NonEmptyMVector (MVector (PrimState m) a -> Int -> m (MVector (PrimState m) a)
forall (m :: * -> *) a.
PrimMonad m =>
MVector (PrimState m) a -> Int -> m (MVector (PrimState m) a)
M.grow MVector (PrimState m) a
v Int
n)
{-# INLINE grow #-}
unsafeGrow
    :: PrimMonad m
    => NonEmptyMVector (PrimState m) a
    -> Int
    -> m (NonEmptyMVector (PrimState m) a)
unsafeGrow :: NonEmptyMVector (PrimState m) a
-> Int -> m (NonEmptyMVector (PrimState m) a)
unsafeGrow (NonEmptyMVector MVector (PrimState m) a
v) Int
n = (MVector (PrimState m) a -> NonEmptyMVector (PrimState m) a)
-> m (MVector (PrimState m) a)
-> m (NonEmptyMVector (PrimState m) a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap MVector (PrimState m) a -> NonEmptyMVector (PrimState m) a
forall s a. MVector s a -> NonEmptyMVector s a
NonEmptyMVector (MVector (PrimState m) a -> Int -> m (MVector (PrimState m) a)
forall (m :: * -> *) a.
PrimMonad m =>
MVector (PrimState m) a -> Int -> m (MVector (PrimState m) a)
M.unsafeGrow MVector (PrimState m) a
v Int
n)
{-# INLINE unsafeGrow #-}
clear :: PrimMonad m => NonEmptyMVector (PrimState m) a -> m ()
clear :: NonEmptyMVector (PrimState m) a -> m ()
clear = MVector (PrimState m) a -> m ()
forall (m :: * -> *) a.
PrimMonad m =>
MVector (PrimState m) a -> m ()
M.clear (MVector (PrimState m) a -> m ())
-> (NonEmptyMVector (PrimState m) a -> MVector (PrimState m) a)
-> NonEmptyMVector (PrimState m) a
-> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonEmptyMVector (PrimState m) a -> MVector (PrimState m) a
forall s a. NonEmptyMVector s a -> MVector s a
_nemVec
{-# INLINE clear #-}
read
    :: PrimMonad m
    => NonEmptyMVector (PrimState m) a
    -> Int
    -> m a
read :: NonEmptyMVector (PrimState m) a -> Int -> m a
read (NonEmptyMVector MVector (PrimState m) a
v) Int
n = MVector (PrimState m) a -> Int -> m a
forall (m :: * -> *) a.
PrimMonad m =>
MVector (PrimState m) a -> Int -> m a
M.read MVector (PrimState m) a
v Int
n
{-# INLINE read #-}
write
    :: PrimMonad m
    => NonEmptyMVector (PrimState m) a
    -> Int
    -> a
    -> m ()
write :: NonEmptyMVector (PrimState m) a -> Int -> a -> m ()
write (NonEmptyMVector MVector (PrimState m) a
v) Int
n a
a = MVector (PrimState m) a -> Int -> a -> m ()
forall (m :: * -> *) a.
PrimMonad m =>
MVector (PrimState m) a -> Int -> a -> m ()
M.write MVector (PrimState m) a
v Int
n a
a
{-# INLINE write #-}
modify
    :: PrimMonad m
    => NonEmptyMVector (PrimState m) a
    -> (a -> a)
    -> Int
    -> m ()
modify :: NonEmptyMVector (PrimState m) a -> (a -> a) -> Int -> m ()
modify (NonEmptyMVector MVector (PrimState m) a
v) a -> a
f Int
n = MVector (PrimState m) a -> (a -> a) -> Int -> m ()
forall (m :: * -> *) a.
PrimMonad m =>
MVector (PrimState m) a -> (a -> a) -> Int -> m ()
M.modify MVector (PrimState m) a
v a -> a
f Int
n
{-# INLINE modify #-}
swap
    :: PrimMonad m
    => NonEmptyMVector (PrimState m) a
    -> Int
    -> Int
    -> m ()
swap :: NonEmptyMVector (PrimState m) a -> Int -> Int -> m ()
swap (NonEmptyMVector MVector (PrimState m) a
v) Int
n Int
m = MVector (PrimState m) a -> Int -> Int -> m ()
forall (m :: * -> *) a.
PrimMonad m =>
MVector (PrimState m) a -> Int -> Int -> m ()
M.swap MVector (PrimState m) a
v Int
n Int
m
{-# INLINE swap #-}
unsafeRead
    :: PrimMonad m
    => NonEmptyMVector (PrimState m) a
    -> Int
    -> m a
unsafeRead :: NonEmptyMVector (PrimState m) a -> Int -> m a
unsafeRead (NonEmptyMVector MVector (PrimState m) a
v) Int
n = MVector (PrimState m) a -> Int -> m a
forall (m :: * -> *) a.
PrimMonad m =>
MVector (PrimState m) a -> Int -> m a
M.unsafeRead MVector (PrimState m) a
v Int
n
{-# INLINE unsafeRead #-}
unsafeWrite
    :: PrimMonad m
    => NonEmptyMVector (PrimState m) a
    -> Int
    -> a
    -> m ()
unsafeWrite :: NonEmptyMVector (PrimState m) a -> Int -> a -> m ()
unsafeWrite (NonEmptyMVector MVector (PrimState m) a
v) Int
n a
a = MVector (PrimState m) a -> Int -> a -> m ()
forall (m :: * -> *) a.
PrimMonad m =>
MVector (PrimState m) a -> Int -> a -> m ()
M.unsafeWrite MVector (PrimState m) a
v Int
n a
a
{-# INLINE unsafeWrite #-}
unsafeModify
    :: PrimMonad m
    => NonEmptyMVector (PrimState m) a
    -> (a -> a)
    -> Int
    -> m ()
unsafeModify :: NonEmptyMVector (PrimState m) a -> (a -> a) -> Int -> m ()
unsafeModify (NonEmptyMVector MVector (PrimState m) a
v) a -> a
f Int
n = MVector (PrimState m) a -> (a -> a) -> Int -> m ()
forall (m :: * -> *) a.
PrimMonad m =>
MVector (PrimState m) a -> (a -> a) -> Int -> m ()
M.unsafeModify MVector (PrimState m) a
v a -> a
f Int
n
{-# INLINE unsafeModify #-}
unsafeSwap :: PrimMonad m => NonEmptyMVector (PrimState m) a -> Int -> Int -> m ()
unsafeSwap :: NonEmptyMVector (PrimState m) a -> Int -> Int -> m ()
unsafeSwap (NonEmptyMVector MVector (PrimState m) a
v) Int
n Int
m = MVector (PrimState m) a -> Int -> Int -> m ()
forall (m :: * -> *) a.
PrimMonad m =>
MVector (PrimState m) a -> Int -> Int -> m ()
M.unsafeSwap MVector (PrimState m) a
v Int
n Int
m
{-# INLINE unsafeSwap #-}
set :: PrimMonad m => NonEmptyMVector (PrimState m) a -> a -> m ()
set :: NonEmptyMVector (PrimState m) a -> a -> m ()
set (NonEmptyMVector MVector (PrimState m) a
v) a
a = MVector (PrimState m) a -> a -> m ()
forall (m :: * -> *) a.
PrimMonad m =>
MVector (PrimState m) a -> a -> m ()
M.set MVector (PrimState m) a
v a
a
{-# INLINE set #-}
copy
    :: PrimMonad m
    => NonEmptyMVector (PrimState m) a
    -> NonEmptyMVector (PrimState m) a
    -> m ()
copy :: NonEmptyMVector (PrimState m) a
-> NonEmptyMVector (PrimState m) a -> m ()
copy (NonEmptyMVector MVector (PrimState m) a
v) (NonEmptyMVector MVector (PrimState m) a
v') = MVector (PrimState m) a -> MVector (PrimState m) a -> m ()
forall (m :: * -> *) a.
PrimMonad m =>
MVector (PrimState m) a -> MVector (PrimState m) a -> m ()
M.copy MVector (PrimState m) a
v MVector (PrimState m) a
v'
{-# INLINE copy #-}
unsafeCopy
    :: PrimMonad m
    => NonEmptyMVector (PrimState m) a
      
    -> NonEmptyMVector (PrimState m) a
      
    -> m ()
unsafeCopy :: NonEmptyMVector (PrimState m) a
-> NonEmptyMVector (PrimState m) a -> m ()
unsafeCopy (NonEmptyMVector MVector (PrimState m) a
v) (NonEmptyMVector MVector (PrimState m) a
v') = MVector (PrimState m) a -> MVector (PrimState m) a -> m ()
forall (m :: * -> *) a.
PrimMonad m =>
MVector (PrimState m) a -> MVector (PrimState m) a -> m ()
M.unsafeCopy MVector (PrimState m) a
v MVector (PrimState m) a
v'
{-# INLINE unsafeCopy #-}
move
    :: PrimMonad m
    => NonEmptyMVector (PrimState m) a
    -> NonEmptyMVector (PrimState m) a -> m ()
move :: NonEmptyMVector (PrimState m) a
-> NonEmptyMVector (PrimState m) a -> m ()
move (NonEmptyMVector MVector (PrimState m) a
v) (NonEmptyMVector MVector (PrimState m) a
v') = MVector (PrimState m) a -> MVector (PrimState m) a -> m ()
forall (m :: * -> *) a.
PrimMonad m =>
MVector (PrimState m) a -> MVector (PrimState m) a -> m ()
M.move MVector (PrimState m) a
v MVector (PrimState m) a
v'
{-# INLINE move #-}
unsafeMove
    :: PrimMonad m
    => NonEmptyMVector (PrimState m) a
      
    -> NonEmptyMVector (PrimState m) a
      
    -> m ()
unsafeMove :: NonEmptyMVector (PrimState m) a
-> NonEmptyMVector (PrimState m) a -> m ()
unsafeMove (NonEmptyMVector MVector (PrimState m) a
v) (NonEmptyMVector MVector (PrimState m) a
v') = MVector (PrimState m) a -> MVector (PrimState m) a -> m ()
forall (m :: * -> *) a.
PrimMonad m =>
MVector (PrimState m) a -> MVector (PrimState m) a -> m ()
M.unsafeMove MVector (PrimState m) a
v MVector (PrimState m) a
v'
{-# INLINE unsafeMove #-}
nextPermutation
    :: (PrimMonad m,Ord e)
    => NonEmptyMVector (PrimState m) e
    -> m Bool
nextPermutation :: NonEmptyMVector (PrimState m) e -> m Bool
nextPermutation = MVector (PrimState m) e -> m Bool
forall (m :: * -> *) e.
(PrimMonad m, Ord e) =>
MVector (PrimState m) e -> m Bool
M.nextPermutation (MVector (PrimState m) e -> m Bool)
-> (NonEmptyMVector (PrimState m) e -> MVector (PrimState m) e)
-> NonEmptyMVector (PrimState m) e
-> m Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonEmptyMVector (PrimState m) e -> MVector (PrimState m) e
forall s a. NonEmptyMVector s a -> MVector s a
_nemVec
{-# INLINE nextPermutation #-}