Merge lp:~mgiuca/mars/newtypes into lp:mars

Proposed by Matt Giuca
Status: Merged
Approved by: Matt Giuca
Approved revision: 1049
Merged at revision: 1030
Proposed branch: lp:~mgiuca/mars/newtypes
Merge into: lp:mars
Diff against target: 2876 lines (+1121/-410)
53 files modified
doc/intro.rst (+3/-3)
doc/ref/procedures.rst (+23/-6)
doc/ref/types.rst (+152/-5)
lib/prelude.mar (+2/-2)
src/ast_cfg.m (+269/-157)
src/builtins.m (+24/-24)
src/interactive.m (+3/-3)
src/ir.m (+6/-2)
src/mars.m (+2/-2)
src/marsc.m (+2/-2)
src/parsem.m (+7/-2)
src/pretty.m (+2/-1)
src/tables.m (+13/-1)
src/typecheck.m (+243/-177)
src/types.m (+7/-1)
src/util.m (+16/-0)
test/cases/compiler/implicitvar.mar (+47/-0)
test/cases/compiler/patterntypeerror.mar (+27/-0)
test/cases/compiler/patterntypeerror.mtc (+8/-0)
test/cases/compiler/phipred.mtc (+0/-1)
test/cases/compiler/switch.mar (+33/-0)
test/cases/compiler/switch.mtc (+0/-5)
test/cases/semantic/assignglobal.mar (+3/-1)
test/cases/semantic/assignglobal.mtc (+1/-3)
test/cases/semantic/casetypecheck.mtc (+0/-1)
test/cases/semantic/dupfield.mar (+3/-2)
test/cases/semantic/dupfield.mtc (+4/-2)
test/cases/semantic/dupfield2.mar (+5/-0)
test/cases/semantic/dupfield2.mtc (+5/-0)
test/cases/semantic/dupfield3.mtc (+1/-1)
test/cases/semantic/dupvarcase.mar (+16/-0)
test/cases/semantic/dupvarcase.mtc (+8/-0)
test/cases/semantic/dupvarcase2.mar (+17/-0)
test/cases/semantic/dupvarcase2.mtc (+8/-0)
test/cases/semantic/localreadwrite.mtc (+0/-1)
test/cases/semantic/localreadwrite2.mar (+12/-0)
test/cases/semantic/localreadwrite2.mtc (+5/-0)
test/cases/semantic/localtypevar.mar (+14/-0)
test/cases/semantic/localtypevar.mtc (+7/-0)
test/cases/semantic/localtypevar2.mar (+10/-0)
test/cases/semantic/localtypevar2.mtc (+6/-0)
test/cases/semantic/monomorphism.mar (+16/-0)
test/cases/semantic/monomorphism.mtc (+9/-0)
test/cases/semantic/monomorphism2.mar (+23/-0)
test/cases/semantic/monomorphism2.mtc (+9/-0)
test/cases/semantic/typeerror2.mar (+6/-0)
test/cases/semantic/typeerror2.mtc (+9/-0)
test/cases/semantic/typeerror3.mar (+6/-0)
test/cases/semantic/typeerror3.mtc (+9/-0)
test/cases/semantic/typeerror4.mar (+6/-0)
test/cases/semantic/typeerror4.mtc (+9/-0)
test/cases/semantic/undefvar2.mar (+4/-2)
test/cases/semantic/undefvar2.mtc (+1/-3)
To merge this branch: bzr merge lp:~mgiuca/mars/newtypes
Reviewer Review Type Date Requested Status
Matt Giuca Approve
Review via email: mp+24972@code.launchpad.net

Description of the change

Ready to merge. All type system changes are complete.

To post a comment you must log in.
Revision history for this message
Matt Giuca (mgiuca) :
review: Approve

Preview Diff

