@@ -17,7 +17,7 @@ module Data.Primitive.Array (
1717 Array (.. ), MutableArray (.. ),
1818
1919 newArray , readArray , writeArray , indexArray , indexArrayM ,
20- freezeArray , thawArray , runArray ,
20+ freezeArray , thawArray , runArray , runArrays , runArraysHetOf ,
2121 unsafeFreezeArray , unsafeThawArray , sameMutableArray ,
2222 copyArray , copyMutableArray ,
2323 cloneArray , cloneMutableArray ,
@@ -341,7 +341,6 @@ emptyArray# _ = case emptyArray of Array ar -> ar
341341{-# NOINLINE emptyArray# #-}
342342#endif
343343
344-
345344die :: String -> String -> a
346345die fun problem = error $ " Data.Primitive.Array." ++ fun ++ " : " ++ problem
347346
@@ -798,3 +797,58 @@ instance (Typeable s, Typeable a) => Data (MutableArray s a) where
798797 toConstr _ = error " toConstr"
799798 gunfold _ _ = error " gunfold"
800799 dataTypeOf _ = mkNoRepType " Data.Primitive.Array.MutableArray"
800+
801+ -- | Create zero or more arrays of the same type within an arbitrary
802+ -- 'Traversable' context. For a more general version, see
803+ -- 'runArraysHetOf'.
804+ runArrays
805+ :: Traversable t
806+ => (forall s . ST s (t (MutableArray s a )))
807+ -> t (Array a )
808+ runArrays m = runST $ m >>= traverse unsafeFreezeArray
809+
810+ -- | Create zero or more arrays that may have different types within
811+ -- a rank-2-traversable context, such as a flipped `vinyl` record.
812+ -- See [rtraverse](https://hackage.haskell.org/package/vinyl-0.8.1.1/docs/Data-Vinyl-Core.html#v:rtraverse)
813+ -- in that package. For a simpler but less general version, see
814+ -- 'runArrays'.
815+ --
816+ -- === __Examples__
817+ --
818+ -- ==== @'runArrays'@
819+ --
820+ -- @
821+ -- newtype Ha t a v = Ha {unHa :: t (v a)}
822+ -- runArrays m = unHa $ runArraysHetOf (\f (Ha t) -> Ha <$> traverse f t) (Ha <$> m)
823+ -- @
824+ --
825+ -- ==== @unzipArray@
826+ --
827+ -- @
828+ -- unzipArray :: Array (a, b) -> (Array a, Array b)
829+ -- unzipArray ar =
830+ -- unPair $ runArraysHetOf traversePair $ do
831+ -- xs <- newArray sz undefined
832+ -- ys <- newArray sz undefined
833+ -- let go k
834+ -- | k == sz = pure (Pair (xs, ys))
835+ -- | otherwise = do
836+ -- (x,y) <- indexArrayM ar k
837+ -- writeArray xs k x
838+ -- writeArray ys k y
839+ -- go (k + 1)
840+ -- go 0
841+ -- where sz = sizeofArray ar
842+ --
843+ -- data Pair ab v where
844+ -- Pair :: {unPair :: (v a, v b)} -> Pair (a,b) v
845+ --
846+ -- traversePair :: Applicative h => (forall x. f x -> h (g x)) -> Pair ab f -> h (Pair ab g)
847+ -- traversePair f (Pair (xs, ys)) = liftA2 (\x y -> Pair (x,y)) (f xs) (f ys)
848+ -- @
849+ runArraysHetOf
850+ :: (forall h f g .
851+ (Applicative h => (forall x . f x -> h (g x )) -> t f -> h (u g ))) -- ^ A rank-2 traversal
852+ -> (forall s . ST s (t (MutableArray s ))) -- ^ An 'ST' action producing a rank-2 container of 'MutableArray's.
853+ -> u Array
854+ runArraysHetOf f m = runST $ m >>= f unsafeFreezeArray
0 commit comments