@@ -493,6 +493,9 @@ traverse f = \ !ary ->
493493 in runSTA len <$> go 0
494494{-# INLINE [1] traverse #-}
495495
496+ -- TODO: Would it be better to just use a lazy traversal
497+ -- and then force the elements of the result? My guess is
498+ -- yes.
496499traverse' :: Applicative f => (a -> f b ) -> Array a -> f (Array b )
497500traverse' f = \ ! ary ->
498501 let
@@ -537,42 +540,17 @@ traverseIO f = \ ary0 ->
537540{-# INLINE traverseIO #-}
538541
539542
543+ -- Why don't we have similar RULES for traverse'? The efficient
544+ -- way to traverse strictly in IO or ST is to force results as
545+ -- they come in, which leads to different semantics. In particular,
546+ -- we need to ensure that
547+ --
548+ -- traverse' (\x -> print x *> pure undefined) xs
549+ --
550+ -- will actually print all the values and then return undefined.
551+ -- We could add a strict mapMWithIndex, operating in an arbitrary
552+ -- Monad, that supported such rules, but we don't have that right now.
540553{-# RULES
541554"traverse/ST" forall f. traverse f = traverseST f
542555"traverse/IO" forall f. traverse f = traverseIO f
543556 #-}
544-
545- -- Traversing in ST, we don't need to get fancy; we
546- -- can just do it directly.
547- traverseST' :: (a -> ST s b ) -> Array a -> ST s (Array b )
548- traverseST' f = \ ary0 ->
549- let
550- ! len = length ary0
551- go k ! mary
552- | k == len = return mary
553- | otherwise = do
554- x <- indexM ary0 k
555- ! y <- f x
556- write mary k y
557- go (k + 1 ) mary
558- in new_ len >>= (go 0 >=> unsafeFreeze)
559- {-# INLINE traverseST' #-}
560-
561- traverseIO' :: (a -> IO b ) -> Array a -> IO (Array b )
562- traverseIO' f = \ ary0 ->
563- let
564- ! len = length ary0
565- go k ! mary
566- | k == len = return mary
567- | otherwise = do
568- x <- stToIO $ indexM ary0 k
569- ! y <- f x
570- stToIO $ write mary k y
571- go (k + 1 ) mary
572- in stToIO (new_ len) >>= (go 0 >=> stToIO . unsafeFreeze)
573- {-# INLINE traverseIO' #-}
574-
575- {-# RULES
576- "traverse'/ST" forall f. traverse' f = traverseST' f
577- "traverse'/IO" forall f. traverse' f = traverseIO' f
578- #-}
0 commit comments