Import Upstream version 20180207
[hcoop/debian/mlton.git] / doc / guide / src / ForLoops.adoc
CommitLineData
7f918cf1
CE
1ForLoops
2========
3
4A `for`-loop is typically used to iterate over a range of consecutive
5integers that denote indices of some sort. For example, in <:OCaml:>
6a `for`-loop takes either the form
7----
8for <name> = <lower> to <upper> do <body> done
9----
10or the form
11----
12for <name> = <upper> downto <lower> do <body> done
13----
14
15Some languages provide considerably more flexible `for`-loop or
16`foreach`-constructs.
17
18A bit surprisingly, <:StandardML:Standard ML> provides special syntax
19for `while`-loops, but not for `for`-loops. Indeed, in SML, many uses
20of `for`-loops are better expressed using `app`, `foldl`/`foldr`,
21`map` and many other higher-order functions provided by the
22<:BasisLibrary:Basis Library> for manipulating lists, vectors and
23arrays. However, the Basis Library does not provide a function for
24iterating over a range of integer values. Fortunately, it is very
25easy to write one.
26
27
28== A fairly simple design ==
29
30The following implementation imitates both the syntax and semantics of
31the OCaml `for`-loop.
32
33[source,sml]
34----
35datatype for = to of int * int
36 | downto of int * int
37
38infix to downto
39
40val for =
41 fn lo to up =>
42 (fn f => let fun loop lo = if lo > up then ()
43 else (f lo; loop (lo+1))
44 in loop lo end)
45 | up downto lo =>
46 (fn f => let fun loop up = if up < lo then ()
47 else (f up; loop (up-1))
48 in loop up end)
49----
50
51For example,
52
53[source,sml]
54----
55for (1 to 9)
56 (fn i => print (Int.toString i))
57----
58
59would print `123456789` and
60
61[source,sml]
62----
63for (9 downto 1)
64 (fn i => print (Int.toString i))
65----
66
67would print `987654321`.
68
69Straightforward formatting of nested loops
70
71[source,sml]
72----
73for (a to b)
74 (fn i =>
75 for (c to d)
76 (fn j =>
77 ...))
78----
79
80is fairly readable, but tends to cause the body of the loop to be
81indented quite deeply.
82
83
84== Off-by-one ==
85
86The above design has an annoying feature. In practice, the upper
87bound of the iterated range is almost always excluded and most loops
88would subtract one from the upper bound:
89
90[source,sml]
91----
92for (0 to n-1) ...
93for (n-1 downto 0) ...
94----
95
96It is probably better to break convention and exclude the upper bound
97by default, because it leads to more concise code and becomes
98idiomatic with very little practice. The iterator combinators
99described below exclude the upper bound by default.
100
101
102== Iterator combinators ==
103
104While the simple `for`-function described in the previous section is
105probably good enough for many uses, it is a bit cumbersome when one
106needs to iterate over a Cartesian product. One might also want to
107iterate over more than just consecutive integers. It turns out that
108one can provide a library of iterator combinators that allow one to
109implement iterators more flexibly.
110
111Since the types of the combinators may be a bit difficult to infer
112from their implementations, let's first take a look at a signature of
113the iterator combinator library:
114
115[source,sml]
116----
117signature ITER =
118 sig
119 type 'a t = ('a -> unit) -> unit
120
121 val return : 'a -> 'a t
122 val >>= : 'a t * ('a -> 'b t) -> 'b t
123
124 val none : 'a t
125
126 val to : int * int -> int t
127 val downto : int * int -> int t
128
129 val inList : 'a list -> 'a t
130 val inVector : 'a vector -> 'a t
131 val inArray : 'a array -> 'a t
132
133 val using : ('a, 'b) StringCvt.reader -> 'b -> 'a t
134
135 val when : 'a t * ('a -> bool) -> 'a t
136 val by : 'a t * ('a -> 'b) -> 'b t
137 val @@ : 'a t * 'a t -> 'a t
138 val ** : 'a t * 'b t -> ('a, 'b) product t
139
140 val for : 'a -> 'a
141 end
142----
143
144Several of the above combinators are meant to be used as infix
145operators. Here is a set of suitable infix declarations:
146
147[source,sml]
148----
149infix 2 to downto
150infix 1 @@ when by
151infix 0 >>= **
152----
153
154A few notes are in order:
155
156* The `'a t` type constructor with the `return` and `>>=` operators forms a monad.
157
158* The `to` and `downto` combinators will omit the upper bound of the range.
159
160* `for` is the identity function. It is purely for syntactic sugar and is not strictly required.
161
162* The `@@` combinator produces an iterator for the concatenation of the given iterators.
163
164* The `**` combinator produces an iterator for the Cartesian product of the given iterators.
165** See <:ProductType:> for the type constructor `('a, 'b) product` used in the type of the iterator produced by `**`.
166
167* The `using` combinator allows one to iterate over slices, streams and many other kinds of sequences.
168
169* `when` is the filtering combinator. The name `when` is inspired by <:OCaml:>'s guard clauses.
170
171* `by` is the mapping combinator.
172
173The below implementation of the `ITER`-signature makes use of the
174following basic combinators:
175
176[source,sml]
177----
178fun const x _ = x
179fun flip f x y = f y x
180fun id x = x
181fun opt fno fso = fn NONE => fno () | SOME ? => fso ?
182fun pass x f = f x
183----
184
185Here is an implementation the `ITER`-signature:
186
187[source,sml]
188----
189structure Iter :> ITER =
190 struct
191 type 'a t = ('a -> unit) -> unit
192
193 val return = pass
194 fun (iA >>= a2iB) f = iA (flip a2iB f)
195
196 val none = ignore
197
198 fun (l to u) f = let fun `l = if l<u then (f l; `(l+1)) else () in `l end
199 fun (u downto l) f = let fun `u = if u>l then (f (u-1); `(u-1)) else () in `u end
200
201 fun inList ? = flip List.app ?
202 fun inVector ? = flip Vector.app ?
203 fun inArray ? = flip Array.app ?
204
205 fun using get s f = let fun `s = opt (const ()) (fn (x, s) => (f x; `s)) (get s) in `s end
206
207 fun (iA when p) f = iA (fn a => if p a then f a else ())
208 fun (iA by g) f = iA (f o g)
209 fun (iA @@ iB) f = (iA f : unit; iB f)
210 fun (iA ** iB) f = iA (fn a => iB (fn b => f (a & b)))
211
212 val for = id
213 end
214----
215
216Note that some of the above combinators (e.g. `**`) could be expressed
217in terms of the other combinators, most notably `return` and `>>=`.
218Another implementation issue worth mentioning is that `downto` is
219written specifically to avoid computing `l-1`, which could cause an
220`Overflow`.
221
222To use the above combinators the `Iter`-structure needs to be opened
223
224[source,sml]
225----
226open Iter
227----
228
229and one usually also wants to declare the infix status of the
230operators as shown earlier.
231
232Here is an example that illustrates some of the features:
233
234[source,sml]
235----
236for (0 to 10 when (fn x => x mod 3 <> 0) ** inList ["a", "b"] ** 2 downto 1 by real)
237 (fn x & y & z =>
238 print ("("^Int.toString x^", \""^y^"\", "^Real.toString z^")\n"))
239----
240
241Using the `Iter` combinators one can easily produce more complicated
242iterators. For example, here is an iterator over a "triangle":
243
244[source,sml]
245----
246fun triangle (l, u) = l to u >>= (fn i => i to u >>= (fn j => return (i, j)))
247----