[m-rev.] for review: Simplify away self-comparisons of variables of int types.

Peter Wang novalazy at gmail.com
Tue Oct 23 16:43:29 AEDT 2018


This change won't remove self-comparisons of `int' and `uint' variables
in pregen grades. I'll see if we can handle that cleanly, in a separate
change, but we don't expect such comparisons in the compiler anyway.

---

Newer versions of gcc and clang may warn about comparison of a variable
to itself that always evaluate to true or false, breaking builds in
which warnings are treated as errors.

compiler/simplify_goal_call.m:
    Replace calls to comparison predicates < > =< >= of int types in
    which both arguments are the same variable with 'true' or 'false'
    goals.

    Replace calls to builtin.compare/3 where the compared arguments are
    the same variable with a goal that assigns (=) as the comparison
    result.

    Factor out common simplifications to all int types.

tests/hard_coded/Mmakefile:
tests/hard_coded/tautological_compare.m:
tests/hard_coded/tautological_compare.exp:
    Add new test case.

tests/typeclasses/typeclass_exist_method.m:
    Revert now-unnecessary workaround.

diff --git a/compiler/simplify_goal_call.m b/compiler/simplify_goal_call.m
index 1d225cba3..45a518450 100644
--- a/compiler/simplify_goal_call.m
+++ b/compiler/simplify_goal_call.m
@@ -1,14 +1,14 @@
 %---------------------------------------------------------------------------%
 % vim: ft=mercury ts=4 sw=4 et
 %---------------------------------------------------------------------------%
-% Copyright (C) 2014-2017 The Mercury team.
+% Copyright (C) 2014-2018 The Mercury team.
 % This file may only be copied under the terms of the GNU General
 % Public License - see the file COPYING in the Mercury distribution.
 %---------------------------------------------------------------------------%
 %
 % File: simplify_goal_call.m.
 %
 % This module handles simplification of plain calls, generic calls and
 % calls to foreign code.
 %
 %---------------------------------------------------------------------------%
@@ -817,51 +817,32 @@ simplify_improve_library_call(InstMap0, ModuleName, PredName, ModeNum, Args,
             R, X, Y, Context, ImprovedGoalExpr, ImprovedGoalInfo)
     ;
         ModuleName = "int",
         simplify_improve_int_call(InstMap0, ModuleName, PredName, ModeNum,
             Args, ImprovedGoalExpr, GoalInfo0, ImprovedGoalInfo, !Info)
     ;
         ModuleName = "uint",
         simplify_improve_uint_call(InstMap0, ModuleName, PredName, ModeNum,
             Args, ImprovedGoalExpr, GoalInfo0, ImprovedGoalInfo, !Info)
     ;
-        ModuleName = "int8",
-        simplify_improve_int8_call(InstMap0, ModuleName, PredName, ModeNum,
-            Args, ImprovedGoalExpr, GoalInfo0, ImprovedGoalInfo, !Info)
-    ;
-        ModuleName = "uint8",
-        simplify_improve_uint8_call(InstMap0, ModuleName, PredName, ModeNum,
-            Args, ImprovedGoalExpr, GoalInfo0, ImprovedGoalInfo, !Info)
-    ;
-        ModuleName = "int16",
-        simplify_improve_int16_call(InstMap0, ModuleName, PredName, ModeNum,
-            Args, ImprovedGoalExpr, GoalInfo0, ImprovedGoalInfo, !Info)
-    ;
-        ModuleName = "uint16",
-        simplify_improve_uint16_call(InstMap0, ModuleName, PredName, ModeNum,
-            Args, ImprovedGoalExpr, GoalInfo0, ImprovedGoalInfo, !Info)
-    ;
-        ModuleName = "int32",
-        simplify_improve_int32_call(InstMap0, ModuleName, PredName, ModeNum,
-            Args, ImprovedGoalExpr, GoalInfo0, ImprovedGoalInfo, !Info)
-    ;
-        ModuleName = "uint32",
-        simplify_improve_uint32_call(InstMap0, ModuleName, PredName, ModeNum,
-            Args, ImprovedGoalExpr, GoalInfo0, ImprovedGoalInfo, !Info)
-    ;
-        ModuleName = "int64",
-        simplify_improve_int64_call(InstMap0, ModuleName, PredName, ModeNum,
-            Args, ImprovedGoalExpr, GoalInfo0, ImprovedGoalInfo, !Info)
-    ;
-        ModuleName = "uint64",
-        simplify_improve_uint64_call(InstMap0, ModuleName, PredName, ModeNum,
-            Args, ImprovedGoalExpr, GoalInfo0, ImprovedGoalInfo, !Info)
+        ( ModuleName = "int8",      IntType = int_type_int8
+        ; ModuleName = "uint8",     IntType = int_type_uint8
+        ; ModuleName = "int16",     IntType = int_type_int16
+        ; ModuleName = "uint16",    IntType = int_type_uint16
+        ; ModuleName = "int32",     IntType = int_type_int32
+        ; ModuleName = "uint32",    IntType = int_type_uint32
+        ; ModuleName = "int64",     IntType = int_type_int64
+        ; ModuleName = "uint64",    IntType = int_type_uint64
+        ),
+        simplify_improve_int_type_call(IntType, InstMap0, ModuleName, PredName,
+            ModeNum, Args, ImprovedGoalExpr, GoalInfo0, ImprovedGoalInfo,
+            !Info)
     ),
     simplify_info_set_should_requantify(!Info).
 
 :- pred simplify_inline_builtin_inequality(prog_var::in,
     prog_var::in, prog_var::in, string::in, bool::in, hlds_goal_info::in,
     hlds_goal_expr::out, instmap::in,
     simplify_info::in, simplify_info::out) is det.
 
 simplify_inline_builtin_inequality(TI, X, Y, Inequality, Invert, GoalInfo,
         ImprovedGoalExpr, InstMap0, !Info) :-
@@ -947,21 +928,21 @@ simplify_improve_builtin_compare(_ModeNum, Args, Context,
     simplify_info_get_var_types(!.Info, VarTypes),
     lookup_var_type(VarTypes, Y, Type),
     type_definitely_has_no_user_defined_equality_pred(ModuleInfo, Type),
 
     require_det (
         % We cannot use simplify_build_compare_ite because there is
         % no builtin_compound_gt predicate (yet).
         % Using simplify_build_compare_ite would yield faster code,
         % because the code we generate here start with an equality test,
         % which is 99+% likely to fail. Starting with a less than or
-        % greater than test would be bette. Since such a test can be expected
+        % greater than test would be better. Since such a test can be expected
         % to determine the final outcome in almost 50% of cases, it would
         % let us avoid the cost of the second test *much* more frequently.
 
         goal_util.generate_simple_call(ModuleInfo,
             mercury_private_builtin_module, "builtin_compound_eq",
             pf_predicate, only_mode, detism_semi, purity_pure, [X, Y], [],
             instmap_delta_bind_no_var, Context, CmpEqGoal),
         goal_util.generate_simple_call(ModuleInfo,
             mercury_private_builtin_module, "builtin_compound_lt",
             pf_predicate, only_mode, detism_semi, purity_pure, [X, Y], [],
@@ -1015,111 +996,75 @@ simplify_build_compare_ite(CmpLtGoal, CmpGtGoal, R, X, Y, Context,
     Builtin = mercury_public_builtin_module,
     CmpRes = qualified(mercury_public_builtin_module, "comparison_result"),
     CmpResTypeCtor = type_ctor(CmpRes, 0),
     FunctorResultLt = cons(qualified(Builtin, "<"), 0, CmpResTypeCtor),
     FunctorResultEq = cons(qualified(Builtin, "="), 0, CmpResTypeCtor),
     FunctorResultGt = cons(qualified(Builtin, ">"), 0, CmpResTypeCtor),
     make_const_construction(Context, R, FunctorResultLt, ReturnLtGoal),
     make_const_construction(Context, R, FunctorResultEq, ReturnEqGoal),
     make_const_construction(Context, R, FunctorResultGt, ReturnGtGoal),
 
-    % This assumes that CmpLtGoal and CmpGtGoal take only X and Y as inputs.
-    % This assumption will be *wrong* if the shared type of X and Y is
-    % polymorphic, because in that case, the typeinfos describing the actual
-    % types bound to the type variables in the polymorphic type will *also*
-    % be nonlocals.
-    %
-    % If we ever want to use this predicate in such cases, we will have to get
-    % our caller to pass us the extra nonlocals.
-    NonLocals = set_of_var.list_to_set([R, X, Y]),
-    goal_info_init(NonLocals, instmap_delta_bind_var(R), detism_det,
-        purity_pure, Context, GoalInfo),
-
-    ReturnGtEqGoalExpr =
-        if_then_else([], CmpGtGoal, ReturnGtGoal, ReturnEqGoal),
-    ReturnGtEqGoal = hlds_goal(ReturnGtEqGoalExpr, GoalInfo),
-    GoalExpr =
-        if_then_else([], CmpLtGoal, ReturnLtGoal, ReturnGtEqGoal).
+    ( if X = Y then
+        ReturnEqGoal = hlds_goal(GoalExpr, GoalInfo)
+    else
+        % This assumes that CmpLtGoal and CmpGtGoal take only X and Y as inputs.
+        % This assumption will be *wrong* if the shared type of X and Y is
+        % polymorphic, because in that case, the typeinfos describing the actual
+        % types bound to the type variables in the polymorphic type will *also*
+        % be nonlocals.
+        %
+        % If we ever want to use this predicate in such cases, we will have to get
+        % our caller to pass us the extra nonlocals.
+        NonLocals = set_of_var.list_to_set([R, X, Y]),
+        goal_info_init(NonLocals, instmap_delta_bind_var(R), detism_det,
+            purity_pure, Context, GoalInfo),
+
+        ReturnGtEqGoalExpr =
+            if_then_else([], CmpGtGoal, ReturnGtGoal, ReturnEqGoal),
+        ReturnGtEqGoal = hlds_goal(ReturnGtEqGoalExpr, GoalInfo),
+        GoalExpr =
+            if_then_else([], CmpLtGoal, ReturnLtGoal, ReturnGtEqGoal)
+    ).
 
 :- pred simplify_improve_int_call(instmap::in, string::in, string::in,
     int::in, list(prog_var)::in, hlds_goal_expr::out,
     hlds_goal_info::in, hlds_goal_info::out,
     simplify_info::in, simplify_info::out) is semidet.
 
-simplify_improve_int_call(InstMap0, ModuleName, PredName, _ModeNum, Args,
+simplify_improve_int_call(InstMap0, ModuleName, PredName, ModeNum, Args,
         ImprovedGoalExpr, !GoalInfo, !Info) :-
     simplify_info_get_module_info(!.Info, ModuleInfo),
     module_info_get_globals(ModuleInfo, Globals),
     globals.lookup_bool_option(Globals, pregenerated_dist, no),
     target_bits_per_int(Globals, bits_per_int(TargetBitsPerInt)),
-    (
-        PredName = "quot_bits_per_int",
+    ( if PredName = "quot_bits_per_int" then
         Args = [X, Y],
         % There is no point in checking whether bits_per_int is 0;
         % it isn't.
         Op = "unchecked_quotient",
         simplify_make_int_ico_op(ModuleName, Op, X, TargetBitsPerInt, Y,
             ImprovedGoalExpr, !.GoalInfo, !Info)
-    ;
-        PredName = "times_bits_per_int",
+    else if PredName = "times_bits_per_int" then
         Args = [X, Y],
         Op = "*",
         simplify_make_int_ico_op(ModuleName, Op, X, TargetBitsPerInt, Y,
             ImprovedGoalExpr, !.GoalInfo, !Info)
-    ;
-        PredName = "rem_bits_per_int",
+    else if PredName = "rem_bits_per_int" then
         Args = [X, Y],
         % There is no point in checking whether bits_per_int is 0;
         % it isn't.
         Op = "unchecked_rem",
         simplify_make_int_ico_op(ModuleName, Op, X, TargetBitsPerInt, Y,
             ImprovedGoalExpr, !.GoalInfo, !Info)
-    ;
-        ( PredName = "/"
-        ; PredName = "//"
-        ),
-        Args = [X, Y, Z],
-        instmap_lookup_var(InstMap0, Y, InstY),
-        InstY = bound(_, _, [bound_functor(int_const(YVal), [])]),
-        YVal \= 0,
-        Op = "unchecked_quotient",
-        simplify_make_binary_op_goal_expr(!.Info, ModuleName, Op,
-            inline_builtin, X, Y, Z, ImprovedGoalExpr)
-    ;
-        PredName = "rem",
-        Args = [X, Y, Z],
-        instmap_lookup_var(InstMap0, Y, InstY),
-        InstY = bound(_, _, [bound_functor(int_const(YVal), [])]),
-        YVal \= 0,
-        Op = "unchecked_rem",
-        simplify_make_binary_op_goal_expr(!.Info, ModuleName, Op,
-            inline_builtin, X, Y, Z, ImprovedGoalExpr)
-    ;
-        PredName = "<<",
-        Args = [X, Y, Z],
-        instmap_lookup_var(InstMap0, Y, InstY),
-        InstY = bound(_, _, [bound_functor(int_const(YVal), [])]),
-        YVal >= 0,
-        YVal < TargetBitsPerInt,
-        Op = "unchecked_left_shift",
-        simplify_make_binary_op_goal_expr(!.Info, ModuleName, Op,
-            inline_builtin, X, Y, Z, ImprovedGoalExpr)
-    ;
-        PredName = ">>",
-        Args = [X, Y, Z],
-        instmap_lookup_var(InstMap0, Y, InstY),
-        InstY = bound(_, _, [bound_functor(int_const(YVal), [])]),
-        YVal >= 0,
-        YVal < TargetBitsPerInt,
-        Op = "unchecked_right_shift",
-        simplify_make_binary_op_goal_expr(!.Info, ModuleName, Op,
-            inline_builtin, X, Y, Z, ImprovedGoalExpr)
+    else
+        simplify_improve_int_type_call(int_type_int, InstMap0, ModuleName,
+            PredName, ModeNum, Args, ImprovedGoalExpr, !GoalInfo, !Info)
     ).
 
     % simplify_make_int_ico_op(ModuleName, Op, X, IntConst, Y, GoalExpr,
     %   OrigGoalInfo, !Info):
     %
     % Return a GoalExpr that computes Y := X Op IntConst.
     % (The ico stands for the three arguments being Input, Constant input,
     % and Output.)
     %
 :- pred simplify_make_int_ico_op(string::in, string::in,
@@ -1212,399 +1157,161 @@ simplify_make_int_const(IntConst, ConstVar, Goal, !Info) :-
     NonLocals = set_of_var.make_singleton(ConstVar),
     InstMapDelta = instmap_delta_bind_var(ConstVar),
     goal_info_init(NonLocals, InstMapDelta, detism_det, purity_pure, GoalInfo),
     Goal = hlds_goal(GoalExpr, GoalInfo).
 
 :- pred simplify_improve_uint_call(instmap::in, string::in, string::in,
     int::in, list(prog_var)::in, hlds_goal_expr::out,
     hlds_goal_info::in, hlds_goal_info::out,
     simplify_info::in, simplify_info::out) is semidet.
 
-simplify_improve_uint_call(InstMap0, ModuleName, PredName, _ModeNum, Args,
+simplify_improve_uint_call(InstMap0, ModuleName, PredName, ModeNum, Args,
         ImprovedGoalExpr, !GoalInfo, !Info) :-
     simplify_info_get_module_info(!.Info, ModuleInfo),
     module_info_get_globals(ModuleInfo, Globals),
     globals.lookup_bool_option(Globals, pregenerated_dist, no),
-    target_bits_per_int(Globals, bits_per_int(TargetBitsPerInt)),
-    (
-        ( PredName = "/"
-        ; PredName = "//"
-        ),
-        Args = [X, Y, Z],
-        instmap_lookup_var(InstMap0, Y, InstY),
-        InstY = bound(_, _, [bound_functor(uint_const(YVal), [])]),
-        YVal \= 0u,
-        Op = "unchecked_quotient"
-    ;
-        PredName = "rem",
-        Args = [X, Y, Z],
-        instmap_lookup_var(InstMap0, Y, InstY),
-        InstY = bound(_, _, [bound_functor(uint_const(YVal), [])]),
-        YVal \= 0u,
-        Op = "unchecked_rem"
-    ;
-        PredName = "<<",
-        Args = [X, Y, Z],
-        instmap_lookup_var(InstMap0, Y, InstY),
-        InstY = bound(_, _, [bound_functor(int_const(YVal), [])]),
-        YVal >= 0,
-        YVal < TargetBitsPerInt,
-        Op = "unchecked_left_shift"
-    ;
-        PredName = ">>",
-        Args = [X, Y, Z],
-        instmap_lookup_var(InstMap0, Y, InstY),
-        InstY = bound(_, _, [bound_functor(int_const(YVal), [])]),
-        YVal >= 0,
-        YVal < TargetBitsPerInt,
-        Op = "unchecked_right_shift"
-    ),
-    simplify_make_binary_op_goal_expr(!.Info, ModuleName, Op,
-        inline_builtin, X, Y, Z, ImprovedGoalExpr).
+    simplify_improve_int_type_call(int_type_uint, InstMap0, ModuleName,
+        PredName, ModeNum, Args, ImprovedGoalExpr, !GoalInfo, !Info).
 
-:- pred simplify_improve_int8_call(instmap::in, string::in, string::in,
-    int::in, list(prog_var)::in, hlds_goal_expr::out,
+:- pred simplify_improve_int_type_call(int_type::in, instmap::in, string::in,
+    string::in, int::in, list(prog_var)::in, hlds_goal_expr::out,
     hlds_goal_info::in, hlds_goal_info::out,
     simplify_info::in, simplify_info::out) is semidet.
 
-simplify_improve_int8_call(InstMap0, ModuleName, PredName, _ModeNum, Args,
-        ImprovedGoalExpr, !GoalInfo, !Info) :-
+simplify_improve_int_type_call(IntType, InstMap0, ModuleName, PredName,
+        _ModeNum, Args, ImprovedGoalExpr, !GoalInfo, !Info) :-
+    simplify_info_get_module_info(!.Info, ModuleInfo),
+    module_info_get_globals(ModuleInfo, Globals),
     (
         ( PredName = "/"
         ; PredName = "//"
         ),
         Args = [X, Y, Z],
         instmap_lookup_var(InstMap0, Y, InstY),
-        InstY = bound(_, _, [bound_functor(int8_const(YVal), [])]),
-        YVal \= 0i8,
-        Op = "unchecked_quotient"
+        InstY = bound(_, _, [bound_functor(ConsY, [])]),
+        is_non_zero_const(IntType, ConsY),
+        Op = "unchecked_quotient",
+        simplify_make_binary_op_goal_expr(!.Info, ModuleName, Op,
+            inline_builtin, X, Y, Z, ImprovedGoalExpr)
     ;
         PredName = "rem",
         Args = [X, Y, Z],
         instmap_lookup_var(InstMap0, Y, InstY),
-        InstY = bound(_, _, [bound_functor(int8_const(YVal), [])]),
-        YVal \= 0i8,
-        Op = "unchecked_rem"
+        InstY = bound(_, _, [bound_functor(ConsY, [])]),
+        is_non_zero_const(IntType, ConsY),
+        Op = "unchecked_rem",
+        simplify_make_binary_op_goal_expr(!.Info, ModuleName, Op,
+            inline_builtin, X, Y, Z, ImprovedGoalExpr)
     ;
         PredName = "<<",
         Args = [X, Y, Z],
         instmap_lookup_var(InstMap0, Y, InstY),
         InstY = bound(_, _, [bound_functor(int_const(YVal), [])]),
         YVal >= 0,
-        YVal < 8,
-        Op = "unchecked_left_shift"
+        YVal < int_type_target_bits(Globals, IntType),
+        Op = "unchecked_left_shift",
+        simplify_make_binary_op_goal_expr(!.Info, ModuleName, Op,
+            inline_builtin, X, Y, Z, ImprovedGoalExpr)
     ;
         PredName = ">>",
         Args = [X, Y, Z],
         instmap_lookup_var(InstMap0, Y, InstY),
         InstY = bound(_, _, [bound_functor(int_const(YVal), [])]),
         YVal >= 0,
-        YVal < 8,
-        Op = "unchecked_right_shift"
-    ),
-    simplify_make_binary_op_goal_expr(!.Info, ModuleName, Op,
-        inline_builtin, X, Y, Z, ImprovedGoalExpr).
-
-:- pred simplify_improve_uint8_call(instmap::in, string::in, string::in,
-    int::in, list(prog_var)::in, hlds_goal_expr::out,
-    hlds_goal_info::in, hlds_goal_info::out,
-    simplify_info::in, simplify_info::out) is semidet.
-
-simplify_improve_uint8_call(InstMap0, ModuleName, PredName, _ModeNum, Args,
-        ImprovedGoalExpr, !GoalInfo, !Info) :-
-    (
-        ( PredName = "/"
-        ; PredName = "//"
-        ),
-        Args = [X, Y, Z],
-        instmap_lookup_var(InstMap0, Y, InstY),
-        InstY = bound(_, _, [bound_functor(uint8_const(YVal), [])]),
-        YVal \= 0u8,
-        Op = "unchecked_quotient"
-    ;
-        PredName = "rem",
-        Args = [X, Y, Z],
-        instmap_lookup_var(InstMap0, Y, InstY),
-        InstY = bound(_, _, [bound_functor(uint8_const(YVal), [])]),
-        YVal \= 0u8,
-        Op = "unchecked_rem"
-    ;
-        PredName = "<<",
-        Args = [X, Y, Z],
-        instmap_lookup_var(InstMap0, Y, InstY),
-        InstY = bound(_, _, [bound_functor(int_const(YVal), [])]),
-        YVal >= 0,
-        YVal < 8,
-        Op = "unchecked_left_shift"
+        YVal < int_type_target_bits(Globals, IntType),
+        Op = "unchecked_right_shift",
+        simplify_make_binary_op_goal_expr(!.Info, ModuleName, Op,
+            inline_builtin, X, Y, Z, ImprovedGoalExpr)
     ;
-        PredName = ">>",
-        Args = [X, Y, Z],
-        instmap_lookup_var(InstMap0, Y, InstY),
-        InstY = bound(_, _, [bound_functor(int_const(YVal), [])]),
-        YVal >= 0,
-        YVal < 8,
-        Op = "unchecked_right_shift"
-    ),
-    simplify_make_binary_op_goal_expr(!.Info, ModuleName, Op,
-        inline_builtin, X, Y, Z, ImprovedGoalExpr).
-
-:- pred simplify_improve_int16_call(instmap::in, string::in ,string::in,
-    int::in, list(prog_var)::in, hlds_goal_expr::out,
-    hlds_goal_info::in, hlds_goal_info::out,
-    simplify_info::in, simplify_info::out) is semidet.
-
-simplify_improve_int16_call(InstMap0, ModuleName, PredName, _ModeNum, Args,
-        ImprovedGoalExpr, !GoalInfo, !Info) :-
-    (
-        ( PredName = "/"
-        ; PredName = "//"
+        ( PredName = "<"
+        ; PredName = ">"
         ),
-        Args = [X, Y, Z],
-        instmap_lookup_var(InstMap0, Y, InstY),
-        InstY = bound(_, _, [bound_functor(int16_const(YVal), [])]),
-        YVal \= 0i16,
-        Op = "unchecked_quotient"
+        Args = [X, X],
+        ImprovedGoalExpr = fail_goal_expr
     ;
-        PredName = "rem",
-        Args = [X, Y, Z],
-        instmap_lookup_var(InstMap0, Y, InstY),
-        InstY = bound(_, _, [bound_functor(int16_const(YVal), [])]),
-        YVal \= 0i16,
-        Op = "unchecked_rem"
-    ;
-        PredName = "<<",
-        Args = [X, Y, Z],
-        instmap_lookup_var(InstMap0, Y, InstY),
-        InstY = bound(_, _, [bound_functor(int_const(YVal), [])]),
-        YVal >= 0,
-        YVal < 16,
-        Op = "unchecked_left_shift"
-    ;
-        PredName = ">>",
-        Args = [X, Y, Z],
-        instmap_lookup_var(InstMap0, Y, InstY),
-        InstY = bound(_, _, [bound_functor(int_const(YVal), [])]),
-        YVal >= 0,
-        YVal < 16,
-        Op = "unchecked_right_shift"
-    ),
-    simplify_make_binary_op_goal_expr(!.Info, ModuleName, Op,
-        inline_builtin, X, Y, Z, ImprovedGoalExpr).
+        ( PredName = "=<"
+        ; PredName = ">="
+        ),
+        Args = [X, X],
+        ImprovedGoalExpr = true_goal_expr
+    ).
 
-:- pred simplify_improve_uint16_call(instmap::in, string::in, string::in,
-    int::in, list(prog_var)::in, hlds_goal_expr::out,
-    hlds_goal_info::in, hlds_goal_info::out,
-    simplify_info::in, simplify_info::out) is semidet.
+:- pred is_non_zero_const(int_type::in, cons_id::in) is semidet.
 
-simplify_improve_uint16_call(InstMap0, ModuleName, PredName, _ModeNum, Args,
-        ImprovedGoalExpr, !GoalInfo, !Info) :-
+is_non_zero_const(IntType, ConsId) :-
+    require_complete_switch[ IntType]
     (
-        ( PredName = "/"
-        ; PredName = "//"
-        ),
-        Args = [X, Y, Z],
-        instmap_lookup_var(InstMap0, Y, InstY),
-        InstY = bound(_, _, [bound_functor(uint16_const(YVal), [])]),
-        YVal \= 0u16,
-        Op = "unchecked_quotient"
+        IntType = int_type_int,
+        ConsId = int_const(Val),
+        Val \= 0
     ;
-        PredName = "rem",
-        Args = [X, Y, Z],
-        instmap_lookup_var(InstMap0, Y, InstY),
-        InstY = bound(_, _, [bound_functor(uint16_const(YVal), [])]),
-        YVal \= 0u16,
-        Op = "unchecked_rem"
+        IntType = int_type_uint,
+        ConsId = uint_const(Val),
+        Val \= 0u
     ;
-        PredName = "<<",
-        Args = [X, Y, Z],
-        instmap_lookup_var(InstMap0, Y, InstY),
-        InstY = bound(_, _, [bound_functor(int_const(YVal), [])]),
-        YVal >= 0,
-        YVal < 16,
-        Op = "unchecked_left_shift"
+        IntType = int_type_int8,
+        ConsId = int8_const(Val),
+        Val \= 0i8
     ;
-        PredName = ">>",
-        Args = [X, Y, Z],
-        instmap_lookup_var(InstMap0, Y, InstY),
-        InstY = bound(_, _, [bound_functor(int_const(YVal), [])]),
-        YVal >= 0,
-        YVal < 16,
-        Op = "unchecked_right_shift"
-    ),
-    simplify_make_binary_op_goal_expr(!.Info, ModuleName, Op,
-        inline_builtin, X, Y, Z, ImprovedGoalExpr).
-
-:- pred simplify_improve_int32_call(instmap::in, string::in, string::in,
-    int::in, list(prog_var)::in, hlds_goal_expr::out,
-    hlds_goal_info::in, hlds_goal_info::out,
-    simplify_info::in, simplify_info::out) is semidet.
-
-simplify_improve_int32_call(InstMap0, ModuleName, PredName, _ModeNum, Args,
-        ImprovedGoalExpr, !GoalInfo, !Info) :-
-    (
-        ( PredName = "/"
-        ; PredName = "//"
-        ),
-        Args = [X, Y, Z],
-        instmap_lookup_var(InstMap0, Y, InstY),
-        InstY = bound(_, _, [bound_functor(int32_const(YVal), [])]),
-        YVal \= 0i32,
-        Op = "unchecked_quotient"
+        IntType = int_type_uint8,
+        ConsId = uint8_const(Val),
+        Val \= 0u8
     ;
-        PredName = "rem",
-        Args = [X, Y, Z],
-        instmap_lookup_var(InstMap0, Y, InstY),
-        InstY = bound(_, _, [bound_functor(int32_const(YVal), [])]),
-        YVal \= 0i32,
-        Op = "unchecked_rem"
+        IntType = int_type_int16,
+        ConsId = int16_const(Val),
+        Val \= 0i16
     ;
-        PredName = "<<",
-        Args = [X, Y, Z],
-        instmap_lookup_var(InstMap0, Y, InstY),
-        InstY = bound(_, _, [bound_functor(int_const(YVal), [])]),
-        YVal >= 0,
-        YVal < 32,
-        Op = "unchecked_left_shift"
+        IntType = int_type_uint16,
+        ConsId = uint16_const(Val),
+        Val \= 0u16
     ;
-        PredName = ">>",
-        Args = [X, Y, Z],
-        instmap_lookup_var(InstMap0, Y, InstY),
-        InstY = bound(_, _, [bound_functor(int_const(YVal), [])]),
-        YVal >= 0,
-        YVal < 32,
-        Op = "unchecked_right_shift"
-    ),
-    simplify_make_binary_op_goal_expr(!.Info, ModuleName, Op,
-        inline_builtin, X, Y, Z, ImprovedGoalExpr).
-
-:- pred simplify_improve_uint32_call(instmap::in, string::in, string::in,
-    int::in, list(prog_var)::in, hlds_goal_expr::out,
-    hlds_goal_info::in, hlds_goal_info::out,
-    simplify_info::in, simplify_info::out) is semidet.
-
-simplify_improve_uint32_call(InstMap0, ModuleName, PredName, _ModeNum, Args,
-        ImprovedGoalExpr, !GoalInfo, !Info) :-
-    (
-        ( PredName = "/"
-        ; PredName = "//"
-        ),
-        Args = [X, Y, Z],
-        instmap_lookup_var(InstMap0, Y, InstY),
-        InstY = bound(_, _, [bound_functor(uint32_const(YVal), [])]),
-        YVal \= 0u32,
-        Op = "unchecked_quotient"
+        IntType = int_type_int32,
+        ConsId = int32_const(Val),
+        Val \= 0i32
     ;
-        PredName = "rem",
-        Args = [X, Y, Z],
-        instmap_lookup_var(InstMap0, Y, InstY),
-        InstY = bound(_, _, [bound_functor(uint32_const(YVal), [])]),
-        YVal \= 0u32,
-        Op = "unchecked_rem"
+        IntType = int_type_uint32,
+        ConsId = uint32_const(Val),
+        Val \= 0u32
     ;
-        PredName = "<<",
-        Args = [X, Y, Z],
-        instmap_lookup_var(InstMap0, Y, InstY),
-        InstY = bound(_, _, [bound_functor(int_const(YVal), [])]),
-        YVal >= 0,
-        YVal < 32,
-        Op = "unchecked_left_shift"
+        IntType = int_type_int64,
+        ConsId = int64_const(Val),
+        Val \= 0i64
     ;
-        PredName = ">>",
-        Args = [X, Y, Z],
-        instmap_lookup_var(InstMap0, Y, InstY),
-        InstY = bound(_, _, [bound_functor(int_const(YVal), [])]),
-        YVal >= 0,
-        YVal < 32,
-        Op = "unchecked_right_shift"
-    ),
-    simplify_make_binary_op_goal_expr(!.Info, ModuleName, Op,
-        inline_builtin, X, Y, Z, ImprovedGoalExpr).
+        IntType = int_type_uint64,
+        ConsId = uint64_const(Val),
+        Val \= 0u64
+    ).
 
-:- pred simplify_improve_int64_call(instmap::in, string::in, string::in,
-    int::in, list(prog_var)::in, hlds_goal_expr::out,
-    hlds_goal_info::in, hlds_goal_info::out,
-    simplify_info::in, simplify_info::out) is semidet.
+:- func int_type_target_bits(globals, int_type) = int.
 
-simplify_improve_int64_call(InstMap0, ModuleName, PredName, _ModeNum, Args,
-        ImprovedGoalExpr, !GoalInfo, !Info) :-
+int_type_target_bits(Globals, IntType) = IntTypeBits :-
     (
-        ( PredName = "/"
-        ; PredName = "//"
+        ( IntType = int_type_int
+        ; IntType = int_type_uint
         ),
-        Args = [X, Y, Z],
-        instmap_lookup_var(InstMap0, Y, InstY),
-        InstY = bound(_, _, [bound_functor(int64_const(YVal), [])]),
-        YVal \= 0i64,
-        Op = "unchecked_quotient"
+        target_bits_per_int(Globals, bits_per_int(TargetBitsPerInt)),
+        IntTypeBits = TargetBitsPerInt
     ;
-        PredName = "rem",
-        Args = [X, Y, Z],
-        instmap_lookup_var(InstMap0, Y, InstY),
-        InstY = bound(_, _, [bound_functor(int64_const(YVal), [])]),
-        YVal \= 0i64,
-        Op = "unchecked_rem"
-    ;
-        PredName = "<<",
-        Args = [X, Y, Z],
-        instmap_lookup_var(InstMap0, Y, InstY),
-        InstY = bound(_, _, [bound_functor(int_const(YVal), [])]),
-        YVal >= 0,
-        YVal < 64,
-        Op = "unchecked_left_shift"
-    ;
-        PredName = ">>",
-        Args = [X, Y, Z],
-        instmap_lookup_var(InstMap0, Y, InstY),
-        InstY = bound(_, _, [bound_functor(int_const(YVal), [])]),
-        YVal >= 0,
-        YVal < 64,
-        Op = "unchecked_right_shift"
-    ),
-    simplify_make_binary_op_goal_expr(!.Info, ModuleName, Op,
-        inline_builtin, X, Y, Z, ImprovedGoalExpr).
-
-:- pred simplify_improve_uint64_call(instmap::in, string::in, string::in,
-    int::in, list(prog_var)::in, hlds_goal_expr::out,
-    hlds_goal_info::in, hlds_goal_info::out,
-    simplify_info::in, simplify_info::out) is semidet.
-
-simplify_improve_uint64_call(InstMap0, ModuleName, PredName, _ModeNum, Args,
-        ImprovedGoalExpr, !GoalInfo, !Info) :-
-    (
-        ( PredName = "/"
-        ; PredName = "//"
+        ( IntType = int_type_int8
+        ; IntType = int_type_uint8
         ),
-        Args = [X, Y, Z],
-        instmap_lookup_var(InstMap0, Y, InstY),
-        InstY = bound(_, _, [bound_functor(uint64_const(YVal), [])]),
-        YVal \= 0u64,
-        Op = "unchecked_quotient"
+        IntTypeBits = 8
     ;
-        PredName = "rem",
-        Args = [X, Y, Z],
-        instmap_lookup_var(InstMap0, Y, InstY),
-        InstY = bound(_, _, [bound_functor(uint64_const(YVal), [])]),
-        YVal \= 0u64,
-        Op = "unchecked_rem"
+        ( IntType = int_type_int16
+        ; IntType = int_type_uint16
+        ),
+        IntTypeBits = 16
     ;
-        PredName = "<<",
-        Args = [X, Y, Z],
-        instmap_lookup_var(InstMap0, Y, InstY),
-        InstY = bound(_, _, [bound_functor(int_const(YVal), [])]),
-        YVal >= 0,
-        YVal < 64,
-        Op = "unchecked_left_shift"
+        ( IntType = int_type_int32
+        ; IntType = int_type_uint32
+        ),
+        IntTypeBits = 32
     ;
-        PredName = ">>",
-        Args = [X, Y, Z],
-        instmap_lookup_var(InstMap0, Y, InstY),
-        InstY = bound(_, _, [bound_functor(int_const(YVal), [])]),
-        YVal >= 0,
-        YVal < 64,
-        Op = "unchecked_right_shift"
-    ),
-    simplify_make_binary_op_goal_expr(!.Info, ModuleName, Op,
-        inline_builtin, X, Y, Z, ImprovedGoalExpr).
+        ( IntType = int_type_int64
+        ; IntType = int_type_uint64
+        ),
+        IntTypeBits = 64
+    ).
 
 %---------------------------------------------------------------------------%
 :- end_module check_hlds.simplify.simplify_goal_call.
 %---------------------------------------------------------------------------%
diff --git a/tests/hard_coded/Mmakefile b/tests/hard_coded/Mmakefile
index b230c8074..39b179c72 100644
--- a/tests/hard_coded/Mmakefile
+++ b/tests/hard_coded/Mmakefile
@@ -359,20 +359,21 @@ ORDINARY_PROGS = \
 	string_switch2 \
 	string_switch3 \
 	string_to_float_overflow \
 	string_various \
 	sv_nested_closures \
 	sv_record_update \
 	switch_detect \
 	system_sort \
 	tag_switch_dup_label \
 	tail_rec_scc \
+	tautological_compare \
 	term_io_test \
 	term_to_univ_test \
 	test234_sorted_insert \
 	test_bag \
 	test_char_digits \
 	test_cord \
 	test_cord2 \
 	test_generic_ref \
 	test_imported_no_tag \
 	test_infinity \
diff --git a/tests/hard_coded/tautological_compare.exp b/tests/hard_coded/tautological_compare.exp
new file mode 100644
index 000000000..69f02c1cc
--- /dev/null
+++ b/tests/hard_coded/tautological_compare.exp
@@ -0,0 +1,72 @@
+
+int:
+ok
+ok
+ok
+ok
+
+uint:
+ok
+ok
+ok
+ok
+
+int8:
+ok
+ok
+ok
+ok
+
+uint8:
+ok
+ok
+ok
+ok
+
+int16:
+ok
+ok
+ok
+ok
+
+uint16:
+ok
+ok
+ok
+ok
+
+int32:
+ok
+ok
+ok
+ok
+
+uint32:
+ok
+ok
+ok
+ok
+
+int64:
+ok
+ok
+ok
+ok
+
+uint64:
+ok
+ok
+ok
+ok
+
+compare:
+ok
+ok
+ok
+ok
+ok
+ok
+ok
+ok
+ok
+ok
diff --git a/tests/hard_coded/tautological_compare.m b/tests/hard_coded/tautological_compare.m
new file mode 100644
index 000000000..f3b10353d
--- /dev/null
+++ b/tests/hard_coded/tautological_compare.m
@@ -0,0 +1,357 @@
+%---------------------------------------------------------------------------%
+% vim: ts=4 sw=4 et ft=mercury
+%---------------------------------------------------------------------------%
+%
+% Avoid generating tautological comparisons that the C compiler may detect.
+%
+
+:- module tautological_compare.
+:- interface.
+
+:- import_module io.
+
+:- pred main(io::di, io::uo) is det.
+
+%---------------------------------------------------------------------------%
+%---------------------------------------------------------------------------%
+
+:- implementation.
+
+:- import_module int.
+:- import_module int8.
+:- import_module uint.
+:- import_module uint8.
+
+main(!IO) :-
+    write_string("\nint:\n", !IO),
+    test_int(1, !IO),
+    write_string("\nuint:\n", !IO),
+    test_uint(1u, !IO),
+
+    write_string("\nint8:\n", !IO),
+    test_int8(1i8, !IO),
+    write_string("\nuint8:\n", !IO),
+    test_uint8(1u8, !IO),
+
+    write_string("\nint16:\n", !IO),
+    test_int16(1i8, !IO),
+    write_string("\nuint16:\n", !IO),
+    test_uint16(1u8, !IO),
+
+    write_string("\nint32:\n", !IO),
+    test_int32(1i8, !IO),
+    write_string("\nuint32:\n", !IO),
+    test_uint32(1u8, !IO),
+
+    write_string("\nint64:\n", !IO),
+    test_int64(1i8, !IO),
+    write_string("\nuint64:\n", !IO),
+    test_uint64(1u8, !IO),
+
+    write_string("\ncompare:\n", !IO),
+    test_compare(!IO).
+
+%---------------------------------------------------------------------------%
+
+:- pred test_int(int::in, io::di, io::uo) is det.
+
+test_int(I, !IO) :-
+    ( if I < I then
+        write_string("wrong\n", !IO)
+    else
+        write_string("ok\n", !IO)
+    ),
+    ( if I > I then
+        write_string("wrong\n", !IO)
+    else
+        write_string("ok\n", !IO)
+    ),
+    ( if I =< I then
+        write_string("ok\n", !IO)
+    else
+        write_string("wrong\n", !IO)
+    ),
+    ( if I >= I then
+        write_string("ok\n", !IO)
+    else
+        write_string("wrong\n", !IO)
+    ).
+
+:- pred test_uint(uint::in, io::di, io::uo) is det.
+
+test_uint(I, !IO) :-
+    ( if I < I then
+        write_string("wrong\n", !IO)
+    else
+        write_string("ok\n", !IO)
+    ),
+    ( if I > I then
+        write_string("wrong\n", !IO)
+    else
+        write_string("ok\n", !IO)
+    ),
+    ( if I =< I then
+        write_string("ok\n", !IO)
+    else
+        write_string("wrong\n", !IO)
+    ),
+    ( if I >= I then
+        write_string("ok\n", !IO)
+    else
+        write_string("wrong\n", !IO)
+    ).
+
+%---------------------------------------------------------------------------%
+
+:- pred test_int8(int8::in, io::di, io::uo) is det.
+
+test_int8(I, !IO) :-
+    ( if I < I then
+        write_string("wrong\n", !IO)
+    else
+        write_string("ok\n", !IO)
+    ),
+    ( if I > I then
+        write_string("wrong\n", !IO)
+    else
+        write_string("ok\n", !IO)
+    ),
+    ( if I =< I then
+        write_string("ok\n", !IO)
+    else
+        write_string("wrong\n", !IO)
+    ),
+    ( if I >= I then
+        write_string("ok\n", !IO)
+    else
+        write_string("wrong\n", !IO)
+    ).
+
+:- pred test_uint8(uint8::in, io::di, io::uo) is det.
+
+test_uint8(I, !IO) :-
+    ( if I < I then
+        write_string("wrong\n", !IO)
+    else
+        write_string("ok\n", !IO)
+    ),
+    ( if I > I then
+        write_string("wrong\n", !IO)
+    else
+        write_string("ok\n", !IO)
+    ),
+    ( if I =< I then
+        write_string("ok\n", !IO)
+    else
+        write_string("wrong\n", !IO)
+    ),
+    ( if I >= I then
+        write_string("ok\n", !IO)
+    else
+        write_string("wrong\n", !IO)
+    ).
+
+%---------------------------------------------------------------------------%
+
+:- pred test_int16(int8::in, io::di, io::uo) is det.
+
+test_int16(I, !IO) :-
+    ( if I < I then
+        write_string("wrong\n", !IO)
+    else
+        write_string("ok\n", !IO)
+    ),
+    ( if I > I then
+        write_string("wrong\n", !IO)
+    else
+        write_string("ok\n", !IO)
+    ),
+    ( if I =< I then
+        write_string("ok\n", !IO)
+    else
+        write_string("wrong\n", !IO)
+    ),
+    ( if I >= I then
+        write_string("ok\n", !IO)
+    else
+        write_string("wrong\n", !IO)
+    ).
+
+:- pred test_uint16(uint8::in, io::di, io::uo) is det.
+
+test_uint16(I, !IO) :-
+    ( if I < I then
+        write_string("wrong\n", !IO)
+    else
+        write_string("ok\n", !IO)
+    ),
+    ( if I > I then
+        write_string("wrong\n", !IO)
+    else
+        write_string("ok\n", !IO)
+    ),
+    ( if I =< I then
+        write_string("ok\n", !IO)
+    else
+        write_string("wrong\n", !IO)
+    ),
+    ( if I >= I then
+        write_string("ok\n", !IO)
+    else
+        write_string("wrong\n", !IO)
+    ).
+
+%---------------------------------------------------------------------------%
+
+:- pred test_int32(int8::in, io::di, io::uo) is det.
+
+test_int32(I, !IO) :-
+    ( if I < I then
+        write_string("wrong\n", !IO)
+    else
+        write_string("ok\n", !IO)
+    ),
+    ( if I > I then
+        write_string("wrong\n", !IO)
+    else
+        write_string("ok\n", !IO)
+    ),
+    ( if I =< I then
+        write_string("ok\n", !IO)
+    else
+        write_string("wrong\n", !IO)
+    ),
+    ( if I >= I then
+        write_string("ok\n", !IO)
+    else
+        write_string("wrong\n", !IO)
+    ).
+
+:- pred test_uint32(uint8::in, io::di, io::uo) is det.
+
+test_uint32(I, !IO) :-
+    ( if I < I then
+        write_string("wrong\n", !IO)
+    else
+        write_string("ok\n", !IO)
+    ),
+    ( if I > I then
+        write_string("wrong\n", !IO)
+    else
+        write_string("ok\n", !IO)
+    ),
+    ( if I =< I then
+        write_string("ok\n", !IO)
+    else
+        write_string("wrong\n", !IO)
+    ),
+    ( if I >= I then
+        write_string("ok\n", !IO)
+    else
+        write_string("wrong\n", !IO)
+    ).
+
+%---------------------------------------------------------------------------%
+
+:- pred test_int64(int8::in, io::di, io::uo) is det.
+
+test_int64(I, !IO) :-
+    ( if I < I then
+        write_string("wrong\n", !IO)
+    else
+        write_string("ok\n", !IO)
+    ),
+    ( if I > I then
+        write_string("wrong\n", !IO)
+    else
+        write_string("ok\n", !IO)
+    ),
+    ( if I =< I then
+        write_string("ok\n", !IO)
+    else
+        write_string("wrong\n", !IO)
+    ),
+    ( if I >= I then
+        write_string("ok\n", !IO)
+    else
+        write_string("wrong\n", !IO)
+    ).
+
+:- pred test_uint64(uint8::in, io::di, io::uo) is det.
+
+test_uint64(I, !IO) :-
+    ( if I < I then
+        write_string("wrong\n", !IO)
+    else
+        write_string("ok\n", !IO)
+    ),
+    ( if I > I then
+        write_string("wrong\n", !IO)
+    else
+        write_string("ok\n", !IO)
+    ),
+    ( if I =< I then
+        write_string("ok\n", !IO)
+    else
+        write_string("wrong\n", !IO)
+    ),
+    ( if I >= I then
+        write_string("ok\n", !IO)
+    else
+        write_string("wrong\n", !IO)
+    ).
+
+%---------------------------------------------------------------------------%
+
+:- pred test_compare(io::di, io::uo) is det.
+
+test_compare(!IO) :-
+    I = 1,
+    compare(RI, I, I),
+    print_comparison(RI, !IO),
+    U = 1u,
+    compare(RU, U, U),
+    print_comparison(RU, !IO),
+
+    I8 = 1i8,
+    compare(R8, I8, I8),
+    print_comparison(R8, !IO),
+    U8 = 1u8,
+    compare(RU8, U8, U8),
+    print_comparison(RU8, !IO),
+
+    I16 = 1i16,
+    compare(R16, I16, I16),
+    print_comparison(R16, !IO),
+    U16 = 1u16,
+    compare(RU16, U16, U16),
+    print_comparison(RU16, !IO),
+
+    I32 = 1i32,
+    compare(R32, I32, I32),
+    print_comparison(R32, !IO),
+    U32 = 1u32,
+    compare(RU32, U32, U32),
+    print_comparison(RU32, !IO),
+
+    I64 = 1i64,
+    compare(R64, I64, I64),
+    print_comparison(R64, !IO),
+    U64 = 1u64,
+    compare(RU64, U64, U64),
+    print_comparison(RU64, !IO).
+
+:- pred print_comparison(comparison_result::in, io::di, io::uo) is det.
+
+print_comparison(R, !IO) :-
+    (
+        R = (=),
+        write_string("ok\n", !IO)
+    ;
+        ( R = (<)
+        ; R = (>)
+        ),
+        write_string("wrong\n", !IO)
+    ).
+
+%---------------------------------------------------------------------------%
diff --git a/tests/typeclasses/typeclass_exist_method.m b/tests/typeclasses/typeclass_exist_method.m
index 44086e333..8f6100a04 100644
--- a/tests/typeclasses/typeclass_exist_method.m
+++ b/tests/typeclasses/typeclass_exist_method.m
@@ -2,22 +2,20 @@
 % vim: ts=4 sw=4 et ft=mercury
 %---------------------------------------------------------------------------%
 
 :- module typeclass_exist_method.
 :- interface.
 :- import_module io.
 
 :- pred main(io::di, io::uo) is det.
 
 :- implementation.
-
-:- import_module int.
 :- import_module require.
 
 :- typeclass toto(T) where
   [
   ].
 
 :- instance toto(float) where [].
 :- instance toto(character) where [].
 
 :- some [V] (pred gen_toto_float(V) => toto(V)).
@@ -35,21 +33,21 @@ gen_toto_char('?').
 ].
 
 :- instance toto2(int) where [
     pred(gen_toto/2) is int_gen_toto
 ].
 
 :- some [V] (pred int_gen_toto(int, V) => toto(V)).
 :- mode int_gen_toto(in, out) is det.
 
 int_gen_toto(X, Y) :-
-    ( compare(=, X, X + 0) ->
+    ( compare(=, X, X) ->
         gen_toto_float(Y)
     ;
         error("oops")
     ).
 
 main -->
     { gen_toto(42, Y) },
     write(Y), nl.
 
 :- end_module typeclass_exist_method.
-- 
2.19.1



More information about the reviews mailing list