@@ -5,6 +5,7 @@ module Data.List.NonEmpty
5
5
, fromList
6
6
, toList
7
7
, singleton
8
+ , length
8
9
, cons
9
10
, snoc
10
11
, head
@@ -13,11 +14,46 @@ module Data.List.NonEmpty
13
14
, init
14
15
, uncons
15
16
, unsnoc
16
- , length
17
+ , (!!), index
18
+ , elemIndex
19
+ , elemLastIndex
20
+ , findIndex
21
+ , findLastIndex
22
+ , insertAt
23
+ , updateAt
24
+ , modifyAt
25
+ , reverse
26
+ , concat
17
27
, concatMap
28
+ , filter
29
+ , filterM
30
+ , mapMaybe
31
+ , catMaybes
18
32
, appendFoldable
33
+ , mapWithIndex
19
34
, sort
20
35
, sortBy
36
+ , take
37
+ , takeWhile
38
+ , drop
39
+ , dropWhile
40
+ , span
41
+ , group
42
+ , group'
43
+ , groupBy
44
+ , partition
45
+ , nub
46
+ , nubBy
47
+ , union
48
+ , unionBy
49
+ , intersect
50
+ , intersectBy
51
+ , zipWith
52
+ , zipWithA
53
+ , zip
54
+ , unzip
55
+ , foldM
56
+ , module Exports
21
57
) where
22
58
23
59
import Prelude
@@ -26,12 +62,50 @@ import Data.Foldable (class Foldable)
26
62
import Data.List ((:))
27
63
import Data.List as L
28
64
import Data.List.Types (NonEmptyList (..))
29
- import Data.Maybe (Maybe (..), maybe , fromMaybe , fromJust )
65
+ import Data.Maybe (Maybe (..), fromMaybe , maybe )
30
66
import Data.NonEmpty ((:|))
31
67
import Data.NonEmpty as NE
32
- import Data.Tuple (Tuple (..))
68
+ import Data.Semigroup.Traversable (sequence1 )
69
+ import Data.Tuple (Tuple (..), fst , snd )
33
70
import Data.Unfoldable (class Unfoldable , unfoldr )
34
- import Partial.Unsafe (unsafePartial )
71
+ import Partial.Unsafe (unsafeCrashWith )
72
+
73
+ import Data.Foldable (foldl , foldr , foldMap , fold , intercalate , elem , notElem , find , findMap , any , all ) as Exports
74
+ import Data.Semigroup.Foldable (fold1 , foldMap1 , for1_ , sequence1_ , traverse1_ ) as Exports
75
+ import Data.Semigroup.Traversable (sequence1 , traverse1 , traverse1Default ) as Exports
76
+ import Data.Traversable (scanl , scanr ) as Exports
77
+
78
+ -- | Internal function: any operation on a list that is guaranteed not to delete
79
+ -- | all elements also applies to a NEL, this function is a helper for defining
80
+ -- | those cases.
81
+ wrappedOperation
82
+ :: forall a b
83
+ . String
84
+ -> (L.List a -> L.List b )
85
+ -> NonEmptyList a
86
+ -> NonEmptyList b
87
+ wrappedOperation name f (NonEmptyList (x :| xs)) =
88
+ case f (x : xs) of
89
+ x' : xs' -> NonEmptyList (x' :| xs')
90
+ L.Nil -> unsafeCrashWith (" Impossible: empty list in NonEmptyList " <> name)
91
+
92
+ -- | Like `wrappedOperation`, but for functions that operate on 2 lists.
93
+ wrappedOperation2
94
+ :: forall a b c
95
+ . String
96
+ -> (L.List a -> L.List b -> L.List c )
97
+ -> NonEmptyList a
98
+ -> NonEmptyList b
99
+ -> NonEmptyList c
100
+ wrappedOperation2 name f (NonEmptyList (x :| xs)) (NonEmptyList (y :| ys)) =
101
+ case f (x : xs) (y : ys) of
102
+ x' : xs' -> NonEmptyList (x' :| xs')
103
+ L.Nil -> unsafeCrashWith (" Impossible: empty list in NonEmptyList " <> name)
104
+
105
+ -- | Lifts a function that operates on a list to work on a NEL. This does not
106
+ -- | preserve the non-empty status of the result.
107
+ lift :: forall a b . (L.List a -> b ) -> NonEmptyList a -> b
108
+ lift f (NonEmptyList (x :| xs)) = f (x : xs)
35
109
36
110
toUnfoldable :: forall f . Unfoldable f => NonEmptyList ~> f
37
111
toUnfoldable =
@@ -79,16 +153,138 @@ unsnoc (NonEmptyList (x :| xs)) = case L.unsnoc xs of
79
153
length :: forall a . NonEmptyList a -> Int
80
154
length (NonEmptyList (x :| xs)) = 1 + L .length xs
81
155
156
+ index :: forall a . NonEmptyList a -> Int -> Maybe a
157
+ index (NonEmptyList (x :| xs)) i
158
+ | i == 0 = Just x
159
+ | otherwise = L .index xs (i - 1 )
160
+
161
+ infixl 8 index as !!
162
+
163
+ elemIndex :: forall a . Eq a => a -> NonEmptyList a -> Maybe Int
164
+ elemIndex x = findIndex (_ == x)
165
+
166
+ elemLastIndex :: forall a . Eq a => a -> NonEmptyList a -> Maybe Int
167
+ elemLastIndex x = findLastIndex (_ == x)
168
+
169
+ findIndex :: forall a . (a -> Boolean ) -> NonEmptyList a -> Maybe Int
170
+ findIndex f (NonEmptyList (x :| xs))
171
+ | f x = Just 0
172
+ | otherwise = (_ + 1 ) <$> L .findIndex f xs
173
+
174
+ findLastIndex :: forall a . (a -> Boolean ) -> NonEmptyList a -> Maybe Int
175
+ findLastIndex f (NonEmptyList (x :| xs)) =
176
+ case L .findLastIndex f xs of
177
+ Just i -> Just (i + 1 )
178
+ Nothing
179
+ | f x -> Just 0
180
+ | otherwise -> Nothing
181
+
182
+ insertAt :: forall a . Int -> a -> NonEmptyList a -> Maybe (NonEmptyList a )
183
+ insertAt i a (NonEmptyList (x :| xs))
184
+ | i == 0 = Just (NonEmptyList (a :| x : xs))
185
+ | otherwise = NonEmptyList <<< (x :| _) <$> L .insertAt (i - 1 ) a xs
186
+
187
+ updateAt :: forall a . Int -> a -> NonEmptyList a -> Maybe (NonEmptyList a )
188
+ updateAt i a (NonEmptyList (x :| xs))
189
+ | i == 0 = Just (NonEmptyList (a :| xs))
190
+ | otherwise = NonEmptyList <<< (x :| _) <$> L .updateAt (i - 1 ) a xs
191
+
192
+ modifyAt :: forall a . Int -> (a -> a ) -> NonEmptyList a -> Maybe (NonEmptyList a )
193
+ modifyAt i f (NonEmptyList (x :| xs))
194
+ | i == 0 = Just (NonEmptyList (f x :| xs))
195
+ | otherwise = NonEmptyList <<< (x :| _) <$> L .modifyAt (i - 1 ) f xs
196
+
197
+ reverse :: forall a . NonEmptyList a -> NonEmptyList a
198
+ reverse = wrappedOperation " reverse" L .reverse
199
+
200
+ filter :: forall a . (a -> Boolean ) -> NonEmptyList a -> L.List a
201
+ filter = lift <<< L .filter
202
+
203
+ filterM :: forall m a . Monad m => (a -> m Boolean ) -> NonEmptyList a -> m (L.List a )
204
+ filterM = lift <<< L .filterM
205
+
206
+ mapMaybe :: forall a b . (a -> Maybe b ) -> NonEmptyList a -> L.List b
207
+ mapMaybe = lift <<< L .mapMaybe
208
+
209
+ catMaybes :: forall a . NonEmptyList (Maybe a ) -> L.List a
210
+ catMaybes = lift L .catMaybes
211
+
212
+ concat :: forall a . NonEmptyList (NonEmptyList a ) -> NonEmptyList a
213
+ concat = (_ >>= id)
214
+
82
215
concatMap :: forall a b . (a -> NonEmptyList b ) -> NonEmptyList a -> NonEmptyList b
83
216
concatMap = flip bind
84
217
85
218
appendFoldable :: forall t a . Foldable t => NonEmptyList a -> t a -> NonEmptyList a
86
219
appendFoldable (NonEmptyList (x :| xs)) ys =
87
220
NonEmptyList (x :| (xs <> L .fromFoldable ys))
88
221
222
+ mapWithIndex :: forall a b . (Int -> a -> b ) -> NonEmptyList a -> NonEmptyList b
223
+ mapWithIndex = wrappedOperation " mapWithIndex" <<< L .mapWithIndex
224
+
89
225
sort :: forall a . Ord a => NonEmptyList a -> NonEmptyList a
90
226
sort xs = sortBy compare xs
91
227
92
228
sortBy :: forall a . (a -> a -> Ordering ) -> NonEmptyList a -> NonEmptyList a
93
- sortBy cmp xs = unsafeFromList $ L .sortBy cmp (toList xs)
94
- where unsafeFromList ys = unsafePartial $ fromJust $ fromList ys
229
+ sortBy = wrappedOperation " sortBy" <<< L .sortBy
230
+
231
+ take :: forall a . Int -> NonEmptyList a -> L.List a
232
+ take = lift <<< L .take
233
+
234
+ takeWhile :: forall a . (a -> Boolean ) -> NonEmptyList a -> L.List a
235
+ takeWhile = lift <<< L .takeWhile
236
+
237
+ drop :: forall a . Int -> NonEmptyList a -> L.List a
238
+ drop = lift <<< L .drop
239
+
240
+ dropWhile :: forall a . (a -> Boolean ) -> NonEmptyList a -> L.List a
241
+ dropWhile = lift <<< L .dropWhile
242
+
243
+ span :: forall a . (a -> Boolean ) -> NonEmptyList a -> { init :: L.List a , rest :: L.List a }
244
+ span = lift <<< L .span
245
+
246
+ group :: forall a . Eq a => NonEmptyList a -> NonEmptyList (NonEmptyList a )
247
+ group = wrappedOperation " group" L .group
248
+
249
+ group' :: forall a . Ord a => NonEmptyList a -> NonEmptyList (NonEmptyList a )
250
+ group' = wrappedOperation " group'" L .group'
251
+
252
+ groupBy :: forall a . (a -> a -> Boolean ) -> NonEmptyList a -> NonEmptyList (NonEmptyList a )
253
+ groupBy = wrappedOperation " groupBy" <<< L .groupBy
254
+
255
+ partition :: forall a . (a -> Boolean ) -> NonEmptyList a -> { yes :: L.List a , no :: L.List a }
256
+ partition = lift <<< L .partition
257
+
258
+ nub :: forall a . Eq a => NonEmptyList a -> NonEmptyList a
259
+ nub = wrappedOperation " nub" L .nub
260
+
261
+ nubBy :: forall a . (a -> a -> Boolean ) -> NonEmptyList a -> NonEmptyList a
262
+ nubBy = wrappedOperation " nubBy" <<< L .nubBy
263
+
264
+ union :: forall a . Eq a => NonEmptyList a -> NonEmptyList a -> NonEmptyList a
265
+ union = wrappedOperation2 " union" L .union
266
+
267
+ unionBy :: forall a . (a -> a -> Boolean ) -> NonEmptyList a -> NonEmptyList a -> NonEmptyList a
268
+ unionBy = wrappedOperation2 " unionBy" <<< L .unionBy
269
+
270
+ intersect :: forall a . Eq a => NonEmptyList a -> NonEmptyList a -> NonEmptyList a
271
+ intersect = wrappedOperation2 " intersect" L .intersect
272
+
273
+ intersectBy :: forall a . (a -> a -> Boolean ) -> NonEmptyList a -> NonEmptyList a -> NonEmptyList a
274
+ intersectBy = wrappedOperation2 " intersectBy" <<< L .intersectBy
275
+
276
+ zipWith :: forall a b c . (a -> b -> c ) -> NonEmptyList a -> NonEmptyList b -> NonEmptyList c
277
+ zipWith f (NonEmptyList (x :| xs)) (NonEmptyList (y :| ys)) =
278
+ NonEmptyList (f x y :| L .zipWith f xs ys)
279
+
280
+ zipWithA :: forall m a b c . Applicative m => (a -> b -> m c ) -> NonEmptyList a -> NonEmptyList b -> m (NonEmptyList c )
281
+ zipWithA f xs ys = sequence1 (zipWith f xs ys)
282
+
283
+ zip :: forall a b . NonEmptyList a -> NonEmptyList b -> NonEmptyList (Tuple a b )
284
+ zip = zipWith Tuple
285
+
286
+ unzip :: forall a b . NonEmptyList (Tuple a b ) -> Tuple (NonEmptyList a ) (NonEmptyList b )
287
+ unzip ts = Tuple (map fst ts) (map snd ts)
288
+
289
+ foldM :: forall m a b . Monad m => (a -> b -> m a ) -> a -> NonEmptyList b -> m a
290
+ foldM f a (NonEmptyList (b :| bs)) = f a b >>= \a' -> L .foldM f a' bs
0 commit comments