@@ -7,7 +7,7 @@ module Data.List.NonEmpty
7
7
, singleton
8
8
, length
9
9
, cons
10
- , cons'
10
+ , (:||), cons'
11
11
, snoc
12
12
, snoc'
13
13
, head
@@ -69,6 +69,7 @@ import Data.List as L
69
69
import Data.List.Types (NonEmptyList (..))
70
70
import Data.Maybe (Maybe (..), fromMaybe , maybe )
71
71
import Data.NonEmpty ((:|))
72
+ import Data.NonEmpty (NonEmpty (..))
72
73
import Data.NonEmpty as NE
73
74
import Data.Semigroup.Traversable (sequence1 )
74
75
import Data.Tuple (Tuple (..), fst , snd )
@@ -93,7 +94,7 @@ wrappedOperation
93
94
-> NonEmptyList b
94
95
wrappedOperation name f (NonEmptyList (x :| xs)) =
95
96
case f (x : xs) of
96
- x' : xs' -> NonEmptyList ( x' :| xs')
97
+ x' : xs' -> x' :|| xs'
97
98
L.Nil -> unsafeCrashWith (" Impossible: empty list in NonEmptyList " <> name)
98
99
99
100
-- | Like `wrappedOperation`, but for functions that operate on 2 lists.
@@ -106,7 +107,7 @@ wrappedOperation2
106
107
-> NonEmptyList c
107
108
wrappedOperation2 name f (NonEmptyList (x :| xs)) (NonEmptyList (y :| ys)) =
108
109
case f (x : xs) (y : ys) of
109
- x' : xs' -> NonEmptyList ( x' :| xs')
110
+ x' : xs' -> x' :|| xs'
110
111
L.Nil -> unsafeCrashWith (" Impossible: empty list in NonEmptyList " <> name)
111
112
112
113
-- | Lifts a function that operates on a list to work on a NEL. This does not
@@ -123,7 +124,7 @@ fromFoldable = fromList <<< L.fromFoldable
123
124
124
125
fromList :: forall a . L.List a -> Maybe (NonEmptyList a )
125
126
fromList L.Nil = Nothing
126
- fromList (x : xs) = Just (NonEmptyList ( x :| xs) )
127
+ fromList (x : xs) = Just (x :|| xs)
127
128
128
129
toList :: NonEmptyList ~> L.List
129
130
toList (NonEmptyList (x :| xs)) = x : xs
@@ -132,16 +133,18 @@ singleton :: forall a. a -> NonEmptyList a
132
133
singleton = NonEmptyList <<< NE .singleton
133
134
134
135
cons :: forall a . a -> NonEmptyList a -> NonEmptyList a
135
- cons y (NonEmptyList (x :| xs)) = NonEmptyList ( y :| x : xs)
136
+ cons y (NonEmptyList (x :| xs)) = y :|| x : xs
136
137
137
138
cons' :: forall a . a -> L.List a -> NonEmptyList a
138
- cons' x xs = NonEmptyList (x :| xs)
139
+ cons' x xs = NonEmptyList (NonEmpty x xs)
140
+
141
+ infixr 5 cons' as :||
139
142
140
143
snoc :: forall a . NonEmptyList a -> a -> NonEmptyList a
141
- snoc (NonEmptyList (x :| xs)) y = NonEmptyList ( x :| L .snoc xs y)
144
+ snoc (NonEmptyList (x :| xs)) y = x :|| L .snoc xs y
142
145
143
146
snoc' :: forall a . L.List a -> a -> NonEmptyList a
144
- snoc' (x : xs) y = NonEmptyList ( x :| L .snoc xs y)
147
+ snoc' (x : xs) y = x :|| L .snoc xs y
145
148
snoc' L.Nil y = singleton y
146
149
147
150
head :: forall a . NonEmptyList a -> a
@@ -195,18 +198,18 @@ findLastIndex f (NonEmptyList (x :| xs)) =
195
198
196
199
insertAt :: forall a . Int -> a -> NonEmptyList a -> Maybe (NonEmptyList a )
197
200
insertAt i a (NonEmptyList (x :| xs))
198
- | i == 0 = Just (NonEmptyList ( a :| x : xs) )
201
+ | i == 0 = Just (a :|| x : xs)
199
202
| otherwise = NonEmptyList <<< (x :| _) <$> L .insertAt (i - 1 ) a xs
200
203
201
204
updateAt :: forall a . Int -> a -> NonEmptyList a -> Maybe (NonEmptyList a )
202
205
updateAt i a (NonEmptyList (x :| xs))
203
- | i == 0 = Just (NonEmptyList ( a :| xs) )
204
- | otherwise = NonEmptyList <<< (x :| _) <$> L .updateAt (i - 1 ) a xs
206
+ | i == 0 = Just (a :|| xs)
207
+ | otherwise = (x :| | _) <$> L .updateAt (i - 1 ) a xs
205
208
206
209
modifyAt :: forall a . Int -> (a -> a ) -> NonEmptyList a -> Maybe (NonEmptyList a )
207
210
modifyAt i f (NonEmptyList (x :| xs))
208
- | i == 0 = Just (NonEmptyList ( f x :| xs) )
209
- | otherwise = NonEmptyList <<< (x :| _) <$> L .modifyAt (i - 1 ) f xs
211
+ | i == 0 = Just (f x :|| xs)
212
+ | otherwise = (x :| | _) <$> L .modifyAt (i - 1 ) f xs
210
213
211
214
reverse :: forall a . NonEmptyList a -> NonEmptyList a
212
215
reverse = wrappedOperation " reverse" L .reverse
@@ -231,7 +234,7 @@ concatMap = flip bind
231
234
232
235
appendFoldable :: forall t a . Foldable t => NonEmptyList a -> t a -> NonEmptyList a
233
236
appendFoldable (NonEmptyList (x :| xs)) ys =
234
- NonEmptyList ( x :| (xs <> L .fromFoldable ys) )
237
+ x :|| (xs <> L .fromFoldable ys)
235
238
236
239
-- | Apply a function to each element and its index in a list starting at 0.
237
240
-- |
@@ -298,7 +301,7 @@ intersectBy = wrappedOperation2 "intersectBy" <<< L.intersectBy
298
301
299
302
zipWith :: forall a b c . (a -> b -> c ) -> NonEmptyList a -> NonEmptyList b -> NonEmptyList c
300
303
zipWith f (NonEmptyList (x :| xs)) (NonEmptyList (y :| ys)) =
301
- NonEmptyList ( f x y :| L .zipWith f xs ys)
304
+ f x y :|| L .zipWith f xs ys
302
305
303
306
zipWithA :: forall m a b c . Applicative m => (a -> b -> m c ) -> NonEmptyList a -> NonEmptyList b -> m (NonEmptyList c )
304
307
zipWithA f xs ys = sequence1 (zipWith f xs ys)
0 commit comments