Skip to content

Commit 363c4cf

Browse files
meooow25andrewthad
authored andcommitted
Use createPrimArray and createByteArray
1 parent c4c7682 commit 363c4cf

File tree

2 files changed

+33
-50
lines changed

2 files changed

+33
-50
lines changed

Data/Primitive/ByteArray.hs

+11-15
Original file line numberDiff line numberDiff line change
@@ -379,18 +379,16 @@ byteArrayFromList xs = byteArrayFromListN (length xs) xs
379379
-- | Create a 'ByteArray' from a list of a known length. If the length
380380
-- of the list does not match the given length, this throws an exception.
381381
byteArrayFromListN :: forall a. Prim a => Int -> [a] -> ByteArray
382-
byteArrayFromListN n ys = runST $ do
383-
marr <- newByteArray (n * sizeOfType @a)
384-
let go !ix [] = if ix == n
385-
then return ()
386-
else die "byteArrayFromListN" "list length less than specified size"
387-
go !ix (x : xs) = if ix < n
388-
then do
389-
writeByteArray marr ix x
390-
go (ix + 1) xs
391-
else die "byteArrayFromListN" "list length greater than specified size"
392-
go 0 ys
393-
unsafeFreezeByteArray marr
382+
byteArrayFromListN n ys = createByteArray (n * sizeOfType @a) $ \marr ->
383+
let go !ix [] = if ix == n
384+
then return ()
385+
else die "byteArrayFromListN" "list length less than specified size"
386+
go !ix (x : xs) = if ix < n
387+
then do
388+
writeByteArray marr ix x
389+
go (ix + 1) xs
390+
else die "byteArrayFromListN" "list length greater than specified size"
391+
in go 0 ys
394392

395393
unI# :: Int -> Int#
396394
unI# (I# n#) = n#
@@ -616,10 +614,8 @@ cloneByteArray
616614
-> Int -- ^ number of bytes to copy
617615
-> ByteArray
618616
{-# INLINE cloneByteArray #-}
619-
cloneByteArray src off n = runByteArray $ do
620-
dst <- newByteArray n
617+
cloneByteArray src off n = createByteArray n $ \dst ->
621618
copyByteArray dst 0 src off n
622-
return dst
623619

624620
-- | Return a newly allocated mutable array with the specified subrange of
625621
-- the provided mutable array. The provided mutable array should contain the

Data/Primitive/PrimArray.hs

+22-35
Original file line numberDiff line numberDiff line change
@@ -235,21 +235,16 @@ primArrayFromList vs = primArrayFromListN (L.length vs) vs
235235
-- | Create a 'PrimArray' from a list of a known length. If the length
236236
-- of the list does not match the given length, this throws an exception.
237237
primArrayFromListN :: forall a. Prim a => Int -> [a] -> PrimArray a
238-
primArrayFromListN len vs = runST run where
239-
run :: forall s. ST s (PrimArray a)
240-
run = do
241-
arr <- newPrimArray len
242-
let go :: [a] -> Int -> ST s ()
243-
go [] !ix = if ix == len
244-
then return ()
245-
else die "fromListN" "list length less than specified size"
246-
go (a : as) !ix = if ix < len
247-
then do
248-
writePrimArray arr ix a
249-
go as (ix + 1)
250-
else die "fromListN" "list length greater than specified size"
251-
go vs 0
252-
unsafeFreezePrimArray arr
238+
primArrayFromListN len vs = createPrimArray len $ \arr ->
239+
let go [] !ix = if ix == len
240+
then return ()
241+
else die "fromListN" "list length less than specified size"
242+
go (a : as) !ix = if ix < len
243+
then do
244+
writePrimArray arr ix a
245+
go as (ix + 1)
246+
else die "fromListN" "list length greater than specified size"
247+
in go vs 0
253248

254249
-- | Convert a 'PrimArray' to a list.
255250
{-# INLINE primArrayToList #-}
@@ -769,31 +764,29 @@ mapPrimArray :: (Prim a, Prim b)
769764
=> (a -> b)
770765
-> PrimArray a
771766
-> PrimArray b
772-
mapPrimArray f arr = runST $ do
773-
let !sz = sizeofPrimArray arr
774-
marr <- newPrimArray sz
767+
mapPrimArray f arr = createPrimArray sz $ \marr ->
775768
let go !ix = when (ix < sz) $ do
776769
let b = f (indexPrimArray arr ix)
777770
writePrimArray marr ix b
778771
go (ix + 1)
779-
go 0
780-
unsafeFreezePrimArray marr
772+
in go 0
773+
where
774+
!sz = sizeofPrimArray arr
781775

782776
-- | Indexed map over the elements of a primitive array.
783777
{-# INLINE imapPrimArray #-}
784778
imapPrimArray :: (Prim a, Prim b)
785779
=> (Int -> a -> b)
786780
-> PrimArray a
787781
-> PrimArray b
788-
imapPrimArray f arr = runST $ do
789-
let !sz = sizeofPrimArray arr
790-
marr <- newPrimArray sz
782+
imapPrimArray f arr = createPrimArray sz $ \marr ->
791783
let go !ix = when (ix < sz) $ do
792784
let b = f ix (indexPrimArray arr ix)
793785
writePrimArray marr ix b
794786
go (ix + 1)
795-
go 0
796-
unsafeFreezePrimArray marr
787+
in go 0
788+
where
789+
!sz = sizeofPrimArray arr
797790

798791
-- | Filter elements of a primitive array according to a predicate.
799792
{-# INLINE filterPrimArray #-}
@@ -963,13 +956,11 @@ generatePrimArray :: Prim a
963956
=> Int -- ^ length
964957
-> (Int -> a) -- ^ element from index
965958
-> PrimArray a
966-
generatePrimArray len f = runST $ do
967-
marr <- newPrimArray len
959+
generatePrimArray len f = createPrimArray len $ \marr ->
968960
let go !ix = when (ix < len) $ do
969961
writePrimArray marr ix (f ix)
970962
go (ix + 1)
971-
go 0
972-
unsafeFreezePrimArray marr
963+
in go 0
973964

974965
-- | Create a primitive array by copying the element the given
975966
-- number of times.
@@ -978,10 +969,8 @@ replicatePrimArray :: Prim a
978969
=> Int -- ^ length
979970
-> a -- ^ element
980971
-> PrimArray a
981-
replicatePrimArray len a = runST $ do
982-
marr <- newPrimArray len
972+
replicatePrimArray len a = createPrimArray len $ \marr ->
983973
setPrimArray marr 0 len a
984-
unsafeFreezePrimArray marr
985974

986975
-- | Generate a primitive array by evaluating the applicative generator
987976
-- function at each index.
@@ -1129,10 +1118,8 @@ clonePrimArray :: Prim a
11291118
-> Int -- ^ number of elements to copy
11301119
-> PrimArray a
11311120
{-# INLINE clonePrimArray #-}
1132-
clonePrimArray src off n = runPrimArray $ do
1133-
dst <- newPrimArray n
1121+
clonePrimArray src off n = createPrimArray n $ \dst ->
11341122
copyPrimArray dst 0 src off n
1135-
return dst
11361123

11371124
-- | Return a newly allocated mutable array with the specified subrange of
11381125
-- the provided mutable array. The provided mutable array should contain the

0 commit comments

Comments
 (0)