Generalize runSTArray and runSTUArray

The "runSTArray" and "runSTUArray" functions allow efficiently working with Arrays in the ST monad before turning them immutable; however, they don't allow any way to return supplemental or alternative information with the array. There are many times when I've wanted to get an (Array i e, w) or a Maybe (UArray i e), but I couldn't, and had to use the far-more-inefficient freezeArray and hope it inlined properly. What I want are functions that generalize the return types given: runSTArrayTrav :: Traversable t => (forall s. ST s (t (STArray s i e))) -> t (Array i e) runSTArrayTrav m = runST $ m >>= traverse unsafeFreezeSTArray runSTUArrayTrav :: Traversable t => (forall s. ST s (t (STUArray s i e))) -> t (UArray i e) runSTUArrayTrav m = runST $ m >>= traverse unsafeFreezeSTUArray And then an even more generalized version, which takes a sort of Lens-like iterator, and allows returning multiple arrays of different kinds, types, and indices: runSTArrayWith :: (forall f s. Applicative f => (forall i e. STArray s i e -> f (Array i e)) -> (forall i e. STUArray s i e -> f (UArray i e)) -> u s -> f v) -> (forall s. ST s (u s)) -> v runSTArrayWith tr m = runST $ m >>= tr unsafeFreezeSTArray unsafeFreezeSTUArray The advantage of the runSTArrayTrav/runSTUArrayTrav functions, if they're subsets of the runSTArrayWith function, is that it works with standard things like (,) and Either, and doesn't require wrapping it in a newtype so that the s is at the end. The names of the functions are up for debate, and I know there will be one, because naming things is one of the two hard problems in computer science, along with cache invalidation and off-by-one errors.

I did some work on this sort of thing for primitive, which didn't want it.
But maybe array does. If I don't link to it in the next day, please ping me.
On Thu, Aug 22, 2019, 1:25 AM Zemyla
The "runSTArray" and "runSTUArray" functions allow efficiently working with Arrays in the ST monad before turning them immutable; however, they don't allow any way to return supplemental or alternative information with the array. There are many times when I've wanted to get an (Array i e, w) or a Maybe (UArray i e), but I couldn't, and had to use the far-more-inefficient freezeArray and hope it inlined properly.
What I want are functions that generalize the return types given:
runSTArrayTrav :: Traversable t => (forall s. ST s (t (STArray s i e))) -> t (Array i e) runSTArrayTrav m = runST $ m >>= traverse unsafeFreezeSTArray
runSTUArrayTrav :: Traversable t => (forall s. ST s (t (STUArray s i e))) -> t (UArray i e) runSTUArrayTrav m = runST $ m >>= traverse unsafeFreezeSTUArray
And then an even more generalized version, which takes a sort of Lens-like iterator, and allows returning multiple arrays of different kinds, types, and indices:
runSTArrayWith :: (forall f s. Applicative f => (forall i e. STArray s i e -> f (Array i e)) -> (forall i e. STUArray s i e -> f (UArray i e)) -> u s -> f v) -> (forall s. ST s (u s)) -> v runSTArrayWith tr m = runST $ m >>= tr unsafeFreezeSTArray unsafeFreezeSTUArray
The advantage of the runSTArrayTrav/runSTUArrayTrav functions, if they're subsets of the runSTArrayWith function, is that it works with standard things like (,) and Either, and doesn't require wrapping it in a newtype so that the s is at the end.
The names of the functions are up for debate, and I know there will be one, because naming things is one of the two hard problems in computer science, along with cache invalidation and off-by-one errors. _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Here's a link to that old PR:
https://github.com/haskell/primitive/pull/109
On Thu, Aug 22, 2019, 1:27 AM David Feuer
I did some work on this sort of thing for primitive, which didn't want it. But maybe array does. If I don't link to it in the next day, please ping me.
On Thu, Aug 22, 2019, 1:25 AM Zemyla
wrote: The "runSTArray" and "runSTUArray" functions allow efficiently working with Arrays in the ST monad before turning them immutable; however, they don't allow any way to return supplemental or alternative information with the array. There are many times when I've wanted to get an (Array i e, w) or a Maybe (UArray i e), but I couldn't, and had to use the far-more-inefficient freezeArray and hope it inlined properly.
What I want are functions that generalize the return types given:
runSTArrayTrav :: Traversable t => (forall s. ST s (t (STArray s i e))) -> t (Array i e) runSTArrayTrav m = runST $ m >>= traverse unsafeFreezeSTArray
runSTUArrayTrav :: Traversable t => (forall s. ST s (t (STUArray s i e))) -> t (UArray i e) runSTUArrayTrav m = runST $ m >>= traverse unsafeFreezeSTUArray
And then an even more generalized version, which takes a sort of Lens-like iterator, and allows returning multiple arrays of different kinds, types, and indices:
runSTArrayWith :: (forall f s. Applicative f => (forall i e. STArray s i e -> f (Array i e)) -> (forall i e. STUArray s i e -> f (UArray i e)) -> u s -> f v) -> (forall s. ST s (u s)) -> v runSTArrayWith tr m = runST $ m >>= tr unsafeFreezeSTArray unsafeFreezeSTUArray
The advantage of the runSTArrayTrav/runSTUArrayTrav functions, if they're subsets of the runSTArrayWith function, is that it works with standard things like (,) and Either, and doesn't require wrapping it in a newtype so that the s is at the end.
The names of the functions are up for debate, and I know there will be one, because naming things is one of the two hard problems in computer science, along with cache invalidation and off-by-one errors. _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Well, the primary difference between putting it in primitive and putting it
in array is that the primitive library is unsafe, and knows it's unsafe,
and puts its functions like "unsafeFreezeArray" right out there in the
open. Thus, you can write functions like that which traverse over a return
value yourself. The primary reason that "runArray" is in the primitive
library is that it directly unboxes the pointer to the array, passes it out
of the ST monad, and then boxes it up again, so that pattern matches can
see it; you don't get that advantage when you are returning a Traversable
with Arrays inside it.
The array library is supposed to be safe, and Data.Array.ST.Safe exports
only a limited set of functions for working with STArrays. The
"unsafeFreezeSTArray" function isn't even in the public documentation; you
can only learn it exists by looking at the un-Haddocked "Data.Array.Base"
module, which definitely can't be imported by a Safe module.
Meanwhile, the runSTArrayTrav, runSTUArrayTrav, and runSTArrayWith
functions are actually safe, because even though you "know" that the "tr"
function is being run in the ST monad, there's no way to prove it to the
compiler, and thus no way to get your hands on the unsafeFreezeSTArray and
unsafeFreezeSTUArray functions and save them for later.
On the other hand, we might want to change the "Applicative" constraint to
a "Monad" constraint, so that you can turn (for instance) an STArray of
STUArrays into an Array of UArrays:
newtype STArrUArr i e s = STArrUArr (STArray s i (STUArray s i e))
freezeSTArrUArr :: (Ix i, Monad m) => (forall i' e'. STArray s i' e' -> m
(Array i' e')) -> (forall i' e'. STUArray s i' e' -> m (UArray i' e')) ->
STArrUArr i e s -> m (Array i (UArray i e))
freezeSTArrUArr frzA frzUA (STArrUArr ma) = frzA ma >>= traverse frzUA
runArrUArr :: Ix i => (forall s. ST s (STArray s i (STUArray s i e))) ->
Array i (UArray i e)
runArrUArr m = runSTArrayWith freezeSTArrUArr (fmap STArrUArr m)
On Wed, Aug 21, 2019, 14:10 David Feuer
Here's a link to that old PR:
https://github.com/haskell/primitive/pull/109
On Thu, Aug 22, 2019, 1:27 AM David Feuer
wrote: I did some work on this sort of thing for primitive, which didn't want it. But maybe array does. If I don't link to it in the next day, please ping me.
On Thu, Aug 22, 2019, 1:25 AM Zemyla
wrote: The "runSTArray" and "runSTUArray" functions allow efficiently working with Arrays in the ST monad before turning them immutable; however, they don't allow any way to return supplemental or alternative information with the array. There are many times when I've wanted to get an (Array i e, w) or a Maybe (UArray i e), but I couldn't, and had to use the far-more-inefficient freezeArray and hope it inlined properly.
What I want are functions that generalize the return types given:
runSTArrayTrav :: Traversable t => (forall s. ST s (t (STArray s i e))) -> t (Array i e) runSTArrayTrav m = runST $ m >>= traverse unsafeFreezeSTArray
runSTUArrayTrav :: Traversable t => (forall s. ST s (t (STUArray s i e))) -> t (UArray i e) runSTUArrayTrav m = runST $ m >>= traverse unsafeFreezeSTUArray
And then an even more generalized version, which takes a sort of Lens-like iterator, and allows returning multiple arrays of different kinds, types, and indices:
runSTArrayWith :: (forall f s. Applicative f => (forall i e. STArray s i e -> f (Array i e)) -> (forall i e. STUArray s i e -> f (UArray i e)) -> u s -> f v) -> (forall s. ST s (u s)) -> v runSTArrayWith tr m = runST $ m >>= tr unsafeFreezeSTArray unsafeFreezeSTUArray
The advantage of the runSTArrayTrav/runSTUArrayTrav functions, if they're subsets of the runSTArrayWith function, is that it works with standard things like (,) and Either, and doesn't require wrapping it in a newtype so that the s is at the end.
The names of the functions are up for debate, and I know there will be one, because naming things is one of the two hard problems in computer science, along with cache invalidation and off-by-one errors. _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

