@@ -17,7 +17,7 @@ module Data.Primitive.Array (
17
17
Array (.. ), MutableArray (.. ),
18
18
19
19
newArray , readArray , writeArray , indexArray , indexArrayM ,
20
- freezeArray , thawArray , runArray ,
20
+ freezeArray , thawArray , runArray , runArrays , runArraysHetOf ,
21
21
unsafeFreezeArray , unsafeThawArray , sameMutableArray ,
22
22
copyArray , copyMutableArray ,
23
23
cloneArray , cloneMutableArray ,
@@ -341,7 +341,6 @@ emptyArray# _ = case emptyArray of Array ar -> ar
341
341
{-# NOINLINE emptyArray# #-}
342
342
#endif
343
343
344
-
345
344
die :: String -> String -> a
346
345
die fun problem = error $ " Data.Primitive.Array." ++ fun ++ " : " ++ problem
347
346
@@ -798,3 +797,57 @@ instance (Typeable s, Typeable a) => Data (MutableArray s a) where
798
797
toConstr _ = error " toConstr"
799
798
gunfold _ _ = error " gunfold"
800
799
dataTypeOf _ = mkNoRepType " Data.Primitive.Array.MutableArray"
800
+
801
+ -- | Create any number of arrays of the same type within an arbitrary
802
+ -- 'Traversable' context. This will often be useful with traversables
803
+ -- like @(c,)@, @'Either' e@, @'Compose' (c,) ('Either' e)@, and
804
+ -- @'Compose' ('Either' e) (c,)@. For a more general version, see
805
+ -- 'runArraysHetOf'.
806
+ runArrays
807
+ :: Traversable t
808
+ => (forall s . ST s (t (MutableArray s a )))
809
+ -> t (Array a )
810
+ runArrays m = runST $ m >>= traverse unsafeFreezeArray
811
+
812
+ -- | Create arbitrarily many arrays that may have different types.
813
+ -- For a simpler but less general version, see 'runArrays'.
814
+ --
815
+ -- === __Examples__
816
+ --
817
+ -- ==== @'runArrays'@
818
+ --
819
+ -- @
820
+ -- newtype Ha t a v = Ha {unHa :: t (v a)}
821
+ -- runArrays m = unHa $ runArraysHetOf (\f (Ha t) -> Ha <$> traverse f t) (Ha <$> m)
822
+ -- @
823
+ --
824
+ -- ==== @unzipArray@
825
+ --
826
+ -- @
827
+ -- unzipArray :: Array (a, b) -> (Array a, Array b)
828
+ -- unzipArray ar =
829
+ -- unPair $ runArraysHetOf traversePair $ do
830
+ -- xs <- newArray sz undefined
831
+ -- ys <- newArray sz undefined
832
+ -- let go k
833
+ -- | k == sz = pure (Pair (xs, ys))
834
+ -- | otherwise = do
835
+ -- (x,y) <- indexArrayM ar k
836
+ -- writeArray xs k x
837
+ -- writeArray ys k y
838
+ -- go (k + 1)
839
+ -- go 0
840
+ -- where sz = sizeofArray ar
841
+ --
842
+ -- data Pair ab v where
843
+ -- Pair :: {unPair :: (v a, v b)} -> Pair (a,b) v
844
+ --
845
+ -- traversePair :: Applicative h => (forall x. f x -> h (g x)) -> Pair ab f -> h (Pair ab g)
846
+ -- traversePair f (Pair (xs, ys)) = liftA2 (\x y -> Pair (x,y)) (f xs) (f ys)
847
+ -- @
848
+ runArraysHetOf
849
+ :: (forall h f g .
850
+ (Applicative h => (forall x . f x -> h (g x )) -> t f -> h (u g ))) -- ^ A rank-2 traversal
851
+ -> (forall s . ST s (t (MutableArray s ))) -- ^ An 'ST' action producing a rank-2 container of 'MutableArray's.
852
+ -> u Array
853
+ runArraysHetOf f m = runST $ m >>= f unsafeFreezeArray
0 commit comments