Skip to content

Commit 0244214

Browse files
committed
Use NonEmptyArray when grouping
1 parent a5a1ed9 commit 0244214

File tree

5 files changed

+120
-105
lines changed

5 files changed

+120
-105
lines changed

src/Data/Array.purs

Lines changed: 28 additions & 25 deletions
Original file line numberDiff line numberDiff line change
@@ -25,7 +25,7 @@
2525
-- | `Data.Foldable.or` tests whether an array of `Boolean` values contains
2626
-- | at least one `true` value.
2727
-- | * `Traversable`, which provides the PureScript version of a for-loop,
28-
-- | allowing you to iterate over an array and accumulate effects.
28+
-- | allowing you to STAI.iterate over an array and accumulate effects.
2929
-- |
3030
module Data.Array
3131
( fromFoldable
@@ -114,22 +114,24 @@ module Data.Array
114114
) where
115115

116116
import Prelude
117+
117118
import Control.Alt ((<|>))
118119
import Control.Alternative (class Alternative)
119120
import Control.Lazy (class Lazy, defer)
120121
import Control.Monad.Rec.Class (class MonadRec, Step(..), tailRecM2)
121122
import Control.Monad.ST as ST
122-
import Data.Array.ST (unsafeFreeze, emptySTArray, pokeSTArray, pushSTArray, modifySTArray, withArray)
123-
import Data.Array.ST.Iterator (iterator, iterate, pushWhile)
123+
import Data.Array.ST as STA
124+
import Data.Array.ST.Iterator as STAI
125+
import Data.Array.NonEmpty.Internal (NonEmptyArray)
124126
import Data.Foldable (class Foldable, foldl, foldr, traverse_)
125127
import Data.Foldable (foldl, foldr, foldMap, fold, intercalate, elem, notElem, find, findMap, any, all) as Exports
126128
import Data.Maybe (Maybe(..), maybe, isJust, fromJust)
127-
import Data.NonEmpty (NonEmpty, (:|))
128129
import Data.Traversable (scanl, scanr) as Exports
129130
import Data.Traversable (sequence, traverse)
130131
import Data.Tuple (Tuple(..), uncurry)
131132
import Data.Unfoldable (class Unfoldable, unfoldr)
132133
import Partial.Unsafe (unsafePartial)
134+
import Unsafe.Coerce (unsafeCoerce)
133135

134136
-- | Convert an `Array` into an `Unfoldable` structure.
135137
toUnfoldable :: forall f. Unfoldable f => Array ~> f
@@ -656,7 +658,7 @@ mapWithIndex f xs =
656658
-- |
657659
updateAtIndices :: forall t a. Foldable t => t (Tuple Int a) -> Array a -> Array a
658660
updateAtIndices us xs =
659-
ST.run (withArray (\res -> traverse_ (uncurry $ pokeSTArray res) us) xs)
661+
ST.run (STA.withArray (\res -> traverse_ (uncurry $ STA.pokeSTArray res) us) xs)
660662

661663
-- | Apply a function to the element at the specified indices,
662664
-- | creating a new array. Out-of-bounds indices will have no effect.
@@ -669,7 +671,7 @@ updateAtIndices us xs =
669671
-- |
670672
modifyAtIndices :: forall t a. Foldable t => t Int -> (a -> a) -> Array a -> Array a
671673
modifyAtIndices is f xs =
672-
ST.run (withArray (\res -> traverse_ (\i -> modifySTArray res i f) is) xs)
674+
ST.run (STA.withArray (\res -> traverse_ (\i -> STA.modifySTArray res i f) is) xs)
673675

674676
--------------------------------------------------------------------------------
675677
-- Sorting ---------------------------------------------------------------------
@@ -836,15 +838,15 @@ span p arr =
836838
-- | ```purescript
837839
-- | group [1,1,2,2,1] == [NonEmpty 1 [1], NonEmpty 2 [2], NonEmpty 1 []]
838840
-- | ```
839-
group :: forall a. Eq a => Array a -> Array (NonEmpty Array a)
841+
group :: forall a. Eq a => Array a -> Array (NonEmptyArray a)
840842
group xs = groupBy eq xs
841843

842844
-- | Sort and then group the elements of an array into arrays.
843845
-- |
844846
-- | ```purescript
845847
-- | group' [1,1,2,2,1] == [NonEmpty 1 [1,1],NonEmpty 2 [2]]
846848
-- | ```
847-
group' :: forall a. Ord a => Array a -> Array (NonEmpty Array a)
849+
group' :: forall a. Ord a => Array a -> Array (NonEmptyArray a)
848850
group' = group <<< sort
849851

