Skip to content

Commit 44e4bc9

Browse files
committed
More changes
* Add notes. * Improve some of the types. * Drop `PolyKinds`. I added it because of unclear thinking, and I don't think any of this benefits meaningfully from having it.
1 parent e8685d6 commit 44e4bc9

File tree

2 files changed

+89
-24
lines changed

2 files changed

+89
-24
lines changed

Data/Primitive/Array.hs

Lines changed: 79 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -1,9 +1,6 @@
11
{-# LANGUAGE CPP, MagicHash, UnboxedTuples, DeriveDataTypeable, BangPatterns #-}
22
{-# LANGUAGE RankNTypes #-}
33
{-# LANGUAGE TypeFamilies #-}
4-
#if __GLASGOW_HASKELL__ >= 706
5-
{-# LANGUAGE PolyKinds #-}
6-
#endif
74

85
-- |
96
-- Module : Data.Primitive.Array
@@ -818,12 +815,61 @@ runArrays m = runST $ m >>= traverse unsafeFreezeArray
818815
-- constraint. To produce arrays of varying types, use 'runArraysHetOf'.
819816
runArraysOf
820817
:: (forall s1 s2.
821-
(MutableArray s1 a -> ST s2 (Array a)) -> t (MutableArray s1 a) -> ST s2 (u (Array a)))
822-
-> (forall s. ST s (t (MutableArray s a)))
823-
-> u (Array a)
818+
(MutableArray s1 a -> ST s2 (Array a)) -> t (mut s1 x) -> ST s2 u)
819+
-> (forall s. ST s (t (mut s x)))
820+
-> u
821+
-- See notes below
824822
runArraysOf trav m = runST $ m >>= trav unsafeFreezeArray
825823

826824
{-
825+
Why do I believe 'runArraysOf' is safe? The key safety property is
826+
that we must never modify an array after it is frozen. The first
827+
thing we do is run the given action, producing something of type
828+
829+
t (mut s x)
830+
831+
and passing it to trav. We need to make sure that trav just applies
832+
its function argument (unsafeFreezeArray) to any MutableArrays that
833+
may contain/produce, and doesn't modify them in any other ways. Consider
834+
the type of trav:
835+
836+
trav :: forall s1 s2.
837+
(MutableArray s1 a -> ST s2 (Array a))
838+
-> t (mut s1 x) -> ST s2 u
839+
840+
trav operates in the state thread labeled s2. We don't let it know that
841+
the mutable arrays it handles live in the same thread! They're off in
842+
s1, a whole different universe. So trav can only apply the freeze it's
843+
passed, or perform whatever actions may ride in on t (mut s x). Can
844+
the latter happen? Imagine something like
845+
846+
data T :: Type -> Type where
847+
T :: ST s (MutableArray s x) -> T (MutableArray s x)
848+
849+
Can trav pull this open and run the action? No! The state thread in
850+
T matches the array in T, but it doesn't match the state thread trav
851+
lives in, so trav can't do anything whatsoever with it.
852+
853+
-----
854+
855+
It's annoying that @t@ takes a @mut s1 x@ argument instead
856+
of just an @s1@ argument, but this allows 'runArraysOf' to be used directly
857+
with 'traverse'. The cleaner version can be implemented efficiently on
858+
top in the following rather disgusting manner:
859+
860+
runArraysOf'
861+
:: (forall s1 s2.
862+
(MutableArray s1 a -> ST s2 (Array a)) -> t s1 -> ST s2 u)
863+
-> (forall s. ST s (t s))
864+
-> u
865+
runArraysOf' trav m = runArraysOf ((. unBar) #. trav) (coerce m)
866+
867+
newtype Bar t x = Bar {unBar :: t (Yuck x)}
868+
type family Yuck x where
869+
Yuck (_ s _) = s
870+
871+
-------
872+
827873
I initially thought we'd need a function like
828874
829875
runArraysOfThen
@@ -886,21 +932,42 @@ clearly not necessary.
886932
-- @
887933
-- runArraysHetOfThen
888934
-- :: (forall s1 s2.
889-
-- ((forall x. MutableArray s1 x -> Compose (ST s2) q (r x)) -> t (MutableArray s1) -> Compose (ST s2) q (u r)))
935+
-- ( (forall x. MutableArray s1 x -> Compose (ST s2) q (r x))
936+
-- -> t (mut s1) -> Compose (ST s2) q u))
890937
-- -- ^ A rank-2 traversal
891938
-- -> (forall x. Array x -> q (r x))
892939
-- -- ^ A function to traverse over the container of 'Array's
893-
-- -> (forall s. ST s (t (MutableArray s)))
940+
-- -> (forall s. ST s (t (mut s)))
894941
-- -- ^ An 'ST' action producing a rank-2 container of 'MutableArray's.
895-
-- -> q (u r)
942+
-- -> q u
896943
-- runArraysHetOfThen trav post m = getConst $
897944
-- runArraysHetOf (\f -> coerce . getCompose . trav (Compose . fmap post . f)) m
898945
-- @
899946
runArraysHetOf
900947
:: (forall s1 s2.
901-
((forall x. MutableArray s1 x -> ST s2 (Array x)) -> t (MutableArray s1) -> ST s2 (u Array)))
948+
((forall x. MutableArray s1 x -> ST s2 (Array x)) -> t (mut s1) -> ST s2 u))
902949
-- ^ A rank-2 traversal
903-
-> (forall s. ST s (t (MutableArray s)))
950+
-> (forall s. ST s (t (mut s)))
904951
-- ^ An 'ST' action producing a rank-2 container of 'MutableArray's.
905-
-> u Array
952+
-> u
906953
runArraysHetOf trav m = runST $ m >>= trav unsafeFreezeArray
954+
955+
{-
956+
This alternative version is arguably prettier, but it's not compatible
957+
with the traversal functions from rank2types or compdata for the same reason
958+
that the prettier version of 'runArraysOf' isn't compatible with 'traverse'.
959+
It can be implemented with a bit of ugliness.
960+
961+
runArraysHetOf'
962+
:: (forall s1 s2.
963+
((forall x. MutableArray s1 x -> ST s2 (Array x)) -> t s1 -> ST s2 u))
964+
-- ^ A rank-2 traversal
965+
-> (forall s. ST s (t s))
966+
-- ^ An 'ST' action producing a rank-2 container of 'MutableArray's.
967+
-> u
968+
runArraysHetOf' trav m = runArraysHetOf (\f -> trav f . unBaz) (coerce m)
969+
970+
type family Gross ms where
971+
Gross (_ s) = s
972+
newtype Baz t ms = Baz {unBaz :: t (Gross ms)}
973+
-}

Data/Primitive/SmallArray.hs

Lines changed: 10 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -7,9 +7,6 @@
77
{-# LANGUAGE DeriveDataTypeable #-}
88
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
99
{-# LANGUAGE BangPatterns #-}
10-
#if __GLASGOW_HASKELL__ >= 706
11-
{-# LANGUAGE PolyKinds #-}
12-
#endif
1310

1411
-- |
1512
-- Module : Data.Primitive.SmallArray
@@ -967,9 +964,9 @@ runSmallArrays m = runST $ m >>= traverse unsafeFreezeSmallArray
967964
runSmallArraysOf
968965
:: (forall s1 s2.
969966
(SmallMutableArray s1 a -> ST s2 (SmallArray a))
970-
-> t (SmallMutableArray s1 a) -> ST s2 (u (SmallArray a)))
971-
-> (forall s. ST s (t (SmallMutableArray s a)))
972-
-> u (SmallArray a)
967+
-> t (mut s1 x) -> ST s2 u)
968+
-> (forall s. ST s (t (mut s x)))
969+
-> u
973970
runSmallArraysOf trav m = runST $ m >>= trav unsafeFreezeSmallArray
974971

975972
-- | Create arbitrarily many arrays that may have different types. For
@@ -1016,22 +1013,23 @@ runSmallArraysOf trav m = runST $ m >>= trav unsafeFreezeSmallArray
10161013
-- @
10171014
-- runSmallArraysHetOfThen
10181015
-- :: (forall s1 s2.
1019-
-- ((forall x. MutableArray s1 x -> Compose (ST s2) q (r x)) -> t (MutableArray s1) -> Compose (ST s2) q (u r)))
1016+
-- ( (forall x. SmallMutableArray s1 x -> Compose (ST s2) q (r x))
1017+
-- -> t (mut s1) -> Compose (ST s2) q u))
10201018
-- -- ^ A rank-2 traversal
10211019
-- -> (forall x. SmallArray x -> q (r x))
10221020
-- -- ^ A function to traverse over a container of 'SmallArray's
1023-
-- -> (forall s. ST s (t (SmallMutableArray s)))
1021+
-- -> (forall s. ST s (t (mut s)))
10241022
-- -- ^ An 'ST' action producing a rank-2 container of 'SmallMutableArray's.
1025-
-- -> q (u r)
1023+
-- -> q u
10261024
-- runSmallArraysHetOfThen trav post m = getConst $
10271025
-- runSmallArraysHetOf (\f -> coerce . getCompose . trav (Compose . fmap post . f)) m
10281026
-- @
10291027
runSmallArraysHetOf
10301028
:: (forall s1 s2.
10311029
((forall x. SmallMutableArray s1 x -> ST s2 (SmallArray x))
1032-
-> t (SmallMutableArray s1) -> ST s2 (u SmallArray)))
1030+
-> t (mut s1) -> ST s2 u))
10331031
-- ^ A rank-2 traversal
1034-
-> (forall s. ST s (t (SmallMutableArray s)))
1032+
-> (forall s. ST s (t (mut s)))
10351033
-- ^ An 'ST' action producing a rank-2 container of 'MutableArray's.
1036-
-> u SmallArray
1034+
-> u
10371035
runSmallArraysHetOf f m = runST $ m >>= f unsafeFreezeSmallArray

0 commit comments

Comments
 (0)