[m-rev.] diff/for review: break up prog_data.m

Julien Fischer juliensf at cs.mu.OZ.AU
Tue Nov 22 18:30:20 AEDT 2005


Estimated hours taken: 3.5
Branches: main

Split the parse tree (currently defined in prog_data.m) into two
separate modules.  The reason for doing this is that while over 80%
of the modules in the compiler import prog_data, very few of them actually
require access to the types that define the parse tree (principally
the item type).  At the moment even small changes to these types can
result in recompiles that rebuild almost all of the compiler.  This change
shifts the item type (and related types) into a new module, prog_item,
that is only imported where these types are required (mostly at the
frontend of the compiler).  This should reduce the size of recompiles
required when the parse tree is modified.

This diff does not change any algorithms; it just shifts things around.

compiler/prog_data.m:
	Move the item type and any related types that are not needed
	after the HLDS has been built to the new prog_item module.

	Fix bitrot in comments.

	Fix formatting and layout of comments.

	Use unexpected/2 in place of error/1 in a spot.

compiler/prog_item.m:
	New file.  This module contains any parts of the parse tree
	that are not needed by the rest of the compiler after the
	HLDS has been built.

compiler/check_typeclass.m:
	s/list(instance_method)/instance_methods/

compiler/equiv_type.m:
compiler/hlds_module.m:
compiler/intermod.m:
compiler/make.module_dep_file.m:
compiler/make_hlds.m:
compiler/mercury_compile.m:
compiler/mercury_to_mercury.m:
compiler/module_qual.m:
compiler/modules.m:
compiler/parse_tree.m:
compiler/prog_io.m:
compiler/prog_io_dcg.m:
compiler/prog_io_goal.m:
compiler/prog_io_pragma.m:
compiler/prog_io_typeclass.m:
compiler/prog_io_util.m:
compiler/prog_out.m:
compiler/prog_util.m:
compiler/recompilation.check.m:
compiler/recompilation.usage.m:
compiler/recompilation.version.m:
compiler/trans_opt.m:
	Conform to the above changes.

compiler/notes/compiler_design.html:
	Mention the new module.

Julien.

Index: compiler/check_typeclass.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/check_typeclass.m,v
retrieving revision 1.83
diff -u -r1.83 check_typeclass.m
--- compiler/check_typeclass.m	4 Nov 2005 03:40:42 -0000	1.83
+++ compiler/check_typeclass.m	22 Nov 2005 06:38:52 -0000
@@ -327,7 +327,7 @@
     % any of the methods from the class interface. If so, add an appropriate
     % error message to the list of error messages.
     %
