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