@@ -184,16 +184,9 @@ import Data.Primitive.Array
184184import qualified Data.Vector.Generic as G
185185import qualified Data.Vector as V
186186
187- import Control.DeepSeq ( NFData (rnf )
188- #if MIN_VERSION_deepseq(1,4,3)
189- , NFData1 (liftRnf )
190- #endif
191- )
187+ import Control.DeepSeq ( NFData (rnf ), NFData1 (liftRnf ))
192188
193189import Control.Monad ( MonadPlus (.. ), ap )
194- #if !MIN_VERSION_base(4,13,0)
195- import Control.Monad (fail )
196- #endif
197190import Control.Monad.ST ( ST , runST )
198191import Control.Monad.Primitive
199192import qualified Control.Monad.Fail as Fail
@@ -234,19 +227,14 @@ newtype Vector a = Vector (V.Vector a)
234227-- parameters (e.g. Eq, Ord) and not OK to derive ones where new
235228-- vector is created (e.g. Read, Functor)
236229
237- liftRnfV :: (a -> () ) -> Vector a -> ()
238- liftRnfV elemRnf = foldl' (\ _ -> elemRnf) ()
239-
240230instance NFData a => NFData (Vector a ) where
241- rnf = liftRnfV rnf
231+ rnf = liftRnf rnf
242232 {-# INLINEABLE rnf #-}
243233
244- #if MIN_VERSION_deepseq(1,4,3)
245234-- | @since 0.13.2.0
246235instance NFData1 Vector where
247- liftRnf = liftRnfV
236+ liftRnf elemRnf = foldl' ( \ _ -> elemRnf) ()
248237 {-# INLINEABLE liftRnf #-}
249- #endif
250238
251239instance Show a => Show (Vector a ) where
252240 showsPrec = G. showsPrec
@@ -335,11 +323,6 @@ instance Monad Vector where
335323 {-# INLINE (>>=) #-}
336324 (>>=) = flip concatMap
337325
338- #if !(MIN_VERSION_base(4,13,0))
339- {-# INLINE fail #-}
340- fail = Fail. fail -- == \ _str -> empty
341- #endif
342-
343326-- | @since 0.13.2.0
344327instance Fail. MonadFail Vector where
345328 {-# INLINE fail #-}
@@ -2576,7 +2559,7 @@ toLazy (Vector v) = v
25762559-- | /O(n)/ Convert lazy array to strict array. This function reduces
25772560-- each element of vector to WHNF.
25782561fromLazy :: V. Vector a -> Vector a
2579- fromLazy vec = liftRnfV (`seq` () ) v `seq` v where v = Vector vec
2562+ fromLazy vec = liftRnf (`seq` () ) v `seq` v where v = Vector vec
25802563
25812564
25822565-- Conversions - Arrays
@@ -2587,7 +2570,7 @@ fromLazy vec = liftRnfV (`seq` ()) v `seq` v where v = Vector vec
25872570-- @since 0.13.2.0
25882571fromArray :: Array a -> Vector a
25892572{-# INLINE fromArray #-}
2590- fromArray arr = liftRnfV (`seq` () ) vec `seq` vec
2573+ fromArray arr = liftRnf (`seq` () ) vec `seq` vec
25912574 where
25922575 vec = Vector $ V. fromArray arr
25932576
@@ -2625,7 +2608,7 @@ unsafeFromArraySlice ::
26252608 -> Int -- ^ Length
26262609 -> Vector a
26272610{-# INLINE unsafeFromArraySlice #-}
2628- unsafeFromArraySlice arr offset len = liftRnfV (`seq` () ) vec `seq` vec
2611+ unsafeFromArraySlice arr offset len = liftRnf (`seq` () ) vec `seq` vec
26292612 where vec = Vector (V. unsafeFromArraySlice arr offset len)
26302613
26312614
0 commit comments