-:- pred check_for_bogus_methods(list(instance_method)::in, class_id::in,
+:- pred check_for_bogus_methods(instance_methods::in, class_id::in,
     list(pred_id)::in, prog_context::in, module_info::in,
     error_messages::in, error_messages::out) is det.

@@ -612,7 +612,7 @@
     % being combined into a single definition.
     %
 :- pred get_matching_instance_defns(instance_body::in, pred_or_func::in,
-    sym_name::in, arity::in, list(instance_method)::out) is det.
+    sym_name::in, arity::in, instance_methods::out) is det.

 get_matching_instance_defns(abstract, _, _, _, []).
 get_matching_instance_defns(concrete(InstanceMethods), PredOrFunc, MethodName,
Index: compiler/equiv_type.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/equiv_type.m,v
retrieving revision 1.55
diff -u -r1.55 equiv_type.m
--- compiler/equiv_type.m	17 Nov 2005 15:57:09 -0000	1.55
+++ compiler/equiv_type.m	18 Nov 2005 06:36:51 -0000
@@ -20,6 +20,7 @@

 :- import_module mdbcomp.prim_data.
 :- import_module parse_tree.prog_data.
+:- import_module parse_tree.prog_item.
 :- import_module recompilation.

 :- import_module bool.
Index: compiler/hlds_module.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/hlds_module.m,v
retrieving revision 1.125
diff -u -r1.125 hlds_module.m
--- compiler/hlds_module.m	14 Nov 2005 05:14:09 -0000	1.125
+++ compiler/hlds_module.m	18 Nov 2005 06:36:16 -0000
@@ -32,6 +32,7 @@
 :- import_module mdbcomp.prim_data.
 :- import_module parse_tree.module_qual.
 :- import_module parse_tree.prog_data.
+:- import_module parse_tree.prog_item.
 :- import_module parse_tree.prog_foreign.
 :- import_module recompilation.

Index: compiler/intermod.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/intermod.m,v
retrieving revision 1.187
diff -u -r1.187 intermod.m
--- compiler/intermod.m	17 Nov 2005 15:57:17 -0000	1.187
+++ compiler/intermod.m	18 Nov 2005 06:45:12 -0000
@@ -40,7 +40,7 @@

 :- import_module hlds.hlds_module.
 :- import_module parse_tree.modules.
-:- import_module parse_tree.prog_data.
+:- import_module parse_tree.prog_item.
 :- import_module parse_tree.prog_io.

 :- import_module bool.
Index: compiler/make.module_dep_file.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/make.module_dep_file.m,v
retrieving revision 1.15
diff -u -r1.15 make.module_dep_file.m
--- compiler/make.module_dep_file.m	28 Oct 2005 02:10:15 -0000	1.15
+++ compiler/make.module_dep_file.m	18 Nov 2005 06:51:53 -0000
@@ -38,6 +38,8 @@

 :- implementation.

+:- import_module parse_tree.prog_item.
+
 %-----------------------------------------------------------------------------%

 get_module_dependencies(ModuleName, MaybeImports, !Info, !IO) :-
Index: compiler/make_hlds.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/make_hlds.m,v
retrieving revision 1.519
diff -u -r1.519 make_hlds.m
--- compiler/make_hlds.m	28 Oct 2005 02:10:16 -0000	1.519
+++ compiler/make_hlds.m	18 Nov 2005 06:34:56 -0000
@@ -31,6 +31,7 @@
 :- import_module parse_tree.equiv_type.
 :- import_module parse_tree.module_qual.
 :- import_module parse_tree.prog_data.
+:- import_module parse_tree.prog_item.

 :- import_module bool.
 :- import_module io.
Index: compiler/mercury_compile.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/mercury_compile.m,v
retrieving revision 1.362
diff -u -r1.362 mercury_compile.m
--- compiler/mercury_compile.m	16 Nov 2005 07:02:00 -0000	1.362
+++ compiler/mercury_compile.m	22 Nov 2005 04:52:47 -0000
@@ -155,6 +155,7 @@
 :- import_module parse_tree.error_util.
 :- import_module parse_tree.mercury_to_mercury.
 :- import_module parse_tree.prog_data.
+:- import_module parse_tree.prog_item.
 :- import_module parse_tree.prog_util.
 :- import_module recompilation.
 :- import_module recompilation.check.
Index: compiler/mercury_to_mercury.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/mercury_to_mercury.m,v
retrieving revision 1.274
diff -u -r1.274 mercury_to_mercury.m
--- compiler/mercury_to_mercury.m	8 Nov 2005 08:14:52 -0000	1.274
+++ compiler/mercury_to_mercury.m	18 Nov 2005 06:37:07 -0000
@@ -47,6 +47,7 @@
 :- import_module libs.globals.
 :- import_module mdbcomp.prim_data.
 :- import_module parse_tree.prog_data.
+:- import_module parse_tree.prog_item.

 :- import_module bool.
 :- import_module char.
Index: compiler/module_qual.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/module_qual.m,v
retrieving revision 1.119
diff -u -r1.119 module_qual.m
--- compiler/module_qual.m	8 Nov 2005 08:14:53 -0000	1.119
+++ compiler/module_qual.m	18 Nov 2005 06:37:43 -0000
@@ -26,6 +26,7 @@

 :- import_module mdbcomp.prim_data.
 :- import_module parse_tree.prog_data.
+:- import_module parse_tree.prog_item.
 :- import_module recompilation.

 :- import_module bool.
Index: compiler/modules.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/modules.m,v
retrieving revision 1.363
diff -u -r1.363 modules.m
--- compiler/modules.m	17 Nov 2005 15:57:24 -0000	1.363
+++ compiler/modules.m	18 Nov 2005 06:38:01 -0000
@@ -45,6 +45,7 @@
 :- import_module libs.timestamp.
 :- import_module mdbcomp.prim_data.
 :- import_module parse_tree.prog_data.
+:- import_module parse_tree.prog_item.
 :- import_module parse_tree.prog_io.

 :- import_module bool.
Index: compiler/parse_tree.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/parse_tree.m,v
retrieving revision 1.13
diff -u -r1.13 parse_tree.m
--- compiler/parse_tree.m	4 Nov 2005 03:40:53 -0000	1.13
+++ compiler/parse_tree.m	18 Nov 2005 06:33:29 -0000
@@ -21,6 +21,10 @@
 :- import_module recompilation.

 % The parse tree data type itself.
+% The parse tree is split in two.  The parts defined in prog_item is
+% only needed in the frontend of the compiler, the parts in prog_data
+% are needed throughout.
+:- include_module prog_item.
 :- include_module prog_data.

 % The parser.
Index: compiler/prog_data.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/prog_data.m,v
retrieving revision 1.148
diff -u -r1.148 prog_data.m
--- compiler/prog_data.m	17 Nov 2005 04:38:44 -0000	1.148
+++ compiler/prog_data.m	22 Nov 2005 07:14:59 -0000
@@ -5,27 +5,28 @@
 % This file may only be copied under the terms of the GNU General
 % Public License - see the file COPYING in the Mercury distribution.
 %-----------------------------------------------------------------------------%
-%
+
 % File: prog_data.m.
 % Main author: fjh.
-%
-% This module defines a data structure for representing Mercury programs.
-%
-% This data structure specifies basically the same information as is
-% contained in the source code, but in a parse tree rather than a flat file.
-% Simplifications are done only by make_hlds.m, which transforms
-% the parse tree which we built here into the HLDS.

-:- module parse_tree__prog_data.
+% This module, together with prog_item, defines a data structure for
+% representing Mercury programs.
+
+% This data structure specifies basically the same information as is contained
+% in the source code, but in a parse tree rather than a flat file.  This
+% module defines the parts of the parse tree that are needed by the various
+% compiler backends; parts of the parse tree that are not needed by the
+% backends are contained in prog_item.m.
+
+%-----------------------------------------------------------------------------%

+:- module parse_tree__prog_data.
 :- interface.

 :- import_module libs.globals.
-:- import_module libs.options.
 :- import_module libs.rat.
-
 :- import_module mdbcomp.prim_data.
-:- import_module recompilation.
+:- import_module parse_tree.prog_item.

 :- import_module assoc_list.
 :- import_module bool.
@@ -37,198 +38,6 @@
 :- import_module varset.

 %-----------------------------------------------------------------------------%
-%
-% This is how programs (and parse errors) are represented.
-%
-
-:- type message_list    ==  list(pair(string, term)).
-                        % the error/warning message, and the
-                        % term to which it relates
-
-:- type compilation_unit
-    --->    module(
-                module_name,
-                item_list
-            ).
-
-    % Did an item originate in user code or was it added by the
-    % compiler as part of a source-to-source transformation, e.g.
-    % the initialise declarations.
-    %
-:- type item_origin
-    --->    user
-    ;       compiler(item_compiler_origin).
-
-    % For items introduced by the compiler, why were they
-    % introduced?
-    %
-:- type item_compiler_origin
-    --->    initialise_decl
-            % The item was introduced by the transformation for `:- initialise'
-            % decls. This should only apply to export pragms.
-
-    ;       finalise_decl
-            % This item was introduced by the transformation for `:- finalise'
-            % decls. This should only apply to export pragmas.
-
-    ;       mutable_decl
-            % The item was introduced by the transformation for `:- mutable'
-            % decls. This should only apply to `:- initialise' decls and
-            % export pragmas.
-
-    ;       solver_type
-            % Solver types cause the compiler to create foreign procs for the
-            % init and representation functions.
-
-    ;       foreign_imports.
-            % The compiler sometimes needs to insert additional foreign_import
-            % pragmas. XXX Why?
-
-:- type item_list == list(item_and_context).
-
-:- type item_and_context == pair(item, prog_context).
-
-:- type item
-    --->    clause(
-                cl_origin                       :: item_origin,
-                cl_varset                       :: prog_varset,
-                cl_pred_or_func                 :: pred_or_func,
-                cl_predname                     :: sym_name,
-                cl_head_args                    :: list(prog_term),
-                cl_body                         :: goal
-            )
-
-            % `:- type ...':
-            % a definition of a type, or a declaration of an abstract type.
-    ;       type_defn(
-                td_tvarset                      :: tvarset,
-                td_ctor_name                    :: sym_name,
-                td_ctor_args                    :: list(type_param),
-                td_ctor_defn                    :: type_defn,
-                td_cond                         :: condition
-            )
-
-            % `:- inst ... = ...':
-            % a definition of an inst.
-    ;       inst_defn(
-                id_varset                       :: inst_varset,
-                id_inst_name                    :: sym_name,
-                id_inst_args                    :: list(inst_var),
-                id_inst_defn                    :: inst_defn,
-                id_cond                         :: condition
-            )
-
-            % `:- mode ... = ...':
-            % a definition of a mode.
-    ;       mode_defn(
-                md_varset                       :: inst_varset,
-                md_mode_name                    :: sym_name,
-                md_mode_args                    :: list(inst_var),
-                md_mode_defn                    :: mode_defn,
-                md_cond                         :: condition
-            )
-
-    ;       module_defn(
-                module_defn_varset              :: prog_varset,
-                module_defn_module_defn         :: module_defn
-            )
-
-            % `:- pred ...' or `:- func ...':
-            % a predicate or function declaration.
-            % This specifies the type of the predicate or function,
-            % and it may optionally also specify the mode and determinism.
-    ;       pred_or_func(
-                pf_tvarset                      :: tvarset,
-                pf_instvarset                   :: inst_varset,
-                pf_existqvars                   :: existq_tvars,
-                pf_which                        :: pred_or_func,
-                pf_name                         :: sym_name,
-                pf_arg_decls                    :: list(type_and_mode),
-                pf_maybe_with_type              :: maybe(mer_type),
-                pf_maybe_with_inst              :: maybe(mer_inst),
-                pf_maybe_detism                 :: maybe(determinism),
-                pf_cond                         :: condition,
-                pf_purity                       :: purity,
-                pf_class_context                :: prog_constraints
-            )
-            %   The WithType and WithInst fields hold the `with_type`
-            %   and `with_inst` annotations, which are syntactic
-            %   sugar that is expanded by equiv_type.m
-            %   equiv_type.m will set these fields to `no'.
-
-            % `:- mode ...':
-            % a mode declaration for a predicate or function.
-    ;       pred_or_func_mode(
-                pfm_instvarset                  :: inst_varset,
-                pfm_which                       :: maybe(pred_or_func),
-                pfm_name                        :: sym_name,
-                pfm_arg_modes                   :: list(mer_mode),
-                pfm_maybe_with_inst             :: maybe(mer_inst),
-                pfm_maybe_detism                :: maybe(determinism),
-                pfm_cond                        :: condition
-            )
-            %   The WithInst field holds the `with_inst` annotation,
-            %   which is syntactic sugar that is expanded by
-            %   equiv_type.m. equiv_type.m will set the field to `no'.
-
-    ;       pragma(
-                pragma_origin                   :: item_origin,
-                pragma_type                     :: pragma_type
-            )
-
-    ;       promise(
-                prom_type                       :: promise_type,
-                prom_clause                     :: goal,
-                prom_varset                     :: prog_varset,
-                prom_univ_quant_vars            :: prog_vars
-            )
-
-    ;       typeclass(
-                tc_constraints                  :: list(prog_constraint),
-                tc_fundeps                      :: list(prog_fundep),
-                tc_class_name                   :: class_name,
-                tc_class_params                 :: list(tvar),
-                tc_class_methods                :: class_interface,
-                tc_varset                       :: tvarset
-            )
-
-    ;       instance(
-                ci_deriving_class               :: list(prog_constraint),
-                ci_class_name                   :: class_name,
-                ci_types                        :: list(mer_type),
-                ci_method_instances             :: instance_body,
-                ci_varset                       :: tvarset,
-                ci_module_containing_instance   :: module_name
-            )
-
-            % :- initialise pred_name.
-    ;       initialise(
-                item_origin,
-                sym_name,
-                arity
-            )
-
-            % :- finalise pred_name.
-    ;       finalise(
-                item_origin,
-                sym_name,
-                arity
-            )
-
-            % :- mutable(var_name, type, inst, value, attrs).
-    ;       mutable(
-                mut_name                        :: string,
-                mut_type                        :: mer_type,
-                mut_init_value                  :: prog_term,
-                mut_inst                        :: mer_inst,
-                mut_attrs                       :: mutable_var_attributes
-            )
-
-            % Used for items that should be ignored (for the
-            % purposes of backwards compatibility etc).
-    ;       nothing(
-                nothing_maybe_warning           :: maybe(item_warning)
-            ).

     % Indicates the type of information the compiler should get from the
     % declaration's clause.
@@ -297,7 +106,7 @@

     % The following predicates implement the tables for computing the
     % determinism of compound goals from the determinism of their components.
-
+
 :- pred det_conjunction_detism(determinism::in, determinism::in,
     determinism::out) is det.

@@ -339,392 +148,26 @@
             % (i.e. the type was declared with
             % `:- solver type ...').

-:- type item_warning
-    --->    item_warning(
-                maybe(option),  % Option controlling whether the
-                                % warning should be reported.
-                string,         % The warning.
-                term            % The term to which it relates.
-            ).
-
 %-----------------------------------------------------------------------------%
 %
-% Mutable variables
+% Stuff for the foreign language interface pragmas
 %

-    % Indicates if updates to the mutable are trailed or untrailed.
-    %
-:- type trailed
-    --->    trailed
-    ;       untrailed.
-
-    % Has the user specified a name for us to use on the target code side
-    % of the FLI?
-    %
-:- type foreign_name
-    --->    foreign_name(
-                foreign_name_lang :: foreign_language,
-                foreign_name_name :: string
-            ).
-
-    % An abstract type for representing a set of mutable variable
-    % attributes.
-    %
-:- type mutable_var_attributes.
-
-    % Return the default attributes for a mutable variable.
-    %
-:- func default_mutable_attributes = mutable_var_attributes.
-
-    % Access functions for the `mutable_var_attributes' structure.
+    % Is the foreign code declarations local to this module or
+    % exported?
     %
-:- func mutable_var_thread_safe(mutable_var_attributes) = thread_safe.
-:- func mutable_var_trailed(mutable_var_attributes) = trailed.
-:- func mutable_var_maybe_foreign_names(mutable_var_attributes)
-	= maybe(list(foreign_name)).
-:- func mutable_var_attach_to_io_state(mutable_var_attributes) = bool.
-
-:- pred set_mutable_var_thread_safe(thread_safe::in,
-    mutable_var_attributes::in, mutable_var_attributes::out) is det.
-
-:- pred set_mutable_var_trailed(trailed::in,
-    mutable_var_attributes::in, mutable_var_attributes::out) is det.
-
-:- pred set_mutable_add_foreign_name(foreign_name::in,
-    mutable_var_attributes::in, mutable_var_attributes::out) is det.
-
-:- pred set_mutable_var_attach_to_io_state(bool::in,
-	mutable_var_attributes::in, mutable_var_attributes::out) is det.
-
-%-----------------------------------------------------------------------------%
-%
-% Pragmas
-%
-
 :- type foreign_decl_is_local
     --->    foreign_decl_is_local
     ;       foreign_decl_is_exported.

-:- type pragma_type
-    %
-    % Foreign language interfacing pragmas
-    %
-            % A foreign language declaration, such as C header code.
-    --->    foreign_decl(
-                decl_lang               :: foreign_language,
-                decl_is_local           :: foreign_decl_is_local,
-                decl_decl               :: string
-            )
-
-    ;       foreign_code(
-                code_lang               :: foreign_language,
-                code_code               :: string
-            )
-
-    ;       foreign_proc(
-                proc_attrs              :: pragma_foreign_proc_attributes,
-                proc_name               :: sym_name,
-                proc_p_or_f             :: pred_or_func,
-                proc_vars               :: list(pragma_var),
-                proc_varset             :: prog_varset,
-                proc_instvarset         :: inst_varset,
-                proc_impl               :: pragma_foreign_code_impl
-                % Set of foreign proc attributes, eg.:
-                %   what language this code is in
-                %   whether or not the code may call Mercury,
-                %   whether or not the code is thread-safe
-                % PredName, Predicate or Function, Vars/Mode,
-                % VarNames, Foreign Code Implementation Info
-            )
-
-    ;       foreign_import_module(
-                imp_lang                :: foreign_language,
-                imp_module              :: module_name
-                % Equivalent to
-                % `:- pragma foreign_decl(Lang, "#include <module>.h").'
-                % except that the name of the header file is not
-                % hard-coded, and mmake can use the dependency information.
-            )
-
-    ;       export(
-                exp_predname            :: sym_name,
-                exp_p_or_f              :: pred_or_func,
-                exp_modes               :: list(mer_mode),
-                exp_foreign_name        :: string
-                % Predname, Predicate/function, Modes, foreign function name.
-            )
-
-    ;       import(
-                import_pred_name        :: sym_name,
-                import_p_or_f           :: pred_or_func,
-                import_modes            :: list(mer_mode),
-                import_attrs            :: pragma_foreign_proc_attributes,
-                import_foreign_name     :: string
-                % Predname, Predicate/function, Modes,
-                % Set of foreign proc attributes, eg.:
-                %    whether or not the foreign code may call Mercury,
-                %    whether or not the foreign code is thread-safe
-                % foreign function name.
-            )
-    %
-    % Optimization pragmas
-    %
-    ;       type_spec(
-                tspec_pred_name         :: sym_name,
-                tspec_new_name          :: sym_name,
-                tspec_arity             :: arity,
-                tspec_p_or_f            :: maybe(pred_or_func),
-                tspec_modes             :: maybe(list(mer_mode)),
-                tspec_tsubst            :: type_subst,
-                tspec_tvarset           :: tvarset,
-                tspec_items             :: set(item_id)
-                % PredName, SpecializedPredName, Arity, PredOrFunc,
-                % Modes if a specific procedure was specified, type
-                % substitution (using the variable names from the pred
-                % declaration), TVarSet, Equivalence types used
-            )
-
-    ;       inline(
-                inline_name             :: sym_name,
-                inline_arity            :: arity
-                % Predname, Arity
-            )
-
-    ;       no_inline(
-                noinline_name           :: sym_name,
-                noinline_arity          :: arity
-                % Predname, Arity
-            )
-
-    ;       unused_args(
-                unused_p_or_f           :: pred_or_func,
-                unused_name             :: sym_name,
-                unused_arity            :: arity,
-                unused_mode             :: mode_num,
-                unused_args             :: list(int)
-                % PredName, Arity, Mode number, Removed arguments.
-                % Used for inter-module unused argument
-                % removal, should only appear in .opt files.
-            )
-
-    ;       exceptions(
-                exceptions_p_or_f       :: pred_or_func,
-                exceptions_name         :: sym_name,
-                exceptions_arity        :: arity,
-                exceptions_mode         :: mode_num,
-                exceptions_status       :: exception_status
-                % PredName, Arity, Mode number, Exception status.
-                % Should only appear in `.opt' or `.trans_opt' files.
-            )
-
-    ;       trailing_info(
-                trailing_info_p_or_f    :: pred_or_func,
-                trailing_info_name      :: sym_name,
-                trailing_info_arity     :: arity,
-                trailing_info_mode      :: mode_num,
-                trailing_info_status    :: trailing_status
-            )
-                % PredName, Arity, Mode number, Trailing status.
-                % Should on appear in `.opt' or `.trans_opt' files.
-
-    %
-    % Diagnostics pragmas (pragmas related to compiler warnings/errors)
-    %
-
-    ;       obsolete(
-                obsolete_name           :: sym_name,
-                obsolete_arity          :: arity
-                % Predname, Arity
-            )
-
-    ;       source_file(
-                source_file             :: string
-                % Source file name.
-            )
-
-    %
-    % Evaluation method pragmas
-    %
-
-    ;       tabled(
-                tabled_method           :: eval_method,
-                tabled_name             :: sym_name,
-                tabled_arity            :: int,
-                tabled_p_or_f           :: maybe(pred_or_func),
-                tabled_mode             :: maybe(list(mer_mode))
-                % Tabling type, Predname, Arity, PredOrFunc?, Mode?
-            )
-
-    ;       fact_table(
-                fact_table_name         :: sym_name,
-                fact_table_arity        :: arity,
-                fact_table_file         :: string
-                % Predname, Arity, Fact file name.
-            )
-
-    ;       reserve_tag(
-                restag_type             :: sym_name,
-                restag_arity            :: arity
-                % Typename, Arity
-            )
-
-    %
-    % Aditi pragmas
-    %
-
-    ;       aditi(
-                aditi_name              :: sym_name,
-                aditi_arity             :: arity
-                % Predname, Arity
-            )
-
-    ;       base_relation(
-                baserel_name            :: sym_name,
-                baserel_arity           :: arity
-                % Predname, Arity
-                %
-                % Eventually, these should only occur in
-                % automatically generated database interface
-                % files, but for now there's no such thing,
-                % so they can occur in user programs.
-            )
-
-    ;       aditi_index(
-                index_name              :: sym_name,
-                index_arity             :: arity,
-                index_spec              :: index_spec
-                % PredName, Arity, IndexType, Attributes
-                %
-                % Specify an index on a base relation.
-            )
-
-    ;       naive(
-                naive_name              :: sym_name,
-                naive_arity             :: arity
-                % Predname, Arity Use naive evaluation.
-            )
-
-    ;       psn(
-                psn_name                :: sym_name,
-                psn_arity               :: arity
-                % Predname, Arity Use predicate semi-naive evaluation.
-            )
-
-    ;       aditi_memo(
-                aditimemo_name          :: sym_name,
-                aditimemo_arity         :: arity
-                % Predname, Arity
-            )
-
-    ;       aditi_no_memo(
-                aditinomemo_name        :: sym_name,
-                aditinomemo_arity       :: arity
-                % Predname, Arity
-            )
-
-    ;       supp_magic(
-                suppmagic_name          :: sym_name,
-                suppmagic_arity         :: arity
-                % Predname, Arity
-            )
-
-    ;       context(
-                context_name            :: sym_name,
-                context_arity           :: arity
-                % Predname, Arity
-            )
-
-    ;       owner(
-                owner_name              :: sym_name,
-                owner_arity             :: arity,
-                owner_id                :: string
-                % PredName, Arity, String.
-            )
-
-    %
-    % Purity pragmas
-    %
-
-    ;       promise_pure(
-                pure_name               :: sym_name,
-                pure_arity              :: arity
-                % Predname, Arity
-            )
-
-    ;       promise_semipure(
-                semipure_name           :: sym_name,
-                semipure_arity          :: arity
-                % Predname, Arity
-            )
-
-    %
-    % Termination analysis pragmas
-    %
-
-    ;       termination_info(
-                terminfo_p_or_f         :: pred_or_func,
-                terminfo_name           :: sym_name,
-                terminfo_mode           :: list(mer_mode),
-                terminfo_args           :: maybe(pragma_arg_size_info),
-                terminfo_term           :: maybe(pragma_termination_info)
-                % The list(mer_mode) is the declared argmodes of the
-                % procedure, unless there are no declared argmodes,
-                % in which case the inferred argmodes are used.
-                % This pragma is used to define information about a
-                % predicates termination properties.  It is most
-                % useful where the compiler has insufficient
-                % information to be able to analyse the predicate.
-                % This includes c_code, and imported predicates.
-                % termination_info pragmas are used in opt and
-                % trans_opt files.
-            )
-
-    ;       termination2_info(
-                terminfo2_p_or_f        :: pred_or_func,
-                terminfo2_name          :: sym_name,
-                terminfo2_mode          :: list(mer_mode),
-                terminfo2_args          :: maybe(pragma_constr_arg_size_info),
-                terminfo2_args2         :: maybe(pragma_constr_arg_size_info),
-                terminfo2_term          :: maybe(pragma_termination_info)
-            )
-
-    ;       terminates(
-                term_name               :: sym_name,
-                term_arity              :: arity
-                % Predname, Arity
-            )
-
-    ;       does_not_terminate(
-                noterm_name             :: sym_name,
-                noterm_arity            :: arity
-                % Predname, Arity
-            )
-
-    ;       check_termination(
-                checkterm_name          :: sym_name,
-                checkterm_arity         :: arity
-                % Predname, Arity
-            )
-
-    ;       mode_check_clauses(
-                mode_check_clause_name  :: sym_name,
-                mode_check_clause_arity :: arity
-            ).
-
-%-----------------------------------------------------------------------------%
-%
-% Stuff for the foreign language interface pragmas
-%
-
     % A foreign_language_type represents a type that is defined in a
     % foreign language and accessed in Mercury (most likely through
     % pragma foreign_type).
     % Currently we only support foreign_language_types for IL.
     %