850852
-- | Group equal, consecutive elements of an array into arrays, using the
@@ -855,17 +857,18 @@ group' = group <<< sort
855857
-- | = [NonEmpty 1 [3], NonEmpty 2 [] , NonEmpty 4 [], NonEmpty 3 [3]]
856858
-- | ```
857859
-- |
858-
groupBy :: forall a. (a -> a -> Boolean) -> Array a -> Array (NonEmpty Array a)
860+
groupBy :: forall a. (a -> a -> Boolean) -> Array a -> Array (NonEmptyArray a)
859861
groupBy op xs =
860862
ST.run do
861-
result <- emptySTArray
862-
iter <- iterator (xs !! _)
863-
iterate iter \x -> void do
864-
sub <- emptySTArray
865-
pushWhile (op x) iter sub
866-
sub_ <- unsafeFreeze sub
867-
pushSTArray result (x :| sub_)
868-
unsafeFreeze result
863+
result <- STA.emptySTArray
864+
iter <- STAI.iterator (xs !! _)
865+
STAI.iterate iter \x -> void do
866+
sub <- STA.emptySTArray
867+
STAI.pushWhile (op x) iter sub
868+
_ <- STA.pushSTArray sub x
869+
grp <- STA.unsafeFreeze sub
870+
STA.pushSTArray result ((unsafeCoerce :: Array ~> NonEmptyArray) grp)
871+
STA.unsafeFreeze result
869872

870873
-- | Remove the duplicates from an array, creating a new array.
871874
-- |
@@ -1032,14 +1035,14 @@ zip = zipWith Tuple
10321035
unzip :: forall a b. Array (Tuple a b) -> Tuple (Array a) (Array b)
10331036
unzip xs =
10341037
ST.run do
1035-
fsts <- emptySTArray
1036-
snds <- emptySTArray
1037-
iter <- iterator (xs !! _)
1038-
iterate iter \(Tuple fst snd) -> do
1039-
void $ pushSTArray fsts fst
1040-
void $ pushSTArray snds snd
1041-
fsts' <- unsafeFreeze fsts
1042-
snds' <- unsafeFreeze snds
1038+
fsts <- STA.emptySTArray
1039+
snds <- STA.emptySTArray
1040+
iter <- STAI.iterator (xs !! _)
1041+
STAI.iterate iter \(Tuple fst snd) -> do
1042+
void $ STA.pushSTArray fsts fst
1043+
void $ STA.pushSTArray snds snd
1044+
fsts' <- STA.unsafeFreeze fsts
1045+
snds' <- STA.unsafeFreeze snds
10431046
pure $ Tuple fsts' snds'
10441047

10451048
-- | Perform a fold using a monadic step function.

src/Data/Array/NonEmpty.purs

Lines changed: 23 additions & 75 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,5 @@
11
module Data.Array.NonEmpty
2-
( NonEmptyArray
2+
( module Data.Array.NonEmpty.Internal
33
, fromArray
44
, fromNonEmpty
55
, toArray
@@ -93,71 +93,27 @@ module Data.Array.NonEmpty
9393

9494
import Prelude
9595

96-
import Control.Alt (class Alt)
9796
import Control.Alternative (class Alternative)
9897
import Control.Lazy (class Lazy)
9998
import Control.Monad.Rec.Class (class MonadRec)
10099
import Data.Array as A
100+
import Data.Array.NonEmpty.Internal (NonEmptyArray)
101101
import Data.Bifunctor (bimap)
102-
import Data.Eq (class Eq1)
103102
import Data.Foldable (class Foldable)
104-
import Data.FoldableWithIndex (class FoldableWithIndex)
105-
import Data.FunctorWithIndex (class FunctorWithIndex)
106103
import Data.Maybe (Maybe(..), fromJust)
107104
import Data.NonEmpty (NonEmpty, (:|))
108-
import Data.Ord (class Ord1)
109-
import Data.Semigroup.Foldable (class Foldable1, foldMap1Default)
110-
import Data.Semigroup.Traversable (class Traversable1, sequence1Default)
111-
import Data.Traversable (class Traversable)
112-
import Data.TraversableWithIndex (class TraversableWithIndex)
105+
import Data.Semigroup.Foldable (class Foldable1)
113106
import Data.Tuple (Tuple)
114107
import Data.Unfoldable (class Unfoldable)
115108
import Partial.Unsafe (unsafePartial)
116-
117-
newtype NonEmptyArray a = NonEmptyArray (Array a)
118-
119-
instance showNonEmptyArray :: Show a => Show (NonEmptyArray a) where
120-
show (NonEmptyArray xs) = "(NonEmptyArray " <> show xs <> ")"
121-
122-
derive newtype instance eqNonEmptyArray :: Eq a => Eq (NonEmptyArray a)
123-
derive newtype instance eq1NonEmptyArray :: Eq1 NonEmptyArray
124-
125-
derive newtype instance ordNonEmptyArray :: Ord a => Ord (NonEmptyArray a)
126-
derive newtype instance ord1NonEmptyArray :: Ord1 NonEmptyArray
127-
128-
derive newtype instance functorNonEmptyArray :: Functor NonEmptyArray
129-
derive newtype instance functorWithIndexNonEmptyArray :: FunctorWithIndex Int NonEmptyArray
130-
131-
derive newtype instance foldableNonEmptyArray :: Foldable NonEmptyArray
132-
derive newtype instance foldableWithIndexNonEmptyArray :: FoldableWithIndex Int NonEmptyArray
133-
134-
instance foldable1NonEmptyArray :: Foldable1 NonEmptyArray where
135-
foldMap1 = foldMap1Default
136-
fold1 = fold1Impl (<>)
137-
138-
derive newtype instance traversableNonEmptyArray :: Traversable NonEmptyArray
139-
derive newtype instance traversableWithIndexNonEmptyArray :: TraversableWithIndex Int NonEmptyArray
140-
141-
instance traversable1NonEmptyArray :: Traversable1 NonEmptyArray where
142-
traverse1 = traverse1Impl apply map
143-
sequence1 = sequence1Default
144-
145-
derive newtype instance applyNonEmptyArray :: Apply NonEmptyArray
146-
147-
derive newtype instance applicativeNonEmptyArray :: Applicative NonEmptyArray
148-
149-
derive newtype instance bindNonEmptyArray :: Bind NonEmptyArray
150-
151-
derive newtype instance monadNonEmptyArray :: Monad NonEmptyArray
152-
153-
derive newtype instance altNonEmptyArray :: Alt NonEmptyArray
109+
import Unsafe.Coerce (unsafeCoerce)
154110

155111
-- | Internal - adapt an Array transform to NonEmptyArray
156112
--
157113
-- Note that this is unsafe: if the transform returns an empty array, this can
158114
-- explode at runtime.
159115
unsafeAdapt :: forall a b. (Array a -> Array b) -> NonEmptyArray a -> NonEmptyArray b
160-
unsafeAdapt f = NonEmptyArray <<< adaptAny f
116+
unsafeAdapt f = unsafeFromArray <<< adaptAny f
161117

162118
-- | Internal - adapt an Array transform to NonEmptyArray,
163119
-- with polymorphic result.
@@ -173,18 +129,21 @@ adaptMaybe f = unsafePartial $ fromJust <<< f <<< toArray
173129

174130
fromArray :: forall a. Array a -> Maybe (NonEmptyArray a)
175131
fromArray xs
176-
| A.length xs > 0 = Just (NonEmptyArray xs)
177-
| otherwise = Nothing
132+
| A.length xs > 0 = Just (unsafeFromArray xs)
133+
| otherwise = Nothing
178134

179135
-- | INTERNAL
180136
unsafeFromArray :: forall a. Array a -> NonEmptyArray a
181-
unsafeFromArray = NonEmptyArray
137+
unsafeFromArray = unsafeCoerce
138+
139+
unsafeFromArrayF :: forall f a. f (Array a) -> f (NonEmptyArray a)
140+
unsafeFromArrayF = unsafeCoerce
182141

183142
fromNonEmpty :: forall a. NonEmpty Array a -> NonEmptyArray a
184143
fromNonEmpty (x :| xs) = cons' x xs
185144

186145
toArray :: forall a. NonEmptyArray a -> Array a
187-
toArray (NonEmptyArray xs) = xs
146+
toArray = unsafeCoerce
188147

189148
toNonEmpty :: forall a. NonEmptyArray a -> NonEmpty Array a
190149
toNonEmpty = uncons >>> \{head: x, tail: xs} -> x :| xs
@@ -199,7 +158,7 @@ toUnfoldable :: forall f a. Unfoldable f => NonEmptyArray a -> f a
199158
toUnfoldable = adaptAny A.toUnfoldable
200159

201160
singleton :: forall a. a -> NonEmptyArray a
202-
singleton = NonEmptyArray <<< A.singleton
161+
singleton = unsafeFromArray <<< A.singleton
203162

204163
range :: Int -> Int -> NonEmptyArray Int
205164
range x y = unsafeFromArray $ A.range x y
@@ -208,14 +167,14 @@ infix 8 range as ..
208167

209168
-- | Replicate an item at least once
210169
replicate :: forall a. Int -> a -> NonEmptyArray a
211-
replicate i x = NonEmptyArray $ A.replicate (max 1 i) x
170+
replicate i x = unsafeFromArray $ A.replicate (max 1 i) x
212171

213172
some
214173
:: forall f a
215174
. Alternative f
216175
=> Lazy (f (Array a))
217176
=> f a -> f (NonEmptyArray a)
218-
some = map NonEmptyArray <<< A.some
177+
some = unsafeFromArrayF <<< A.some
219178

220179
length :: forall a. NonEmptyArray a -> Int
221180
length = adaptAny A.length
@@ -279,19 +238,19 @@ findLastIndex :: forall a. (a -> Boolean) -> NonEmptyArray a -> Maybe Int
279238
findLastIndex x = adaptAny $ A.findLastIndex x
280239

281240
insertAt :: forall a. Int -> a -> NonEmptyArray a -> Maybe (NonEmptyArray a)
282-
insertAt i x = map NonEmptyArray <<< A.insertAt i x <<< toArray
241+
insertAt i x = unsafeFromArrayF <<< A.insertAt i x <<< toArray
283242

284243
deleteAt :: forall a. Int -> NonEmptyArray a -> Maybe (Array a)
285244
deleteAt i = adaptAny $ A.deleteAt i
286245

287246
updateAt :: forall a. Int -> a -> NonEmptyArray a -> Maybe (NonEmptyArray a)
288-
updateAt i x = map NonEmptyArray <<< A.updateAt i x <<< toArray
247+
updateAt i x = unsafeFromArrayF <<< A.updateAt i x <<< toArray
289248

290249
updateAtIndices :: forall t a. Foldable t => t (Tuple Int a) -> NonEmptyArray a -> NonEmptyArray a
291250
updateAtIndices pairs = unsafeAdapt $ A.updateAtIndices pairs
292251

293252
modifyAt :: forall a. Int -> (a -> a) -> NonEmptyArray a -> Maybe (NonEmptyArray a)
294-
modifyAt i f = map NonEmptyArray <<< A.modifyAt i f <<< toArray
253+
modifyAt i f = unsafeFromArrayF <<< A.modifyAt i f <<< toArray
295254

296255
modifyAtIndices :: forall t a. Foldable t => t Int -> (a -> a) -> NonEmptyArray a -> NonEmptyArray a
297256
modifyAtIndices is f = unsafeAdapt $ A.modifyAtIndices is f
@@ -303,7 +262,7 @@ reverse :: forall a. NonEmptyArray a -> NonEmptyArray a
303262
reverse = unsafeAdapt A.reverse
304263

305264
concat :: forall a. NonEmptyArray (NonEmptyArray a) -> NonEmptyArray a
306-
concat = NonEmptyArray <<< A.concat <<< toArray <<< map toArray
265+
concat = unsafeFromArray <<< A.concat <<< toArray <<< map toArray
307266

308267
concatMap :: forall a b. (a -> NonEmptyArray b) -> NonEmptyArray a -> NonEmptyArray b
309268
concatMap = flip bind
@@ -439,7 +398,7 @@ zipWith
439398
-> NonEmptyArray a
440399
-> NonEmptyArray b
441400
-> NonEmptyArray c
442-
zipWith f xs ys = NonEmptyArray $ A.zipWith f (toArray xs) (toArray ys)
401+
zipWith f xs ys = unsafeFromArray $ A.zipWith f (toArray xs) (toArray ys)
443402

444403

445404
zipWithA
@@ -449,13 +408,13 @@ zipWithA
449408
-> NonEmptyArray a
450409
-> NonEmptyArray b
451410
-> m (NonEmptyArray c)
452-
zipWithA f xs ys = NonEmptyArray <$> A.zipWithA f (toArray xs) (toArray ys)
411+
zipWithA f xs ys = unsafeFromArrayF $ A.zipWithA f (toArray xs) (toArray ys)
453412

454413
zip :: forall a b. NonEmptyArray a -> NonEmptyArray b -> NonEmptyArray (Tuple a b)
455-
zip xs ys = NonEmptyArray $ toArray xs `A.zip` toArray ys
414+
zip xs ys = unsafeFromArray $ toArray xs `A.zip` toArray ys
456415

457416
unzip :: forall a b. NonEmptyArray (Tuple a b) -> Tuple (NonEmptyArray a) (NonEmptyArray b)
458-
unzip = bimap NonEmptyArray NonEmptyArray <<< A.unzip <<< toArray
417+
unzip = bimap unsafeFromArray unsafeFromArray <<< A.unzip <<< toArray
459418

460419
foldM :: forall m a b. Monad m => (a -> b -> m a) -> a -> NonEmptyArray b -> m a
461420
foldM f acc = adaptAny $ A.foldM f acc
@@ -465,14 +424,3 @@ foldRecM f acc = adaptAny $ A.foldRecM f acc
465424

466425
unsafeIndex :: forall a. Partial => NonEmptyArray a -> Int -> a
467426
unsafeIndex = adaptAny A.unsafeIndex
468-
469-
-- we use FFI here to avoid the unnecessary copy created by `tail`
470-
foreign import fold1Impl :: forall a. (a -> a -> a) -> NonEmptyArray a -> a
471-
472-
foreign import traverse1Impl
473-
:: forall m a b
474-
. (forall a' b'. (m (a' -> b') -> m a' -> m b'))
475-
-> (forall a' b'. (a' -> b') -> m a' -> m b')
476-
-> (a -> m b)
477-
-> NonEmptyArray a
478-
-> m (NonEmptyArray b)
File renamed without changes.
Lines changed: 63 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,63 @@
1+
module Data.Array.NonEmpty.Internal (NonEmptyArray) where
2+
3+
import Prelude
4+
5+
import Control.Alt (class Alt)
6+
import Data.Eq (class Eq1)
7+
import Data.Foldable (class Foldable)
8+
import Data.FoldableWithIndex (class FoldableWithIndex)
9+
import Data.FunctorWithIndex (class FunctorWithIndex)
10+
import Data.Ord (class Ord1)
11+
import Data.Semigroup.Foldable (class Foldable1, foldMap1Default)
12+
import Data.Semigroup.Traversable (class Traversable1, sequence1Default)
13+
import Data.Traversable (class Traversable)
14+
import Data.TraversableWithIndex (class TraversableWithIndex)
15+
16+
newtype NonEmptyArray a = NonEmptyArray (Array a)
17+
18+
instance showNonEmptyArray :: Show a => Show (NonEmptyArray a) where
19+
show (NonEmptyArray xs) = "(NonEmptyArray " <> show xs <> ")"
20+
21+
derive newtype instance eqNonEmptyArray :: Eq a => Eq (NonEmptyArray a)
22+
derive newtype instance eq1NonEmptyArray :: Eq1 NonEmptyArray
23+
24+
derive newtype instance ordNonEmptyArray :: Ord a => Ord (NonEmptyArray a)
25+
derive newtype instance ord1NonEmptyArray :: Ord1 NonEmptyArray
26+
27+
derive newtype instance functorNonEmptyArray :: Functor NonEmptyArray
28+
derive newtype instance functorWithIndexNonEmptyArray :: FunctorWithIndex Int NonEmptyArray
29+
30+
derive newtype instance foldableNonEmptyArray :: Foldable NonEmptyArray
31+
derive newtype instance foldableWithIndexNonEmptyArray :: FoldableWithIndex Int NonEmptyArray
32+
33+
instance foldable1NonEmptyArray :: Foldable1 NonEmptyArray where
34+
foldMap1 = foldMap1Default
35+
fold1 = fold1Impl (<>)
36+
37+
derive newtype instance traversableNonEmptyArray :: Traversable NonEmptyArray
38+
derive newtype instance traversableWithIndexNonEmptyArray :: TraversableWithIndex Int NonEmptyArray
39+
40+
instance traversable1NonEmptyArray :: Traversable1 NonEmptyArray where
41+
traverse1 = traverse1Impl apply map
42+
sequence1 = sequence1Default
43+
44+
derive newtype instance applyNonEmptyArray :: Apply NonEmptyArray
45+
46+
derive newtype instance applicativeNonEmptyArray :: Applicative NonEmptyArray
47+
48+
derive newtype instance bindNonEmptyArray :: Bind NonEmptyArray
49+
50+
derive newtype instance monadNonEmptyArray :: Monad NonEmptyArray
51+
52+
derive newtype instance altNonEmptyArray :: Alt NonEmptyArray
53+
54+
-- we use FFI here to avoid the unnecessary copy created by `tail`
55+
foreign import fold1Impl :: forall a. (a -> a -> a) -> NonEmptyArray a -> a
56+
57+
foreign import traverse1Impl
58+
:: forall m a b
59+
. (forall a' b'. (m (a' -> b') -> m a' -> m b'))
60+
-> (forall a' b'. (a' -> b') -> m a' -> m b')
61+
-> (a -> m b)
62+
-> NonEmptyArray a
63+
-> m (NonEmptyArray b)

0 commit comments

Comments
 (0)