Add a createT analogue for arrays
David Feuer
david.feuer at gmail.com
Fri Mar 23 04:19:04 UTC 2018
I still think this is a good idea, and probably the furthest it should
go in the array package proper, but something about it has been
bothering me: the fact that I can't produce multiple arrays of
different types. I realized it's actually possible to get that too,
using something similar to the rtraverse function in vinyl.
class HTraversable (t :: (k -> Type) -> Type) where
htraverse :: Applicative h
=> (forall x. f x -> h (g x))
-> t f -> h (t g)
Vinyl records themselves are a bit backwards for this purpose, but one
could write
newtype FlipRec ts f = FlipRec {unFlipRec :: Rec f ts}
instance HTraversable (FlipRec ts) where
htraverse f (FlipRec xs) = FlipRec <$> rtraverse f xs
Anyway, HTraversable lets us write
runArraysHet :: HTraversable t
=> (forall s. ST s (t (MutableArray s)))
-> t Array
runArraysHet m = runST $ m >>= htraverse unsafeFreezeArray
which can produce arrays of multiple types in one go. We can add some
extra information/context to each array with a little more machinery:
-- The context will be expressed using Traversable' types
class Traversable' (t :: k -> Type -> Type) where
traverse' :: Applicative f
=> (a -> f b) -> t x a -> f (t x b)
default traverse' :: (Applicative f, Traversable (t x))
=> (a -> f b) -> t x a -> f (t x b)
traverse' = traverse
-- examples
instance Traversable' Either
instance Traversable' (,)
newtype S f g t = S {unS :: f t (g t)}
newtype Contextify (f :: k -> Type -> Type) (t :: (k -> Type) ->
Type) (g :: k -> Type) =
Contextify {unContextify :: t (S f g)}
instance (HTraversable t, Traversable' u)
=> HTraversable (Contextify (u :: k -> Type -> Type) (t :: (k ->
Type) -> Type)) where
htraverse f t = fmap Contextify $ htraverse (fmap S . traverse' f
. unS) (unContextify t)
and finally
runArraysContextHet
:: (HTraversable t, Traversable' u)
=> (forall s. ST s (t (S u (MutableArray s))))
-> t (S u Array)
runArraysContextHet m =
runST $ m >>= htraverse (fmap S . traverse' unsafeFreezeArray . unS)
Whew!
On Sun, Mar 11, 2018 at 1:29 AM, David Feuer <david.feuer at gmail.com> wrote:
> The vector package offers
>
> createT :: Traversable t
> => (forall s. ST s (t (MVector s a)))
> -> t (Vector a)
>
> This is a generalization of create, which is very similar to runSTArray in
> the array package. I suggest we add functions
>
> runSTArrays :: Traversable t
> => (forall s. ST s (t (STArray s i e)))
> -> t (Array i e)
>
> runSTUArrays :: Traversable t
> => (forall s. ST s (t (STUArray s i e)))
> -> t (UArray i e)
>
> Why do I think it's worth the trouble? While it's occasionally useful to
> create multiple arrays of the same type in one go, I think the Maybe and
> (a,) Traversable instances, and their compositions, are likely more
> important. I can use (a,) to record some extra information while building an
> array. I can use Maybe to give up and not produce an array. And the
> compositions let me do both in different ways.
More information about the Libraries
mailing list