-    % It is important to distinguish between IL value types and
-    % reference types, the compiler may need to generate different code
-    % for each of these cases.
-    %
+    % It is important to distinguish between IL value types and reference
+    % types, the compiler may need to generate different code for each of
+    % these cases.
     %
 :- type foreign_language_type
     --->    il(il_foreign_type)
@@ -764,6 +207,7 @@

     % The evaluation method that should be used for a procedure.
     % Ignored for Aditi procedures.
+    %
 :- type eval_method
     --->    eval_normal                 % normal mercury evaluation
     ;       eval_loop_check             % loop check only
@@ -814,10 +258,11 @@

     % For Aditi base relations, an index_spec specifies how the base
     % relation is indexed.
+    %
 :- type index_spec
     --->    index_spec(
                 index_type,
-                list(int)   % which attributes are being indexed on
+                list(int)   % Which attributes are being indexed on
                             % (attribute numbers start at 1)
             ).

@@ -834,15 +279,13 @@

 :- type generic_arg_size_info(ErrorInfo)
     --->    finite(int, list(bool))
-            % The termination constant is a finite integer.
-            % The list of bool has a 1:1 correspondence
-            % with the input arguments of the procedure.
-            % It stores whether the argument contributes
-            % to the size of the output arguments.
+            % The termination constant is a finite integer.  The list of bool
+            % has a 1:1 correspondence with the input arguments of the
+            % procedure.  It stores whether the argument contributes to the
+            % size of the output arguments.

     ;       infinite(ErrorInfo).
-            % There is no finite integer for which the
-            % above equation is true.
+            % There is no finite integer for which the above equation is true.

 :- type generic_termination_info(TermInfo, ErrorInfo)
     --->    cannot_loop(TermInfo)   % This procedure definitely terminates
@@ -884,7 +327,8 @@
     % automatically-generated `pragma unused_args' pragmas in `.opt' files.
     % The mode_num gets converted to an HLDS proc_id by make_hlds.m.
     % We don't want to use the `proc_id' type here since the parse tree
-    % (prog_data.m) should not depend on the HLDS.
+    % (prog_data.m and prog_item.m) should not depend on the HLDS.
+    %
 :- type mode_num == int.

 %-----------------------------------------------------------------------------%
@@ -953,8 +397,8 @@
     % code in the Mercury program. The context is missing if the foreign code
     % was constructed by the compiler.
     %
