1- # scott-lists .lc
1+ # scott-list .lc
22
33#import combinators.lc
44B = \ f g x . f (g x)
@@ -18,7 +18,7 @@ Y = \ f . ( \ x . f (x x) ) ( \ x . f (x x) )
1818#import scott-booleans.ls
1919False = K
2020True = KI
21- not = \ p . p True False
21+ not = C
2222and = M
2323or = W C
2424#import scott-ordering.lc
@@ -58,7 +58,7 @@ is-none = \ x . x True (K False) # = is-zero
5858is-some = \ x . x False (K True)
5959from-option = \ z x . x z I
6060from-some = \ x . x () I
61- # additional definitions depend on nil and cons
61+ # additional definitions depend on nil, cons, singleton
6262
6363# data List a = Nil | Cons a (List a)
6464
@@ -71,32 +71,43 @@ cons = \ x xs . \ _nil cons . cons x xs
7171# singleton :: a -> List a
7272singleton = \ x . cons x nil
7373
74- # these scott-options definitions depend on nil, cons, singleton
74+ # these scott-option definitions depend on nil, cons, singleton
7575list-to-option = \ xs . xs None \ x _xs . Some x
7676option-to-list = \ x . x nil singleton
7777map-option = \ fn xs . xs nil \ x xs . fn x (map-option fn xs) (C cons (map-option fn xs))
7878cat-options = map-option I
7979
80- # continuing scott-lists .lc
80+ # continuing scott-list .lc
8181
8282# foldr :: (a -> z -> z) -> z -> List a -> z
83- foldr = \ fn z xs . xs z ( \ x xs . fn x (foldr fn z xs) )
83+ foldr = \ fn z xs . xs z \ x xs . fn x (foldr fn z xs)
8484
85- # null :: List a -> Boolean
86- null = \ xs . xs True (KK False)
85+ # foldl :: (z -> a -> z) -> z -> List a -> z
86+ foldl = \ fn z xs . xs z (B (foldl fn) (fn z))
87+
88+ # scanr :: (a -> z -> z) -> z -> List a -> List z
89+ scanr = \ fn z xs . xs (singleton z) \ x xs . ( \ zs . zs () \ z _zs . cons (fn x z) zs ) (scanr fn z xs)
90+
91+ # scanl :: (z -> a -> z) -> z -> List a -> List z
92+ scanl = \ fn z xs . cons z (xs nil (B (scanl fn) (fn z)))
8793
8894# take :: Number -> List a -> List a
8995take = \ n xs . is-zero n (xs nil \ x xs . cons x (take (pred n) xs)) nil
9096
97+ # drop :: Number -> List a -> List a
98+ drop = \ n xs . is-zero n (xs nil (K (drop (pred n)))) xs
99+
91100# append :: List a -> List a -> List a
92101append = C (foldr cons)
93102
94103# concat :: List (List a) -> List a
95- concat = \ xss . foldr xss append nil
104+ concat = foldr append nil
96105
97- # sum,product :: List Number -> Number
98- sum = foldr add zero
99- product = foldr mul one
106+ # snoc :: List a -> a -> List a
107+ snoc = C (B (foldr cons) singleton)
108+
109+ # uncons :: List a -> Option (Pair a (List a))
110+ uncons = \ xs . xs None (BB Some Pair)
100111
101112# iterate :: (a -> a) -> a -> List a
102113iterate = \ fn x . cons x (iterate fn (fn x))
@@ -105,47 +116,57 @@ iterate = \ fn x . cons x (iterate fn (fn x))
105116repeat = \ x . cons x (repeat x) # repeat = Y (S cons)
106117
107118# cycle :: List a -> List a
108- cycle = \ xs . null xs (concat (repeat xs)) ( )
119+ cycle = \ xs . xs () ( concat (repeat xs))
109120
110121# replicate :: Number -> a -> List a
111122replicate = \ n . B (take n) repeat
112123
124+ # unfold :: (a -> Option (Pair z a)) -> a -> List z
125+ unfold = \ fn x . fn x nil (T \ z x . cons z (unfold fn x))
126+
113127# head :: List a -> a
114128head = \ xs . xs () K
115129
116130# tail :: List a -> List a
117131tail = \ xs . xs () KI
118132
133+ # null :: List a -> Boolean
134+ null = \ xs . xs True (KK False)
135+
119136# length :: List a -> Number
120137length = foldr (K succ) zero
121138
122- # snoc :: List a -> a -> List a
123- snoc = C (B (foldr cons) singleton)
139+ # sum,product :: List Number -> Number
140+ sum = foldr add zero
141+ product = foldr mul one
124142
125143# map :: (a -> b) -> List a -> List b
126144map = \ fn . foldr (B cons fn) nil
127145
128146# concat-map :: (a -> List b) -> List a -> List b
129147concat-map = BB concat map
130148
131- # filter :: () -> List a -> List a
149+ # filter :: (a -> Boolean ) -> List a -> List a
132150filter = \ p . foldr ( \ x z . p x z (cons x z) ) nil
133- filter = \ p . foldr ( \ x . S (p x) (cons x) ) nil
134- filter = \ p . foldr (S (B S p) cons) nil
135151
136- # drop :: Number -> List a -> List a
137- drop = \ n xs . is-zero n ( \ _x xs . drop (pred n) xs ) xs
138- drop = \ n . is-zero n (K (drop (pred n)))
152+ # take-while :: (a -> Boolean) -> List a -> List a
153+ take-while = \ p xs . xs nil \ x xs . p x nil (cons x (take-while p xs))
154+
155+ # drop-while :: (a -> Boolean) -> List a -> List a
156+ drop-while = \ p xs . xs nil \ x xs . p x xs (drop-while p xs)
157+
158+ # drop-while-end :: (a -> Boolean) -> List a -> List a
159+ drop-while-end = \ p . foldr ( \ x z . and (null z) (p x) (cons x z) nil ) nil
139160
140161# split-at :: Number -> List a -> Pair (List a) (List a)
141162split-at = \ i xs . is-zero i (xs (Pair nil nil) \ x xs . first (cons x) (split-at (pred i) xs)) (Pair nil xs)
142163
143164# get :: Number -> List a -> a
144- get = \ i xs . is-zero i ( \ x xs . xs () (get (pred i) xs) ) (head xs)
165+ get = \ i xs . is-zero i (xs () (K ( get (pred i))) ) (head xs)
145166
146167# set :: Number -> a -> List a -> List a
147168set = \ i x xs . uncurry append (second (B (cons x) tail) (split-at i xs))
148- set = \ i x xs . is-zero i (xs nil \ y ys . cons y (set (pred i) x ys )) (xs nil (K (cons x)))
169+ set = \ i x xs . is-zero i (xs nil \ y . cons y (set (pred i) x)) (xs nil (K (cons x)))
149170
150171# any :: (a -> Boolean) -> List a -> Boolean
151172any = \ p . foldr (B or p) False
@@ -154,96 +175,78 @@ any = \ p . foldr (B or p) False
154175all = \ p . foldr (B and p) True
155176
156177# find :: (a -> Boolean) -> List a -> Option a
157- find = \ p . foldr ( \ x z . p x z (Some x) ) None
178+ find = BB list-to-option filter
158179
159180# find-indices :: (a -> Boolean) -> List a -> List Number
160181find-indices = \ p . foldr ( \ x k i . p x I (cons i) (k (succ i)) ) (K nil) zero
161182
162183# find-index :: (a -> Boolean) -> List a -> Option Number
163- find-index = \ p . B list-to-option ( find-indices p)
184+ find-index = BB list-to-option find-indices
164185
165186# partition :: (a -> Boolean) -> List a -> Pair (List a) (List a)
166187partition = \ p . foldr ( \ x . p x second first (cons x) ) (Pair nil nil)
167188
168189# span :: (a -> Boolean) -> List a -> Pair (List a) (List a)
169190span = \ p xs . xs (Pair nil nil) \ y ys . p y (Pair nil xs) (first (cons y) (span p ys))
170191
171- # minimum-by :: (a -> a -> Boolean) -> List a -> a # cmp ~ le
172- minimum-by = \ cmp xs . xs () (foldr \ x z . cmp x z z x)
173-
174- # maximum-by :: (a -> a -> Boolean) -> List a -> a # cmp ~ le
175- maximum-by = \ cmp xs . xs () (foldr \ x z . cmp x z x z)
192+ # minimum-by :: (a -> a -> Boolean) -> List a -> a
193+ minimum-by = \ le xs . xs () (foldl \ z x . le z x x z)
176194
177- # insert -by :: (a-> a -> Boolean) -> a -> List a -> List a # cmp ~ le
178- insert -by = \ cmp x xs . uncurry append (second (cons x) (span (C cmp x) xs) )
195+ # maximum -by :: (a -> a -> Boolean) -> List a -> a
196+ maximum -by = \ le xs . xs () (foldl \ z x . le z x z x )
179197
180- # sort-by :: (a -> a -> Boolean) -> List a -> List a # cmp ~ le
181- sort-by = \ cmp . foldr (insert-by cmp) nil
182-
183- # foldl :: (z -> a -> z) -> z -> List a -> z
184- foldl = \ fn z xs . xs z (B (foldl fn) (fn z))
185-
186- # scanl :: (z -> a -> z) -> z -> List a -> List z
187- scanl = \ fn z xs . cons z (xs nil (B (scanl fn) (fn z)))
198+ # insert-by :: (a -> a -> Boolean) -> a -> List a -> List a
199+ insert-by = \ le x xs . uncurry append (second (cons x) (span (C le x) xs))
188200
189- # scanr :: (a -> z -> z) -> z -> List a -> List z
190- scanr = \ fn z xs . xs (singleton z) \ x xs . ( \ zs . zs \ z _zs . cons (fn x z) zs ) (scanr fn z xs)
201+ # sort-by :: (a -> a -> Boolean) -> List a -> List a
202+ sort-by = \ le . foldr (insert-by le) nil
203+ # has all sorts of bad implementation details, but it's simple
191204
192205# reverse :: List a -> List a
193206reverse = foldl (C cons) nil
194207
195- # unzip :: List (Pair a b) -> Pair (List a) (List b)
196- unzip = foldr ( \ xy xys . xy \ x y . bimap (cons x) (cons y) xys ) (Pair nil nil)
197- unzip = foldr (CB \ x y . bimap (cons x) (cons y)) (Pair nil nil)
198-
199208# zip-with :: (a -> b -> z) -> List a -> List b -> List z
200209zip-with = \ fn xs ys . xs nil \ x xs . ys nil \ y ys . cons (fn x y) (zip-with fn xs ys)
201210
202211# zip :: List a -> List b -> List (Pair a b)
203212zip = zip-with Pair
204213
205- # init :: List a -> List a
206- init = \ xs . xs () (S (zip-with K) tail xs)
207-
208- # last :: List a -> a
209- last = foldl KI ()
210-
211- # slice :: Number -> Number -> List a -> List a
212- slice = \ i j xs . gt j i nil (take (sub j i) (drop i xs))
213-
214- # uncons :: List a -> Option (Pair (a) (List a))
215- uncons = \ xs . xs None (B Some Pair)
214+ # unzip :: List (Pair a b) -> Pair (List a) (List b)
215+ unzip = foldr ( \ xy xys . xy \ x y . bimap (cons x) (cons y) xys ) (Pair nil nil)
216+ unzip = foldr (CB \ x y . bimap (cons x) (cons y)) (Pair nil nil)
216217
217- # transpose :: List (List a) -> List (List a)
218- transpose = \ xss . xss nil
219- \ ys yss . ys (transpose yss)
220- (unzip (map-option uncons xss) \ xs xxs . cons xs (transpose xss))
218+ # group-by :: (a -> a -> Bool) -> List a -> List (List a)
219+ group-by = \ eq xs . xs nil \ x xs . span (eq x) xs \ left right . cons (cons x left) (group-by eq right)
221220
222- # unfold :: (a -> Option (Pair z a)) -> a -> List z
223- unfold = \ fn x . fn x nil (T \ z x . cons z (unfold fn x) )
221+ # lookup-by :: (a -> Boolean) -> List (Pair a b) -> Option b
222+ lookup-by = \ p xys . xys None \ xy xys . xy \ x y . p x (lookup-by p xys) (Some y )
224223
225- # take-while :: (a -> Boolean) -> List a -> List a
226- take-while = \ p xs . xs nil \ x xs . p x nil (cons x (take-while p xs))
224+ # nub-by :: (a -> a -> Boolean) -> List a -> List a
225+ go = \ z eq xs . xs z \ x xs . go (is-none (find (eq x) z) z (cons x z)) eq xs
226+ nub-by = go nil
227227
228- # drop-while :: (a -> Boolean) -> List a -> List a
229- drop-while = \ p xs . xs nil \ x xs . p x xs (drop-while p xs)
228+ # delete-by :: (a -> a -> Boolean) -> a -> List a -> List a
229+ delete-by = \ eq x xs . xs nil \ y ys . eq x y (cons y (delete-by eq x ys)) ys
230230
231- # drop-while-end :: (a -> Boolean) -> List a -> List a
232- drop-while-end = \ p . foldr ( \ x z . and (null z) (p x) (cons x z) nil ) nil
231+ # delete-firsts-by :: (a -> a -> Boolean) -> List a -> List a -> List a
232+ delete-firsts-by = \ eq . foldl (C (delete-by eq))
233233
234- # group-by :: (a -> a -> Bool) -> List a -> List (List a)
235- group-by = \ eq xs . xs nil \ x xs . span (eq x) xs \ left right . cons (cons x left) (group-by eq right)
236- group-by = \ eq xs . xs nil \ x xs . uncurry cons (bimap (cons x) (group-by eq) (span (eq x) xs))
234+ # init :: List a -> List a
235+ init = \ xs . xs () (S (zip-with K) tail xs)
237236
238- # inits
237+ # last :: List a -> a
238+ last = foldl KI ()
239239
240240# tails :: List a -> List (List a)
241241tails = \ xs . cons xs (xs nil (K tails))
242242
243- # lookup-by :: ( a -> Boolean) -> List (Pair a b) -> Option b
244- lookup-by = \ eq xys . xys None \ xy xys . xy \ x y . eq x (lookup-by eq xys ) (Some y )
243+ # inits :: List a -> List (List a)
244+ inits = \ xs . xs (singleton nil) \ x xs . cons nil (map (cons x ) (inits xs) )
245245
246- # nub-by
247- # delete-by
248- # delete-firsts-by
249- # sort-on
246+ # slice :: Number -> Number -> List a -> List a
247+ slice = \ i j xs . le i j nil (take (sub j i) (drop i xs))
248+
249+ # transpose :: List (List a) -> List (List a)
250+ transpose = \ xss . xss nil
251+ \ ys yss . ys (transpose yss)
252+ (unzip (map-option uncons xss) \ xs xss . cons xs (transpose xss))
0 commit comments