@@ -72,16 +72,16 @@ module Data.Vector.Strict.Mutable (
72
72
PrimMonad , PrimState , RealWorld
73
73
) where
74
74
75
- import Control.Monad (when , liftM )
75
+ import Control.Monad (when )
76
76
import qualified Data.Vector.Generic.Mutable as G
77
77
import Data.Vector.Internal.Check
78
78
import Data.Primitive.Array
79
79
import Control.Monad.Primitive
80
80
81
81
import Prelude
82
- ( Ord , Monad , Bool , Ordering (.. ), Int , Maybe
82
+ ( Ord , Monad ( .. ) , Bool , Ordering (.. ), Int , Maybe
83
83
, compare , return , otherwise , error
84
- , (>>=) , ( +) , (-) , (*) , (<) , (>) , (>=) , (&&) , (||) , ($) , (>>) )
84
+ , (+) , (-) , (*) , (<) , (>) , (>=) , (&&) , (||) , ($) , (>>) , (<$ >) )
85
85
86
86
import Data.Typeable ( Typeable )
87
87
@@ -804,14 +804,18 @@ ifoldrM' = G.ifoldrM'
804
804
-- Conversions - Arrays
805
805
-- -----------------------------
806
806
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
808
809
--
809
810
-- @since 0.13.2.0
810
811
fromMutableArray :: PrimMonad m => MutableArray (PrimState m ) a -> m (MVector (PrimState m ) a )
811
812
{-# 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
815
819
816
820
-- | /O(n)/ Make a copy of a mutable vector into a new mutable array.
817
821
--
0 commit comments