-    % NOTE: nondet pragma foreign definitions might not be
-    % possible in all foreign languages.
+    % NOTE: nondet pragma foreign definitions might not be possible in all
+    % foreign languages.
     %
 :- type pragma_foreign_code_impl
     --->    ordinary(
@@ -973,35 +417,30 @@

                 string,
                 maybe(prog_context),
-                    % The info saved for the time when
-                    % backtracking reenters this procedure
-                    % is stored in a data structure.
-                    % This arg contains the field
-                    % declarations.
+                    % The info saved for the time when backtracking reenters
+                    % this procedure is stored in a data structure.  This arg
+                    % contains the field declarations.

                 string,
                 maybe(prog_context),
-                    % Gives the code to be executed when
-                    % the procedure is called for the first
-                    % time. This code may access the input
-                    % variables.
+                    % Gives the code to be executed when the procedure is
+                    % called for the first time. This code may access the
+                    % input variables.

                 string,
                 maybe(prog_context),
-                    % Gives the code to be executed when
-                    % control backtracks into the procedure.
-                    % This code may not access the input
+                    % Gives the code to be executed when control backtracks
+                    % into the procedure.  This code may not access the input
                     % variables.

                 pragma_shared_code_treatment,
-                    % How should the shared code be
-                    % treated during code generation.
+                    % How should the shared code be treated during code
+                    % generation.

                 string,
                 maybe(prog_context)
-                    % Shared code that is executed after
-                    % both the previous code fragments.
-                    % May not access the input variables.
+                    % Shared code that is executed after both the previous
+                    % code fragments.  May not access the input variables.
             )

     ;       import(
@@ -1014,6 +453,7 @@

     % The use of this type is explained in the comment at the top of
     % pragma_c_gen.m.
+    %
 :- type pragma_shared_code_treatment
     --->    duplicate
     ;       share
@@ -1031,7 +471,7 @@

 %-----------------------------------------------------------------------------%
 %
-% Stuff for type classes
+% Type classes
 %

     % A class constraint represents a constraint that a given list of types
@@ -1077,55 +517,6 @@
     --->    abstract
     ;       concrete(list(class_method)).

-    % The name class_method is a slight misnomer; this type actually represents
-    % any declaration that occurs in the body of a type class definition.
-    % Such declarations may either declare class methods, or they may declare
-    % modes of class methods.
-    %
-:- type class_method
-    --->    pred_or_func(
-                % pred_or_func(...) here represents a `pred ...' or `func ...'
-                % declaration in a type class body, which declares
-                % a predicate or function method.  Such declarations
-                % specify the type of the predicate or function,
-                % and may optionally also specify the mode and determinism.
-
-                tvarset,            % type variables
-                inst_varset,        % inst variables
-                existq_tvars,       % existentially quantified
-                                    % type variables
-                pred_or_func,
-                sym_name,           % name of the pred or func
-                list(type_and_mode),% the arguments' types and modes
-                maybe(mer_type),    % any `with_type` annotation
-                maybe(mer_inst),    % any `with_inst` annotation
-                maybe(determinism), % any determinism declaration
-                condition,          % any attached declaration
-                purity,             % any purity annotation
-                prog_constraints,   % the typeclass constraints on
-                                    % the declaration
-                prog_context        % the declaration's context
-            )
-
-    ;   pred_or_func_mode(
-            % pred_or_func_mode(...) here represents a `mode ...'
-            % declaration in a type class body.  Such a declaration
-            % declares a mode for one of the type class methods.
-
-                inst_varset,        % inst variables
-                maybe(pred_or_func),% whether the method is a pred
-                                    % or a func; for declarations
-                                    % using `with_inst`, we don't
-                                    % know which until we've
-                                    % expanded the inst.
-                sym_name,           % the method name
-                list(mer_mode),     % the arguments' modes
-                maybe(mer_inst),    % any `with_inst` annotation
-                maybe(determinism), % any determinism declaration
-                condition,          % any attached condition
-                prog_context        % the declaration's context
-            ).
-
 :- type instance_method
     --->    instance_method(
                 pred_or_func,
@@ -1262,29 +653,26 @@
     %
 :- type terminates
     --->    terminates
-            % The foreign code will terminate for all input.
-            % (assuming any input streams are finite).
+            % The foreign code will terminate for all input assuming
+            % that any input streams are finite.

     ;       does_not_terminate
-            % The foreign code will not necessarily terminate for
-            % some (possibly all) input.
+            % The foreign code will not necessarily terminate for some
+            % (possibly all) input.

     ;       depends_on_mercury_calls.
-            % The termination of the foreign code depends
-            % on whether the code makes calls back to Mercury
-            % (See termination.m for details).
+            % The termination of the foreign code depends on whether the code
+            % makes calls back to Mercury (See termination.m for details).

 :- type may_throw_exception
     --->    will_not_throw_exception
-            % The foreign code will not result in an
-            % exception being thrown.
+            % The foreign code will not result in an exception being thrown.

     ;       default_exception_behaviour.
-            % If the foreign proc. is erroneous then
-            % mark it as throwing an exception.  Otherwise
-            % mark it as throwing an exception if it makes
-            % calls back to Mercury and not throwing an
-            % exception otherwise.
+            % If the foreign_proc is erroneous then mark it as throwing an
+            % exception.  Otherwise mark it as throwing an exception if it
+            % makes calls back to Mercury and not throwing an exception
+            % otherwise.

 :- type pragma_foreign_proc_extra_attribute
     --->    max_stack_size(int)
@@ -1305,71 +693,16 @@
 % Goals
 %

-    % Here's how clauses and goals are represented.
-    % a => b --> implies(a, b)
-    % a <= b --> implies(b, a) [just flips the goals around!]
-    % a <=> b --> equivalent(a, b)
-
-% clause/4 defined above
-
-:- type goal        ==  pair(goal_expr, prog_context).
-
-:- type goal_expr
-    % conjunctions
-    --->    (goal , goal)   % (non-empty) conjunction
-    ;       true            % empty conjunction
-    ;       {goal & goal}   % parallel conjunction
-                            % (The curly braces just quote the '&'/2.)
-
-    % disjunctions
-    ;       {goal ; goal}   % (non-empty) disjunction
-                            % (The curly braces just quote the ';'/2.)
-    ;       fail            % empty disjunction
-
-    % quantifiers
-    ;       { some(prog_vars, goal) }
-                            % existential quantification
-                            % (The curly braces just quote the 'some'/2.)
-    ;       all(prog_vars, goal)
-                            % % universal quantification
-    ;       some_state_vars(prog_vars, goal)
-    ;       all_state_vars(prog_vars, goal)
-                            % state variables extracted from
-                            % some/2 and all/2 quantifiers.
-
-    % other scopes
-    ;       promise_purity(implicit_purity_promise, purity, goal)
-    ;       promise_equivalent_solutions(prog_vars, prog_vars, prog_vars, goal)
-                            % (OrdinaryVars, DotStateVars, ColonStateVars,
-                            % % Goal)
-
-    % implications
-    ;       implies(goal, goal)
-                            % A => B
-    ;       equivalent(goal, goal)
-                            % A <=> B
-
-    % negation and if-then-else
-    ;       not(goal)
-    ;       if_then(prog_vars, prog_vars, goal, goal)
-                            % if_then(SomeVars, StateVars, If, Then)
-    ;       if_then_else(prog_vars, prog_vars, goal, goal, goal)
-                            % if_then_else(SomeVars, StateVars, If, Then, Else)
-
-    % atomic goals
-    ;       call(sym_name, list(prog_term), purity)
-    ;       unify(prog_term, prog_term, purity).
-
+% NOTE: the representation of goals in the parse tree is defined in
+%       prog_item.m.

 :- type implicit_purity_promise
     --->    make_implicit_promises
     ;       dont_make_implicit_promises.

-:- type goals       ==  list(goal).
-
     % These type equivalences are for the type of program variables
     % and associated structures.
-
+    %
 :- type prog_var_type   --->    prog_var_type.
 :- type prog_var    ==  var(prog_var_type).
 :- type prog_varset ==  varset(prog_var_type).
@@ -1378,7 +711,7 @@
 :- type prog_vars   ==  list(prog_var).

     % A prog_context is just a term__context.
-
+    %
 :- type prog_context    ==  term__context.

 %-----------------------------------------------------------------------------%
@@ -1482,6 +815,7 @@
     %
     % `lambda_aditi_bottom_up' expressions are used as database queries to
     % produce a set of tuples to be inserted or deleted.
+    %
 :- type lambda_eval_method
     --->    lambda_normal
     ;       lambda_aditi_bottom_up.
@@ -1491,12 +825,12 @@
 % Types
 %

-    % This is how types are represented.
+% This is how types are represented.

-    % One day we might allow types to take
-    % value parameters as well as type parameters.
+% One day we might allow types to take
+% value parameters as well as type parameters.

-% type_defn/3 is defined above as a constructor for item/0
+% type_defn/3 is defined in prog_item.m as a constructor for item/0

 :- type type_defn
     --->    du_type(
@@ -1576,12 +910,15 @@
     % An equality_pred specifies the name of a user-defined predicate
     % used for equality on a type.  See the chapter on them in the
     % Mercury Language Reference Manual.
+    %
 :- type equality_pred   ==  sym_name.

-     % The name of a user-defined comparison predicate.
+    % The name of a user-defined comparison predicate.
+    %
 :- type comparison_pred ==  sym_name.

     % Parameters of type definitions.
+    %
 :- type type_param  ==  tvar.

     % Use type_util.type_to_ctor_and_args to convert a type to a qualified
@@ -1649,6 +986,7 @@

     % existq_tvars is used to record the set of type variables which are
     % existentially quantified
+    %
 :- type existq_tvars    ==  list(tvar).

     % Types may have arbitrary assertions associated with them
@@ -1656,7 +994,7 @@
     % Similarly, pred declarations can have assertions attached.
     % The compiler will ignore these assertions - they are intended
     % to be used by other tools, such as the debugger.
-
+    %
 :- type condition
     --->    true
     ;       where(term).
@@ -1716,9 +1054,6 @@
 %

     % This is how instantiatednesses and modes are represented.
-    % Note that while we use the normal term data structure to represent
-    % type terms (see above), we need a separate data structure for inst
-    % terms.
     %
 :- type mer_inst
     --->        any(uniqueness)
@@ -1764,11 +1099,11 @@
                                     % restore the old value on backtracking.

     % The ground_inst_info type gives extra information about ground insts.
+    %
 :- type ground_inst_info
     --->    higher_order(pred_inst_info)
             % The ground inst is higher-order.
     ;       none.
-
             % No extra information is available.

     % higher-order predicate terms are given the inst
@@ -1776,7 +1111,7 @@
     % where the PredInstInfo contains the extra modes and the determinism
     % for the predicate.  Note that the higher-order predicate term
     % itself must be ground.
-
+    %
 :- type pred_inst_info
     --->    pred_inst_info(
                 pred_or_func,       % Is this a higher-order func mode or a
@@ -1803,7 +1138,7 @@

 :- type inst_var_sub    ==  map(inst_var, mer_inst).

-% inst_defn/3 defined above
+% inst_defn/5 is defined in prog_item.m.

 :- type inst_defn
     --->    eqv_inst(mer_inst)
@@ -1812,7 +1147,7 @@
     % An `inst_name' is used as a key for the inst_table.
     % It is either a user-defined inst `user_inst(Name, Args)',
     % or some sort of compiler-generated inst, whose name
-    % is a representation of it's meaning.
+    % is a representation of its meaning.
     %
     % For example, `merge_inst(InstA, InstB)' is the name used for the
     % inst that results from merging InstA and InstB using `merge_inst'.
@@ -1870,8 +1205,6 @@

 :- type mode_id     ==  pair(sym_name, arity).

-% mode_defn/3 defined above
-
 :- type mode_defn
     --->    eqv_mode(mer_mode).

@@ -1879,75 +1212,11 @@
     --->    (mer_inst -> mer_inst)
     ;       user_defined_mode(sym_name, list(mer_inst)).

-% mode/4 defined above
-
 %-----------------------------------------------------------------------------%
 %
 % Module system
 %

-    % This is how module-system declarations (such as imports
-    % and exports) are represented.
-    %
-:- type module_defn
-    --->    module(module_name)
-    ;       end_module(module_name)
-
-    ;       interface
-    ;       implementation
-
-    ;       private_interface
-            % This is used internally by the compiler, to identify items
-            % which originally came from an implementation section for a
-            % module that contains sub-modules; such items need to be exported
-            % to the sub-modules.
-
-    ;       imported(import_locn)
-            % This is used internally by the compiler, to identify declarations
-            % which originally came from some other module imported with a
-            % `:- import_module' declaration, and which section the module
-            % was imported.
-
-    ;       used(import_locn)
-            % This is used internally by the compiler, to identify declarations
-            % which originally came from some other module and for which all
-            % uses must be module qualified. This applies to items from modules
-            % imported using `:- use_module', and items from `.opt' and `.int2'
-            % files. It also records from which section the module was
-            % imported.
-
-    ;       abstract_imported
-            % This is used internally by the compiler, to identify items which
-            % originally came from the implementation section of an interface
-            % file; usually type declarations (especially equivalence types)
-            % which should be used in code generation but not in type checking.
-
-    ;       opt_imported
-            % This is used internally by the compiler, to identify items which
-            % originally came from a .opt file.
-
-    ;       transitively_imported
-            % This is used internally by the compiler, to identify items which
-            % originally came from a `.opt' or `.int2' file. These should not
-            % be allowed to match items in the current module. Note that unlike
-            % `:- interface', `:- implementation' and the other
-            % pseudo-declarations `:- imported(interface)', etc., a
-            % `:- transitively_imported' declaration applies to all of the
-            % following items in the list, not just up to the next
-            % pseudo-declaration.
-
-    ;       external(maybe(backend), sym_name_specifier)
-
-    ;       export(sym_list)
-    ;       import(sym_list)
-    ;       use(sym_list)
-
-    ;       include_module(list(module_name))
-
-    ;       version_numbers(module_name, recompilation__version_numbers).
-            % This is used to represent the version numbers of items in an
-            % interface file for use in smart recompilation.
-
 :- type backend
     --->    high_level_backend
     ;       low_level_backend.
@@ -2033,8 +1302,9 @@
 :- type module_specifier == sym_name.
 :- type arity       ==  int.

-    % Describes whether an item can be used without an
-    % explicit module qualifier.
+    % Describes whether an item can be used without an explicit module
+    % qualifier.
+    %
 :- type need_qualifier
     --->    must_be_qualified
     ;       may_be_unqualified.
@@ -2046,7 +1316,6 @@

 :- import_module libs.compiler_util.

-:- import_module require.
 :- import_module string.

 %-----------------------------------------------------------------------------%
@@ -2202,11 +1471,11 @@
 less_pure(P1, P2) :-
     \+ ( worst_purity(P1, P2) = P2).

-% worst_purity/3 could be written more compactly, but this definition
-% guarantees us a determinism error if we add to type `purity'.  We also
-% define less_pure/2 in terms of worst_purity/3 rather than the other way
-% around for the same reason.
-
+    % worst_purity/3 could be written more compactly, but this definition
+    % guarantees us a determinism error if we add to type `purity'.  We also
+    % define less_pure/2 in terms of worst_purity/3 rather than the other way
+    % around for the same reason.
+    %
 worst_purity(purity_pure, purity_pure) = purity_pure.
 worst_purity(purity_pure, purity_semipure) = purity_semipure.
 worst_purity(purity_pure, purity_impure) = purity_impure.
@@ -2217,8 +1486,9 @@
 worst_purity(purity_impure, purity_semipure) = purity_impure.
 worst_purity(purity_impure, purity_impure) = purity_impure.

-% best_purity/3 is written as a switch for the same reason as worst_purity/3.
-
+    % best_purity/3 is written as a switch for the same reason as
+    % worst_purity/3.
+    %
 best_purity(purity_pure, purity_pure) = purity_pure.
 best_purity(purity_pure, purity_semipure) = purity_pure.
 best_purity(purity_pure, purity_impure) = purity_pure.
@@ -2306,7 +1576,7 @@
 det_conjunction_maxsoln(at_most_many_cc, at_most_many,    _) :-
     % If the first conjunct could be cc pruned, the second conj ought to have
     % been cc pruned too.
-    error("det_conjunction_maxsoln: many_cc , many").
+    unexpected(this_file, "det_conjunction_maxsoln: many_cc , many").

 det_conjunction_maxsoln(at_most_many,    at_most_zero,    at_most_zero).
 det_conjunction_maxsoln(at_most_many,    at_most_one,     at_most_many).
@@ -2379,51 +1649,6 @@

 %-----------------------------------------------------------------------------%

-%-----------------------------------------------------------------------------%
-%
-% Mutable variables
-%
-
-    % Attributes for mutable variables.
-    %
-:- type mutable_var_attributes
-    --->    mutable_var_attributes(
-                mutable_trailed            :: trailed,
-                mutable_thread_safe        :: thread_safe,
-                mutable_foreign_names      :: maybe(list(foreign_name)),
-                mutable_attach_to_io_state :: bool
-            ).
-
-default_mutable_attributes =
-	mutable_var_attributes(trailed, not_thread_safe, no, no).
-
-mutable_var_thread_safe(MVarAttrs) = MVarAttrs ^ mutable_thread_safe.
-mutable_var_trailed(MVarAttrs) = MVarAttrs ^ mutable_trailed.
-mutable_var_maybe_foreign_names(MVarAttrs) = MVarAttrs ^ mutable_foreign_names.
-mutable_var_attach_to_io_state(MVarAttrs) =
-    MVarAttrs ^ mutable_attach_to_io_state.
-
-set_mutable_var_thread_safe(ThreadSafe, !Attributes) :-
-    !:Attributes = !.Attributes ^ mutable_thread_safe := ThreadSafe.
-set_mutable_var_trailed(Trailed, !Attributes) :-
-    !:Attributes = !.Attributes ^ mutable_trailed := Trailed.
-set_mutable_add_foreign_name(ForeignName, !Attributes) :-
-	MaybeForeignNames0 = !.Attributes ^ mutable_foreign_names,
-	(
-		MaybeForeignNames0 = no,
-		MaybeForeignNames  = yes([ForeignName])
-	;
-		MaybeForeignNames0 = yes(ForeignNames0),
-		ForeignNames = [ ForeignName | ForeignNames0],
-		MaybeForeignNames   = yes(ForeignNames)
-	),
-	!:Attributes = !.Attributes ^ mutable_foreign_names := MaybeForeignNames.
-set_mutable_var_attach_to_io_state(AttachToIOState, !Attributes) :-
-	!:Attributes =
-        !.Attributes ^ mutable_attach_to_io_state := AttachToIOState.
-
-%-----------------------------------------------------------------------------%
-
 tvarset_merge_renaming(TVarSetA, TVarSetB, TVarSet, Renaming) :-
     varset__merge_subst(TVarSetA, TVarSetB, TVarSet, Subst),
     map__map_values(convert_subst_term_to_tvar, Subst, Renaming).
Index: compiler/prog_foreign.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/prog_foreign.m,v
retrieving revision 1.3
diff -u -r1.3 prog_foreign.m
--- compiler/prog_foreign.m	14 Oct 2005 01:47:07 -0000	1.3
+++ compiler/prog_foreign.m	22 Nov 2005 05:30:53 -0000
@@ -25,7 +25,6 @@
 %-----------------------------------------------------------------------------%

 :- module parse_tree.prog_foreign.
-
 :- interface.

 :- import_module libs.globals.
@@ -39,9 +38,9 @@

 %-----------------------------------------------------------------------------%

-:- type foreign_decl_info       == list(foreign_decl_code).
+:- type foreign_decl_info == list(foreign_decl_code).
                                 % in reverse order
-:- type foreign_body_info       == list(foreign_body_code).
+:- type foreign_body_info == list(foreign_body_code).
                                 % in reverse order

 :- type foreign_decl_code
@@ -293,7 +292,7 @@
     % Currently we don't use the globals to compare foreign language
     % interfaces, but if we added appropriate options we might want
     % to do this later.
-
+    %
 prefer_foreign_language(_Globals, c, Lang1, Lang2) =
     % When compiling to C, C is always preferred over any other language.
     ( Lang2 = c, not Lang1 = c ->
Index: compiler/prog_io.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/prog_io.m,v
retrieving revision 1.257
diff -u -r1.257 prog_io.m
--- compiler/prog_io.m	28 Oct 2005 02:10:29 -0000	1.257
+++ compiler/prog_io.m	18 Nov 2005 06:39:47 -0000
@@ -60,6 +60,7 @@
 :- import_module libs.timestamp.
 :- import_module mdbcomp.prim_data.
 :- import_module parse_tree.prog_data.
+:- import_module parse_tree.prog_item.
 :- import_module parse_tree.prog_io_util.

 :- import_module bool.
Index: compiler/prog_io_dcg.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/prog_io_dcg.m,v
retrieving revision 1.33
diff -u -r1.33 prog_io_dcg.m
--- compiler/prog_io_dcg.m	28 Oct 2005 02:10:29 -0000	1.33
+++ compiler/prog_io_dcg.m	18 Nov 2005 07:10:44 -0000
@@ -23,6 +23,7 @@

 :- import_module mdbcomp.prim_data.
 :- import_module parse_tree.prog_data.
+:- import_module parse_tree.prog_item.
 :- import_module parse_tree.prog_io_util.

 :- import_module term.
Index: compiler/prog_io_goal.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/prog_io_goal.m,v
retrieving revision 1.38
diff -u -r1.38 prog_io_goal.m
--- compiler/prog_io_goal.m	28 Oct 2005 02:10:29 -0000	1.38
+++ compiler/prog_io_goal.m	18 Nov 2005 07:13:20 -0000
@@ -16,6 +16,7 @@
 :- interface.

 :- import_module parse_tree.prog_data.
+:- import_module parse_tree.prog_item.

 :- import_module list.
 :- import_module term.
Index: compiler/prog_io_pragma.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/prog_io_pragma.m,v
retrieving revision 1.94
diff -u -r1.94 prog_io_pragma.m
--- compiler/prog_io_pragma.m	8 Nov 2005 08:14:54 -0000	1.94
+++ compiler/prog_io_pragma.m	18 Nov 2005 06:40:56 -0000
@@ -17,7 +17,7 @@

 :- import_module libs.globals.
 :- import_module mdbcomp.prim_data.
-:- import_module parse_tree.prog_data.
+:- import_module parse_tree.prog_item.
 :- import_module parse_tree.prog_io_util.

 :- import_module list.
@@ -40,8 +40,9 @@

 :- implementation.

-:- import_module libs.lp_rational.
+%:- import_module libs.lp_rational.
 :- import_module libs.rat.
+:- import_module parse_tree.prog_data.
 :- import_module parse_tree.prog_io.
 :- import_module parse_tree.prog_io_goal.
 :- import_module parse_tree.prog_util.
Index: compiler/prog_io_typeclass.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/prog_io_typeclass.m,v
retrieving revision 1.45
diff -u -r1.45 prog_io_typeclass.m
--- compiler/prog_io_typeclass.m	28 Oct 2005 02:10:30 -0000	1.45
+++ compiler/prog_io_typeclass.m	22 Nov 2005 06:39:14 -0000
@@ -18,6 +18,7 @@

 :- import_module mdbcomp.prim_data.
 :- import_module parse_tree.prog_data.
+:- import_module parse_tree.prog_item.
 :- import_module parse_tree.prog_io_util.

 :- import_module list.
@@ -683,7 +684,7 @@
     ).

 :- pred parse_instance_methods(module_name::in, term::in, varset::in,
-    maybe1(list(instance_method))::out) is det.
+    maybe1(instance_methods)::out) is det.

 parse_instance_methods(ModuleName, Methods, VarSet, Result) :-
     ( list_term_to_term_list(Methods, MethodList) ->
Index: compiler/prog_io_util.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/prog_io_util.m,v
retrieving revision 1.42
diff -u -r1.42 prog_io_util.m
--- compiler/prog_io_util.m	28 Oct 2005 02:10:30 -0000	1.42
+++ compiler/prog_io_util.m	18 Nov 2005 06:42:12 -0000
@@ -27,6 +27,7 @@

 :- import_module mdbcomp.prim_data.
 :- import_module parse_tree.prog_data.
+:- import_module parse_tree.prog_item.

 :- import_module list.
 :- import_module map.
Index: compiler/prog_item.m
===================================================================
RCS file: compiler/prog_item.m
diff -N compiler/prog_item.m
--- /dev/null	1 Jan 1970 00:00:00 -0000
+++ compiler/prog_item.m	22 Nov 2005 06:37:04 -0000
@@ -0,0 +1,828 @@
+%-----------------------------------------------------------------------------%
+% vim: ft=mercury ts=4 sw=4 et
+%-----------------------------------------------------------------------------%
+% Copyright (C) 1996-2005 The University of Melbourne.
+% This file may only be copied under the terms of the GNU General
+% Public License - see the file COPYING in the Mercury distribution.
+%-----------------------------------------------------------------------------%
+
+% File: prog_item.m.
+% Main author: fjh.
+
+% This module, together with prog_data, defines a data structure for
+% representing Mercury programs.
+
+% This data structure specifies basically the same information as is
+% contained in the source code, but in a parse tree rather than a flat
+% file.  This module defines the parts of the parse tree that are *not*
+% needed by the various compiler backends; parts of the parse tree that
+% are needed by the backends are contained in prog_data.m.
+
+%-----------------------------------------------------------------------------%
+
+:- module parse_tree.prog_item.
+:- interface.
+
+:- import_module libs.globals.
+:- import_module libs.options.
+:- import_module mdbcomp.prim_data.
+:- import_module recompilation.
+:- import_module parse_tree.prog_data.
+
+:- import_module bool.
+:- import_module list.
+:- import_module set.
+:- import_module std_util.
+:- import_module term.
+
+%-----------------------------------------------------------------------------%
+%
+% This is how programs (and parse errors) are represented
+%
+
+    % An error/warning message, and the term to which it relates.
+    %
+:- type message_list == list(pair(string, term)).
+
+:- type compilation_unit
+    --->    module(
+                module_name,
+                item_list
+            ).
+
+    % Did an item originate in user code or was it added by the compiler as
+    % part of a source-to-source transformation, e.g.  the initialise
+    % declarations.
+    %
+:- type item_origin
+    --->    user
+    ;       compiler(item_compiler_origin).
+
+    % For items introduced by the compiler, why were they introduced?
+    %
+:- type item_compiler_origin
+    --->    initialise_decl
+            % The item was introduced by the transformation for `:- initialise'
+            % decls. This should only apply to export pragms.
+
+    ;       finalise_decl
+            % This item was introduced by the transformation for `:- finalise'
+            % decls. This should only apply to export pragmas.
+
+    ;       mutable_decl
+            % The item was introduced by the transformation for `:- mutable'
+            % decls. This should only apply to `:- initialise' decls and
+            % export pragmas.
+
+    ;       solver_type
+            % Solver types cause the compiler to create foreign procs for the
+            % init and representation functions.
+
+    ;       foreign_imports.
+            % The compiler sometimes needs to insert additional foreign_import
+            % pragmas. XXX Why?
+
+:- type item_list == list(item_and_context).
+
+:- type item_and_context == pair(item, prog_context).
+
+:- type item
+    --->    clause(
+                cl_origin                       :: item_origin,
+                cl_varset                       :: prog_varset,
+                cl_pred_or_func                 :: pred_or_func,
+                cl_predname                     :: sym_name,
+                cl_head_args                    :: list(prog_term),
+                cl_body                         :: goal
+            )
+
+            % `:- type ...':
+            % a definition of a type, or a declaration of an abstract type.
+    ;       type_defn(
+                td_tvarset                      :: tvarset,
+                td_ctor_name                    :: sym_name,
+                td_ctor_args                    :: list(type_param),
+                td_ctor_defn                    :: type_defn,
+                td_cond                         :: condition
+            )
+
+            % `:- inst ... = ...':
+            % a definition of an inst.
+    ;       inst_defn(
+                id_varset                       :: inst_varset,
+                id_inst_name                    :: sym_name,
+                id_inst_args                    :: list(inst_var),
+                id_inst_defn                    :: inst_defn,
+                id_cond                         :: condition
+            )
+
+            % `:- mode ... = ...':
+            % a definition of a mode.
+    ;       mode_defn(
+                md_varset                       :: inst_varset,
+                md_mode_name                    :: sym_name,
+                md_mode_args                    :: list(inst_var),
+                md_mode_defn                    :: mode_defn,
+                md_cond                         :: condition
+            )
+
+    ;       module_defn(
+                module_defn_varset              :: prog_varset,
+                module_defn_module_defn         :: module_defn
+            )
+
+            % `:- pred ...' or `:- func ...':
+            % a predicate or function declaration.
+            % This specifies the type of the predicate or function,
+            % and it may optionally also specify the mode and determinism.
+    ;       pred_or_func(
+                pf_tvarset                      :: tvarset,
+                pf_instvarset                   :: inst_varset,
+                pf_existqvars                   :: existq_tvars,
+                pf_which                        :: pred_or_func,
+                pf_name                         :: sym_name,
+                pf_arg_decls                    :: list(type_and_mode),
+                pf_maybe_with_type              :: maybe(mer_type),
+                pf_maybe_with_inst              :: maybe(mer_inst),
+                pf_maybe_detism                 :: maybe(determinism),
+                pf_cond                         :: condition,
+                pf_purity                       :: purity,
+                pf_class_context                :: prog_constraints
+            )
+            %   The WithType and WithInst fields hold the `with_type`
+            %   and `with_inst` annotations, which are syntactic
+            %   sugar that is expanded by equiv_type.m
+            %   equiv_type.m will set these fields to `no'.
+
+            % `:- mode ...':
+            % a mode declaration for a predicate or function.
+    ;       pred_or_func_mode(
+                pfm_instvarset                  :: inst_varset,
+                pfm_which                       :: maybe(pred_or_func),
+                pfm_name                        :: sym_name,
+                pfm_arg_modes                   :: list(mer_mode),
+                pfm_maybe_with_inst             :: maybe(mer_inst),
+                pfm_maybe_detism                :: maybe(determinism),
+                pfm_cond                        :: condition
+            )
+            %   The WithInst field holds the `with_inst` annotation,
+            %   which is syntactic sugar that is expanded by
+            %   equiv_type.m. equiv_type.m will set the field to `no'.
+
+    ;       pragma(
+                pragma_origin                   :: item_origin,
+                pragma_type                     :: pragma_type
+            )
+
+    ;       promise(
+                prom_type                       :: promise_type,
+                prom_clause                     :: goal,
+                prom_varset                     :: prog_varset,
+                prom_univ_quant_vars            :: prog_vars
+            )
+
+    ;       typeclass(
+                tc_constraints                  :: list(prog_constraint),
+                tc_fundeps                      :: list(prog_fundep),
+                tc_class_name                   :: class_name,
+                tc_class_params                 :: list(tvar),
+                tc_class_methods                :: class_interface,
+                tc_varset                       :: tvarset
+            )
+
+    ;       instance(
+                ci_deriving_class               :: list(prog_constraint),
+                ci_class_name                   :: class_name,
+                ci_types                        :: list(mer_type),
+                ci_method_instances             :: instance_body,
+                ci_varset                       :: tvarset,
+                ci_module_containing_instance   :: module_name
+            )
+
+            % :- initialise pred_name.
+    ;       initialise(
+                item_origin,
+                sym_name,
+                arity
+            )
+
+            % :- finalise pred_name.
+    ;       finalise(
+                item_origin,
+                sym_name,
+                arity
+            )
+
+            % :- mutable(var_name, type, inst, value, attrs).
+    ;       mutable(
+                mut_name                        :: string,
+                mut_type                        :: mer_type,
+                mut_init_value                  :: prog_term,
+                mut_inst                        :: mer_inst,
+                mut_attrs                       :: mutable_var_attributes
+            )
+
+            % Used for items that should be ignored (for the
+            % purposes of backwards compatibility etc).
+    ;       nothing(
+                nothing_maybe_warning           :: maybe(item_warning)
+            ).
+
+:- type item_warning
+    --->    item_warning(
+                maybe(option),  % Option controlling whether the
+                                % warning should be reported.
+                string,         % The warning.
+                term            % The term to which it relates.
+            ).
+
+%-----------------------------------------------------------------------------%
+%
+% Type classes
+%
+
+    % The name class_method is a slight misnomer; this type actually represents
+    % any declaration that occurs in the body of a type class definition.
+    % Such declarations may either declare class methods, or they may declare
+    % modes of class methods.
+    %
+:- type class_method
+    --->    pred_or_func(
+                % pred_or_func(...) here represents a `pred ...' or `func ...'
+                % declaration in a type class body, which declares
+                % a predicate or function method.  Such declarations
+                % specify the type of the predicate or function,
+                % and may optionally also specify the mode and determinism.
+
+                tvarset,            % type variables
+                inst_varset,        % inst variables
+                existq_tvars,       % existentially quantified
+                                    % type variables
+                pred_or_func,
+                sym_name,           % name of the pred or func
+                list(type_and_mode),% the arguments' types and modes
+                maybe(mer_type),    % any `with_type` annotation
+                maybe(mer_inst),    % any `with_inst` annotation
+                maybe(determinism), % any determinism declaration
+                condition,          % any attached declaration
+                purity,             % any purity annotation
+                prog_constraints,   % the typeclass constraints on
+                                    % the declaration
+                prog_context        % the declaration's context
+            )
+
+    ;   pred_or_func_mode(
+            % pred_or_func_mode(...) here represents a `mode ...'
+            % declaration in a type class body.  Such a declaration
+            % declares a mode for one of the type class methods.
+
+                inst_varset,        % inst variables
+                maybe(pred_or_func),% whether the method is a pred
+                                    % or a func; for declarations
+                                    % using `with_inst`, we don't
+                                    % know which until we've
+                                    % expanded the inst.
+                sym_name,           % the method name
+                list(mer_mode),     % the arguments' modes
+                maybe(mer_inst),    % any `with_inst` annotation
+                maybe(determinism), % any determinism declaration
+                condition,          % any attached condition
+                prog_context        % the declaration's context
+            ).
+
+%-----------------------------------------------------------------------------%
+%
+% Mutable variables
+%
+
+    % Indicates if updates to the mutable are trailed or untrailed.
+    %
+:- type trailed
+    --->    trailed
+    ;       untrailed.
+
+    % Has the user specified a name for us to use on the target code side
+    % of the FLI?
+    %
+:- type foreign_name
+    --->    foreign_name(
+                foreign_name_lang :: foreign_language,
+                foreign_name_name :: string
+            ).
+
+    % An abstract type for representing a set of mutable variable
+    % attributes.
+    %
+:- type mutable_var_attributes.
+
+    % Return the default attributes for a mutable variable.
+    %
+:- func default_mutable_attributes = mutable_var_attributes.
+
+    % Access functions for the `mutable_var_attributes' structure.
+    %
+:- func mutable_var_thread_safe(mutable_var_attributes) = thread_safe.
+:- func mutable_var_trailed(mutable_var_attributes) = trailed.
+:- func mutable_var_maybe_foreign_names(mutable_var_attributes)
+	= maybe(list(foreign_name)).
+:- func mutable_var_attach_to_io_state(mutable_var_attributes) = bool.
+
+:- pred set_mutable_var_thread_safe(thread_safe::in,
+    mutable_var_attributes::in, mutable_var_attributes::out) is det.
+
+:- pred set_mutable_var_trailed(trailed::in,
+    mutable_var_attributes::in, mutable_var_attributes::out) is det.
+
+:- pred set_mutable_add_foreign_name(foreign_name::in,
+    mutable_var_attributes::in, mutable_var_attributes::out) is det.
+
+:- pred set_mutable_var_attach_to_io_state(bool::in,
+	mutable_var_attributes::in, mutable_var_attributes::out) is det.
+
+%-----------------------------------------------------------------------------%
+%
+% Pragmas
+%
+
+:- type pragma_type
+    %
+    % Foreign language interfacing pragmas
+    %
+            % A foreign language declaration, such as C header code.
+    --->    foreign_decl(
+                decl_lang               :: foreign_language,
+                decl_is_local           :: foreign_decl_is_local,
+                decl_decl               :: string
+            )
+
+    ;       foreign_code(
+                code_lang               :: foreign_language,
+                code_code               :: string
+            )
+
+    ;       foreign_proc(
+                proc_attrs              :: pragma_foreign_proc_attributes,
+                proc_name               :: sym_name,
+                proc_p_or_f             :: pred_or_func,
+                proc_vars               :: list(pragma_var),
+                proc_varset             :: prog_varset,
+                proc_instvarset         :: inst_varset,
+                proc_impl               :: pragma_foreign_code_impl
+                % Set of foreign proc attributes, eg.:
+                %   what language this code is in
+                %   whether or not the code may call Mercury,
+                %   whether or not the code is thread-safe
+                % PredName, Predicate or Function, Vars/Mode,
+                % VarNames, Foreign Code Implementation Info
+            )
+
+    ;       foreign_import_module(
+                imp_lang                :: foreign_language,
+                imp_module              :: module_name
+                % Equivalent to
+                % `:- pragma foreign_decl(Lang, "#include <module>.h").'
+                % except that the name of the header file is not
+                % hard-coded, and mmake can use the dependency information.
+            )
+
+    ;       export(
+                exp_predname            :: sym_name,
+                exp_p_or_f              :: pred_or_func,
+                exp_modes               :: list(mer_mode),
+                exp_foreign_name        :: string
+                % Predname, Predicate/function, Modes, foreign function name.
+            )
+
+    ;       import(
+                import_pred_name        :: sym_name,
+                import_p_or_f           :: pred_or_func,
+                import_modes            :: list(mer_mode),
+                import_attrs            :: pragma_foreign_proc_attributes,
+                import_foreign_name     :: string
+                % Predname, Predicate/function, Modes,
+                % Set of foreign proc attributes, eg.:
+                %    whether or not the foreign code may call Mercury,
+                %    whether or not the foreign code is thread-safe
+                % foreign function name.
+            )
+    %
+    % Optimization pragmas
+    %
+    ;       type_spec(
+                tspec_pred_name         :: sym_name,
+                tspec_new_name          :: sym_name,
+                tspec_arity             :: arity,
+                tspec_p_or_f            :: maybe(pred_or_func),
+                tspec_modes             :: maybe(list(mer_mode)),
+                tspec_tsubst            :: type_subst,
+                tspec_tvarset           :: tvarset,
+                tspec_items             :: set(item_id)
+                % PredName, SpecializedPredName, Arity, PredOrFunc,
+                % Modes if a specific procedure was specified, type
+                % substitution (using the variable names from the pred
+                % declaration), TVarSet, Equivalence types used
+            )
+
+    ;       inline(
+                inline_name             :: sym_name,
+                inline_arity            :: arity
+                % Predname, Arity
+            )
+
+    ;       no_inline(
+                noinline_name           :: sym_name,
+                noinline_arity          :: arity
+                % Predname, Arity
+            )
+
+    ;       unused_args(
+                unused_p_or_f           :: pred_or_func,
+                unused_name             :: sym_name,
+                unused_arity            :: arity,
+                unused_mode             :: mode_num,
+                unused_args             :: list(int)
+                % PredName, Arity, Mode number, Removed arguments.
+                % Used for intermodule unused argument removal, should only
+                % appear in .opt files.
+            )
+
+    ;       exceptions(
+                exceptions_p_or_f       :: pred_or_func,
+                exceptions_name         :: sym_name,
+                exceptions_arity        :: arity,
+                exceptions_mode         :: mode_num,
+                exceptions_status       :: exception_status
+                % PredName, Arity, Mode number, Exception status.
+                % Should only appear in `.opt' or `.trans_opt' files.
+            )
+
+    ;       trailing_info(
+                trailing_info_p_or_f    :: pred_or_func,
+                trailing_info_name      :: sym_name,
+                trailing_info_arity     :: arity,
+                trailing_info_mode      :: mode_num,
+                trailing_info_status    :: trailing_status
+            )
+                % PredName, Arity, Mode number, Trailing status.
+                % Should on appear in `.opt' or `.trans_opt' files.
+
+    %
+    % Diagnostics pragmas (pragmas related to compiler warnings/errors)
+    %
+
+    ;       obsolete(
+                obsolete_name           :: sym_name,
+                obsolete_arity          :: arity
+                % Predname, Arity
+            )
+
+    ;       source_file(
+                source_file             :: string
+                % Source file name.
+            )
+
+    %
+    % Evaluation method pragmas
+    %
+
+    ;       tabled(
+                tabled_method           :: eval_method,
+                tabled_name             :: sym_name,
+                tabled_arity            :: int,
+                tabled_p_or_f           :: maybe(pred_or_func),
+                tabled_mode             :: maybe(list(mer_mode))
+                % Tabling type, Predname, Arity, PredOrFunc?, Mode?
+            )
+
+    ;       fact_table(
+                fact_table_name         :: sym_name,
+                fact_table_arity        :: arity,
+                fact_table_file         :: string
+                % Predname, Arity, Fact file name.
+            )
+
+    ;       reserve_tag(
+                restag_type             :: sym_name,
+                restag_arity            :: arity
+                % Typename, Arity
+            )
+
+    %
+    % Aditi pragmas
+    %
+
+    ;       aditi(
+                aditi_name              :: sym_name,
+                aditi_arity             :: arity
+                % Predname, Arity
+            )
+
+    ;       base_relation(
+                baserel_name            :: sym_name,
+                baserel_arity           :: arity
+                % Predname, Arity
+                %
+                % Eventually, these should only occur in
+                % automatically generated database interface
+                % files, but for now there's no such thing,
+                % so they can occur in user programs.
+            )
+
+    ;       aditi_index(
+                index_name              :: sym_name,
+                index_arity             :: arity,
+                index_spec              :: index_spec
+                % PredName, Arity, IndexType, Attributes
+                %
+                % Specify an index on a base relation.
+            )
+
+    ;       naive(
+                naive_name              :: sym_name,
+                naive_arity             :: arity
+                % Predname, Arity Use naive evaluation.
+            )
+
+    ;       psn(
+                psn_name                :: sym_name,
+                psn_arity               :: arity
+                % Predname, Arity Use predicate semi-naive evaluation.
+            )
+
+    ;       aditi_memo(
+                aditimemo_name          :: sym_name,
+                aditimemo_arity         :: arity
+                % Predname, Arity
+            )
+
+    ;       aditi_no_memo(
+                aditinomemo_name        :: sym_name,
+                aditinomemo_arity       :: arity
+                % Predname, Arity
+            )
+
+    ;       supp_magic(
+                suppmagic_name          :: sym_name,
+                suppmagic_arity         :: arity
+                % Predname, Arity
+            )
+
+    ;       context(
+                context_name            :: sym_name,
+                context_arity           :: arity
+                % Predname, Arity
+            )
+
+    ;       owner(
+                owner_name              :: sym_name,
+                owner_arity             :: arity,
+                owner_id                :: string
+                % PredName, Arity, String.
+            )
+
+    %
+    % Purity pragmas
+    %
+
+    ;       promise_pure(
+                pure_name               :: sym_name,
+                pure_arity              :: arity
+                % Predname, Arity
+            )
+
+    ;       promise_semipure(
+                semipure_name           :: sym_name,
+                semipure_arity          :: arity
+                % Predname, Arity
+            )
+
+    %
+    % Termination analysis pragmas
+    %
+
+    ;       termination_info(
+                terminfo_p_or_f         :: pred_or_func,
+                terminfo_name           :: sym_name,
+                terminfo_mode           :: list(mer_mode),
+                terminfo_args           :: maybe(pragma_arg_size_info),
+                terminfo_term           :: maybe(pragma_termination_info)
+                % The list(mer_mode) is the declared argmodes of the
+                % procedure, unless there are no declared argmodes, in which
+                % case the inferred argmodes are used.  This pragma is used to
+                % define information about a predicates termination
+                % properties.  It is most useful where the compiler has
+                % insufficient information to be able to analyse the
+                % predicate.  This includes c_code, and imported predicates.
+                % termination_info pragmas are used in opt and trans_opt
+                % files.
+            )
+
+    ;       termination2_info(
+                terminfo2_p_or_f        :: pred_or_func,
+                terminfo2_name          :: sym_name,
+                terminfo2_mode          :: list(mer_mode),
+                terminfo2_args          :: maybe(pragma_constr_arg_size_info),
+                terminfo2_args2         :: maybe(pragma_constr_arg_size_info),
+                terminfo2_term          :: maybe(pragma_termination_info)
+            )
+
+    ;       terminates(
+                term_name               :: sym_name,
+                term_arity              :: arity
+                % Predname, Arity
+            )
+
+    ;       does_not_terminate(
+                noterm_name             :: sym_name,
+                noterm_arity            :: arity
+                % Predname, Arity
+            )
+
+    ;       check_termination(
+                checkterm_name          :: sym_name,
+                checkterm_arity         :: arity
+                % Predname, Arity
+            )
+
+    ;       mode_check_clauses(
+                mode_check_clause_name  :: sym_name,
+                mode_check_clause_arity :: arity
+            ).
+
+%-----------------------------------------------------------------------------%
+%
+% Goals
+%
+
+    % Here's how clauses and goals are represented.
+    % a => b --> implies(a, b)
+    % a <= b --> implies(b, a) [just flips the goals around!]
+    % a <=> b --> equivalent(a, b)
+    %
+:- type goal == pair(goal_expr, prog_context).
+
+:- type goals == list(goal).
+
+:- type goal_expr
+    % conjunctions
+    --->    (goal , goal)   % (non-empty) conjunction
+    ;       true            % empty conjunction
+    ;       {goal & goal}   % parallel conjunction
+                            % (The curly braces just quote the '&'/2.)
+
+    % disjunctions
+    ;       {goal ; goal}   % (non-empty) disjunction
+                            % (The curly braces just quote the ';'/2.)
+    ;       fail            % empty disjunction
+
+    % quantifiers
+    ;       { some(prog_vars, goal) }
+                            % existential quantification
+                            % (The curly braces just quote the 'some'/2.)
+    ;       all(prog_vars, goal)
+                            % % universal quantification
+    ;       some_state_vars(prog_vars, goal)
+    ;       all_state_vars(prog_vars, goal)
+                            % state variables extracted from
+                            % some/2 and all/2 quantifiers.
+
+    % other scopes
+    ;       promise_purity(implicit_purity_promise, purity, goal)
+    ;       promise_equivalent_solutions(prog_vars, prog_vars, prog_vars, goal)
+                            % (OrdinaryVars, DotStateVars, ColonStateVars,
+                            % % Goal)
+
+    % implications
+    ;       implies(goal, goal)
+                            % A => B
+    ;       equivalent(goal, goal)
+                            % A <=> B
+
+    % negation and if-then-else
+    ;       not(goal)
+    ;       if_then(prog_vars, prog_vars, goal, goal)
+                            % if_then(SomeVars, StateVars, If, Then)
+    ;       if_then_else(prog_vars, prog_vars, goal, goal, goal)
+                            % if_then_else(SomeVars, StateVars, If, Then, Else)
+
+    % atomic goals
+    ;       call(sym_name, list(prog_term), purity)
+    ;       unify(prog_term, prog_term, purity).
+
+%-----------------------------------------------------------------------------%
+%
+% Module system
+%
+
+    % This is how module-system declarations (such as imports
+    % and exports) are represented.
+    %
+:- type module_defn
+    --->    module(module_name)
+    ;       end_module(module_name)
+
+    ;       interface
+    ;       implementation
+
+    ;       private_interface
+            % This is used internally by the compiler, to identify items
+            % which originally came from an implementation section for a
+            % module that contains sub-modules; such items need to be exported
+            % to the sub-modules.
+
+    ;       imported(import_locn)
+            % This is used internally by the compiler, to identify declarations
+            % which originally came from some other module imported with a
+            % `:- import_module' declaration, and which section the module
+            % was imported.
+
+    ;       used(import_locn)
+            % This is used internally by the compiler, to identify declarations
+            % which originally came from some other module and for which all
+            % uses must be module qualified. This applies to items from modules
+            % imported using `:- use_module', and items from `.opt' and `.int2'
+            % files. It also records from which section the module was
+            % imported.
+
+    ;       abstract_imported
+            % This is used internally by the compiler, to identify items which
+            % originally came from the implementation section of an interface
+            % file; usually type declarations (especially equivalence types)
+            % which should be used in code generation but not in type checking.
+
+    ;       opt_imported
+            % This is used internally by the compiler, to identify items which
+            % originally came from a .opt file.
+
+    ;       transitively_imported
+            % This is used internally by the compiler, to identify items which
+            % originally came from a `.opt' or `.int2' file. These should not
+            % be allowed to match items in the current module. Note that unlike
+            % `:- interface', `:- implementation' and the other
+            % pseudo-declarations `:- imported(interface)', etc., a
+            % `:- transitively_imported' declaration applies to all of the
+            % following items in the list, not just up to the next
+            % pseudo-declaration.
+
+    ;       external(maybe(backend), sym_name_specifier)
+
+    ;       export(sym_list)
+    ;       import(sym_list)
+    ;       use(sym_list)
+
+    ;       include_module(list(module_name))
+
+    ;       version_numbers(module_name, recompilation__version_numbers).
+            % This is used to represent the version numbers of items in an
+            % interface file for use in smart recompilation.
+
+%-----------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
+
+:- implementation.
+
+%-----------------------------------------------------------------------------%
+%
+% Mutable variables
+%
+
+    % Attributes for mutable variables.
+    %
+:- type mutable_var_attributes
+    --->    mutable_var_attributes(
+                mutable_trailed            :: trailed,
+                mutable_thread_safe        :: thread_safe,
+                mutable_foreign_names      :: maybe(list(foreign_name)),
+                mutable_attach_to_io_state :: bool
+            ).
+
+default_mutable_attributes =
+	mutable_var_attributes(trailed, not_thread_safe, no, no).
+
+mutable_var_thread_safe(MVarAttrs) = MVarAttrs ^ mutable_thread_safe.
+mutable_var_trailed(MVarAttrs) = MVarAttrs ^ mutable_trailed.
+mutable_var_maybe_foreign_names(MVarAttrs) = MVarAttrs ^ mutable_foreign_names.
+mutable_var_attach_to_io_state(MVarAttrs) =
+    MVarAttrs ^ mutable_attach_to_io_state.
+
+set_mutable_var_thread_safe(ThreadSafe, !Attributes) :-
+    !:Attributes = !.Attributes ^ mutable_thread_safe := ThreadSafe.
+set_mutable_var_trailed(Trailed, !Attributes) :-
+    !:Attributes = !.Attributes ^ mutable_trailed := Trailed.
+set_mutable_add_foreign_name(ForeignName, !Attributes) :-
+	MaybeForeignNames0 = !.Attributes ^ mutable_foreign_names,
+	(
+		MaybeForeignNames0 = no,
+		MaybeForeignNames  = yes([ForeignName])
+	;
+		MaybeForeignNames0 = yes(ForeignNames0),
+		ForeignNames = [ ForeignName | ForeignNames0],
+		MaybeForeignNames   = yes(ForeignNames)
+	),
+	!:Attributes = !.Attributes ^ mutable_foreign_names := MaybeForeignNames.
+set_mutable_var_attach_to_io_state(AttachToIOState, !Attributes) :-
+	!:Attributes =
+        !.Attributes ^ mutable_attach_to_io_state := AttachToIOState.
+
+%-----------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
Index: compiler/prog_mutable.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/prog_mutable.m,v
retrieving revision 1.5
diff -u -r1.5 prog_mutable.m
--- compiler/prog_mutable.m	24 Oct 2005 04:14:25 -0000	1.5
+++ compiler/prog_mutable.m	18 Nov 2005 06:43:37 -0000
@@ -18,6 +18,7 @@

 :- import_module mdbcomp.prim_data.
 :- import_module parse_tree.prog_data.
+:- import_module parse_tree.prog_item.
 :- import_module string.

 %-----------------------------------------------------------------------------%
Index: compiler/prog_out.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/prog_out.m,v
retrieving revision 1.65
diff -u -r1.65 prog_out.m
--- compiler/prog_out.m	28 Oct 2005 02:10:30 -0000	1.65
+++ compiler/prog_out.m	18 Nov 2005 06:43:59 -0000
@@ -23,6 +23,7 @@

 :- import_module mdbcomp.prim_data.
 :- import_module parse_tree.prog_data.
+:- import_module parse_tree.prog_item.

 :- import_module bool.
 :- import_module io.
Index: compiler/prog_util.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/prog_util.m,v
retrieving revision 1.81
diff -u -r1.81 prog_util.m
--- compiler/prog_util.m	28 Oct 2005 02:10:31 -0000	1.81
+++ compiler/prog_util.m	18 Nov 2005 07:11:08 -0000
@@ -17,6 +17,7 @@

 :- import_module mdbcomp.prim_data.
 :- import_module parse_tree.prog_data.
+:- import_module parse_tree.prog_item.

 :- import_module list.
 :- import_module std_util.
Index: compiler/recompilation.check.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/recompilation.check.m,v
retrieving revision 1.23
diff -u -r1.23 recompilation.check.m
--- compiler/recompilation.check.m	28 Oct 2005 02:10:32 -0000	1.23
+++ compiler/recompilation.check.m	18 Nov 2005 07:18:02 -0000
@@ -66,6 +66,7 @@
 :- import_module libs.options.
 :- import_module libs.timestamp.
 :- import_module parse_tree.error_util.
+:- import_module parse_tree.prog_item.
 :- import_module parse_tree.prog_io_util.
 :- import_module parse_tree.prog_out.
 :- import_module parse_tree.prog_util.
Index: compiler/recompilation.usage.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/recompilation.usage.m,v
retrieving revision 1.24
diff -u -r1.24 recompilation.usage.m
--- compiler/recompilation.usage.m	11 Nov 2005 05:06:50 -0000	1.24
+++ compiler/recompilation.usage.m	18 Nov 2005 07:18:31 -0000
@@ -93,6 +93,7 @@
 :- import_module mdbcomp.prim_data.
 :- import_module parse_tree.mercury_to_mercury.
 :- import_module parse_tree.prog_data.
+:- import_module parse_tree.prog_item.
 :- import_module parse_tree.prog_out.
 :- import_module parse_tree.prog_type.
 :- import_module parse_tree.prog_util.
Index: compiler/recompilation.version.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/recompilation.version.m,v
retrieving revision 1.32
diff -u -r1.32 recompilation.version.m
--- compiler/recompilation.version.m	8 Nov 2005 08:14:54 -0000	1.32
+++ compiler/recompilation.version.m	18 Nov 2005 06:44:39 -0000
@@ -18,7 +18,7 @@
 :- interface.

 :- import_module libs.timestamp.
-:- import_module parse_tree.prog_data.
+:- import_module parse_tree.prog_item.
 :- import_module parse_tree.prog_io_util.

 :- import_module io.
Index: compiler/trans_opt.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/trans_opt.m,v
retrieving revision 1.34
diff -u -r1.34 trans_opt.m
--- compiler/trans_opt.m	17 Nov 2005 15:57:31 -0000	1.34
+++ compiler/trans_opt.m	18 Nov 2005 07:21:45 -0000
@@ -89,6 +89,7 @@
 :- import_module mdbcomp.prim_data.
 :- import_module parse_tree.mercury_to_mercury.
 :- import_module parse_tree.prog_data.
+:- import_module parse_tree.prog_item.
 :- import_module parse_tree.prog_io.
 :- import_module parse_tree.prog_out.
 :- import_module transform_hlds.exception_analysis.
Index: compiler/notes/compiler_design.html
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/notes/compiler_design.html,v
retrieving revision 1.109
diff -u -r1.109 compiler_design.html
--- compiler/notes/compiler_design.html	16 Nov 2005 07:02:00 -0000	1.109
+++ compiler/notes/compiler_design.html	22 Nov 2005 07:13:31 -0000
@@ -264,13 +264,13 @@
 	<p>
 	The result of this stage is a parse tree that has a one-to-one
 	correspondence with the source code.  The parse tree data structure
-	definition is in prog_data.m, while the code to create it is in
-	prog_io.m and its submodules prog_io_dcg.m (which handles clauses
-	using Definite Clause Grammar notation), prog_io_goal.m (which handles
-	goals), prog_io_pragma.m (which handles pragma declarations),
-	prog_io_typeclass.m (which handles typeclass and instance declarations)
-	and prog_io_util.m (which defines predicates and types needed by the
-	other prog_io*.m modules.
+	definition is in prog_data.m and prog_item.m, while the code to create
+	it is in prog_io.m and its submodules prog_io_dcg.m (which handles
+	clauses using Definite Clause Grammar notation), prog_io_goal.m (which
+	handles goals), prog_io_pragma.m (which handles pragma declarations),
+	prog_io_typeclass.m (which handles typeclass and instance
+	declarations) and prog_io_util.m (which defines predicates and types
+	needed by the other prog_io*.m modules.

 	<p>


--------------------------------------------------------------------------
mercury-reviews mailing list
post:  mercury-reviews at cs.mu.oz.au
administrative address: owner-mercury-reviews at cs.mu.oz.au
unsubscribe: Address: mercury-reviews-request at cs.mu.oz.au Message: unsubscribe
subscribe:   Address: mercury-reviews-request at cs.mu.oz.au Message: subscribe
--------------------------------------------------------------------------



More information about the reviews mailing list