On Wed, 21 Aug 2019, Zemyla wrote:
The "runSTArray" and "runSTUArray" functions allow efficiently working with Arrays in the ST monad before turning them immutable
I think instead of some new functions we should have a Kleisli Arrow data type that hides unsafeFreeze for us. newtype Freezer s a b = -- private constructor and accessor Freezer {getFreezer :: a -> ST s b} instance Category Freezer where instance Arrow Freezer where quickFreeze :: Freezer s (STArray s i e) (Array i e) quickFreeze = Freezer unsafeFreeze runFrozen :: (forall s. Freezer s a b) -> (forall s. ST s a) -> b runFrozen freezer st = runST (getFreezer (freezer st)) For moving two arrays and an additional value out, you would do runFrozen ((quickFreeze *** quickFreeze) *** id) st

Even simpler, Freezer could just be a Monad denoting arbitrary "cleanup" actions, as long as they don't involve writes. -- | A computation that is guaranteed to run after all modifications are complete. newtype Freeze s a = {- private constructor and accessor -} Freeze { getFreeze :: ST s a } deriving (Functor, Applicative, Monad) freezeArray :: (Ix i, MArray a e (ST s), IArray b e) => a i e -> Freeze s (b i e) freezeArray arr = Freeze (unsafeFreeze arr) -- Reads are fine too, just not writes freezeRef :: STRef s a -> Freeze s a freezeRef ref = Freeze (readSTRef ref) runSTFreeze :: (forall s . ST s (Freeze s a)) -> a runSTFreeze act = runST (act >>= getFreeze) The proposed -Trav and -With functions can be implemented straightforwardly from that if desired: runSTArrayTrav m = runSTFreeze (m >>= traverse freezeArray) runSTUArrayTrav m = runSTFreeze (m >>= traverse freezeArray) runSTArrayWith tr m = runSTFreeze (m >>= tr freezeArray freezeArray) On Wed, Aug 21, 2019 at 11:46 PM Henning Thielemann < lemming@henning-thielemann.de> wrote:
On Wed, 21 Aug 2019, Zemyla wrote:
The "runSTArray" and "runSTUArray" functions allow efficiently working with Arrays in the ST monad before turning them immutable
I think instead of some new functions we should have a Kleisli Arrow data type that hides unsafeFreeze for us.
newtype Freezer s a b = -- private constructor and accessor Freezer {getFreezer :: a -> ST s b}
instance Category Freezer where instance Arrow Freezer where
quickFreeze :: Freezer s (STArray s i e) (Array i e) quickFreeze = Freezer unsafeFreeze
runFrozen :: (forall s. Freezer s a b) -> (forall s. ST s a) -> b runFrozen freezer st = runST (getFreezer (freezer st))
For moving two arrays and an additional value out, you would do
runFrozen ((quickFreeze *** quickFreeze) *** id) st _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

On Thu, 22 Aug 2019, Jonathan S wrote:
Even simpler, Freezer could just be a Monad denoting arbitrary "cleanup" actions, as long as they don't involve writes.
This was actually my first idea and I thought this would not be safe. But now I think you are right and this is both safe and more flexible.
participants (4)
-
David Feuer
-
Henning Thielemann
-
Jonathan S
-
Zemyla