Skip to content

Commit 7aea84f

Browse files
committed
fromMutableArray now evaluates all array eleemnts to WHNF
1 parent 78db774 commit 7aea84f

File tree

1 file changed

+11
-7
lines changed

1 file changed

+11
-7
lines changed

vector/src/Data/Vector/Strict/Mutable.hs

Lines changed: 11 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -72,16 +72,16 @@ module Data.Vector.Strict.Mutable (
7272
PrimMonad, PrimState, RealWorld
7373
) where
7474

75-
import Control.Monad (when, liftM)
75+
import Control.Monad (when)
7676
import qualified Data.Vector.Generic.Mutable as G
7777
import Data.Vector.Internal.Check
7878
import Data.Primitive.Array
7979
import Control.Monad.Primitive
8080

8181
import Prelude
82-
( Ord, Monad, Bool, Ordering(..), Int, Maybe
82+
( Ord, Monad(..), Bool, Ordering(..), Int, Maybe
8383
, compare, return, otherwise, error
84-
, (>>=), (+), (-), (*), (<), (>), (>=), (&&), (||), ($), (>>) )
84+
, (+), (-), (*), (<), (>), (>=), (&&), (||), ($), (>>), (<$>) )
8585

8686
import Data.Typeable ( Typeable )
8787

@@ -804,14 +804,18 @@ ifoldrM' = G.ifoldrM'
804804
-- Conversions - Arrays
805805
-- -----------------------------
806806

807-
-- | /O(n)/ Make a copy of a mutable array to a new mutable vector.
807+
-- | /O(n)/ Make a copy of a mutable array to a new mutable
808+
-- vector. All elements of a vector are evaluated to WHNF
808809
--
809810
-- @since 0.13.2.0
810811
fromMutableArray :: PrimMonad m => MutableArray (PrimState m) a -> m (MVector (PrimState m) a)
811812
{-# INLINE fromMutableArray #-}
812-
fromMutableArray marr =
813-
let size = sizeofMutableArray marr
814-
in MVector 0 size `liftM` cloneMutableArray marr 0 size
813+
fromMutableArray marr = stToPrim $ do
814+
mvec <- MVector 0 size <$> cloneMutableArray marr 0 size
815+
foldM' (\_ !_ -> return ()) () mvec
816+
return mvec
817+
where
818+
size = sizeofMutableArray marr
815819

816820
-- | /O(n)/ Make a copy of a mutable vector into a new mutable array.
817821
--

0 commit comments

Comments
 (0)