[H/L] Next/Prev Comment, [J/K] Next/Prev File, [N/P] Next/Prev Hunk
1=== modified file 'doc/intro.rst'
2--- doc/intro.rst 2010-05-07 09:02:21 +0000
3+++ doc/intro.rst 2010-05-10 05:50:41 +0000
4@@ -192,9 +192,9 @@
5
6 .. highlight:: mars
7
8-Variables must be explicitly declared, using the :keyword:`var` keyword
9-(because Mars doesn't currently have type inference). All declarations must
10-come at the top of the function.
11+Mars will automatically infer the type of any variable assigned in the body of
12+a function. Variables may also be explicitly declared, using the
13+:keyword:`var` keyword. All declarations must come at the top of the function.
14
15 You can use a while loop just as you might expect. Assignment statements are
16 also quite straightforward, using the :keyword:`=` operator, much to the
17
18=== modified file 'doc/ref/procedures.rst'
19--- doc/ref/procedures.rst 2009-02-05 23:38:09 +0000
20+++ doc/ref/procedures.rst 2010-05-10 05:50:41 +0000
21@@ -166,9 +166,21 @@
22 Local variables
23 ---------------
24
25-Mars currently requires all local variables to be declared before use. For
26-simplicity, all declarations must appear before any statements. Declarations
27-have the following syntax:
28+Mars distinguishes between local and global variables. All local variables are
29+scoped to the entire procedure body (there is no block scope). A name refers
30+to a local variable if and only if it:
31+
32+* Is a formal parameter, or
33+* Is explicitly declared with the :keyword:`var` keyword, or
34+* Appears on the left-hand side of an assignment statement, or
35+* Appears in a pattern.
36+
37+Local variables may be given the same name as a global constant or function.
38+In this case, the local variable shadows the global constant of the same name.
39+
40+Local variables may optionally be explicitly declared. For simplicity, all
41+declarations must appear before any statements. Declarations have the
42+following syntax:
43
44 .. productionlist::
45 var_decl: "var" `var_name` "::" `type` NEWLINE
46@@ -179,8 +191,13 @@
47 name as a formal parameter, or if two local variables are declared with the
48 same name.
49
50-Local variables may be given the same name as a global constant or function.
51-In this case, the local variable shadows the global constant of the same name.
52+.. Launchpad bug #482947:
53+
54+It is currently an error to declare a local variable with a type which
55+includes a type variable not found in the procedure header. This is generally
56+not a useful thing (since type variables are monomorphic; see :ref:`type
57+unification <ref-type-unification>`), but if it is desired, the variable
58+cannot be explicitly declared.
59
60 Local variables (other than parameters) are not initialised with any
61 particular value. The compiler is required to guarantee that variables are not
62@@ -192,7 +209,7 @@
63 ====================
64
65 The evaluation of procedures is the heart of the Mars execution model. Mars
66-procetures are evaluated eagerly, and arguments are passed by-value.
67+procedures are evaluated eagerly, and arguments are passed by-value.
68
69 Global constant references
70 --------------------------
71
72=== modified file 'doc/ref/types.rst'
73--- doc/ref/types.rst 2009-11-23 05:40:42 +0000
74+++ doc/ref/types.rst 2010-05-10 05:50:41 +0000
75@@ -189,6 +189,130 @@
76 * This is a classic "curried style" function, as may be found in Haskell.
77 * This type may also be written as :class:`->(a, ->(b, c))`.
78
79+.. _ref-type-unification:
80+
81+Type unification
82+----------------
83+
84+Unification is the main algorithm Mars uses for type checking and type
85+inference. For a general overview of unification, see
86+`Unification <http://en.wikipedia.org/wiki/Unification>`_ on Wikipedia.
87+
88+When two or more values are expected to have the same type, their types are
89+unified. The specification explicitly states when types should be unified. If
90+the two types are the same, they successfully unify. Otherwise, they fail to
91+unify, and the program must be rejected (due to a type error).
92+
93+For example, the type :class:`Int` will unify with the type :class:`Int`, but
94+fail to unify with the type :class:`Array(Int)`.
95+
96+This is complicated by type variables. Each type variable is either **free**,
97+**bound** or **rigid**.
98+
99+* A **free** type variable *a* will successfully unify with any type *t*, but
100+ once unified, *a* is bound to *t* for the entirety of the function.
101+* A **bound** type variable *a*, bound to type *t*, will unify with *s* if and
102+ only if *t* unifies with *s*.
103+* A **rigid** type variable *a* is never bound, and unifies only with *a*.
104+
105+For example, the type :class:`a` (if *a* is a free type variable) will unify
106+with the type :class:`Int`, but result in *a* being bound to :class:`Int`. In
107+future unifications within the same function, :class:`a` will unify only with
108+:class:`Int`.
109+
110+Type variables explicitly named in the header or body of a procedure are
111+**rigid**, and will not unify with any type other than themselves. For
112+example, this code is invalid::
113+
114+ def to_int(x :: a) :: Int:
115+ return x # Type error
116+
117+It is invalid because the header specifies that the caller may pass an
118+argument of non-:class:`Int` type, but in that case, it won't be able to
119+return an :class:`Int`. Thus the type variable *a* is rigid; the procedure is
120+only valid if *a* is not unified with any other type.
121+
122+Non-rigid type variables are introduced by implicitly-typed variables (for
123+type inference) or by expressions with polymorphic types (such as the empty
124+array literal, or global variables and functions with polymorphic types). For
125+example::
126+
127+ def singleton(x :: Int) :: Array(Int):
128+ v = []
129+ return array_add(v, x)
130+
131+In this example, the variable `v` is given the free type variable *a* when it
132+is first assigned. During the call to :func:`array_add`, its type is unified
133+with :class:`Int`. It would be a type error to treat `v` as a different type
134+elsewhere, even though it hasn't got any data in it (once its type is bound,
135+it is bound for the entire body of the function; type variables in Mars are
136+*monomorphic*), as in the following example::
137+
138+ def monomorphic(x :: Int) :: Array(Int):
139+ v = []
140+ r = array_add(v, x)
141+ w = array_add(v, [1]) # Type error
142+ return r
143+
144+The unification rules are as follows (note all rules are symmetric):
145+
146+* Type variable *a* unifies with type *t* with the rules as above (regardless
147+ of whether *t* is a type name, a type variable or a type application). If
148+ successful, this results in variable *a* becoming bound.
149+* Type name *x* unifies with type name *x*, and no other type name.
150+* Type names do not unify with type applications.
151+* Type application *t* ( *t1*, ..., *tn* ) unifies with type application *s*
152+ ( *s1*, ..., *sn* ) if and only if *t* unifies with *s* and *ti* unifies
153+ with *si* for all *i* <= *n*. Any bindings made in the recursive
154+ unifications apply.
155+
156+Polymorphism in global constants
157+++++++++++++++++++++++++++++++++
158+
159+The example above shows that type variables in Mars are monomorphic. This is
160+true only for local variables. As a special rule, global constants (including
161+functions and data constructors) in Mars are polymorphic, meaning they can be
162+given a different binding upon each use.
163+
164+The type of each global constant is "generalised" by taking each type variable
165+in its original type, and universally quantifying it. A variable of type *t*
166+containing type variables *a1*, ..., *an* is generalised as "∀ *a1*, ...,
167+*an*. *t*"
168+
169+A successful unification of a type with a universal quantification will *not*
170+cause the quantified variables to become bound, so they may be unified again
171+as a free variable.
172+
173+The example above can be "fixed" by making `v` a global constant::
174+
175+ def v :: Array(a) = []
176+
177+ def monomorphic(x :: Int) :: Array(Int):
178+ r = array_add(v, x)
179+ w = array_add(v, [1])
180+ return r
181+
182+Now `v` has type :class:`∀a. Array(a)`. The first unification between
183+:class:`∀a. Array(a)` and :class:`Array(Int)` succeeds without binding *a*.
184+Thus, the second unification between :class:`∀a. Array(a)` and
185+:class:`Array(Array(Int))` also succeeds.
186+
187+The polymorphic / monomorphic distinction is important when dealing with
188+polymorphic functions. Consider::
189+
190+ def twomaps(f :: a -> b, g :: a -> c, x :: Array(a)) :: Pair(Array(b), Array(c)):
191+ y = array_map(f, x)
192+ z = array_map(g, x)
193+ return Pair(y, z)
194+
195+Contrast with::
196+
197+ def twomaps(f :: a -> b, g :: a -> c, x :: Array(a)) :: Pair(Array(b), Array(c)):
198+ mymap = array_map
199+ y = mymap(f, x)
200+ z = mymap(g, x) # Type error
201+ return Pair(y, z)
202+
203 Built-In Types
204 --------------
205
206@@ -266,10 +390,10 @@
207 must have a name (an identifier beginning with an uppercase letter), and at
208 least one constructor.
209
210-A type may optionally have zero or more parameters. If a type does not have
211-parameters, its kind is :class:`*`. If a type has *n* parameters, its kind is
212-:class:`(*1, *2, ..., *n) -> *`. Any parameter variables may be used in the
213-types of the constructor parameters.
214+A type may optionally have zero or more type parameters. If a type does not
215+have parameters, its kind is :class:`*`. If a type has *n* parameters, its
216+kind is :class:`(*1, *2, ..., *n) -> *`. Any parameter variables may be used
217+in the types of the constructor parameters.
218
219 This statement only creates type constructors of the form
220 :class:`(*,*,...,*) -> *`. It is not possible to create a user-defined type
221@@ -291,7 +415,30 @@
222 Types have one or more constructors. Each constructor has a globally-unique
223 name, and zero or more parameters. The constructor declares a
224 globally-available function of the same name, which takes the given arguments
225-as inputs, and returns a value of the type being declared.
226+as inputs, and returns a value of the type being declared. Each constructor
227+parameter may optionally have a name. No two parameters of a constructor may
228+have the same name. The same parameter name *may* appear in multiple
229+constructors, but it MUST have the same type in all constructors.
230+
231+For example, the following type is illegal, as a constructor has two
232+parameters with the same name::
233+
234+ type Foo:
235+ X(v :: Int, v :: Array(Int)) # Error: Duplicate field name
236+
237+The following type is valid, as the name `v` appears in multiple constructors,
238+but has the same type in all instances::
239+
240+ type Foo:
241+ X(u :: Int, v :: Int)
242+ Y(v :: Int)
243+
244+The following type is illegal, as the name `v` appears in multiple
245+constructors with differing types::
246+
247+ type Foo:
248+ A(u :: Int, v :: Int)
249+ B(v :: Array(Int)) # Error: Duplicate field name
250
251 .. note::
252 A constructor without parameters is, in effect, declaring a global
253
254=== modified file 'lib/prelude.mar'
255--- lib/prelude.mar 2010-05-06 13:26:56 +0000
256+++ lib/prelude.mar 2010-05-10 05:50:41 +0000
257@@ -216,8 +216,8 @@
258 switch x:
259 case Nil:
260 return y
261- case Cons(x, xs):
262- return Cons(x, append(xs, y))
263+ case Cons(h, t):
264+ return Cons(h, append(t, y))
265
266 # Returns the index of the first occurence of a particular element in a
267 # list, or -1 if not found.
268
269=== modified file 'src/ast_cfg.m'
270--- src/ast_cfg.m 2010-05-06 13:13:04 +0000
271+++ src/ast_cfg.m 2010-05-10 05:50:41 +0000
272@@ -80,10 +80,13 @@
273 :- import_module integer.
274 :- import_module bool.
275 :- import_module require.
276+:- import_module varset.
277
278 :- import_module cfg.
279+:- import_module types.
280 :- import_module context.
281 :- import_module util.
282+:- import_module pretty.
283
284 prog_to_cfg(PT, program(Nodes0), program(Nodes)) :-
285 prog_nodes_to_cfg(PT, Nodes0, Nodes).
286@@ -120,6 +123,26 @@
287 def_map_insert_local(Name-_, !DefMap) :-
288 map.det_insert(!.DefMap, Name, unbound, !:DefMap).
289
290+% Take the union of two type maps. It is an error if they have overlapping
291+% keys.
292+:- func type_map_union(type_map, type_map) = type_map.
293+type_map_union(X, Y) = map.union(
294+ %(func(_,_) = _ :- error(string.format(
295+ % "ast_cfg.type_map_union: Keys not disjoint (%s versus %s)",
296+ % [s(string.join_list(", ",
297+ % map(ir.varname_to_string_noescape, map.keys(X)))),
298+ % s(string.join_list(", ",
299+ % map(ir.varname_to_string_noescape, map.keys(Y))))]))),
300+ % XXX Possibility of binding the same variable name twice (bug #578068)
301+ % For now, just allow overlapping keys, and take the first (should always
302+ % be the same type anyway)
303+ (func(Z,_) = Z),
304+ X, Y).
305+
306+% Take the union of all the type maps in a list.
307+:- func type_map_union_list(list(type_map)) = type_map.
308+type_map_union_list(Ts) = foldl(type_map_union, Ts, map.init).
309+
310 func_to_cfg(PT, !Func) :-
311 % Create a new defmap with all of the params.
312 new_def_map(DefMap0),
313@@ -127,33 +150,41 @@
314 (
315 % No parameters
316 Params = no,
317- DefMap = DefMap0
318+ DefMap = DefMap0,
319+ Types = map.init
320 ;
321 Params = yes(YesParams),
322- foldl(def_map_insert_param, YesParams, DefMap0, DefMap)
323+ foldl(def_map_insert_param, YesParams, DefMap0, DefMap),
324+ Types = map.from_assoc_list(map(func({N,T,_}) = svname(N)-T,
325+ YesParams))
326 ),
327- func_body_to_cfg(PT, DefMap, !.Func ^ func_context, !.Func ^ func_body,
328- CFGBody),
329+ func_body_to_cfg(PT, DefMap, !.Func^func_varset, Types,
330+ !.Func ^ func_context, !.Func ^ func_body, CFGBody),
331 !:Func = !.Func ^ func_body := CFGBody.
332
333 % Note: def_map argument should have all of the function's parameters already
334-% bound in the map.
335-:- pred func_body_to_cfg(progtable::in, def_map::in, context::in,
336- func_body::in, func_body::out) is det.
337-func_body_to_cfg(_PT, _DefMap, _Ctx, B@func_builtin, B).
338-func_body_to_cfg(_PT, _DefMap, _Ctx, B@func_body_cfg(_,_), B).
339-func_body_to_cfg(PT, DefMap0, Ctx, func_body_ast(Decls,Stmts), NewFuncBody) :-
340- NewFuncBody = 'new func_body_cfg'(Decls, CFG),
341+% bound in the map. Likewise, type_map should have the type of each of the
342+% function's parameters' types.
343+:- pred func_body_to_cfg(progtable::in, def_map::in, varset::in, type_map::in,
344+ context::in, func_body::in, func_body::out) is det.
345+func_body_to_cfg(_PT, _DefMap, _Varset, _Types, _Ctx, B@func_builtin, B).
346+func_body_to_cfg(_PT, _DefMap, _Vset, _Types, _Ctx, B@func_body_cfg(_,_), B).
347+func_body_to_cfg(PT, DefMap0, Varset, Types0, Ctx,
348+ func_body_ast(Decls0,Stmts), NewFuncBody):-
349+ NewFuncBody = 'new func_body_cfg'(Types, CFG),
350 % Insert all of the function's locals into the defmap, unbound
351- foldl(def_map_insert_local, Decls, DefMap0, DefMap),
352- ast_to_cfg(PT, DefMap, Ctx, Stmts, CFG).
353+ foldl(def_map_insert_local, Decls0, DefMap0, DefMap),
354+ ast_to_cfg(PT, DefMap, Ctx, Stmts, Types1, CFG),
355+ Types_Raw = type_map_union(Types0, Types1),
356+ % Dereference all the types
357+ map.map_values_only(types.deref(Varset), Types_Raw, Types).
358
359 % ast_to_cfg(DefMap, Stmts, CFG) converts a statement block (AST form) to a
360 % control flow graph, translating the code.
361 % This also performs error checking (see func_to_cfg).
362 :- some [S] pred ast_to_cfg(progtable::in, def_map::in, context::in,
363- stmt_block::in, cfg(S)::out) is det.
364-ast_to_cfg(PT, DefMap, Ctx, Stmts, CFG) :-
365+ stmt_block::in, type_map::out, cfg(S)::out) is det.
366+ast_to_cfg(PT, DefMap, Ctx, Stmts, Types, CFG) :-
367 some [!CFG]
368 (
369 % Need to create the entry block and exit block so that
370@@ -162,7 +193,7 @@
371 !:CFG = cfg.new_cfg,
372 Entry = cfg.get_entry(!.CFG),
373 Exit = cfg.get_exit(!.CFG),
374- stmt_block_to_cfg(PT, Stmts, Entry, Exit, DefMap,
375+ stmt_block_to_cfg(PT, Stmts, Entry, Exit, DefMap, Types,
376 map.init,AfterPredMap, map.init, ExitPredMap, !CFG),
377 % The union of AfterPredMap and ExitPredMap contains information about
378 % all predecessors to Exit. Use this to compute phi instructions for
379@@ -228,6 +259,10 @@
380 % have a key in the map.
381 :- type subscript_map == map(varname, int).
382
383+% type_map
384+% Map SSA variable names to types.
385+:- type type_map == map(varname, typeval).
386+
387 % new_ssa_variable(BlockID, VarName, QualVarName, !SubscriptMap, !DefMap).
388 % Given an unqualified variable name, produces a new qualified variable name
389 % which is unique, and updates the subscript map accordingly.
390@@ -404,6 +439,10 @@
391 )
392 ;
393 % Disagreement. See if the variable is bound for all predecessors.
394+ % XXX This assumes that all predecessors have an entry in the PredMap,
395+ % which is only true for all predecessors in which this variable was
396+ % in-scope (this is only true because Mars has no block-level scopes,
397+ % but wasn't always true -- see Launchpad bug #567082).
398 ( foldl((pred(X-bound(V)::in, Map0::in, Map::out) is semidet :-
399 map.set(Map0, X, V, Map)),
400 PredAssoc, map.init, BoundAssoc) ->
401@@ -459,7 +498,7 @@
402 map.det_insert(!.Map, U, TVMap, !:Map)
403 ).
404
405-% stmt_block_to_cfg(+Stmts, +BBCurrent, +BBAfter, +DefMap,
406+% stmt_block_to_cfg(+Stmts, +BBCurrent, +BBAfter, +DefMap, -Types,
407 % !AfterPredMap, !ExitPredMap, !CFG).
408 % Compiles a statement block into basic blocks. Begins inserting statements
409 % into BBCurrent, and may create more blocks as necessary.
410@@ -471,39 +510,41 @@
411 % AfterPredMap contains information about predecessors to the BBAfter block --
412 % this may append to the map information about blocks which branch to BBAfter,
413 % for the purpose of computing phis.
414+% Returns the types of all assigned variables in Types.
415 % Throws a context error if there is an attempt to read from a variable which
416 % may not have been assigned on some or all code paths.
417 :- pred stmt_block_to_cfg(progtable::in, stmt_block::in, bbref(S)::in,
418- bbref(S)::in, def_map::in, pred_map(S)::in, pred_map(S)::out,
419- pred_map(S)::in, pred_map(S)::out, cfg(S)::in, cfg(S)::out)
420- is det.
421-stmt_block_to_cfg(PT, Stmts, BBCurrent, BBAfter, DefMap, !AfterPredMap,
422- !ExitPredMap, !CFG) :-
423+ bbref(S)::in, def_map::in, type_map::out,
424+ pred_map(S)::in, pred_map(S)::out, pred_map(S)::in, pred_map(S)::out,
425+ cfg(S)::in, cfg(S)::out) is det.
426+stmt_block_to_cfg(PT, Stmts, BBCurrent, BBAfter, DefMap, Types,
427+ !AfterPredMap, !ExitPredMap, !CFG) :-
428 map.init(SubscriptMap),
429 stmt_block_to_cfg(PT, Stmts, BBCurrent, BBAfter, SubscriptMap, DefMap,
430- !AfterPredMap, !ExitPredMap, !CFG).
431+ Types, !AfterPredMap, !ExitPredMap, !CFG).
432
433 :- pred stmt_block_to_cfg(progtable::in, stmt_block::in, bbref(S)::in,
434- bbref(S)::in,
435- subscript_map::in, def_map::in, pred_map(S)::in, pred_map(S)::out,
436+ bbref(S)::in, subscript_map::in, def_map::in, type_map::out,
437+ pred_map(S)::in, pred_map(S)::out,
438 pred_map(S)::in, pred_map(S)::out, cfg(S)::in, cfg(S)::out) is det.
439-stmt_block_to_cfg(_PT, [], BBCurrent, BBAfter, _SubscriptMap, DefMap,
440- !AfterPredMap, !ExitPredMap, !CFG) :-
441+stmt_block_to_cfg(_PT, [], BBCurrent, BBAfter, _SubscriptMap,
442+ DefMap, map.init, !AfterPredMap, !ExitPredMap, !CFG) :-
443 % Special case for empty block - just branch to BBAfter.
444 add_to_pred_map(BBCurrent, DefMap, BBAfter, !AfterPredMap, !CFG),
445 cfg.set_terminator(BBCurrent, branch(BBAfter, blank_context), !CFG).
446-stmt_block_to_cfg(PT, [S], BBCurrent, BBAfter, SubscriptMap, DefMap,
447+stmt_block_to_cfg(PT, [S], BBCurrent, BBAfter, SubscriptMap, DefMap, Types,
448 !AfterPredMap, !ExitPredMap, !CFG) :-
449 % Base-case for the last statement in a block - compile statement into
450 % BBCurrent, but end up by branching to BBAfter.
451- stmt_to_cfg_last(PT, S, BBCurrent, BBAfter, SubscriptMap, DefMap,
452+ stmt_to_cfg_last(PT, S, BBCurrent, BBAfter, SubscriptMap, DefMap, Types,
453 !AfterPredMap, !ExitPredMap, !CFG).
454-stmt_block_to_cfg(PT, [S|Ss@[_|_]], BBCurrent, BBAfter, SubscriptMap0,DefMap0,
455- !AfterPredMap, !ExitPredMap, !CFG) :-
456+stmt_block_to_cfg(PT, [S|Ss@[_|_]], BBCurrent, BBAfter, SubscriptMap0,
457+ DefMap0, Types, !AfterPredMap, !ExitPredMap, !CFG) :-
458 % Compile a single statement into BBCurrent. BBContinue is the block to
459 % compile subsequent statements into (may be equal to BBCurrent).
460- stmt_to_cfg(PT, S, BBCurrent, BBContinue, Terminated,
461- SubscriptMap0, SubscriptMap, DefMap0, DefMap, !ExitPredMap, !CFG),
462+ stmt_to_cfg(PT, S, BBCurrent, BBContinue, Terminated, Types0,
463+ SubscriptMap0, SubscriptMap, DefMap0, DefMap, !ExitPredMap,
464+ !CFG),
465 % Compile subsequent statements into BBContinue, if not terminated.
466 % If Terminated is 'yes', the rest of this block is inaccessible, so DO
467 % NOT generate code for it. This doesn't just save time -- it is NECESSARY
468@@ -511,16 +552,18 @@
469 % contain local variables -- this can cause malformed code generation --
470 % see bug #517403.
471 (
472- Terminated = yes
473+ Terminated = yes,
474+ Types = Types0
475 ;
476 Terminated = no,
477 stmt_block_to_cfg(PT, Ss, BBContinue, BBAfter, SubscriptMap, DefMap,
478- !AfterPredMap, !ExitPredMap, !CFG)
479+ Types1, !AfterPredMap, !ExitPredMap, !CFG),
480+ Types = type_map_union(Types0, Types1)
481 ).
482
483 %%% HIGH-LEVEL STATEMENT-COMPILATION PREDICATES %%%
484
485-% stmt_to_cfg(+Stmt, +BBCurrent, -BBAfter, -Terminated, !SubscriptMap,
486+% stmt_to_cfg(+Stmt, +BBCurrent, -BBAfter, -Terminated, -Types, !SubscriptMap,
487 % !DefMap, !ExitPredMap, !CFG).
488 % Compiles a single statement into basic blocks. Assumes this statement is NOT
489 % the last statement in its containing block (if it is, no harm, but may
490@@ -537,18 +580,18 @@
491 % and therefore, the rest of the block is inaccessible.
492 % May also update def_map with any new variable definitions.
493 :- pred stmt_to_cfg(progtable::in, stmt::in, bbref(S)::in, bbref(S)::out,
494- bool::out, subscript_map::in, subscript_map::out,
495+ bool::out, type_map::out, subscript_map::in, subscript_map::out,
496 def_map::in, def_map::out, pred_map(S)::in, pred_map(S)::out,
497 cfg(S)::in, cfg(S)::out) is det.
498-stmt_to_cfg(_PT, basic_stmt(S,Ctx), !BBRef, no, !SubscriptMap, !DefMap,
499+stmt_to_cfg(_PT, basic_stmt(S,Ctx), !BBRef, no, Types, !SubscriptMap, !DefMap,
500 !ExitPredMap, !CFG) :-
501- basic_stmt_to_cfg(S, Ctx, !.BBRef, !SubscriptMap, !DefMap, !CFG).
502-stmt_to_cfg(PT, compound_stmt(S,Ctx), BBCurrent, BBAfter, Terminated,
503+ basic_stmt_to_cfg(S, Ctx, !.BBRef, Types, !SubscriptMap, !DefMap, !CFG).
504+stmt_to_cfg(PT, compound_stmt(S,Ctx), BBCurrent, BBAfter, Terminated, Types,
505 !SubscriptMap, !DefMap, !ExitPredMap, !CFG) :-
506 % Generate a target block for the compound statement to branch to
507 cfg.new_basic_block(BBAfter, !CFG),
508 compound_stmt_to_cfg(PT, S, Ctx, BBCurrent, BBAfter, !.SubscriptMap,
509- !.DefMap, map.init, AfterPredMap, !ExitPredMap, !CFG),
510+ !.DefMap, Types, map.init, AfterPredMap, !ExitPredMap, !CFG),
511 % AfterPredMap contains information about all predecessors to BBAfter.
512 % Use this to compute phi instructions for BBAfter and update DefMap.
513 AfterID = ref_id(BBAfter, !.CFG),
514@@ -564,7 +607,7 @@
515 cfg.set_phis(BBAfter, Phis, !CFG).
516
517 % stmt_to_cfg_last(+Stmt, +BBCurrent, +BBAfter, +SubscriptMap, +DefMap,
518-% !AfterPredMap, !ExitPredMap, !CFG).
519+% -Types, !AfterPredMap, !ExitPredMap, !CFG).
520 % Special version of stmt_to_cfg, used on the last statement in a statement
521 % block to avoid generating redundant empty basic blocks.
522 % Inserts the statement into BBCurrent, and ensures BBCurrent is complete.
523@@ -576,31 +619,41 @@
524 % May update DefMap with new bindings, but SubscriptMap is read-only (since it
525 % will definitely branch to a new block).
526 :- pred stmt_to_cfg_last(progtable::in, stmt::in, bbref(S)::in, bbref(S)::in,
527- subscript_map::in, def_map::in, pred_map(S)::in, pred_map(S)::out,
528- pred_map(S)::in, pred_map(S)::out, cfg(S)::in, cfg(S)::out) is det.
529+ subscript_map::in, def_map::in, type_map::out,
530+ pred_map(S)::in, pred_map(S)::out, pred_map(S)::in, pred_map(S)::out,
531+ cfg(S)::in, cfg(S)::out) is det.
532 stmt_to_cfg_last(_PT, basic_stmt(S,Ctx), BBCurrent, BBAfter, SubscriptMap,
533- DefMap, !AfterPredMap, !ExitPredMap, !CFG) :-
534- basic_stmt_to_cfg(S, Ctx, BBCurrent, SubscriptMap, _, DefMap, NewDefMap,
535- !CFG),
536+ DefMap, Types, !AfterPredMap, !ExitPredMap, !CFG) :-
537+ basic_stmt_to_cfg(S, Ctx, BBCurrent, Types, SubscriptMap, _, DefMap,
538+ NewDefMap, !CFG),
539 % Branch to the provided BBAfter
540 add_to_pred_map(BBCurrent, NewDefMap, BBAfter, !AfterPredMap, !CFG),
541 cfg.set_terminator(BBCurrent, branch(BBAfter, Ctx), !CFG).
542 stmt_to_cfg_last(PT, compound_stmt(S,Ctx), BBCurrent, BBAfter, SubscriptMap,
543- DefMap, !AfterPredMap, !ExitPredMap, !CFG) :-
544+ DefMap, Types, !AfterPredMap, !ExitPredMap, !CFG) :-
545 compound_stmt_to_cfg(PT, S, Ctx, BBCurrent, BBAfter, SubscriptMap,
546- DefMap, !AfterPredMap, !ExitPredMap, !CFG).
547+ DefMap, Types, !AfterPredMap, !ExitPredMap, !CFG).
548
549 %%% LOW-LEVEL STATEMENT-COMPILATION PREDICATES %%%
550 % Either of the above two statement compilation predicates may call either of
551 % the two low-level predicates, which handle the compilation of each statement
552 % kind.
553
554-% exprs_to_instrs(+BlockID, +Ctx, +Exprs, -VarNames, -Instrs, !SubscriptMap).
555+% Put an expression's type in a singleton typemap bound to V.
556+% Raises an error if the expression has no type annotation.
557+:- func expr_typemap(varname, expr) = type_map.
558+expr_typemap(_, E@expr(_,no)) = _ :-
559+ error("ast_cfg: Expression has no associated type: " ++
560+ pretty.string_expr(E)).
561+expr_typemap(V, expr(_, yes(T))) = map.from_assoc_list([V-T]).
562+
563+% exprs_to_instrs(+BlockID, +Ctx, +Exprs, -VarNames, -Instrs, -Types,
564+% !SubscriptMap).
565 :- pred exprs_to_instrs(int::in, context::in, list(expr)::in,
566- list(varname)::out, list(instr)::out,
567+ list(varname)::out, list(instr)::out, type_map::out,
568 subscript_map::in, subscript_map::out) is det.
569-exprs_to_instrs(BlockID, Ctx, Es, VarNames, Instrs, !SubscriptMap) :-
570- exprs_to_instrs_(BlockID, Ctx, Es, [], VarNamesRev, [], LLInstrsRev,
571+exprs_to_instrs(BlockID, Ctx, Es, VarNames, Instrs, Types, !SubscriptMap) :-
572+ exprs_to_instrs_(BlockID, Ctx, Es, Types, [], VarNamesRev, [],LLInstrsRev,
573 !SubscriptMap),
574 list.reverse(VarNamesRev, VarNames),
575 list.reverse(LLInstrsRev, LLInstrs),
576@@ -611,144 +664,176 @@
577 % (so it ends up reversed).
578 % Instrs is a list of lists (to be flattened). The outer list is reversed, the
579 % inner list is not -- this is to allow prepending.
580-:- pred exprs_to_instrs_(int::in, context::in, list(expr)::in,
581+:- pred exprs_to_instrs_(int::in, context::in, list(expr)::in, type_map::out,
582 list(varname)::in, list(varname)::out,
583 list(list(instr))::in, list(list(instr))::out,
584 subscript_map::in, subscript_map::out) is det.
585-exprs_to_instrs_(_BlockID, _Ctx, [], !VarNames, !Instrs, !SubscriptMap).
586-exprs_to_instrs_(BlockID, Ctx, [E|Es], !VarNames, !Instrs, !SubscriptMap) :-
587+exprs_to_instrs_(_BlockID, _Ctx, [], map.init, !VarNames, !Instrs,
588+ !SubscriptMap).
589+exprs_to_instrs_(BlockID,Ctx,[E|Es],Types,!VarNames,!Instrs,!SubscriptMap) :-
590 % Create a new variable name and generate instructions for each expr
591- expr_to_instrs(BlockID, Ctx, E, V, Is, !SubscriptMap),
592+ expr_to_instrs(BlockID, Ctx, E, V, Is, Types0, !SubscriptMap),
593 !:VarNames = [V | !.VarNames],
594 !:Instrs = [Is | !.Instrs], % Do not flatten Is; keep as list of lists
595- exprs_to_instrs_(BlockID, Ctx, Es, !VarNames, !Instrs, !SubscriptMap).
596+ exprs_to_instrs_(BlockID, Ctx, Es, Types1, !VarNames, !Instrs,
597+ !SubscriptMap),
598+ Types = type_map_union(Types0, Types1).
599
600 % expr_to_instrs(+BlockID, +Ctx, +Expr, -VarName, -Instrs, !SubscriptMap).
601 % Converts a single expression into a sequence of low-level instructions
602 % which compute the expression and assign it to a variable (possibly a
603 % new temporary variable name). Returns the assigned variable name in VarName.
604 :- pred expr_to_instrs(int::in, context::in, expr::in, varname::out,
605- list(instr)::out, subscript_map::in, subscript_map::out) is det.
606-expr_to_instrs(BlockID, Ctx, E, V, Is, !SubscriptMap) :-
607+ list(instr)::out, type_map::out, subscript_map::in, subscript_map::out)
608+ is det.
609+expr_to_instrs(BlockID, Ctx, E, V, Is, Types, !SubscriptMap) :-
610 (E = expr(varref(Var), _) ->
611 % Special case -- expr_to_instrs_as will generate a mov.
612 % We can avoid this by not generating a temp var, and just returning
613 % the variable name (with no instructions at all).
614 V = Var,
615- Is = []
616+ Is = [],
617+ Types = map.init
618 ;
619 new_temp_variable(BlockID, V, !SubscriptMap),
620- expr_to_instrs_as(BlockID, Ctx, E, V, Is, !SubscriptMap)
621+ expr_to_instrs_as(BlockID, Ctx, E, V, Is, Types, !SubscriptMap)
622 ).
623
624 expr_to_instrs(E, V, Is) :-
625- expr_to_instrs(0, context.blank_context, E, V, Is, map.init, _).
626+ expr_to_instrs(0, context.blank_context, E, V, Is, _, map.init, _).
627
628-% expr_to_instrs_as(+BlockID, +Ctx, +Expr, +VarName, -Instrs, !SubscriptMap).
629+% expr_to_instrs_as(+BlockID, +Ctx, +Expr, +VarName, -Instrs, -Types,
630+% !SubscriptMap).
631 % Like expr_to_instrs, but it assigns to a specific VarName as given.
632 % (This is less efficient as it may generate a mov instruction).
633 :- pred expr_to_instrs_as(int::in, context::in, expr::in, varname::in,
634- list(instr)::out, subscript_map::in, subscript_map::out) is det.
635-expr_to_instrs_as(_BlockID, Ctx, expr(intlit(Val),_), V, Is, !SubscriptMap) :-
636+ list(instr)::out, type_map::out, subscript_map::in, subscript_map::out)
637+ is det.
638+expr_to_instrs_as(_BlockID, Ctx, E@expr(intlit(Val),_), V, Is, Types,
639+ !SubscriptMap) :-
640+ Types = expr_typemap(V, E),
641 Is = [instr(ld_intlit(V, Val), Ctx)].
642-expr_to_instrs_as(BlockID, Ctx, expr(arraylit(Elems0),_), V, Is,
643+expr_to_instrs_as(BlockID, Ctx, E@expr(arraylit(Elems0),_), V, Is, Types,
644 !SubscriptMap) :-
645- exprs_to_instrs(BlockID, Ctx, Elems0, Elems, Is0, !SubscriptMap),
646+ ( varname_is_global(V) ->
647+ % Don't assign types to global variables
648+ Types0 = map.init
649+ ;
650+ Types0 = expr_typemap(V, E)
651+ ),
652+ exprs_to_instrs(BlockID, Ctx, Elems0, Elems, Is0, Types1, !SubscriptMap),
653+ Types = type_map_union(Types0, Types1),
654 Is = Is0 ++ [instr(ld_arraylit(V, Elems), Ctx)].
655-expr_to_instrs_as(_BlockID, Ctx, expr(varref(Var),_), V, Is, !SubscriptMap) :-
656+expr_to_instrs_as(_BlockID, Ctx, E@expr(varref(Var),_), V, Is, Types,
657+ !SubscriptMap) :-
658+ Types = expr_typemap(V, E),
659 Is = [instr(mov(V, Var), Ctx)].
660-expr_to_instrs_as(_BlockID, Ctx, expr(ctorref(Name),_), V, Is,
661+expr_to_instrs_as(_BlockID, Ctx, E@expr(ctorref(Name),_), V, Is, Types,
662 !SubscriptMap) :-
663+ Types = expr_typemap(V, E),
664 Is = [instr(ld_ctor(V, Name), Ctx)].
665-expr_to_instrs_as(BlockID, Ctx, expr(fieldref(Obj0, Field),_), V, Is,
666+expr_to_instrs_as(BlockID, Ctx, E@expr(fieldref(Obj0, Field),_), V, Is, Types,
667 !SubscriptMap) :-
668- expr_to_instrs(BlockID, Ctx, Obj0, Obj, Is0, !SubscriptMap),
669+ Types0 = expr_typemap(V, E),
670+ expr_to_instrs(BlockID, Ctx, Obj0, Obj, Is0, Types1, !SubscriptMap),
671+ Types = type_map_union(Types0, Types1),
672 Is = Is0 ++ [instr(ld_field(V, Obj, Field), Ctx)].
673-expr_to_instrs_as(BlockID, Ctx, expr(app(Func0, Args0),_), V, Is,
674+expr_to_instrs_as(BlockID, Ctx, E@expr(app(Func0, Args0),_), V, Is, Types,
675 !SubscriptMap) :-
676- expr_to_instrs(BlockID, Ctx, Func0, Func, Is0, !SubscriptMap),
677- exprs_to_instrs(BlockID, Ctx, Args0, Args, Is1, !SubscriptMap),
678+ Types0 = expr_typemap(V, E),
679+ expr_to_instrs(BlockID, Ctx, Func0, Func, Is0, Types1, !SubscriptMap),
680+ exprs_to_instrs(BlockID, Ctx, Args0, Args, Is1, Types2, !SubscriptMap),
681+ Types = type_map_union(Types0, type_map_union(Types1, Types2)),
682 Is2 = [instr(call(V, Func, Args), Ctx)],
683 Is = Is0 ++ Is1 ++ Is2.
684-expr_to_instrs_as(BlockID, Ctx, expr(parapp(Func0, Args0),_), V, Is,
685+expr_to_instrs_as(BlockID, Ctx, E@expr(parapp(Func0, Args0),_), V, Is, Types,
686 !SubscriptMap) :-
687- expr_to_instrs(BlockID, Ctx, Func0, Func, Is0, !SubscriptMap),
688- exprs_to_instrs(BlockID, Ctx, Args0, Args, Is1, !SubscriptMap),
689+ Types0 = expr_typemap(V, E),
690+ expr_to_instrs(BlockID, Ctx, Func0, Func, Is0, Types1, !SubscriptMap),
691+ exprs_to_instrs(BlockID, Ctx, Args0, Args, Is1, Types2, !SubscriptMap),
692+ Types = type_map_union(Types0, type_map_union(Types1, Types2)),
693 Is2 = [instr(parcall(V, Func, Args), Ctx)],
694 Is = Is0 ++ Is1 ++ Is2.
695
696 basic_stmt_to_instrs(BasicStmt, Instrs) :-
697- basic_stmt_to_instrs(0, BasicStmt, context.blank_context, Instrs,
698+ basic_stmt_to_instrs(0, BasicStmt, context.blank_context, _, Instrs,
699 map.init, _).
700
701-% basic_stmt_to_instrs(+BlockID, +BasicStmt, +Ctx, -Instrs, !SubscriptMap).
702+% basic_stmt_to_instrs(+BlockID, +BasicStmt, +Ctx, -Types, -Instrs,
703+% !SubscriptMap).
704 % Converts a single basic statement into a sequence of low-level instructions
705 % which do the same thing. This will potentially assign many temporary
706 % variables.
707 :- pred basic_stmt_to_instrs(int::in, basic_stmt::in, context::in,
708- list(instr)::out, subscript_map::in, subscript_map::out) is det.
709-basic_stmt_to_instrs(_BlockID, pass, _Ctx, [], !SubscriptMap).
710-basic_stmt_to_instrs(BlockID, assign(V, E), Ctx, Is, !SubscriptMap) :-
711- expr_to_instrs_as(BlockID, Ctx, E, V, Is, !SubscriptMap).
712-basic_stmt_to_instrs(BlockID, fieldset(Obj0, Field, Val0), Ctx, Is,
713+ type_map::out, list(instr)::out, subscript_map::in, subscript_map::out)
714+ is det.
715+basic_stmt_to_instrs(_BlockID, pass, _Ctx, map.init, [], !SubscriptMap).
716+basic_stmt_to_instrs(BlockID, assign(V, E), Ctx, Types, Is, !SubscriptMap) :-
717+ expr_to_instrs_as(BlockID, Ctx, E, V, Is, Types, !SubscriptMap).
718+basic_stmt_to_instrs(BlockID, fieldset(Obj0, Field, Val0), Ctx, Types, Is,
719 !SubscriptMap) :-
720- expr_to_instrs(BlockID, Ctx, Obj0, Obj, Is0, !SubscriptMap),
721- expr_to_instrs(BlockID, Ctx, Val0, Val, Is1, !SubscriptMap),
722+ expr_to_instrs(BlockID, Ctx, Obj0, Obj, Is0, Types0, !SubscriptMap),
723+ expr_to_instrs(BlockID, Ctx, Val0, Val, Is1, Types1, !SubscriptMap),
724+ Types = type_map_union(Types0, Types1),
725 Is2 = [instr(i_fieldset(Obj, Field, Val), Ctx)],
726 Is = Is0 ++ Is1 ++ Is2.
727-basic_stmt_to_instrs(BlockID, fieldreplace(Obj0, Field, Val0), Ctx, Is,
728+basic_stmt_to_instrs(BlockID, fieldreplace(Obj0, Field, Val0), Ctx, Types, Is,
729 !SubscriptMap) :-
730 % XXX fieldreplace statement is very weird (should be an expr).
731 % Currently re-assign to the same variable.
732- expr_to_instrs(BlockID, Ctx, Obj0, Obj, Is0, !SubscriptMap),
733- expr_to_instrs(BlockID, Ctx, Val0, Val, Is1, !SubscriptMap),
734+ expr_to_instrs(BlockID, Ctx, Obj0, Obj, Is0, Types0, !SubscriptMap),
735+ expr_to_instrs(BlockID, Ctx, Val0, Val, Is1, Types1, !SubscriptMap),
736+ Types = type_map_union(Types0, Types1),
737 Is2 = [instr(i_fieldreplace(Obj, Obj, Field, Val), Ctx)],
738 Is = Is0 ++ Is1 ++ Is2.
739-basic_stmt_to_instrs(BlockID, eval(E), Ctx, Is, !SubscriptMap) :-
740+basic_stmt_to_instrs(BlockID, eval(E), Ctx, Types, Is, !SubscriptMap) :-
741 % The variable _T is assigned to, then thrown away.
742- expr_to_instrs(BlockID, Ctx, E, _T, Is, !SubscriptMap).
743+ expr_to_instrs(BlockID, Ctx, E, _T, Is, Types, !SubscriptMap).
744
745-% basic_stmt_to_cfg(+BasicStmt, +Ctx, +BBCurrent, !SubscriptMap, !DefMap,
746-% !CFG).
747+% basic_stmt_to_cfg(+BasicStmt, +Ctx, +BBCurrent, -Types, !SubscriptMap,
748+% !DefMap, !CFG).
749 % Compiles a single basic statement into a basic block. Appends the statement
750 % to the end of BBCurrent. May also update SubscriptMap and DefMap with any
751 % newly-defined variables.
752 :- pred basic_stmt_to_cfg(basic_stmt::in, context::in, bbref(S)::in,
753- subscript_map::in, subscript_map::out, def_map::in, def_map::out,
754- cfg(S)::in, cfg(S)::out) is det.
755+ type_map::out, subscript_map::in, subscript_map::out,
756+ def_map::in, def_map::out, cfg(S)::in, cfg(S)::out) is det.
757 % "pass" statements disappear at this point
758-basic_stmt_to_cfg(pass, _Ctx, _BBCurrent, !SubscriptMap, !DefMap, !CFG).
759-basic_stmt_to_cfg(assign(Var0, E0), Ctx, BBCurrent, !SubscriptMap, !DefMap,
760- !CFG) :-
761+basic_stmt_to_cfg(pass, _Ctx, _BBCurrent, map.init, !SubscriptMap, !DefMap,
762+ !CFG).
763+basic_stmt_to_cfg(assign(Var0, E0), Ctx, BBCurrent, Types, !SubscriptMap,
764+ !DefMap, !CFG) :-
765 apply_def_map_to_expr(!.DefMap, Ctx, E0, E),
766 BlockID = ref_id(BBCurrent, !.CFG),
767 new_ssa_variable(BlockID, Var0, Var, !SubscriptMap, !DefMap),
768- basic_stmt_to_instrs(BlockID, assign(Var, E), Ctx, Instrs, !SubscriptMap),
769+ basic_stmt_to_instrs(BlockID, assign(Var, E), Ctx, Types, Instrs,
770+ !SubscriptMap),
771 cfg.append_instrs(BBCurrent, Instrs, !CFG).
772-basic_stmt_to_cfg(fieldset(Target0,FieldName,Expr0), Ctx, BBCurrent,
773+basic_stmt_to_cfg(fieldset(Target0,FieldName,Expr0), Ctx, BBCurrent, Types,
774 !SubscriptMap, !DefMap, !CFG) :-
775 apply_def_map_to_expr(!.DefMap, Ctx, Target0, Target),
776 apply_def_map_to_expr(!.DefMap, Ctx, Expr0, Expr),
777 BlockID = ref_id(BBCurrent, !.CFG),
778 basic_stmt_to_instrs(BlockID, fieldset(Target, FieldName, Expr), Ctx,
779- Instrs, !SubscriptMap),
780+ Types, Instrs, !SubscriptMap),
781 cfg.append_instrs(BBCurrent, Instrs, !CFG).
782 basic_stmt_to_cfg(fieldreplace(Target0,FieldName,Expr0), Ctx, BBCurrent,
783- !SubscriptMap, !DefMap, !CFG) :-
784+ Types, !SubscriptMap, !DefMap, !CFG) :-
785 apply_def_map_to_expr(!.DefMap, Ctx, Target0, Target),
786 apply_def_map_to_expr(!.DefMap, Ctx, Expr0, Expr),
787 BlockID = ref_id(BBCurrent, !.CFG),
788 basic_stmt_to_instrs(BlockID, fieldreplace(Target, FieldName, Expr), Ctx,
789- Instrs, !SubscriptMap),
790+ Types, Instrs, !SubscriptMap),
791 cfg.append_instrs(BBCurrent, Instrs, !CFG).
792-basic_stmt_to_cfg(eval(E0), Ctx, BBCurrent, !SubscriptMap, !DefMap, !CFG) :-
793+basic_stmt_to_cfg(eval(E0), Ctx, BBCurrent, Types, !SubscriptMap, !DefMap,
794+ !CFG) :-
795 apply_def_map_to_expr(!.DefMap, Ctx, E0, E),
796 BlockID = ref_id(BBCurrent, !.CFG),
797- basic_stmt_to_instrs(BlockID, eval(E), Ctx, Instrs, !SubscriptMap),
798+ basic_stmt_to_instrs(BlockID, eval(E), Ctx, Types, Instrs, !SubscriptMap),
799 cfg.append_instrs(BBCurrent, Instrs, !CFG).
800
801 % compound_stmt_to_cfg(+CompoundStmt, +Ctx, +BBCurrent, +BBAfter,
802-% +SubscriptMap, +DefMap, !AfterPredMap, !ExitPredMap, !CFG).
803+% +SubscriptMap, +DefMap, -Types, !AfterPredMap, !ExitPredMap, !CFG).
804 % Compiles a single compound statement into a basic block. Appends statements
805 % to the end of BBCurrent and completes that block (with a terminator). May
806 % generate new basic blocks, and ensures they are complete as well.
807@@ -761,30 +846,33 @@
808 % DefMap is read-only (the resulting def-maps should be appended to
809 % AfterPredMap).
810 :- pred compound_stmt_to_cfg(progtable::in, compound_stmt::in, context::in,
811- bbref(S)::in, bbref(S)::in, subscript_map::in, def_map::in,
812+ bbref(S)::in, bbref(S)::in, subscript_map::in, def_map::in, type_map::out,
813 pred_map(S)::in, pred_map(S)::out, pred_map(S)::in, pred_map(S)::out,
814 cfg(S)::in, cfg(S)::out) is det.
815 compound_stmt_to_cfg(_PT,return(Expr), Ctx, BBCurrent, _BBAfter, SubscriptMap,
816- DefMap0, !AfterPredMap, !ExitPredMap, !CFG) :-
817+ DefMap0, Types, !AfterPredMap, !ExitPredMap, !CFG) :-
818 % Return is expressed in CFG as $RET = expr, followed by a branch to the
819 % exit block.
820- basic_stmt_to_cfg(assign(retvname, Expr), Ctx, BBCurrent,
821+ basic_stmt_to_cfg(assign(retvname, Expr), Ctx, BBCurrent, Types,
822 SubscriptMap, _, DefMap0, DefMap, !CFG),
823 ExitBlock = cfg.get_exit(!.CFG),
824 add_to_pred_map(BBCurrent, DefMap, ExitBlock, !ExitPredMap, !CFG),
825 cfg.set_terminator(BBCurrent, branch(ExitBlock, Ctx), !CFG).
826 compound_stmt_to_cfg(PT, switch(Ctrl0, Cases0), Ctx, BBCurrent, BBAfter,
827- SubscriptMap, DefMap, !AfterPredMap, !ExitPredMap, !CFG) :-
828+ SubscriptMap, DefMap, Types, !AfterPredMap, !ExitPredMap, !CFG) :-
829 % Calculate the condition expression at the end of BBCurrent
830 apply_def_map_to_expr(DefMap, Ctx, Ctrl0, Ctrl),
831 BlockID = ref_id(BBCurrent, !.CFG),
832- expr_to_instrs(BlockID, Ctx, Ctrl, CtrlVar, CtrlInstrs, SubscriptMap, _),
833+ expr_to_instrs(BlockID, Ctx, Ctrl, CtrlVar, CtrlInstrs, Types0,
834+ SubscriptMap, _),
835 cfg.append_instrs(BBCurrent, CtrlInstrs, !CFG),
836 % Convert all patterns to use SSA variables, and generate CFG code for the
837 % bodies of all case statements. The resulting Cases contains goto
838 % statements for each generated block.
839 list.map_foldl3(case_stmt_to_jmp(PT,BBCurrent,BBAfter,SubscriptMap,DefMap),
840- Cases0, Cases, !AfterPredMap, !ExitPredMap, !CFG),
841+ Cases0, CasesTypes, !AfterPredMap, !ExitPredMap, !CFG),
842+ Cases = map(fst, CasesTypes),
843+ Types = type_map_union_list([Types0|map(snd, CasesTypes)]),
844 % Now begin switch factoring transformation
845 % Convert each case statement to a matcher (flatten the patterns)
846 Matchers = list.map(case_to_matcher, Cases),
847@@ -793,35 +881,39 @@
848 SubscriptMap, Ctx, map.init, PhiTable, !CFG),
849 map.foldl(generate_case_block_phis, PhiTable, !CFG).
850 compound_stmt_to_cfg(PT, if_then_else(Cond0,ThenPart,ElsePart), Ctx,BBCurrent,
851- BBAfter, SubscriptMap, DefMap, !AfterPredMap, !ExitPredMap, !CFG) :-
852+ BBAfter, SubscriptMap, DefMap, Types, !AfterPredMap, !ExitPredMap,
853+ !CFG) :-
854 % Calculate the condition expression at the end of BBCurrent
855 apply_def_map_to_expr(DefMap, Ctx, Cond0, Cond),
856 BlockID = ref_id(BBCurrent, !.CFG),
857- expr_to_instrs(BlockID, Ctx, Cond, CondVar, CondInstrs, SubscriptMap, _),
858+ expr_to_instrs(BlockID, Ctx, Cond, CondVar, CondInstrs, Types0,
859+ SubscriptMap, _),
860 cfg.append_instrs(BBCurrent, CondInstrs, !CFG),
861 % Create a new basic block for the "then" part.
862 cfg.new_basic_block(ThenEnter, !CFG),
863 cfg.append_predecessor(ThenEnter, BBCurrent, !CFG),
864- stmt_block_to_cfg(PT, ThenPart, ThenEnter, BBAfter, DefMap, !AfterPredMap,
865- !ExitPredMap, !CFG),
866+ stmt_block_to_cfg(PT, ThenPart, ThenEnter, BBAfter, DefMap, Types1,
867+ !AfterPredMap, !ExitPredMap, !CFG),
868 ( list.is_empty(ElsePart) ->
869 % Branch straight to the "after" block if the condition fails
870 add_to_pred_map(BBCurrent, DefMap, BBAfter, !AfterPredMap, !CFG),
871 cfg.set_terminator(BBCurrent,
872- cond_branch(CondVar,ThenEnter,BBAfter,Ctx), !CFG)
873+ cond_branch(CondVar,ThenEnter,BBAfter,Ctx), !CFG),
874+ Types = type_map_union(Types0, Types1)
875 ;
876 % Create a new basic block for the "else" part.
877 cfg.new_basic_block(ElseEnter, !CFG),
878 cfg.append_predecessor(ElseEnter, BBCurrent, !CFG),
879- stmt_block_to_cfg(PT, ElsePart, ElseEnter, BBAfter, DefMap,
880+ stmt_block_to_cfg(PT, ElsePart, ElseEnter, BBAfter, DefMap, Types2,
881 !AfterPredMap, !ExitPredMap, !CFG),
882 % Have the current block terminate by branching into the then/else
883 % blocks
884 cfg.set_terminator(BBCurrent,
885- cond_branch(CondVar,ThenEnter,ElseEnter,Ctx), !CFG)
886+ cond_branch(CondVar,ThenEnter,ElseEnter,Ctx), !CFG),
887+ Types = type_map_union(Types0, type_map_union(Types1, Types2))
888 ).
889 compound_stmt_to_cfg(PT, while(Cond0, Body), Ctx, BBCurrent, BBAfter,
890- SubscriptMap, DefMap, !AfterPredMap, !ExitPredMap, !CFG) :-
891+ SubscriptMap, DefMap, Types, !AfterPredMap, !ExitPredMap, !CFG) :-
892 % Create a new basic block for the condition and body
893 cfg.new_basic_block(CondBlock, !CFG),
894 cfg.new_basic_block(BodyEnter, !CFG),
895@@ -840,7 +932,7 @@
896
897 % Do the whole fixpoint. Updates CFG by setting CondBlock's phis, and
898 % compiling Body.
899- while_fixpoint(PT, CondBlock, BodyEnter, Body, CondBlockPredMap,
900+ while_fixpoint(PT, CondBlock, BodyEnter, Body, CondBlockPredMap, Types0,
901 !ExitPredMap, DefMap, CondBlockDefMap, !CFG),
902
903 % CondBlock branches to BodyBlock or BBAfter, based on the condition
904@@ -853,36 +945,38 @@
905 % Calculate the condition expression at the end of CondBlock
906 apply_def_map_to_expr(CondBlockDefMap, Ctx, Cond0, Cond),
907 BlockID = ref_id(CondBlock, !.CFG),
908- expr_to_instrs(BlockID, Ctx, Cond, CondVar, CondInstrs, SubscriptMap, _),
909+ expr_to_instrs(BlockID, Ctx, Cond, CondVar, CondInstrs, Types1,
910+ SubscriptMap, _),
911+ Types = type_map_union(Types0, Types1),
912 cfg.append_instrs(CondBlock, CondInstrs, !CFG),
913 cfg.set_terminator(CondBlock, cond_branch(CondVar,BodyEnter,BBAfter,Ctx),
914 !CFG).
915
916-% while_fixpoint(CondBlock, BodyEnter, Body, CondPredMap, !ExitPredMap,
917-% !DefMap, !CFG).
918+% while_fixpoint(CondBlock, BodyEnter, Body, CondPredMap, -Types,
919+% !ExitPredMap, !DefMap, !CFG).
920 % Does fixpoint iteration over the condition and body block of the while loop
921 % until they agree on the phi nodes for the condition block.
922 % Updates the CFG as follows:
923 % - Sets the phis of CondBlock to the computed phi nodes.
924 % - Compiles the body into BodyEnter, branching to CondBlock.
925 :- pred while_fixpoint(progtable::in, bbref(S)::in, bbref(S)::in,
926- stmt_block::in,
927- pred_map(S)::in, pred_map(S)::in, pred_map(S)::out,
928+ stmt_block::in, pred_map(S)::in, type_map::out,
929+ pred_map(S)::in, pred_map(S)::out,
930 def_map::in, def_map::out, cfg(S)::in, cfg(S)::out) is det.
931-while_fixpoint(PT, CondBlock, BodyEnter, Body, CondPredMap, !ExitPredMap,
932- !DefMap, !CFG) :-
933+while_fixpoint(PT, CondBlock, BodyEnter, Body, CondPredMap, Types,
934+ !ExitPredMap, !DefMap, !CFG) :-
935 % First iteration, assume there are no phis
936- while_fixpoint_(PT, CondBlock, BodyEnter, Body, CondPredMap, [],
937+ while_fixpoint_(PT, CondBlock, BodyEnter, Body, CondPredMap, [], Types,
938 !ExitPredMap, !DefMap, !CFG).
939
940 :- pred while_fixpoint_(progtable::in, bbref(S)::in, bbref(S)::in,
941- stmt_block::in,
942- pred_map(S)::in, list(phi(S))::in, pred_map(S)::in, pred_map(S)::out,
943+ stmt_block::in, pred_map(S)::in, list(phi(S))::in, type_map::out,
944+ pred_map(S)::in, pred_map(S)::out,
945 def_map::in, def_map::out, cfg(S)::in, cfg(S)::out) is det.
946-while_fixpoint_(PT, CondBlock, BodyEnter, Body, CondPredMap0, Phis0,
947+while_fixpoint_(PT, CondBlock, BodyEnter, Body, CondPredMap0, Phis0, Types,
948 !ExitPredMap, !CondDefMap, !CFG) :-
949 % Compute CondPredMap (after another iteration of the body)
950- stmt_block_to_cfg(PT, Body, BodyEnter, CondBlock, !.CondDefMap,
951+ stmt_block_to_cfg(PT, Body, BodyEnter, CondBlock, !.CondDefMap, Types0,
952 CondPredMap0, CondPredMap, !ExitPredMap, !.CFG, PotentialFinalCFG),
953 % Now we can compute the phis for the cond block
954 CondBlockID = ref_id(CondBlock, !.CFG),
955@@ -892,11 +986,12 @@
956 !:CFG = PotentialFinalCFG,
957 % Write the phi into the cond block
958 cfg.set_phis(CondBlock, Phis, !CFG),
959+ Types = Types0,
960 !:CondDefMap = CondDefMap1
961 ;
962 % Now iterate till fixpoint
963 while_fixpoint_(PT, CondBlock, BodyEnter, Body, CondPredMap, Phis,
964- !ExitPredMap, CondDefMap1, !:CondDefMap, !CFG)
965+ Types, !ExitPredMap, CondDefMap1, !:CondDefMap, !CFG)
966 ).
967
968 % Intermediate representation of a case statement -- still contains recursive
969@@ -1305,8 +1400,8 @@
970 cfg.append_phi(TargetBlock, PhiInstr, CFG0, CFG)
971 ), Phis, !CFG).
972
973-% case_stmt_to_jmp(+BBAfter, +SubscriptMap, +DefMap, +CaseStmt, -CFGCaseStmt,
974-% !AfterPredMap, !ExitPredMap, !CFG).
975+% case_stmt_to_jmp(+BBAfter, +SubscriptMap, +DefMap, +CaseStmt,
976+% -(CFGCaseStmt - Types), !AfterPredMap, !ExitPredMap, !CFG).
977 % Compiles a case statement into a jmp case statement (which is
978 % branch-oriented rather than sub-statement-block-oriented).
979 % Compiles the sub-statement-block in the case statement to new basic blocks,
980@@ -1319,51 +1414,68 @@
981 % DefMap is read-only (the resulting def-maps should be appended to
982 % AfterPredMap).
983 :- pred case_stmt_to_jmp(progtable::in, bbref(S)::in, bbref(S)::in,
984- subscript_map::in, def_map::in, case_stmt::in, jmp_case_stmt(S)::out,
985- pred_map(S)::in, pred_map(S)::out, pred_map(S)::in, pred_map(S)::out,
986- cfg(S)::in, cfg(S)::out) is det.
987+ subscript_map::in, def_map::in, case_stmt::in,
988+ pair(jmp_case_stmt(S), type_map)::out, pred_map(S)::in, pred_map(S)::out,
989+ pred_map(S)::in, pred_map(S)::out, cfg(S)::in, cfg(S)::out) is det.
990 case_stmt_to_jmp(PT, BBCurrent, BBAfter, SubscriptMap, DefMap,
991- case_stmt(Pattern0, Stmts, Ctx), jmp_case_stmt(Pattern, BBFirst, Ctx),
992- !AfterPredMap, !ExitPredMap, !CFG) :-
993+ case_stmt(Pattern0, Stmts, Ctx),
994+ jmp_case_stmt(Pattern, BBFirst, Ctx) - Types, !AfterPredMap, !ExitPredMap,
995+ !CFG) :-
996 % Traverse the pattern and uniquely label each newly-introduced
997 % variable, as well as adding them to DefMap.
998 BlockID = ref_id(BBCurrent, !.CFG),
999- pattern_to_ssa(BlockID, Pattern0, Pattern, SubscriptMap, _, DefMap,
1000- InnerScopeDefMap),
1001+ pattern_to_ssa(BlockID, Pattern0, Pattern-Types0, SubscriptMap, _,
1002+ DefMap, InnerScopeDefMap),
1003
1004 cfg.new_basic_block(BBFirst, !CFG),
1005- stmt_block_to_cfg(PT, Stmts, BBFirst, BBAfter, InnerScopeDefMap,
1006- !AfterPredMap, !ExitPredMap, !CFG).
1007-
1008-% pattern_to_ssa(BlockID, !Pattern, !SubscriptMap, !DefMap).
1009+ stmt_block_to_cfg(PT, Stmts, BBFirst, BBAfter, InnerScopeDefMap, Types1,
1010+ !AfterPredMap, !ExitPredMap, !CFG),
1011+
1012+ Types = type_map_union(Types0, Types1).
1013+
1014+% pattern_to_ssa(BlockID, +Pattern, -(Pattern-Types), !SubscriptMap, !DefMap).
1015 % Converts a pattern to SSA form by replacing all of its introduced variables
1016 % with subscripted SSA variables.
1017 % BlockID: An int identifying the block the pattern is in (for computing
1018 % subscripts).
1019+% Types: Output -- Type map for all bound variables in the pattern.
1020 % SubscriptMap and DefMap are updated with the new variable definitions.
1021-:- pred pattern_to_ssa(int::in, pattern::in, pattern::out,
1022+:- pred pattern_to_ssa(int::in, pattern::in, pair(pattern, type_map)::out,
1023 subscript_map::in, subscript_map::out, def_map::in, def_map::out) is det.
1024-pattern_to_ssa(BlockID, pattern(Pat0, PatType), pattern(Pat, PatType),
1025+pattern_to_ssa(BlockID, pattern(Pat0, PatType), pattern(Pat, PatType) - Types,
1026 !SubscriptMap, !DefMap) :-
1027 (
1028+ PatType = yes(Type)
1029+ ;
1030+ PatType = no,
1031+ error("ast_cfg: Pattern has no associated type: " ++
1032+ pretty.string_pattern(pattern(Pat0, no)))
1033+ ),
1034+ (
1035 Pat0 = pat_any,
1036- Pat = Pat0
1037+ Pat = Pat0,
1038+ Types = map.init
1039 ;
1040 Pat0 = pat_var(Var0),
1041 new_ssa_variable(BlockID, Var0, Var, !SubscriptMap, !DefMap),
1042- Pat = pat_var(Var)
1043+ Pat = pat_var(Var),
1044+ Types = map.from_assoc_list([Var-Type])
1045 ;
1046 Pat0 = pat_ctor(CtorName, SubPatterns0),
1047 (
1048 SubPatterns0 = yes(YesSubPatterns0),
1049- map_foldl2(pattern_to_ssa(BlockID), YesSubPatterns0, SubPatterns,
1050- !SubscriptMap, !DefMap),
1051- Pat = pat_ctor(CtorName, yes(SubPatterns))
1052+ map_foldl2(pattern_to_ssa(BlockID), YesSubPatterns0,
1053+ SubPatternsTypes, !SubscriptMap, !DefMap),
1054+ SubPatterns = map(fst, SubPatternsTypes),
1055+ Pat = pat_ctor(CtorName, yes(SubPatterns)),
1056+ Types = type_map_union_list(map(snd, SubPatternsTypes))
1057 ;
1058 SubPatterns0 = no,
1059- Pat = pat_ctor(CtorName, no)
1060+ Pat = pat_ctor(CtorName, no),
1061+ Types = map.init
1062 )
1063 ;
1064 Pat0 = pat_intlit(_),
1065- Pat = Pat0
1066+ Pat = Pat0,
1067+ Types = map.init
1068 ).
1069
1070=== modified file 'src/builtins.m'
1071--- src/builtins.m 2009-11-26 08:09:50 +0000
1072+++ src/builtins.m 2010-05-10 05:50:41 +0000
1073@@ -110,7 +110,7 @@
1074 func_eq = function("eq", yes([{"x", types.variable(A), def_argmode},
1075 {"y", types.variable(A), def_argmode}]),
1076 types.const("Int"),
1077- Varset,
1078+ Varset, [A],
1079 func_builtin,
1080 ctx) :-
1081 varset.new_named_var(varset.init, "a", A, Varset).
1082@@ -119,7 +119,7 @@
1083 func_is = function("is", yes([{"x", types.variable(A), def_argmode},
1084 {"y", types.variable(A), def_argmode}]),
1085 types.const("Int"),
1086- Varset,
1087+ Varset, [A],
1088 func_builtin,
1089 ctx) :-
1090 varset.new_named_var(varset.init, "a", A, Varset).
1091@@ -128,7 +128,7 @@
1092 func_cmp = function("cmp", yes([{"x", types.const("Int"), def_argmode},
1093 {"y", types.const("Int"), def_argmode}]),
1094 types.const("Int"),
1095- varset.init,
1096+ varset.init, [],
1097 func_builtin,
1098 ctx).
1099
1100@@ -138,7 +138,7 @@
1101 func_add = function("add", yes([{"x", types.const("Int"), def_argmode},
1102 {"y", types.const("Int"), def_argmode}]),
1103 types.const("Int"),
1104- varset.init,
1105+ varset.init, [],
1106 func_builtin,
1107 ctx).
1108
1109@@ -146,7 +146,7 @@
1110 func_sub = function("sub", yes([{"x", types.const("Int"), def_argmode},
1111 {"y", types.const("Int"), def_argmode}]),
1112 types.const("Int"),
1113- varset.init,
1114+ varset.init, [],
1115 func_builtin,
1116 ctx).
1117
1118@@ -154,7 +154,7 @@
1119 func_mul = function("mul", yes([{"x", types.const("Int"), def_argmode},
1120 {"y", types.const("Int"), def_argmode}]),
1121 types.const("Int"),
1122- varset.init,
1123+ varset.init, [],
1124 func_builtin,
1125 ctx).
1126
1127@@ -162,7 +162,7 @@
1128 func_div = function("div", yes([{"x", types.const("Int"), def_argmode},
1129 {"y", types.const("Int"), def_argmode}]),
1130 types.const("Int"),
1131- varset.init,
1132+ varset.init, [],
1133 func_builtin,
1134 ctx).
1135
1136@@ -170,7 +170,7 @@
1137 func_mod = function("mod", yes([{"x", types.const("Int"), def_argmode},
1138 {"y", types.const("Int"), def_argmode}]),
1139 types.const("Int"),
1140- varset.init,
1141+ varset.init, [],
1142 func_builtin,
1143 ctx).
1144
1145@@ -182,7 +182,7 @@
1146 {"default", types.variable(A), def_argmode}]),
1147 types.app(types.const("Array"),
1148 [types.variable(A)]),
1149- Varset,
1150+ Varset, [A],
1151 func_builtin,
1152 ctx) :-
1153 varset.new_named_var(varset.init, "a", A, Varset).
1154@@ -194,7 +194,7 @@
1155 [types.variable(A)]), def_argmode},
1156 {"index", types.const("Int"), def_argmode}]),
1157 types.variable(A),
1158- Varset,
1159+ Varset, [A],
1160 func_builtin,
1161 ctx) :-
1162 varset.new_named_var(varset.init, "a", A, Varset).
1163@@ -208,7 +208,7 @@
1164 {"value", types.variable(A), def_argmode}]),
1165 types.app(types.const("Array"),
1166 [types.variable(A)]),
1167- Varset,
1168+ Varset, [A],
1169 func_builtin,
1170 ctx) :-
1171 varset.new_named_var(varset.init, "a", A, Varset).
1172@@ -222,7 +222,7 @@
1173 {"value", types.variable(A), def_argmode}]),
1174 types.app(types.const("Array"),
1175 [types.variable(A)]),
1176- Varset,
1177+ Varset, [A],
1178 func_builtin,
1179 ctx) :-
1180 varset.new_named_var(varset.init, "a", A, Varset).
1181@@ -233,7 +233,7 @@
1182 types.const("Array"),
1183 [types.variable(A)]), def_argmode}]),
1184 types.const("Int"),
1185- Varset,
1186+ Varset, [A],
1187 func_builtin,
1188 ctx) :-
1189 varset.new_named_var(varset.init, "a", A, Varset).
1190@@ -246,7 +246,7 @@
1191 {"value", types.variable(A), def_argmode}]),
1192 types.app(types.const("Array"),
1193 [types.variable(A)]),
1194- Varset,
1195+ Varset, [A],
1196 func_builtin,
1197 ctx) :-
1198 varset.new_named_var(varset.init, "a", A, Varset).
1199@@ -261,7 +261,7 @@
1200 [types.variable(A)]), def_argmode}]),
1201 types.app(types.const("Array"),
1202 [types.variable(A)]),
1203- Varset,
1204+ Varset, [A],
1205 func_builtin,
1206 ctx) :-
1207 varset.new_named_var(varset.init, "a", A, Varset).
1208@@ -273,7 +273,7 @@
1209 [types.variable(A)]), def_argmode},
1210 {"value", types.variable(A), def_argmode}]),
1211 types.app(types.const("Array"), [types.variable(A)]),
1212- Varset,
1213+ Varset, [A],
1214 func_builtin,
1215 ctx) :-
1216 varset.new_named_var(varset.init, "a", A, Varset).
1217@@ -287,7 +287,7 @@
1218 types.const("Array"),
1219 [types.variable(A)]), def_argmode}]),
1220 types.app(types.const("Array"), [types.variable(A)]),
1221- Varset,
1222+ Varset, [A],
1223 func_builtin,
1224 ctx) :-
1225 varset.new_named_var(varset.init, "a", A, Varset).
1226@@ -300,7 +300,7 @@
1227 {"index", types.const("Int"), def_argmode}]),
1228 types.app(types.const("Array"),
1229 [types.variable(A)]),
1230- Varset,
1231+ Varset, [A],
1232 func_builtin,
1233 ctx) :-
1234 varset.new_named_var(varset.init, "a", A, Varset).
1235@@ -313,7 +313,7 @@
1236 {"index", types.const("Int"), def_argmode}]),
1237 types.app(types.const("Array"),
1238 [types.variable(A)]),
1239- Varset,
1240+ Varset, [A],
1241 func_builtin,
1242 ctx) :-
1243 varset.new_named_var(varset.init, "a", A, Varset).
1244@@ -324,7 +324,7 @@
1245 func_put_char = function("put_char",
1246 yes([{"c", types.const("Int"), def_argmode}]),
1247 types.const("Int"),
1248- varset.init,
1249+ varset.init, [],
1250 func_builtin,
1251 ctx).
1252
1253@@ -332,7 +332,7 @@
1254 func_get_char = function("get_char",
1255 yes([]),
1256 types.const("Int"),
1257- varset.init,
1258+ varset.init, [],
1259 func_builtin,
1260 ctx).
1261
1262@@ -343,7 +343,7 @@
1263 def_argmode}]),
1264 types.app(types.const("Array"),
1265 [types.const("Int")]),
1266- varset.init,
1267+ varset.init, [],
1268 func_builtin,
1269 ctx).
1270
1271@@ -353,7 +353,7 @@
1272 func_show = function("show", yes([{"x", types.variable(A), def_argmode}]),
1273 types.app(types.const("Array"),
1274 [types.const("Int")]),
1275- Varset,
1276+ Varset, [],
1277 func_builtin,
1278 ctx) :-
1279 varset.new_named_var(varset.init, "a", A, Varset).
1280@@ -364,7 +364,7 @@
1281 [types.const("Int")]),
1282 def_argmode}]),
1283 types.variable(A),
1284- Varset,
1285+ Varset, [A],
1286 func_builtin,
1287 ctx) :-
1288 varset.new_named_var(varset.init, "a", A, Varset).
1289
1290=== modified file 'src/interactive.m'
1291--- src/interactive.m 2010-05-10 05:10:31 +0000
1292+++ src/interactive.m 2010-05-10 05:50:41 +0000
1293@@ -206,7 +206,7 @@
1294 parsem.parse_expr(Tokens, UserExpr),
1295 % Get the type of this expression
1296 typecheck.expr_type(Context, ProgTable, LocalTable,
1297- !.State^st_localvarset, Varset, UserExpr, _, Type),
1298+ !.State^st_localvarset, Varset, [], UserExpr, _, Type),
1299 io.write_string(pretty.string_expr(UserExpr), !IO),
1300 io.write_string(" :: ", !IO),
1301 io.write_string(pretty.string_typeval(Varset, Type), !IO),
1302@@ -289,14 +289,14 @@
1303 assignment_update_locals(!BasicStmt, Ctx, !State) :-
1304 ( !.BasicStmt = assign(Target, Expr0) ->
1305 typecheck.expr_type(Ctx, !.State^st_progtable, !.State^st_localtable,
1306- !.State^st_localvarset, NewVarset, Expr0, Expr, Type),
1307+ !.State^st_localvarset, NewVarset, [], Expr0, Expr, Type),
1308 tables.update_localtable(Target, Type, !.State^st_localtable, NewLT),
1309 !State^st_localvarset := NewVarset,
1310 !State^st_localtable := NewLT,
1311 !:BasicStmt = assign(Target, Expr)
1312 ;
1313 typecheck.check_basic_stmt(Ctx, !.State^st_progtable,
1314- !.State^st_localtable, !.State^st_localvarset, _Varset,
1315+ !.State^st_localtable, !.State^st_localvarset, _Varset, [],
1316 !BasicStmt)
1317 % Note: Do not update localvarset (could do, but there wouldn't be
1318 % anything useful since we didn't add anything to localtable).
1319
1320=== modified file 'src/ir.m'
1321--- src/ir.m 2010-04-28 05:20:46 +0000
1322+++ src/ir.m 2010-05-10 05:50:41 +0000
1323@@ -52,6 +52,7 @@
1324 :- import_module bool.
1325 :- import_module list.
1326 :- import_module assoc_list.
1327+:- import_module map.
1328 :- import_module maybe.
1329 :- import_module pair.
1330
1331@@ -298,6 +299,8 @@
1332 func_params :: maybe(list({string, typeval, argmode})),
1333 func_ret_type :: typeval,
1334 func_varset :: varset,
1335+ % Set of type vars which may not be unified in the body
1336+ func_rigids :: list(var),
1337 func_body :: func_body,
1338 func_context :: context.context
1339 ).
1340@@ -314,7 +317,9 @@
1341 )
1342 % The function is represented by a CFG.
1343 ; some [S] func_body_cfg(
1344- list(pair(varname, typeval)),
1345+ % Type of each SSA variable and argument. Must not contain any
1346+ % references to unbound variables (must be dereferenced).
1347+ map(varname, typeval),
1348 cfg(S)
1349 ).
1350
1351@@ -402,7 +407,6 @@
1352 :- implementation.
1353
1354 :- import_module int.
1355-:- import_module map.
1356 :- import_module require.
1357
1358 :- func tab_width = int.
1359
1360=== modified file 'src/mars.m'
1361--- src/mars.m 2010-04-28 05:59:37 +0000
1362+++ src/mars.m 2010-05-10 05:50:41 +0000
1363@@ -127,11 +127,11 @@
1364 MainExpr = expr(varref(svname(MainFuncName)),no),
1365 % Typecheck this expression (makes sure main exists, and get its type)
1366 typecheck.expr_type(blank_context, ProgTable, empty_localtable,
1367- varset.init, VarSet, MainExpr, _, MainType),
1368+ varset.init, VarSet, [], MainExpr, _, MainType),
1369 % Ensure that MainType is () -> Int
1370 ExpType = app(functype, [const("Int")]),
1371 typecheck.det_unify(blank_context, MainFuncName, MainExpr, MainType,
1372- ExpType, VarSet, _NewVarset),
1373+ ExpType, [], VarSet, _NewVarset),
1374 % MainInstr is the instruction "$T = MainFuncName()"
1375 MainInstr = instr(call(tempvname, gvname(MainFuncName), []),
1376 context.blank_context),
1377
1378=== modified file 'src/marsc.m'
1379--- src/marsc.m 2010-04-28 05:59:37 +0000
1380+++ src/marsc.m 2010-05-10 05:50:41 +0000
1381@@ -133,11 +133,11 @@
1382 MainExpr = expr(varref(svname(MainFunc)),no),
1383 % Typecheck this expression (makes sure main exists, and get its type)
1384 typecheck.expr_type(blank_context, PT, empty_localtable,
1385- varset.init, VarSet, MainExpr, _, MainType),
1386+ varset.init, VarSet, [], MainExpr, _, MainType),
1387 % Ensure that MainType is () -> Int
1388 ExpType = app(functype, [const("Int")]),
1389 typecheck.det_unify(blank_context, MainFunc, MainExpr, MainType,
1390- ExpType, VarSet, _NewVarset).
1391+ ExpType, [], VarSet, _NewVarset).
1392
1393 % Does the whole program, (taking a filename as input), but does not catch
1394 % exceptions. Any context.error exceptions will be propagated upwards.
1395
1396=== modified file 'src/parsem.m'
1397--- src/parsem.m 2010-03-29 08:58:37 +0000
1398+++ src/parsem.m 2010-05-10 05:50:41 +0000
1399@@ -417,7 +417,7 @@
1400 % Consumes a single function.
1401 :- pred function(function::out, tokenparser::in, tokenparser::out) is semidet.
1402 function(
1403- function(FuncName, Params, RetType, Varset, Body, Context)) -->
1404+ function(FuncName, Params, RetType, Varset, Rigids, Body, Context)) -->
1405 some [!Varset, !VarNames] (
1406 {varset.init(!:Varset)},
1407 {map.init(!:VarNames)},
1408@@ -464,7 +464,12 @@
1409 ;
1410 throw_expected("lowercase identifier")
1411 ),
1412- {Varset = !.Varset}
1413+ {Varset = !.Varset},
1414+ % The rigid type variables are all those which have been explicitly
1415+ % named.
1416+ % (If we support type inference, implicitly-typed variables will not
1417+ % have names, and should not be rigid, so this logic still applies.)
1418+ {Rigids = map.values(!.VarNames)}
1419 ).
1420
1421 % func_param(Param, !Varset, !VarNames, !Parser).
1422
1423=== modified file 'src/pretty.m'
1424--- src/pretty.m 2010-01-25 01:42:15 +0000
1425+++ src/pretty.m 2010-05-10 05:50:41 +0000
1426@@ -494,7 +494,8 @@
1427 foldl(print_stmt(Indent+1), Stmts, !IO)
1428 ;
1429 Func^func_body = func_body_cfg(Decls, CFG),
1430- foldl(print_decl(Indent+1, Func^func_varset), Decls, !IO),
1431+ foldl(print_decl(Indent+1, Func^func_varset),
1432+ map.to_assoc_list(Decls), !IO),
1433 indent(Indent+1, !IO),
1434 io.write_string("# XXX CFG representation (not valid Mars code)\n",
1435 !IO),
1436
1437=== modified file 'src/tables.m'
1438--- src/tables.m 2010-04-28 05:29:04 +0000
1439+++ src/tables.m 2010-05-10 05:50:41 +0000
1440@@ -129,6 +129,7 @@
1441 :- import_module require.
1442
1443 :- import_module context.
1444+:- import_module util.
1445
1446 empty_progtable = progtable(map.init, map.init, map.init).
1447 empty_localtable = map.init.
1448@@ -199,7 +200,8 @@
1449 ( Func^func_body = func_body_ast(Decls,_) ->
1450 list.foldl(add_to_localtable(Func, "variable"), Decls, !Table)
1451 ; Func^func_body = func_body_cfg(Decls,_) ->
1452- list.foldl(add_to_localtable(Func, "variable"), Decls, !Table)
1453+ map.foldl(pred(K::in,V::in,A0::in,A::out) is det :-
1454+ add_to_localtable(Func, "variable", K-V, A0, A), Decls, !Table)
1455 ;
1456 true
1457 ).
1458@@ -223,6 +225,16 @@
1459 Table = Table0
1460 ;
1461 Args = yes(YesArgs),
1462+ % Test for duplicate parameter names
1463+ filter_map(pred(yes(Name)-_::in, Name::out) is semidet,
1464+ YesArgs, FieldNames),
1465+ ( util.list_first_duplicate(FieldNames, DupName) ->
1466+ % FieldNames contains duplicates
1467+ context.throw_error("Duplicate field name: " ++ DupName,
1468+ Ctor ^ ctor_context)
1469+ ;
1470+ true
1471+ ),
1472 list.foldl(add_ctor_field_to_fieldtable(Ctor ^ ctor_context),
1473 YesArgs, Table0, Table)
1474 ).
1475
1476=== modified file 'src/typecheck.m'
1477--- src/typecheck.m 2010-05-10 05:15:01 +0000
1478+++ src/typecheck.m 2010-05-10 05:50:41 +0000
1479@@ -22,7 +22,9 @@
1480
1481 :- interface.
1482
1483+:- import_module list.
1484 :- import_module varset.
1485+:- use_module term.
1486
1487 :- import_module ir.
1488 :- import_module tables.
1489@@ -42,7 +44,7 @@
1490 % Otherwise, succeeds. Note that this may bind variables, or create new
1491 % variables, which will be reflected in the output varset.
1492 :- pred expr_type(context::in, progtable::in, localtable::in,
1493- varset::in, varset::out,
1494+ varset::in, varset::out, list(term.var)::in,
1495 expr::in, expr::out, typeval::out)
1496 is det.
1497
1498@@ -63,14 +65,14 @@
1499 % Updates Stmt so its expressions hold their type values.
1500 % Throws a context.error on reference or type errors.
1501 :- pred check_stmt(progtable::in, localtable::in, typeval::in,
1502- varset::in, varset::out,
1503+ varset::in, varset::out, list(term.var)::in,
1504 stmt::in, stmt::out) is det.
1505
1506 % check_basic_stmt(Context, ProgTable, LocalTable, !Varsete, !BasicStmt).
1507 % Checks to see if a basic statement is type-correct.
1508 % Does not require a function return type.
1509 :- pred check_basic_stmt(context::in, progtable::in, localtable::in,
1510- varset::in, varset::out,
1511+ varset::in, varset::out, list(term.var)::in,
1512 basic_stmt::in, basic_stmt::out) is det.
1513
1514 % check_function(ProgTable, LocalTable, !Function).
1515@@ -100,7 +102,7 @@
1516 % Succeeds if they do, and possibly updates varset with new bindings.
1517 % "What" : see type_error
1518 :- pred det_unify(context::in, string::in, expr::in, typeval::in, typeval::in,
1519- varset::in, varset::out) is det.
1520+ list(term.var)::in, varset::in, varset::out) is det.
1521
1522 % -------------------------------------------------------------------------- %
1523 % -------------------------------------------------------------------------- %
1524@@ -112,9 +114,9 @@
1525 :- import_module string.
1526 :- import_module maybe.
1527 :- import_module pair.
1528-:- import_module list.
1529 :- import_module set.
1530 :- import_module svset.
1531+:- import_module assoc_list.
1532 :- import_module require.
1533
1534 :- import_module pretty.
1535@@ -128,21 +130,21 @@
1536 % "What" : see type_error
1537 :- pred list_elem_type(context::in, progtable::in, localtable::in, string::in,
1538 typeval::in, list(expr)::in, list(expr)::out,
1539- varset::in, varset::out) is det.
1540-list_elem_type(_Ctx, _PT, _LT, _What, _T1, [], [], !Varset).
1541-list_elem_type(Ctx, PT, LT, What, T1, [E0|Es0], [E|Es], !Varset) :-
1542- expr_type(Ctx, PT, LT, !Varset, E0, E, EType),
1543- det_unify(Ctx, What, E, EType, T1, !Varset),
1544- list_elem_type(Ctx, PT, LT, What, T1, Es0, Es, !Varset).
1545+ list(term.var)::in, varset::in, varset::out) is det.
1546+list_elem_type(_Ctx, _PT, _LT, _What, _T1, [], [], _Rigids, !Varset).
1547+list_elem_type(Ctx, PT, LT, What, T1, [E0|Es0], [E|Es], Rigids, !Varset) :-
1548+ expr_type(Ctx, PT, LT, !Varset, Rigids, E0, E, EType),
1549+ det_unify(Ctx, What, E, EType, T1, Rigids, !Varset),
1550+ list_elem_type(Ctx, PT, LT, What, T1, Es0, Es, Rigids, !Varset).
1551
1552 % expr_type for expressions with a computed type.
1553 % Still check the type, unify to make sure the existing annotation was good,
1554 % and recurse (bug #578082).
1555-expr_type(Ctx, PT, LT, !Varset, expr(Expr0,yes(Type)),
1556+expr_type(Ctx, PT, LT, !Varset, Rigids, expr(Expr0,yes(Type)),
1557 expr(Expr,yes(Type)), Type) :-
1558- expr_type_(Ctx, PT, LT, !Varset, Expr0, Expr, InfType),
1559+ expr_type_(Ctx, PT, LT, !Varset, Rigids, Expr0, Expr, InfType),
1560 % Match the existing annotation with the inferred type
1561- ( types.unify(Type, InfType, !Varset) ->
1562+ ( types.unify(Type, InfType, Rigids, !Varset) ->
1563 true
1564 ;
1565 error(string.format("typecheck: Expression %s with existing type "
1566@@ -153,24 +155,27 @@
1567 ).
1568 % expr_type for expressions without a computed type.
1569 % Compute the type and store it in the output expr.
1570-expr_type(Ctx, PT, LT, !Varset, expr(Expr0,no), expr(Expr,yes(Type)), Type) :-
1571- expr_type_(Ctx, PT, LT, !Varset, Expr0, Expr, Type).
1572+expr_type(Ctx, PT, LT, !Varset, Rigids, expr(Expr0,no), expr(Expr,yes(Type)),
1573+ Type) :-
1574+ expr_type_(Ctx, PT, LT, !Varset, Rigids, Expr0, Expr, Type).
1575
1576 % expr_type_(ProgTable, LocalTable, !Varset, !Expr_, Type).
1577 % Determines the type of an expr_ (the data structure inside expr).
1578 :- pred expr_type_(context::in, progtable::in, localtable::in,
1579- varset::in, varset::out,
1580+ varset::in, varset::out, list(term.var)::in,
1581 expr_::in, expr_::out, typeval::out)
1582 is det.
1583 % Type of intlit is Int.
1584-expr_type_(_Ctx, _PT, _LT, !Varset, E@intlit(_), E, types.const("Int")).
1585-expr_type_(Ctx, PT, LT, !Varset, E@arraylit(Elems0), arraylit(Elems),
1586+expr_type_(_Ctx, _PT, _LT, !Varset, _Rigids, E@intlit(_), E,
1587+ types.const("Int")).
1588+expr_type_(Ctx, PT, LT, !Varset, Rigids, E@arraylit(Elems0), arraylit(Elems),
1589 types.app(types.const("Array"), [ElemType])) :-
1590 % Find the type of each element. (Type error unless all unify).
1591 types.new_var(ElemType, !Varset),
1592 What = "expression '" ++ pretty.string_expr(expr(E,no)) ++ "'",
1593- list_elem_type(Ctx, PT, LT, What, ElemType, Elems0, Elems, !Varset).
1594-expr_type_(Ctx, PT, LT, !Varset, E@varref(VarName), E, Type) :-
1595+ list_elem_type(Ctx, PT, LT, What, ElemType, Elems0, Elems, Rigids,
1596+ !Varset).
1597+expr_type_(Ctx, PT, LT, !Varset, _Rigids, E@varref(VarName), E, Type) :-
1598 ( tables.lookup_local(LT, VarName, Type_) ->
1599 % Found in local table
1600 Type = Type_
1601@@ -187,7 +192,7 @@
1602 context.throw_error("Undefined variable: "
1603 ++ ir.varname_to_string_noescape(VarName), Ctx)
1604 ).
1605-expr_type_(Ctx, PT, _LT, !Varset, E@ctorref(VarName), E, Type) :-
1606+expr_type_(Ctx, PT, _LT, !Varset, _Rigids, E@ctorref(VarName), E, Type) :-
1607 ( tables.lookup_ctor(PT, VarName, TypeDef, _) ->
1608 % Found in global ctor table - get its type and varset
1609 ( ctor_type(TypeDef, VarName, CtorVarset, Type0) ->
1610@@ -201,9 +206,9 @@
1611 ;
1612 context.throw_error("Undefined variable: " ++ VarName, Ctx)
1613 ).
1614-expr_type_(Ctx, PT, LT, !Varset,
1615+expr_type_(Ctx, PT, LT, !Varset, Rigids,
1616 fieldref(Expr0, FieldName), fieldref(Expr, FieldName), Type) :-
1617- expr_type(Ctx, PT, LT, !Varset, Expr0, Expr, ObjType0),
1618+ expr_type(Ctx, PT, LT, !Varset, Rigids, Expr0, Expr, ObjType0),
1619 types.deref(!.Varset, ObjType0, ObjType),
1620 % ObjType is the type which we are accessing
1621 ( ObjType = variable(_) ->
1622@@ -217,10 +222,10 @@
1623 ++ "references", Ctx)
1624 ),
1625 Type = ObjType.
1626-expr_type_(Ctx, PT, LT, !Varset, app(Func0, Args0), Expr@app(Func, Args),
1627- RetType) :-
1628- expr_type(Ctx, PT, LT, !Varset, Func0, Func, FuncType0),
1629- expr_types(Ctx, PT, LT, !Varset, Args0, Args, ArgTypes),
1630+expr_type_(Ctx, PT, LT, !Varset, Rigids,
1631+ app(Func0, Args0), Expr@app(Func, Args), RetType) :-
1632+ expr_type(Ctx, PT, LT, !Varset, Rigids, Func0, Func, FuncType0),
1633+ expr_types(Ctx, PT, LT, !Varset, Rigids, Args0, Args, ArgTypes),
1634 types.deref(!.Varset, FuncType0, FuncType),
1635 What = "expression '" ++ pretty.string_expr(expr(Expr,no)) ++ "'",
1636 % Unify: FuncType = ArgType -> Type
1637@@ -231,7 +236,8 @@
1638 Arity = list.length(InputTypes),
1639 NumArgs = list.length(Args),
1640 ( Arity = NumArgs ->
1641- det_unify_lists(Ctx, What, Args, ArgTypes, InputTypes, !Varset)
1642+ det_unify_lists(Ctx, What, Args, ArgTypes, InputTypes, Rigids,
1643+ !Varset)
1644 ;
1645 type_error_arity(Ctx, !.Varset, What, Func, FuncType, Arity,
1646 NumArgs)
1647@@ -241,16 +247,16 @@
1648 types.new_var(RetType, !Varset),
1649 det_unify(Ctx, What, Func, FuncType,
1650 types.app(types.functype, ArgTypes ++ [RetType]),
1651- !Varset)
1652+ Rigids, !Varset)
1653 ;
1654 % All other alternatives - not going to unify with ArgType -> Type.
1655 % Hence, "this is not a function" error.
1656 error_not_a_function(Ctx, !.Varset, What, Func, FuncType)
1657 ).
1658-expr_type_(Ctx, PT, LT, !Varset, parapp(Func0, Args0),
1659+expr_type_(Ctx, PT, LT, !Varset, Rigids, parapp(Func0, Args0),
1660 Expr@parapp(Func, Args), ResultType) :-
1661- expr_type(Ctx, PT, LT, !Varset, Func0, Func, FuncType0),
1662- expr_types(Ctx, PT, LT, !Varset, Args0, Args, ArgTypes),
1663+ expr_type(Ctx, PT, LT, !Varset, Rigids, Func0, Func, FuncType0),
1664+ expr_types(Ctx, PT, LT, !Varset, Rigids, Args0, Args, ArgTypes),
1665 types.deref(!.Varset, FuncType0, FuncType),
1666 What = "expression '" ++ pretty.string_expr(expr(Expr,no)) ++ "'",
1667 % Unify: FuncType = ArgType -> Type
1668@@ -264,7 +270,8 @@
1669 list.det_split_list(NumArgs, InputTypes, GotInputTypes,
1670 RemInputTypes),
1671 % Unify all supplied args (remaining input types are not checked)
1672- det_unify_lists(Ctx, What, Args, ArgTypes, GotInputTypes, !Varset)
1673+ det_unify_lists(Ctx, What, Args, ArgTypes, GotInputTypes, Rigids,
1674+ !Varset)
1675 ;
1676 type_error_arity(Ctx, !.Varset, What, Func, FuncType, Arity,
1677 NumArgs)
1678@@ -286,13 +293,13 @@
1679 % Applies expr_types to each element of the list, updating the list and
1680 % returning a list of types.
1681 :- pred expr_types(context::in, progtable::in, localtable::in,
1682- varset::in, varset::out,
1683+ varset::in, varset::out, list(term.var)::in,
1684 list(expr)::in, list(expr)::out, list(typeval)::out)
1685 is det.
1686-expr_types(_Ctx, _PT, _LT, !Varset, [], [], []).
1687-expr_types(Ctx, PT, LT, !Varset, [E0|Es0], [E|Es], [T|Ts]) :-
1688- expr_type(Ctx, PT, LT, !Varset, E0, E, T),
1689- expr_types(Ctx, PT, LT, !Varset, Es0, Es, Ts).
1690+expr_types(_Ctx, _PT, _LT, !Varset, _Rigids, [], [], []).
1691+expr_types(Ctx, PT, LT, !Varset, Rigids, [E0|Es0], [E|Es], [T|Ts]) :-
1692+ expr_type(Ctx, PT, LT, !Varset, Rigids, E0, E, T),
1693+ expr_types(Ctx, PT, LT, !Varset, Rigids, Es0, Es, Ts).
1694
1695 type_kind(Ctx, PT, Varset, Type0, Kind) :-
1696 types.deref(Varset, Type0, Type),
1697@@ -351,41 +358,51 @@
1698 kind_error(Ctx, Varset, Type, Type, Kind, kind_star)
1699 ).
1700
1701-% check_pattern(Context, ProgTable, !LocalTable, !Varset,
1702+% check_pattern(Context, ProgTable, LocalTable, !Varset,
1703 % What, SwitchType, !PatVars, !Pattern).
1704 % Checks to see if a pattern is type-correct, with respect to its parent
1705 % switch type.
1706-% Updates the varset and localtable with the extra type and term variables
1707-% created by the pattern.
1708 % Updates pattern by embedding the switch type.
1709 % !PatVars is the variables bound by this pattern so far.
1710 % A top-level call to check_pattern should pass set.init, and ignore result.
1711 % What: The entire top-level pattern, for error purposes.
1712-:- pred check_pattern(context::in, progtable::in,
1713- localtable::in, localtable::out,
1714- varset::in, varset::out,
1715+:- pred check_pattern(context::in, progtable::in, localtable::in,
1716+ varset::in, varset::out, list(term.var)::in,
1717 pattern::in, typeval::in,
1718 set(varname)::in, set(varname)::out,
1719 pattern::in, pattern::out)
1720 is det.
1721-check_pattern(Ctx, PT, !LT, !Varset, What, SwitchType, !PatVars,
1722+check_pattern(Ctx, PT, LT, !Varset, Rigids, What, SwitchType, !PatVars,
1723 pattern(Pattern0, _), pattern(Pattern, yes(SwitchType))) :-
1724- check_pattern_(Ctx, PT, !LT, !Varset, What, SwitchType, !PatVars,
1725+ check_pattern_(Ctx, PT, LT, !Varset, Rigids, What, SwitchType, !PatVars,
1726 Pattern0, Pattern).
1727
1728-:- pred check_pattern_(context::in, progtable::in,
1729- localtable::in, localtable::out,
1730- varset::in, varset::out,
1731+:- pred check_pattern_(context::in, progtable::in, localtable::in,
1732+ varset::in, varset::out, list(term.var)::in,
1733 pattern::in, typeval::in,
1734 set(varname)::in, set(varname)::out,
1735 pattern_::in, pattern_::out)
1736 is det.
1737-check_pattern_(_Ctx, _PT, !LT, !Varset, _What, _SwitchType, !PatVars,
1738+check_pattern_(_Ctx, _PT, _LT, !Varset, _Rigids, _What, _SwitchType, !PatVars,
1739 pat_any, pat_any).
1740-check_pattern_(Ctx, _PT, !LT, !Varset, _What, SwitchType, !PatVars,
1741+check_pattern_(Ctx, _PT, LT, !Varset, Rigids, What, SwitchType, !PatVars,
1742 P@pat_var(Name), P) :-
1743- % Create a new variable in the localtable
1744- tables.update_localtable(Name, SwitchType, !LT),
1745+ % Unify the SwitchType with the type of the bound variable
1746+ % Name is guaranteed to be a declared local variable by the implicit
1747+ % declaration pass applied before typechecking
1748+ ( tables.lookup_local(LT, Name, Type_) ->
1749+ TargetType = Type_
1750+ ;
1751+ error(string.format("Pattern variable \"%s\" not in local table",
1752+ [s(varname_to_string_noescape(Name))]))
1753+ ),
1754+ ( types.unify(TargetType, SwitchType, Rigids, !Varset) ->
1755+ true
1756+ ;
1757+ type_error_pattern(Ctx, !.Varset, What, pattern(P,no), TargetType,
1758+ SwitchType)
1759+ ),
1760+
1761 % Check that this variable has not been bound previously in this same
1762 % pattern, and record the binding
1763 ( set.contains(!.PatVars, Name) ->
1764@@ -394,7 +411,7 @@
1765 ;
1766 svset.insert(Name, !PatVars)
1767 ).
1768-check_pattern_(Ctx, PT, !LT, !Varset, What, SwitchType, !PatVars,
1769+check_pattern_(Ctx, PT, LT, !Varset, Rigids, What, SwitchType, !PatVars,
1770 P@pat_ctor(VarName, Args0), pat_ctor(VarName, Args)) :-
1771 ( tables.lookup_ctor(PT, VarName, TypeDef, _) ->
1772 % Found in global ctor table
1773@@ -418,6 +435,13 @@
1774 ;
1775 error("check_pattern: varset_merge returned bad output")
1776 ),
1777+ % Check that the constructor matches the given switch type.
1778+ ( types.unify(OutputType, SwitchType, Rigids, !Varset) ->
1779+ true
1780+ ;
1781+ type_error_pattern(Ctx, !.Varset, What, pattern(P,no),
1782+ OutputType, SwitchType)
1783+ ),
1784 % Make sure the pattern also has arguments
1785 ( list.length(CtorArgTypes) = 1 ->
1786 Arguments = " argument"
1787@@ -454,8 +478,8 @@
1788 Ctx)
1789 ),
1790 % Make sure each argument matches the ctor argument type
1791- check_patterns(Ctx, PT, !LT, !Varset, What, CtorArgTypes,
1792- !PatVars, YesArgs0, YesArgs),
1793+ check_patterns(Ctx, PT, LT, !Varset, Rigids, What, CtorArgTypes,
1794+ !PatVars, YesArgs0, YesArgs),
1795 Args = yes(YesArgs)
1796 ;
1797 CtorArgTypes0 = no,
1798@@ -467,6 +491,13 @@
1799 ;
1800 error("check_pattern: varset_merge returned bad output")
1801 ),
1802+ % Check that the constructor matches the given switch type.
1803+ ( types.unify(OutputType, SwitchType, Rigids, !Varset) ->
1804+ true
1805+ ;
1806+ type_error_pattern(Ctx, !.Varset, What, pattern(P,no),
1807+ OutputType, SwitchType)
1808+ ),
1809 % Make sure the pattern is also parameter-less
1810 (
1811 Args0 = yes(_),
1812@@ -481,21 +512,14 @@
1813 Args0 = no
1814 ),
1815 Args = no
1816- ),
1817- % Finally, check that the constructor matches the given switch type.
1818- ( types.unify(OutputType, SwitchType, !Varset) ->
1819- true
1820- ;
1821- type_error_pattern(Ctx, !.Varset, What, pattern(P,no), OutputType,
1822- SwitchType)
1823 )
1824 ;
1825 context.throw_error("Undefined constructor: " ++ VarName, Ctx)
1826 ).
1827-check_pattern_(Ctx, _PT, !LT, !Varset, What, SwitchType0, !PatVars,
1828+check_pattern_(Ctx, _PT, _LT, !Varset, Rigids, What, SwitchType0, !PatVars,
1829 P@pat_intlit(_), P) :-
1830 deref(!.Varset, SwitchType0, SwitchType),
1831- ( types.unify(types.const("Int"), SwitchType, !Varset) ->
1832+ ( types.unify(types.const("Int"), SwitchType, Rigids, !Varset) ->
1833 true
1834 ;
1835 type_error_pattern(Ctx, !.Varset, What, pattern(P,no),
1836@@ -505,123 +529,111 @@
1837 % Check a list of patterns against a list of switch types.
1838 % Note it stops when either list reaches empty. Should check lengths
1839 % separately.
1840-:- pred check_patterns(context::in, progtable::in,
1841- localtable::in, localtable::out,
1842- varset::in, varset::out,
1843+:- pred check_patterns(context::in, progtable::in, localtable::in,
1844+ varset::in, varset::out, list(term.var)::in,
1845 pattern::in, list(typeval)::in,
1846 set(varname)::in, set(varname)::out,
1847 list(pattern)::in, list(pattern)::out)
1848 is det.
1849-check_patterns(_Ctx, _PT, !LT, !Varset, _What, [], !PV, Ps, Ps).
1850-check_patterns(_Ctx, _PT, !LT, !Varset, _What, [_|_], !PV, [], []).
1851-check_patterns(Ctx, PT, !LT, !Varset, What, [S|Ss], !PV, [P0|Ps0], [P|Ps]) :-
1852- check_pattern(Ctx, PT, !LT, !Varset, What, S, !PV, P0, P),
1853- check_patterns(Ctx, PT, !LT, !Varset, What, Ss, !PV, Ps0, Ps).
1854+check_patterns(_Ctx, _PT, _LT, !Varset, _Rigids, _What, [], !PV, Ps, Ps).
1855+check_patterns(_Ctx, _PT, _LT, !Varset, _Rigids, _What, [_|_], !PV, [], []).
1856+check_patterns(Ctx, PT, LT, !Varset, Rigids, What, [S|Ss], !PV, [P0|Ps0],
1857+ [P|Ps]) :-
1858+ check_pattern(Ctx, PT, LT, !Varset, Rigids, What, S, !PV, P0, P),
1859+ check_patterns(Ctx, PT, LT, !Varset, Rigids, What, Ss, !PV, Ps0, Ps).
1860
1861 :- func ctor_arg_types(ctor) = maybe(list(typeval)).
1862 ctor_arg_types(ctor(_,no,_)) = no.
1863 ctor_arg_types(ctor(_,yes(Args),_)) = yes(map(pair.snd, Args)).
1864
1865-check_stmt(PT, LT, _RetType, !Varset,
1866+check_stmt(PT, LT, _RetType, !Varset, Rigids,
1867 basic_stmt(Stmt0, Ctx), basic_stmt(Stmt, Ctx)) :-
1868- check_basic_stmt(Ctx, PT, LT, !Varset, Stmt0, Stmt).
1869-check_stmt(PT, LT, RetType, !Varset,
1870+ check_basic_stmt(Ctx, PT, LT, !Varset, Rigids, Stmt0, Stmt).
1871+check_stmt(PT, LT, RetType, !Varset, Rigids,
1872 compound_stmt(Stmt0, Ctx), compound_stmt(Stmt, Ctx)) :-
1873- check_compound_stmt(Ctx, PT, LT, RetType, !Varset, Stmt0, Stmt).
1874+ check_compound_stmt(Ctx, PT, LT, RetType, !Varset, Rigids, Stmt0, Stmt).
1875
1876-check_basic_stmt(_Ctx, _PT, _LT, !Varset, pass, pass).
1877-check_basic_stmt(Ctx, PT, LT, !Varset,
1878+check_basic_stmt(_Ctx, _PT, _LT, !Varset, _Rigids, pass, pass).
1879+check_basic_stmt(Ctx, PT, LT, !Varset, Rigids,
1880 assign(VarName, Expr0), assign(VarName, Expr)) :-
1881 % Get the type of both sides
1882- get_local_var(Ctx, PT, LT, VarName, TargetType), % Throws any errors
1883- expr_type(Ctx, PT, LT, !Varset, Expr0, Expr, ExprType),
1884+ % VarName is guaranteed to be a declared local variable by the implicit
1885+ % declaration pass applied before typechecking
1886+ ( tables.lookup_local(LT, VarName, Type_) ->
1887+ TargetType = Type_
1888+ ;
1889+ error(string.format("Assignment target \"%s\" not in local table",
1890+ [s(varname_to_string_noescape(VarName))]))
1891+ ),
1892+ expr_type(Ctx, PT, LT, !Varset, Rigids, Expr0, Expr, ExprType),
1893 What = "statement '" ++ ir.varname_to_string_noescape(VarName)
1894 ++ " = " ++ pretty.string_expr(Expr) ++ "'",
1895 % Unify: TargetType = ExprType
1896- det_unify(Ctx, What, Expr, ExprType, TargetType, !Varset).
1897-check_basic_stmt(Ctx, _PT, _LT, !Varset,
1898+ det_unify(Ctx, What, Expr, ExprType, TargetType, Rigids, !Varset).
1899+check_basic_stmt(Ctx, _PT, _LT, !Varset, _Rigids,
1900 fieldset(Target0, FieldName, Expr0),
1901 fieldset(Target0, FieldName, Expr0)) :-
1902 context.throw_error("Sorry: Type checker can't handle fieldset", Ctx).
1903-check_basic_stmt(Ctx, _PT, _LT, !Varset,
1904+check_basic_stmt(Ctx, _PT, _LT, !Varset, _Rigids,
1905 fieldreplace(Target0, FieldName, Expr0),
1906 fieldreplace(Target0, FieldName, Expr0)) :-
1907 context.throw_error("Sorry: Type checker can't handle fieldreplace", Ctx).
1908-check_basic_stmt(Ctx, PT, LT, !Varset, eval(Expr0), eval(Expr)) :-
1909- expr_type(Ctx, PT, LT, !Varset, Expr0, Expr, _).
1910+check_basic_stmt(Ctx, PT, LT, !Varset, Rigids, eval(Expr0), eval(Expr)) :-
1911+ expr_type(Ctx, PT, LT, !Varset, Rigids, Expr0, Expr, _).
1912
1913 :- pred check_compound_stmt(context::in, progtable::in, localtable::in,
1914- typeval::in, varset::in, varset::out,
1915+ typeval::in, varset::in, varset::out, list(term.var)::in,
1916 compound_stmt::in, compound_stmt::out) is det.
1917-check_compound_stmt(Ctx, PT, LT, Ret, !Varset, return(Expr0), return(Expr)) :-
1918- expr_type(Ctx, PT, LT, !Varset, Expr0, Expr, ExprType),
1919+check_compound_stmt(Ctx, PT, LT, Ret, !Varset, Rigids,
1920+ return(Expr0), return(Expr)) :-
1921+ expr_type(Ctx, PT, LT, !Varset, Rigids, Expr0, Expr, ExprType),
1922 What = "statement 'return " ++ pretty.string_expr(Expr) ++ "'",
1923 % Unify with function return type
1924- det_unify(Ctx, What, Expr, ExprType, Ret, !Varset).
1925-check_compound_stmt(Ctx, PT, LT, Ret, !Varset, switch(Expr0, Cases0),
1926+ det_unify(Ctx, What, Expr, ExprType, Ret, Rigids, !Varset).
1927+check_compound_stmt(Ctx, PT, LT, Ret, !Varset, Rigids, switch(Expr0, Cases0),
1928 switch(Expr, Cases)) :-
1929- expr_type(Ctx, PT, LT, !Varset, Expr0, Expr, SwitchType),
1930- check_cases(PT, LT, Ret, SwitchType, !Varset, Cases0, Cases).
1931-check_compound_stmt(Ctx, PT, LT, Ret, !Varset,
1932+ expr_type(Ctx, PT, LT, !Varset, Rigids, Expr0, Expr, SwitchType),
1933+ check_cases(PT, LT, Ret, SwitchType, !Varset, Rigids, Cases0, Cases).
1934+check_compound_stmt(Ctx, PT, LT, Ret, !Varset, Rigids,
1935 if_then_else(Cond0, ThenPart0, ElsePart0),
1936 if_then_else(Cond, ThenPart, ElsePart)) :-
1937- expr_type(Ctx, PT, LT, !Varset, Cond0, Cond, CondType),
1938+ expr_type(Ctx, PT, LT, !Varset, Rigids, Cond0, Cond, CondType),
1939 What = "statement 'if " ++ pretty.string_expr(Cond) ++ ":'",
1940 % Unify with Int type (all conditions must be Int).
1941- det_unify(Ctx, What, Cond, CondType, types.const("Int"), !Varset),
1942- check_stmts(PT, LT, Ret, !Varset, ThenPart0, ThenPart),
1943- check_stmts(PT, LT, Ret, !Varset, ElsePart0, ElsePart).
1944-check_compound_stmt(Ctx, PT, LT, Ret, !Varset, while(Cond0, Stmts0),
1945+ det_unify(Ctx, What, Cond, CondType, types.const("Int"), Rigids, !Varset),
1946+ check_stmts(PT, LT, Ret, !Varset, Rigids, ThenPart0, ThenPart),
1947+ check_stmts(PT, LT, Ret, !Varset, Rigids, ElsePart0, ElsePart).
1948+check_compound_stmt(Ctx, PT, LT, Ret, !Varset, Rigids, while(Cond0, Stmts0),
1949 while(Cond, Stmts)) :-
1950- expr_type(Ctx, PT, LT, !Varset, Cond0, Cond, CondType),
1951+ expr_type(Ctx, PT, LT, !Varset, Rigids, Cond0, Cond, CondType),
1952 What = "statement 'while " ++ pretty.string_expr(Cond) ++ ":'",
1953 % Unify with Int type (all conditions must be Int).
1954- det_unify(Ctx, What, Cond, CondType, types.const("Int"), !Varset),
1955- check_stmts(PT, LT, Ret, !Varset, Stmts0, Stmts).
1956+ det_unify(Ctx, What, Cond, CondType, types.const("Int"), Rigids, !Varset),
1957+ check_stmts(PT, LT, Ret, !Varset, Rigids, Stmts0, Stmts).
1958
1959 % check_stmts(PT, LT, RetType, !Varset, !Stmts).
1960 :- pred check_stmts(progtable::in, localtable::in, typeval::in,
1961- varset::in, varset::out, list(stmt)::in, list(stmt)::out) is det.
1962-check_stmts(_,_,_,!Varset,[],[]).
1963-check_stmts(PT, LT, RetType, !Varset, [Stmt0|Stmts0],[Stmt|Stmts]) :-
1964- check_stmt(PT, LT, RetType, !Varset, Stmt0, Stmt),
1965- check_stmts(PT, LT, RetType, !Varset, Stmts0, Stmts).
1966+ varset::in, varset::out, list(term.var)::in,
1967+ list(stmt)::in, list(stmt)::out) is det.
1968+check_stmts(_,_,_,!Varset,_,[],[]).
1969+check_stmts(PT, LT, RetType, !Varset, Rigids, [Stmt0|Stmts0],[Stmt|Stmts]) :-
1970+ check_stmt(PT, LT, RetType, !Varset, Rigids, Stmt0, Stmt),
1971+ check_stmts(PT, LT, RetType, !Varset, Rigids, Stmts0, Stmts).
1972
1973 % check_cases(PT, LT, RetType, SwitchType, !Varset, !Stmts).
1974 :- pred check_cases(progtable::in, localtable::in,
1975- typeval::in, typeval::in, varset::in, varset::out,
1976+ typeval::in, typeval::in, varset::in, varset::out, list(term.var)::in,
1977 list(case_stmt)::in,list(case_stmt)::out) is det.
1978-check_cases(_,_,_,_,!Varset,[],[]).
1979-check_cases(PT, LT, RetType, SwitchType, !Varset,
1980+check_cases(_,_,_,_,!Varset,_,[],[]).
1981+check_cases(PT, LT, RetType, SwitchType, !Varset, Rigids,
1982 [case_stmt(Pattern0, Stmts0, Ctx)|Cases0],
1983 [case_stmt(Pattern, Stmts, Ctx)|Cases]) :-
1984- check_pattern(Ctx, PT, LT, LT_Inside, !Varset,
1985- Pattern0, SwitchType, set.init, _, Pattern0, Pattern),
1986+ check_pattern(Ctx, PT, LT, !Varset, Rigids, Pattern0, SwitchType,
1987+ set.init, _, Pattern0, Pattern),
1988 % Note: Checking the statements uses the new LT which contains the
1989 % newly-bound variables by this pattern.
1990- check_stmts(PT, LT_Inside, RetType, !Varset, Stmts0, Stmts),
1991- check_cases(PT, LT, RetType, SwitchType, !Varset, Cases0, Cases).
1992-
1993-% Gets the name of a local variable, giving an appropriate error if not found.
1994-% (Note: Takes a progtable so it gives a different error if it's found
1995-% globally than not at all).
1996-:- pred get_local_var(context::in, progtable::in, localtable::in,
1997- varname::in, typeval::out) is det.
1998-get_local_var(Ctx, PT, LT, VarName, Type) :-
1999- ( tables.lookup_local(LT, VarName, Type_) ->
2000- % Found in local table
2001- Type = Type_
2002- ;
2003- VarName = svname(UnqualVarName),
2004- tables.lookup_function(PT, UnqualVarName, _)
2005- ->
2006- % Found in global function table - cannot assign
2007- context.throw_error("Cannot assign global variable: "
2008- ++ UnqualVarName, Ctx)
2009- ;
2010- context.throw_error("Undefined variable: "
2011- ++ ir.varname_to_string_noescape(VarName), Ctx)
2012- ).
2013+ check_stmts(PT, LT, RetType, !Varset, Rigids, Stmts0, Stmts),
2014+ check_cases(PT, LT, RetType, SwitchType, !Varset, Rigids, Cases0, Cases).
2015
2016 check_function(_PT, _LT, !Func) :-
2017 !.Func^func_body = func_builtin.
2018@@ -638,22 +650,11 @@
2019 ),
2020 check_type_star(Ctx, PT, !.Func^func_varset, !.Func^func_ret_type),
2021 check_types_star(Ctx, PT, !.Func^func_varset, list.map(pair.snd, Decls)),
2022- % Universally-quantify all the variables in Params, by binding them to
2023- % constants of the same name. (Note: It is important to ensure no name
2024- % conflict with actual type names, but this is already ensured by having
2025- % type vars in a different namespace).
2026- some [!Varset] (
2027- !:Varset = !.Func^func_varset,
2028- (
2029- !.Func^func_params = no
2030- ;
2031- !.Func^func_params = yes(Params2),
2032- foldl(bind_type, list.map(func({_,B,_})=B, Params2), !Varset)
2033- ),
2034- bind_type(!.Func^func_ret_type, !Varset),
2035- check_stmts(PT, LT, !.Func^func_ret_type, !Varset, Stmts0, Stmts),
2036- !Func ^ func_varset := !.Varset
2037- ),
2038+ % Check the function body and update the varset as a result
2039+ % (Checking may create or unify type variables.)
2040+ check_stmts(PT, LT, !.Func^func_ret_type, !.Func^func_varset, NewVarset,
2041+ !.Func^func_rigids, Stmts0, Stmts),
2042+ !Func ^ func_varset := NewVarset,
2043 !Func ^ func_body := func_body_ast(Decls, Stmts).
2044 % TODO: Type-check CFG-bodied functions.
2045 % This is difficult due to existential type. For now, does not do any checking
2046@@ -662,20 +663,6 @@
2047 !.Func^func_body = func_body_cfg(_,_),
2048 error("Not Implemented: Type checking on a function in CFG form").
2049
2050-% bind_type(Type, !Varset).
2051-% Bind all variables in the Type to a const type of the same name.
2052-:- pred bind_type(typeval::in, varset::in, varset::out) is det.
2053-bind_type(Type, !Varset) :-
2054- ( Type = variable(V) ->
2055- Term = types.const(types.varset_lookup_name(!.Varset, V)),
2056- types.varset_bind_var(V, Term, !Varset)
2057- ; Type = app(T1, T2) ->
2058- bind_type(T1, !Varset),
2059- foldl(bind_type, T2, !Varset)
2060- ;
2061- true
2062- ).
2063-
2064 check_typedef(PT, Typedef) :-
2065 check_ctors(PT, Typedef ^ typedef_varset, Typedef ^ typedef_ctors).
2066
2067@@ -702,8 +689,9 @@
2068 check_program_(PT, [Node0|Nodes0], [Node|Nodes]) :-
2069 (
2070 Node0 = pfunction(Func0),
2071- tables.build_localtable(Func0, LT),
2072- check_function(PT, LT, Func0, Func),
2073+ add_implicit_decls(Func0, Func1),
2074+ tables.build_localtable(Func1, LT),
2075+ check_function(PT, LT, Func1, Func),
2076 Node = pfunction(Func)
2077 ;
2078 Node0 = ptypedef(Typedef),
2079@@ -716,26 +704,104 @@
2080 ),
2081 check_program_(PT, Nodes0, Nodes).
2082
2083-det_unify(Ctx, What, Term, T1, T2, !Varset) :-
2084- ( types.unify(T1, T2, !Varset) ->
2085+% --- Implicit variable detection --- %
2086+
2087+% Augment a function's Decls with all variables which are bound anywhere in
2088+% the body of the function, but not explicitly declared.
2089+% (All variables assigned or appearing in a pattern.)
2090+% Each of these variables is given, as its type, a fresh type variable. (The
2091+% true type will be automatically inferred from unifications during checking.)
2092+:- pred add_implicit_decls(function::in, function::out) is det.
2093+add_implicit_decls(!Func) :-
2094+ !.Func^func_body = func_builtin.
2095+add_implicit_decls(!Func) :-
2096+ !.Func^func_body = func_body_ast(Decls0, Stmts),
2097+ Varset0 = !.Func^func_varset,
2098+ (
2099+ !.Func^func_params = no,
2100+ Params = []
2101+ ;
2102+ !.Func^func_params = yes(FuncParams),
2103+ Params = map(func({N,_,_}) = svname(N), FuncParams)
2104+ ),
2105+ DeclsSet = set(assoc_list.keys(Decls0) ++ Params),
2106+ % Get the set of all variables bound in the function's body
2107+ BoundVars0 = remove_dups(boundvars_stmts(Stmts)),
2108+ % ... which are not already explicitly declared
2109+ filter((pred(V::in) is semidet :- \+ member(V, DeclsSet)),
2110+ BoundVars0, BoundVars),
2111+ % Construct NewDecls, an assoc list which maps each BoundVar onto a fresh
2112+ % type variable
2113+ map_foldl((pred(V::in, V-T::out, VS0::in, VS::out) is det :-
2114+ types.new_var(T, VS0, VS)),
2115+ BoundVars, NewDecls, Varset0, Varset),
2116+ !Func^func_body := func_body_ast(Decls0 ++ NewDecls, Stmts),
2117+ !Func^func_varset := Varset.
2118+add_implicit_decls(!Func) :-
2119+ !.Func^func_body = func_body_cfg(_, _),
2120+ error("Not Implemented: Implicit decls of a function in CFG form").
2121+
2122+% Get the set of all variables bound in the statement block.
2123+:- func boundvars_stmts(list(stmt)) = list(varname).
2124+boundvars_stmts(Stmts) = condense(map(boundvars_stmt, Stmts)).
2125+
2126+% Get the set of all variables bound in the statement.
2127+:- func boundvars_stmt(stmt) = list(varname).
2128+boundvars_stmt(basic_stmt(Stmt, _)) = boundvars_basic_stmt(Stmt).
2129+boundvars_stmt(compound_stmt(Stmt, _)) = boundvars_compound_stmt(Stmt).
2130+
2131+:- func boundvars_basic_stmt(basic_stmt) = list(varname).
2132+boundvars_basic_stmt(Stmt) = Vars :-
2133+ % Only assignment statements bind variables
2134+ ( Stmt = assign(Var, _) ->
2135+ Vars = [Var]
2136+ ;
2137+ Vars = []
2138+ ).
2139+
2140+:- func boundvars_compound_stmt(compound_stmt) = list(varname).
2141+boundvars_compound_stmt(return(_)) = [].
2142+boundvars_compound_stmt(switch(_, Cases))
2143+ = condense(map(boundvars_case, Cases)).
2144+boundvars_compound_stmt(if_then_else(_, ThenPart, ElsePart))
2145+ = boundvars_stmts(ThenPart) ++ boundvars_stmts(ElsePart).
2146+boundvars_compound_stmt(while(_, Body)) = boundvars_stmts(Body).
2147+
2148+:- func boundvars_case(case_stmt) = list(varname).
2149+boundvars_case(case_stmt(Pat, Body, _))
2150+ = boundvars_pattern(Pat^pat_pattern) ++ boundvars_stmts(Body).
2151+
2152+:- func boundvars_pattern(pattern_) = list(varname).
2153+boundvars_pattern(pat_any) = [].
2154+boundvars_pattern(pat_var(V)) = [V].
2155+boundvars_pattern(pat_ctor(_, no)) = [].
2156+boundvars_pattern(pat_ctor(_, yes(Pats)))
2157+ = condense(map(boundvars_pattern, map(func(P) = P^pat_pattern, Pats))).
2158+boundvars_pattern(pat_intlit(_)) = [].
2159+
2160+det_unify(Ctx, What, Term, T1, T2, BoundVars, !Varset) :-
2161+ ( types.unify(T1, T2, BoundVars, !Varset) ->
2162 true
2163 ;
2164 type_error(Ctx, !.Varset, What, Term, T1, T2)
2165 ).
2166
2167+% --- Utility functions and errors --- %
2168+
2169 % det_unify_lists(Context, What, Term, Type1, Type2, !Varset).
2170 % Unify two lists types with respect to a single varset.
2171 % Zips with det_unify across 3 lists (with Term corresponding to Type1).
2172 % Precond: All 3 lists are the same size
2173 :- pred det_unify_lists(context::in, string::in, list(expr)::in,
2174 list(typeval)::in, list(typeval)::in,
2175- varset::in, varset::out) is det.
2176-det_unify_lists(_Ctx, _What, [], _, _, !Varset).
2177-det_unify_lists(_Ctx, _What, [_|_], [], _, !Varset).
2178-det_unify_lists(_Ctx, _What, [_|_], [_|_], [], !Varset).
2179-det_unify_lists(Ctx, What, [Term|Terms], [T1|T1s], [T2|T2s], !Varset) :-
2180- det_unify(Ctx, What, Term, T1, T2, !Varset),
2181- det_unify_lists(Ctx, What, Terms, T1s, T2s, !Varset).
2182+ list(term.var)::in, varset::in, varset::out) is det.
2183+det_unify_lists(_Ctx, _What, [], _, _, _, !Varset).
2184+det_unify_lists(_Ctx, _What, [_|_], [], _, _, !Varset).
2185+det_unify_lists(_Ctx, _What, [_|_], [_|_], [], _, !Varset).
2186+det_unify_lists(Ctx, What, [Term|Terms], [T1|T1s], [T2|T2s], Rigids,
2187+ !Varset) :-
2188+ det_unify(Ctx, What, Term, T1, T2, Rigids, !Varset),
2189+ det_unify_lists(Ctx, What, Terms, T1s, T2s, Rigids, !Varset).
2190
2191 % type_error(Context, Varset, What, Term, Term_Type, Other_Type).
2192 % Throws an error resulting from failing to unify Type1 and Type2 with
2193
2194=== modified file 'src/types.m'
2195--- src/types.m 2010-05-05 04:05:24 +0000
2196+++ src/types.m 2010-05-10 05:50:41 +0000
2197@@ -87,6 +87,10 @@
2198 % Fails if the types can't unify.
2199 % Succeeds if they do, and possibly updates varset with new bindings.
2200 :- pred unify(typeval::in, typeval::in, varset::in, varset::out) is semidet.
2201+% Like unify, but also takes a list of vars which must not be bound.
2202+% (The unification fails if these vars get bound.)
2203+:- pred unify(typeval::in, typeval::in, list(var)::in,
2204+ varset::in, varset::out) is semidet.
2205
2206 % Get the name of a variable from a varset.
2207 % Prefix some number with "t_" if not found.
2208@@ -155,9 +159,11 @@
2209 term.apply_rec_substitution(Type0, Sub, Type).
2210
2211 unify(T1, T2, !Varset) :-
2212+ unify(T1, T2, [], !Varset).
2213+unify(T1, T2, BoundVars, !Varset) :-
2214 some [!Sub] (
2215 varset.get_bindings(!.Varset, !:Sub),
2216- term.unify_term(T1, T2, !Sub), % Can fail
2217+ term.unify_term_dont_bind(T1, T2, BoundVars, !Sub), % Can fail
2218 varset.set_bindings(!.Varset, !.Sub, !:Varset)
2219 ).
2220
2221
2222=== modified file 'src/util.m'
2223--- src/util.m 2010-05-05 04:06:15 +0000
2224+++ src/util.m 2010-05-10 05:50:41 +0000
2225@@ -91,6 +91,10 @@
2226 % is in the output, then Y-X won't also be in the output set).
2227 :- func list_all_pairs(list(A)) = list(pair(A,A)).
2228
2229+% list_first_duplicate(L, X). If L contains duplicates, X is the first
2230+% duplicate. Fails if L does not contain duplicates.
2231+:- pred list_first_duplicate(list(A)::in, A::out) is semidet.
2232+
2233 % set_all_true(Pred, Set) takes a closure with one input argument.
2234 % Succeeds if Pred succeeds for every member of Set, else fails.
2235 :- pred set_all_true(pred(X)::in(pred(in) is semidet), set(X)::in)
2236@@ -234,6 +238,7 @@
2237 :- import_module dir.
2238 :- import_module unit.
2239 :- import_module term_io.
2240+:- use_module set_tree234.
2241
2242 zipwith(_Pred, [], [], []).
2243 zipwith(Pred, [X|Xs], [Y|Ys], [A|As]) :-
2244@@ -287,6 +292,17 @@
2245 XPairXs = map(func(Y) = X-Y, Xs),
2246 XsAllPairs = list_all_pairs(Xs).
2247
2248+list_first_duplicate(L, X) :-
2249+ list_first_duplicate_(L, set_tree234.init, X).
2250+:- pred list_first_duplicate_(list(A)::in, set_tree234.set_tree234(A)::in,
2251+ A::out) is semidet.
2252+list_first_duplicate_([X|Xs], S, D) :-
2253+ ( set_tree234.member(S, X) ->
2254+ D = X
2255+ ;
2256+ list_first_duplicate_(Xs, set_tree234.insert(X, S), D)
2257+ ).
2258+
2259 repeat(Pred, Count, !A) :-
2260 ( Count =< 0 ->
2261 true
2262
2263=== added file 'test/cases/compiler/implicitvar.mar'
2264--- test/cases/compiler/implicitvar.mar 1970-01-01 00:00:00 +0000
2265+++ test/cases/compiler/implicitvar.mar 2010-05-10 05:50:41 +0000
2266@@ -0,0 +1,47 @@
2267+# Assignment to an undeclared variable (should infer the type).
2268+# Bug #483082 -- Variables should not require declaration
2269+
2270+import unittest
2271+
2272+def my_id(x :: a) :: a = x
2273+
2274+# Test basic ability to assign a variable without declaring it
2275+def assign_implicit(x :: Int) :: Int:
2276+ y = x
2277+ return y
2278+
2279+# Test ability to implicitly shadow a global variable by assigning to a local
2280+# of the same name
2281+def shadow_global(x :: Int) :: Int:
2282+ my_id = x
2283+ return my_id
2284+
2285+# Test that the assigned variable has a monomorphic (bindable) type
2286+def implicit_type(x :: Int) :: Array(Int):
2287+ # Test using a special construct which creates a monomorphic type variable
2288+ y = [] # y :: Array(a)
2289+ z = array_add(y, x) # z :: Array(Int)
2290+ return z
2291+
2292+def implicit_type2(x :: Int) :: Int:
2293+ # Test using a global variable with a type var (all type variables in the
2294+ # global are converted into new monomorphic type variables)
2295+ f = my_id # f :: a -> a
2296+ y = f(x) # y :: Int
2297+ return y
2298+
2299+# Unit tests
2300+def test_assign_implicit() :: Int:
2301+ begin_case("assign_implicit")
2302+ assert_eq(assign_implicit(3), 3, "assign_implicit(3) != 3")
2303+ end_case("assign_implicit")
2304+ begin_case("shadow_global")
2305+ assert_eq(shadow_global(3), 3, "shadow_global(3) != 3")
2306+ end_case("shadow_global")
2307+ begin_case("implicit_type")
2308+ assert_eq(implicit_type(3), [3], "implicit_type(3) != [3]")
2309+ end_case("implicit_type")
2310+ begin_case("implicit_type")
2311+ assert_eq(implicit_type2(3), 3, "implicit_type2(3) != 3")
2312+ end_case("implicit_type")
2313+ return 0
2314
2315=== added file 'test/cases/compiler/patterntypeerror.mar'
2316--- test/cases/compiler/patterntypeerror.mar 1970-01-01 00:00:00 +0000
2317+++ test/cases/compiler/patterntypeerror.mar 2010-05-10 05:50:41 +0000
2318@@ -0,0 +1,27 @@
2319+# A very picky test about the pattern matching type error
2320+# (Launchpad Bug #574277).
2321+
2322+type FooType(a):
2323+ Foo(a)
2324+
2325+type BarType:
2326+ Bar
2327+
2328+type BazType:
2329+ Baz
2330+
2331+# This function contains a type error:
2332+# Type error in pattern 'Foo(Baz)'
2333+# Term: Baz
2334+# Type: BazType
2335+# Expected: BarType.
2336+# The error is printed at too high a level due to type variable bindings:
2337+# Type error in pattern 'Foo(Baz)'
2338+# Term: Foo(Baz)
2339+# Type: FooType(BazType)
2340+# Expected: FooType(BarType).
2341+def foo(x :: FooType(BarType)) :: Int:
2342+ switch x:
2343+ case Foo(Baz):
2344+ return 1
2345+ return 0
2346
2347=== added file 'test/cases/compiler/patterntypeerror.mtc'
2348--- test/cases/compiler/patterntypeerror.mtc 1970-01-01 00:00:00 +0000
2349+++ test/cases/compiler/patterntypeerror.mtc 2010-05-10 05:50:41 +0000
2350@@ -0,0 +1,8 @@
2351+# vim: filetype=yaml
2352+compile:
2353+ outcome: fail
2354+ errors: |
2355+ patterntypeerror.mar:25: (foo) Type error in pattern 'Foo(Baz)'
2356+ Term: Baz
2357+ Type: BazType
2358+ Expected: BarType.
2359
2360=== modified file 'test/cases/compiler/phipred.mtc'
2361--- test/cases/compiler/phipred.mtc 2010-05-06 12:19:45 +0000
2362+++ test/cases/compiler/phipred.mtc 2010-05-10 05:50:41 +0000
2363@@ -3,4 +3,3 @@
2364 run:
2365 - call: twoswitch(Nothing, Nothing)
2366 stdout: "0\n"
2367- expect: fail
2368
2369=== modified file 'test/cases/compiler/switch.mar'
2370--- test/cases/compiler/switch.mar 2010-05-03 01:50:15 +0000
2371+++ test/cases/compiler/switch.mar 2010-05-10 05:50:41 +0000
2372@@ -16,6 +16,10 @@
2373 type Box(a):
2374 Box(a)
2375
2376+type OneOrTwo:
2377+ One(Int)
2378+ Two(Int)
2379+
2380 # Test cases with multiple levels of pattern matching
2381 def switchtest(x :: Foo) :: Int:
2382 switch x:
2383@@ -72,6 +76,18 @@
2384 # declaration, so calls this an undefined variable).
2385 return y
2386
2387+# scopes_declare2(4) should be 4.
2388+# Same test as scopes_declare, but does not contain an explicit assignment
2389+# (only a pattern binding). Tests that the pattern binding itself is able to
2390+# escape the scope.
2391+def scopes_declare2(x :: Int) :: Int:
2392+ switch x:
2393+ case y:
2394+ pass
2395+ # y must still be bound after the switch statement
2396+ # (Bug #513638).
2397+ return y
2398+
2399 # Test trivial (unconditional) binding of a variable
2400 # Although the test suite won't test for this, it should be compiled to code
2401 # without a switch, because there is no actual condition.
2402@@ -97,6 +113,14 @@
2403 case Pair(m, Box(n)):
2404 return add(m, n)
2405
2406+# Test that it is legal to bind the same variable name twice
2407+def twobinds(x :: OneOrTwo) :: Int:
2408+ switch x:
2409+ case One(y):
2410+ return y
2411+ case Two(y):
2412+ return add(y, 1)
2413+
2414 # From fully-worked example in doc/dev/switchfactor.
2415 # Test that factoring doesn't break the precedence of the cases
2416 def factor(x :: Pair(Bar, Int)) :: Int:
2417@@ -185,6 +209,15 @@
2418 end_case("switch (trickybind)")
2419 return 0
2420
2421+def test_twobinds() :: Int:
2422+ begin_case("switch (twobinds)")
2423+ assert_eq(twobinds(One(7)), 7, "twobinds(One(7)) != 7")
2424+ end_case("switch (twobinds)")
2425+ begin_case("switch (twobinds)")
2426+ assert_eq(twobinds(Two(7)), 8, "twobinds(Two(7)) != 8")
2427+ end_case("switch (twobinds)")
2428+ return 0
2429+
2430 def test_factor() :: Int:
2431 begin_case("switch (factoring)")
2432 assert_eq(factor(Pair(B, 1)), 1, "factor(Pair(B, 1)) != 1")
2433
2434=== removed file 'test/cases/compiler/switch.mtc'
2435--- test/cases/compiler/switch.mtc 2010-05-03 02:53:53 +0000
2436+++ test/cases/compiler/switch.mtc 1970-01-01 00:00:00 +0000
2437@@ -1,5 +0,0 @@
2438-# vim: filetype=yaml
2439-# Temporary: Expect failure due to bug #513578
2440-compile:
2441- outcome: succeed
2442- expect: compile_error
2443
2444=== modified file 'test/cases/semantic/assignglobal.mar'
2445--- test/cases/semantic/assignglobal.mar 2010-01-28 06:26:27 +0000
2446+++ test/cases/semantic/assignglobal.mar 2010-05-10 05:50:41 +0000
2447@@ -1,4 +1,6 @@
2448-# Expects a "cannot assign global" error.
2449+# Used to expect a "cannot assign global" error.
2450+# (Now, due to implicit declarations, myconstant is just a shadowed local
2451+# variable, so this is no longer an error.)
2452
2453 def myconstant :: Int = 3
2454
2455
2456=== modified file 'test/cases/semantic/assignglobal.mtc'
2457--- test/cases/semantic/assignglobal.mtc 2010-01-28 06:26:27 +0000
2458+++ test/cases/semantic/assignglobal.mtc 2010-05-10 05:50:41 +0000
2459@@ -1,5 +1,3 @@
2460 # vim: filetype=yaml
2461 compile:
2462- outcome: fail
2463- errors: |
2464- assignglobal.mar:6: (foo) Cannot assign global variable: myconstant.
2465+ outcome: succeed
2466
2467=== modified file 'test/cases/semantic/casetypecheck.mtc'
2468--- test/cases/semantic/casetypecheck.mtc 2010-01-28 06:47:47 +0000
2469+++ test/cases/semantic/casetypecheck.mtc 2010-05-10 05:50:41 +0000
2470@@ -1,7 +1,6 @@
2471 # vim: filetype=yaml
2472 compile:
2473 outcome: fail
2474- expect: fail
2475 errors: |
2476 casetypecheck.mar:5: (foo) Type error in pattern 'x'
2477 Term: x
2478
2479=== modified file 'test/cases/semantic/dupfield.mar'
2480--- test/cases/semantic/dupfield.mar 2010-01-28 04:26:55 +0000
2481+++ test/cases/semantic/dupfield.mar 2010-05-10 05:50:41 +0000
2482@@ -1,4 +1,5 @@
2483-# Expects a "duplicate field name" error.
2484+# Expects a "duplicate field name" error, in the same constructor, with
2485+# distinct types.
2486
2487 type Foo:
2488- X(v :: Int, v :: Int)
2489+ X(v :: Int, v :: Array(Int))
2490
2491=== modified file 'test/cases/semantic/dupfield.mtc'
2492--- test/cases/semantic/dupfield.mtc 2010-01-28 04:26:55 +0000
2493+++ test/cases/semantic/dupfield.mtc 2010-05-10 05:50:41 +0000
2494@@ -1,6 +1,8 @@
2495 # vim: filetype=yaml
2496 compile:
2497 outcome: fail
2498- expect: fail
2499+ # Note: Unacceptable to have the "with differing types" error (from
2500+ # dupfield3), as it implies that making them the same type will correct
2501+ # the error. It won't (see dupfield2).
2502 errors: |
2503- dupfield.mar:4: (Foo) Duplicate field name: v.
2504+ dupfield.mar:5: (Foo) Duplicate field name: v.
2505
2506=== added file 'test/cases/semantic/dupfield2.mar'
2507--- test/cases/semantic/dupfield2.mar 1970-01-01 00:00:00 +0000
2508+++ test/cases/semantic/dupfield2.mar 2010-05-10 05:50:41 +0000
2509@@ -0,0 +1,5 @@
2510+# Expects a "duplicate field name" error, in the same constructor, even with
2511+# the same types.
2512+
2513+type Foo:
2514+ X(v :: Int, v :: Int)
2515
2516=== added file 'test/cases/semantic/dupfield2.mtc'
2517--- test/cases/semantic/dupfield2.mtc 1970-01-01 00:00:00 +0000
2518+++ test/cases/semantic/dupfield2.mtc 2010-05-10 05:50:41 +0000
2519@@ -0,0 +1,5 @@
2520+# vim: filetype=yaml
2521+compile:
2522+ outcome: fail
2523+ errors: |
2524+ dupfield2.mar:5: (Foo) Duplicate field name: v.
2525
2526=== renamed file 'test/cases/semantic/dupfield2.mar' => 'test/cases/semantic/dupfield3.mar'
2527=== renamed file 'test/cases/semantic/dupfield2.mtc' => 'test/cases/semantic/dupfield3.mtc'
2528--- test/cases/semantic/dupfield2.mtc 2010-01-28 06:26:27 +0000
2529+++ test/cases/semantic/dupfield3.mtc 2010-05-10 05:50:41 +0000
2530@@ -2,4 +2,4 @@
2531 compile:
2532 outcome: fail
2533 errors: |
2534- dupfield2.mar:10: (Bar) Duplicate field name with differing types: v.
2535+ dupfield3.mar:10: (Bar) Duplicate field name with differing types: v.
2536
2537=== added file 'test/cases/semantic/dupvarcase.mar'
2538--- test/cases/semantic/dupvarcase.mar 1970-01-01 00:00:00 +0000
2539+++ test/cases/semantic/dupvarcase.mar 2010-05-10 05:50:41 +0000
2540@@ -0,0 +1,16 @@
2541+# Error if you re-use a name already in-scope in a pattern
2542+# (Technically a type error, since you're trying to bind an existing variable
2543+# to a new value with a different type. If it happens to have the same type,
2544+# then it's not an error.)
2545+# This used to be a common idiom, until pattern variables were changed so they
2546+# were scoped to the whole function, making it a type error.
2547+
2548+type Box(a):
2549+ Box(a)
2550+
2551+def unbox(x :: Box(a)) :: a:
2552+ switch x:
2553+ # Type error: the "x" in the pattern is the same "x" as outside the
2554+ # pattern, and they have different types
2555+ case Box(x):
2556+ return x
2557
2558=== added file 'test/cases/semantic/dupvarcase.mtc'
2559--- test/cases/semantic/dupvarcase.mtc 1970-01-01 00:00:00 +0000
2560+++ test/cases/semantic/dupvarcase.mtc 2010-05-10 05:50:41 +0000
2561@@ -0,0 +1,8 @@
2562+# vim: filetype=yaml
2563+compile:
2564+ outcome: fail
2565+ errors: |
2566+ dupvarcase.mar:15: (unbox) Type error in pattern 'Box(x)'
2567+ Term: x
2568+ Type: Box(a)
2569+ Expected: a.
2570
2571=== added file 'test/cases/semantic/dupvarcase2.mar'
2572--- test/cases/semantic/dupvarcase2.mar 1970-01-01 00:00:00 +0000
2573+++ test/cases/semantic/dupvarcase2.mar 2010-05-10 05:50:41 +0000
2574@@ -0,0 +1,17 @@
2575+# Error if you bind the same variable name in different patterns, and the
2576+# types don't unify.
2577+# (Technically a type error, since you're trying to bind an two variables
2578+# with different types. If it happens to have the same type, then it's not an
2579+# error -- this is tested in compiler/switch.twobinds.)
2580+
2581+type OneOrTwo:
2582+ One(Int)
2583+ Two(Array(Int))
2584+
2585+# Test that it is legal to bind the same variable name twice
2586+def twobinds(x :: OneOrTwo) :: Int:
2587+ switch x:
2588+ case One(y):
2589+ return y
2590+ case Two(y):
2591+ return add(array_ref(y, 0), 1)
2592
2593=== added file 'test/cases/semantic/dupvarcase2.mtc'
2594--- test/cases/semantic/dupvarcase2.mtc 1970-01-01 00:00:00 +0000
2595+++ test/cases/semantic/dupvarcase2.mtc 2010-05-10 05:50:41 +0000
2596@@ -0,0 +1,8 @@
2597+# vim: filetype=yaml
2598+compile:
2599+ outcome: fail
2600+ errors: |
2601+ dupvarcase2.mar:16: (twobinds) Type error in pattern 'Two(y)'
2602+ Term: y
2603+ Type: Int
2604+ Expected: Array(Int).
2605
2606=== modified file 'test/cases/semantic/localreadwrite.mtc'
2607--- test/cases/semantic/localreadwrite.mtc 2010-01-28 07:16:24 +0000
2608+++ test/cases/semantic/localreadwrite.mtc 2010-05-10 05:50:41 +0000
2609@@ -1,6 +1,5 @@
2610 # vim: filetype=yaml
2611 compile:
2612 outcome: fail
2613- expect: fail
2614 errors: |
2615 localreadwrite.mar:8: (foo) Use of uninitialised variable: x.
2616
2617=== added file 'test/cases/semantic/localreadwrite2.mar'
2618--- test/cases/semantic/localreadwrite2.mar 1970-01-01 00:00:00 +0000
2619+++ test/cases/semantic/localreadwrite2.mar 2010-05-10 05:50:41 +0000
2620@@ -0,0 +1,12 @@
2621+# Test that reading a local variable before it is defined is a "use of
2622+# uninitialised variable" error, not an "undefined variable" error.
2623+
2624+def foo() :: Int:
2625+ var y :: Int
2626+ y = x # "Use of uninitialised variable: x"
2627+ # (Bug #513638: Prints "undefined variable" instead.)
2628+ # Now bind x = 4
2629+ switch 4:
2630+ case x:
2631+ pass
2632+ return y
2633
2634=== added file 'test/cases/semantic/localreadwrite2.mtc'
2635--- test/cases/semantic/localreadwrite2.mtc 1970-01-01 00:00:00 +0000
2636+++ test/cases/semantic/localreadwrite2.mtc 2010-05-10 05:50:41 +0000
2637@@ -0,0 +1,5 @@
2638+# vim: filetype=yaml
2639+compile:
2640+ outcome: fail
2641+ errors: |
2642+ localreadwrite2.mar:6: (foo) Use of uninitialised variable: x.
2643
2644=== added file 'test/cases/semantic/localtypevar.mar'
2645--- test/cases/semantic/localtypevar.mar 1970-01-01 00:00:00 +0000
2646+++ test/cases/semantic/localtypevar.mar 2010-05-10 05:50:41 +0000
2647@@ -0,0 +1,14 @@
2648+# Test that programs are rejected if they name a type variable explicitly in
2649+# the body, which isn't in the head.
2650+# (Arguably this should be allowed, but it currently isn't, as per
2651+# doc/ref/types. See Bug #482947).
2652+
2653+# Should be fine
2654+def foo :: Int:
2655+ x = error("xxx")
2656+ return 0
2657+
2658+def bar :: Int:
2659+ var x :: a # Undefined type variable
2660+ x = error("xxx")
2661+ return 0
2662
2663=== added file 'test/cases/semantic/localtypevar.mtc'
2664--- test/cases/semantic/localtypevar.mtc 1970-01-01 00:00:00 +0000
2665+++ test/cases/semantic/localtypevar.mtc 2010-05-10 05:50:41 +0000
2666@@ -0,0 +1,7 @@
2667+# vim: filetype=yaml
2668+
2669+compile:
2670+ outcome: fail
2671+ # For some reason this is reported as a syntax error
2672+ errors: |
2673+ localtypevar.mar:12: (bar) Syntax error: Undefined type variable "a".
2674
2675=== added file 'test/cases/semantic/localtypevar2.mar'
2676--- test/cases/semantic/localtypevar2.mar 1970-01-01 00:00:00 +0000
2677+++ test/cases/semantic/localtypevar2.mar 2010-05-10 05:50:41 +0000
2678@@ -0,0 +1,10 @@
2679+# Test that programs are rejected if they name a type variable explicitly in
2680+# the body, which isn't in the head.
2681+# This example should NOT be allowed even if local type variables may be
2682+# mentioned. If mentioned, they should be rigid, so this would be a type error
2683+# (cannot unify rigid variable 'a" with Int).
2684+
2685+def foo :: Int:
2686+ var x :: a # Undefined type variable
2687+ x = 4
2688+ return x
2689
2690=== added file 'test/cases/semantic/localtypevar2.mtc'
2691--- test/cases/semantic/localtypevar2.mtc 1970-01-01 00:00:00 +0000
2692+++ test/cases/semantic/localtypevar2.mtc 2010-05-10 05:50:41 +0000
2693@@ -0,0 +1,6 @@
2694+# vim: filetype=yaml
2695+
2696+compile:
2697+ outcome: fail
2698+ errors: |
2699+ localtypevar2.mar:8: (foo) Syntax error: Undefined type variable "a".
2700
2701=== added file 'test/cases/semantic/monomorphism.mar'
2702--- test/cases/semantic/monomorphism.mar 1970-01-01 00:00:00 +0000
2703+++ test/cases/semantic/monomorphism.mar 2010-05-10 05:50:41 +0000
2704@@ -0,0 +1,16 @@
2705+# Test that local type variables are monomorphic (once bound, they remain
2706+# bound)
2707+# From doc/ref/types:
2708+
2709+def g :: Array(a) = []
2710+
2711+def polymorphic(x :: Int) :: Array(Int):
2712+ r = array_add(g, x)
2713+ w = array_add(g, [1]) # Should be fine
2714+ return r
2715+
2716+def monomorphic(x :: Int) :: Array(Int):
2717+ v = []
2718+ r = array_add(v, x)
2719+ w = array_add(v, [1]) # Type error
2720+ return r
2721
2722=== added file 'test/cases/semantic/monomorphism.mtc'
2723--- test/cases/semantic/monomorphism.mtc 1970-01-01 00:00:00 +0000
2724+++ test/cases/semantic/monomorphism.mtc 2010-05-10 05:50:41 +0000
2725@@ -0,0 +1,9 @@
2726+# vim: filetype=yaml
2727+
2728+compile:
2729+ outcome: fail
2730+ errors: |
2731+ monomorphism.mar:15: (monomorphic) Type error in expression 'array_add(v, [1])'
2732+ Term: [1]
2733+ Type: Array(Int)
2734+ Expected: Int.
2735
2736=== added file 'test/cases/semantic/monomorphism2.mar'
2737--- test/cases/semantic/monomorphism2.mar 1970-01-01 00:00:00 +0000
2738+++ test/cases/semantic/monomorphism2.mar 2010-05-10 05:50:41 +0000
2739@@ -0,0 +1,23 @@
2740+# Test that local type variables are monomorphic (once bound, they remain
2741+# bound).
2742+# This time, test lifting a global constant into a local variable
2743+# From doc/ref/types:
2744+
2745+type Pair(a, b):
2746+ Pair(a, b)
2747+
2748+def array_map(f :: a -> b, a :: Array(a)) :: Array(b):
2749+ # Doesn't matter how it's implemented
2750+ return []
2751+
2752+# Should be fine
2753+def polymorphic(f :: a -> b, g :: a -> c, x :: Array(a)) :: Pair(Array(b), Array(c)):
2754+ y = array_map(f, x)
2755+ z = array_map(g, x) # array_map used polymorphically
2756+ return Pair(y, z)
2757+
2758+def monomorphic(f :: a -> b, g :: a -> c, x :: Array(a)) :: Pair(Array(b), Array(c)):
2759+ mymap = array_map
2760+ y = mymap(f, x)
2761+ z = mymap(g, x) # Type error
2762+ return Pair(y, z)
2763
2764=== added file 'test/cases/semantic/monomorphism2.mtc'
2765--- test/cases/semantic/monomorphism2.mtc 1970-01-01 00:00:00 +0000
2766+++ test/cases/semantic/monomorphism2.mtc 2010-05-10 05:50:41 +0000
2767@@ -0,0 +1,9 @@
2768+# vim: filetype=yaml
2769+
2770+compile:
2771+ outcome: fail
2772+ errors: |
2773+ monomorphism2.mar:22: (monomorphic) Type error in expression 'mymap(g, x)'
2774+ Term: g
2775+ Type: a -> c
2776+ Expected: a -> b.
2777
2778=== added file 'test/cases/semantic/typeerror2.mar'
2779--- test/cases/semantic/typeerror2.mar 1970-01-01 00:00:00 +0000
2780+++ test/cases/semantic/typeerror2.mar 2010-05-10 05:50:41 +0000
2781@@ -0,0 +1,6 @@
2782+# Expects a type error for unifying an explicit type variable with Int
2783+
2784+def badint(x :: a) :: Int:
2785+ var y :: Int
2786+ y = x
2787+ return y
2788
2789=== added file 'test/cases/semantic/typeerror2.mtc'
2790--- test/cases/semantic/typeerror2.mtc 1970-01-01 00:00:00 +0000
2791+++ test/cases/semantic/typeerror2.mtc 2010-05-10 05:50:41 +0000
2792@@ -0,0 +1,9 @@
2793+# vim: filetype=yaml
2794+
2795+compile:
2796+ outcome: fail
2797+ errors: |
2798+ typeerror2.mar:5: (badint) Type error in statement 'y = x'
2799+ Term: x
2800+ Type: a
2801+ Expected: Int.
2802
2803=== added file 'test/cases/semantic/typeerror3.mar'
2804--- test/cases/semantic/typeerror3.mar 1970-01-01 00:00:00 +0000
2805+++ test/cases/semantic/typeerror3.mar 2010-05-10 05:50:41 +0000
2806@@ -0,0 +1,6 @@
2807+# Expects a type error for unifying Int with an explicit type variable
2808+# (This tests the opposite direction of unification than typeerror2)
2809+
2810+def badint(x :: a) :: Int:
2811+ x = 4
2812+ return 0
2813
2814=== added file 'test/cases/semantic/typeerror3.mtc'
2815--- test/cases/semantic/typeerror3.mtc 1970-01-01 00:00:00 +0000
2816+++ test/cases/semantic/typeerror3.mtc 2010-05-10 05:50:41 +0000
2817@@ -0,0 +1,9 @@
2818+# vim: filetype=yaml
2819+
2820+compile:
2821+ outcome: fail
2822+ errors: |
2823+ typeerror3.mar:5: (badint) Type error in statement 'x = 4'
2824+ Term: 4
2825+ Type: Int
2826+ Expected: a.
2827
2828=== added file 'test/cases/semantic/typeerror4.mar'
2829--- test/cases/semantic/typeerror4.mar 1970-01-01 00:00:00 +0000
2830+++ test/cases/semantic/typeerror4.mar 2010-05-10 05:50:41 +0000
2831@@ -0,0 +1,6 @@
2832+# The evil cast function
2833+# Expects a type error for trying to cast one arbitrary type to another
2834+# (Tests the same as typeerror 1 - 3, but with both sides as a variable)
2835+
2836+def cast(x :: a) :: b:
2837+ return x
2838
2839=== added file 'test/cases/semantic/typeerror4.mtc'
2840--- test/cases/semantic/typeerror4.mtc 1970-01-01 00:00:00 +0000
2841+++ test/cases/semantic/typeerror4.mtc 2010-05-10 05:50:41 +0000
2842@@ -0,0 +1,9 @@
2843+# vim: filetype=yaml
2844+
2845+compile:
2846+ outcome: fail
2847+ errors: |
2848+ typeerror4.mar:6: (cast) Type error in statement 'return x'
2849+ Term: x
2850+ Type: a
2851+ Expected: b.
2852
2853=== modified file 'test/cases/semantic/undefvar2.mar'
2854--- test/cases/semantic/undefvar2.mar 2010-01-28 06:26:27 +0000
2855+++ test/cases/semantic/undefvar2.mar 2010-05-10 05:50:41 +0000
2856@@ -1,5 +1,7 @@
2857-# Expects an "undefined variable" error.
2858+# Used to expect an "undefined variable" error.
2859+# (Now, due to implicit declarations, y is just assigned as expected,
2860+# so this is no longer an error.)
2861
2862 def foo(x :: Int) :: Int:
2863- y = x # Undefined variable
2864+ y = x
2865 return x
2866
2867=== modified file 'test/cases/semantic/undefvar2.mtc'
2868--- test/cases/semantic/undefvar2.mtc 2010-01-28 06:26:27 +0000
2869+++ test/cases/semantic/undefvar2.mtc 2010-05-10 05:50:41 +0000
2870@@ -1,5 +1,3 @@
2871 # vim: filetype=yaml
2872 compile:
2873- outcome: fail
2874- errors: |
2875- undefvar2.mar:4: (foo) Undefined variable: y.
2876+ outcome: succeed

Subscribers

People subscribed via source and target branches

to all changes: