https://gcc.gnu.org/g:127a24ede2f82eafecb5eb142e21dbda38d06c18

commit r15-8877-g127a24ede2f82eafecb5eb142e21dbda38d06c18
Author: Gaius Mulley <gaiusm...@gmail.com>
Date:   Tue Mar 25 02:08:05 2025 +0000

    PR modula2/119449 MAX of SYSTEM.REAL64 cause an ICE
    
    This bugfix implements MAX(REAL64) and MIN(REAL64) etc for
    REAL64, REAL96 and REAL128.
    
    gcc/m2/ChangeLog:
    
            PR modula2/119449
            * gm2-compiler/M2GCCDeclare.def (TryDeclareType): Remove tokenno
            parameter.
            * gm2-compiler/M2GCCDeclare.mod (TryDeclareType): Ditto.
            * gm2-compiler/M2GenGCC.mod (FoldTBitsize): Remove op2 and
            rename op1 as res and op3 as type.
            (FoldStandardFunction): Call FoldTBitsize omitting op2.
            * gm2-compiler/M2Quads.mod (GetTypeMin): Rewrite.
            (GetTypeMinLower): New procedure function.
            (GetTypeMax): Rewrite.
            (GetTypeMaxLower): New procedure function.
            * gm2-compiler/M2Range.mod (CheckCancelled): Comment out.
            * gm2-compiler/M2System.mod (CreateMinMaxFor): Add realtype
            parameter.
            (MapType): Rewrite to use realtype.
            (CreateType): Ditto.
            (AttemptToCreateType): Ditto.
            (MakeFixedSizedTypes): Add realtype boolean.
            (InitPIMTypes): Ditto.
            (InitISOTypes): Ditto.
            (MakeExtraSystemTypes): Ditto.
            * gm2-gcc/m2pp.cc (m2pp_nop_expr): Remove code.
            * gm2-gcc/m2type.cc (IsGccRealType): New function.
            (m2type_GetMinFrom): Rewrite.
            (m2type_GetMaxFrom): Ditto.
            (do_min_real): Declare static.
            (do_max_real): Declare static.
    
    gcc/testsuite/ChangeLog:
    
            PR modula2/119449
            * gm2/pim/pass/minmaxreal.mod: New test.
            * gm2/pim/pass/minmaxreal2.mod: New test.
            * gm2/pim/pass/minmaxreal3.mod: New test.
    
    Signed-off-by: Gaius Mulley <gaiusm...@gmail.com>

Diff:
---
 gcc/m2/gm2-compiler/M2GCCDeclare.def       |   2 +-
 gcc/m2/gm2-compiler/M2GCCDeclare.mod       |   6 +-
 gcc/m2/gm2-compiler/M2GenGCC.mod           |  13 ++-
 gcc/m2/gm2-compiler/M2Quads.mod            |  56 ++++++++++---
 gcc/m2/gm2-compiler/M2Range.mod            |   2 +
 gcc/m2/gm2-compiler/M2System.mod           | 123 ++++++++++++++++-------------
 gcc/m2/gm2-gcc/m2pp.cc                     |   1 -
 gcc/m2/gm2-gcc/m2type.cc                   |  29 ++++---
 gcc/testsuite/gm2/pim/pass/minmaxreal.mod  |   7 ++
 gcc/testsuite/gm2/pim/pass/minmaxreal2.mod |   8 ++
 gcc/testsuite/gm2/pim/pass/minmaxreal3.mod |  10 +++
 11 files changed, 168 insertions(+), 89 deletions(-)

diff --git a/gcc/m2/gm2-compiler/M2GCCDeclare.def 
b/gcc/m2/gm2-compiler/M2GCCDeclare.def
index 1d87d6b212af..b3a5790df972 100644
--- a/gcc/m2/gm2-compiler/M2GCCDeclare.def
+++ b/gcc/m2/gm2-compiler/M2GCCDeclare.def
@@ -98,7 +98,7 @@ PROCEDURE TryDeclareConstant (tokenno: CARDINAL; sym: 
CARDINAL) ;
                     then enter it into the to do list.
 *)
 
-PROCEDURE TryDeclareType (tokenno: CARDINAL; type: CARDINAL) ;
+PROCEDURE TryDeclareType (type: CARDINAL) ;
 
 
 (*
diff --git a/gcc/m2/gm2-compiler/M2GCCDeclare.mod 
b/gcc/m2/gm2-compiler/M2GCCDeclare.mod
index 7dcf439985a1..b12add6b26e8 100644
--- a/gcc/m2/gm2-compiler/M2GCCDeclare.mod
+++ b/gcc/m2/gm2-compiler/M2GCCDeclare.mod
@@ -144,7 +144,7 @@ FROM M2Base IMPORT IsPseudoBaseProcedure, 
IsPseudoBaseFunction,
                    Boolean, True, False, Nil,
                    IsRealType, IsNeededAtRunTime, IsComplexType ;
 
-FROM M2System IMPORT IsPseudoSystemFunction, IsSystemType,
+FROM M2System IMPORT IsPseudoSystemFunction, IsSystemType, IsRealN,
                      GetSystemTypeMinMax, Address, Word, Byte, Loc,
                      System, IntegerN, CardinalN, WordN, RealN, SetN, ComplexN,
                     CSizeT, CSSizeT, COffT ;
@@ -1918,7 +1918,7 @@ END IsAnyType ;
                     then enter it into the to do list.
 *)
 
-PROCEDURE TryDeclareType (tokenno: CARDINAL; type: CARDINAL) ;
+PROCEDURE TryDeclareType (type: CARDINAL) ;
 BEGIN
    IF (type#NulSym) AND IsAnyType (type)
    THEN
@@ -2013,7 +2013,7 @@ BEGIN
          ELSIF IsConstructor(sym)
          THEN
             DeclareConstantFromTree(sym, PopConstructorTree(tokenno))
-         ELSIF IsRealType(GetDType(sym))
+         ELSIF IsRealType (GetDType (sym)) OR IsRealN (GetDType (sym))
          THEN
             type := GetDType(sym) ;
             DeclareConstantFromTree(sym, 
BuildConvert(TokenToLocation(tokenno), Mod2Gcc(type), PopRealTree(), TRUE))
diff --git a/gcc/m2/gm2-compiler/M2GenGCC.mod b/gcc/m2/gm2-compiler/M2GenGCC.mod
index 3665751f4f97..a1e3c07809aa 100644
--- a/gcc/m2/gm2-compiler/M2GenGCC.mod
+++ b/gcc/m2/gm2-compiler/M2GenGCC.mod
@@ -4837,18 +4837,17 @@ END FoldBuiltinTypeInfo ;
 
 PROCEDURE FoldTBitsize  (tokenno: CARDINAL; p: WalkAction;
                          quad: CARDINAL;
-                         op1, op2, op3: CARDINAL) ;
+                         res, type: CARDINAL) ;
 VAR
-   type    : CARDINAL ;
    location: location_t ;
 BEGIN
    location := TokenToLocation(tokenno) ;
-   TryDeclareType (tokenno, op3) ;
-   type := GetDType (op3) ;
+   TryDeclareType (type) ;
+   type := GetDType (type) ;
    IF CompletelyResolved (type)
    THEN
-      AddModGcc (op1, BuildSystemTBitSize (location, Mod2Gcc (type))) ;
-      p (op1) ;
+      AddModGcc (res, BuildSystemTBitSize (location, Mod2Gcc (type))) ;
+      p (res) ;
       NoChange := FALSE ;
       SubQuad (quad)
    END
@@ -4987,7 +4986,7 @@ BEGIN
       END
    ELSIF op2=TBitSize
    THEN
-      FoldTBitsize (tokenno, p, quad, op1, op2, op3)
+      FoldTBitsize (tokenno, p, quad, op1, op3)
    ELSE
       InternalError ('only expecting LENGTH, CAP, ABS, IM, RE')
    END
diff --git a/gcc/m2/gm2-compiler/M2Quads.mod b/gcc/m2/gm2-compiler/M2Quads.mod
index a45d67a198ab..573fd74e4f15 100644
--- a/gcc/m2/gm2-compiler/M2Quads.mod
+++ b/gcc/m2/gm2-compiler/M2Quads.mod
@@ -9776,10 +9776,29 @@ END CheckBaseTypeValue ;
 
 
 (*
-   GetTypeMin - returns the minimium value of type.
+   GetTypeMin - returns the minimium value of type and generate an error
+                if this is unavailable.
 *)
 
 PROCEDURE GetTypeMin (tok: CARDINAL; func, type: CARDINAL) : CARDINAL ;
+VAR
+   min: CARDINAL ;
+BEGIN
+   min := GetTypeMinLower (tok, func, type) ;
+   IF min = NulSym
+   THEN
+      MetaErrorT1 (tok,
+                   'unable to obtain the {%AkMIN} value for type {%1ad}', type)
+   END ;
+   RETURN min
+END GetTypeMin ;
+
+
+(*
+   GetTypeMinLower - obtain the maximum value for type.
+*)
+
+PROCEDURE GetTypeMinLower (tok: CARDINAL; func, type: CARDINAL) : CARDINAL ;
 VAR
    min, max: CARDINAL ;
 BEGIN
@@ -9803,21 +9822,37 @@ BEGIN
       RETURN min
    ELSIF GetSType (type) = NulSym
    THEN
-      MetaErrorT1 (tok,
-                   'unable to obtain the {%AkMIN} value for type {%1ad}', 
type) ;
-      (* non recoverable error.  *)
-      InternalError ('MetaErrorT1 {%AkMIN} should call abort')
+      RETURN NulSym
    ELSE
       RETURN GetTypeMin (tok, func, GetSType (type))
    END
-END GetTypeMin ;
+END GetTypeMinLower ;
 
 
 (*
-   GetTypeMax - returns the maximum value of type.
+   GetTypeMax - returns the maximum value of type and generate an error
+                if this is unavailable.
 *)
 
 PROCEDURE GetTypeMax (tok: CARDINAL; func, type: CARDINAL) : CARDINAL ;
+VAR
+   max: CARDINAL ;
+BEGIN
+   max := GetTypeMaxLower (tok, func, type) ;
+   IF max = NulSym
+   THEN
+      MetaErrorT1 (tok,
+                   'unable to obtain the {%AkMAX} value for type {%1ad}', type)
+   END ;
+   RETURN max
+END GetTypeMax ;
+
+
+(*
+   GetTypeMaxLower - obtain the maximum value for type.
+*)
+
+PROCEDURE GetTypeMaxLower (tok: CARDINAL; func, type: CARDINAL) : CARDINAL ;
 VAR
    min, max: CARDINAL ;
 BEGIN
@@ -9841,14 +9876,11 @@ BEGIN
       RETURN max
    ELSIF GetSType (type) = NulSym
    THEN
-      MetaErrorT1 (tok,
-                   'unable to obtain the {%AkMAX} value for type {%1ad}', 
type) ;
-      (* non recoverable error.  *)
-      InternalError ('MetaErrorT1 {%AkMAX} should call abort')
+      RETURN NulSym
    ELSE
       RETURN GetTypeMax (tok, func, GetSType (type))
    END
-END GetTypeMax ;
+END GetTypeMaxLower ;
 
 
 (*
diff --git a/gcc/m2/gm2-compiler/M2Range.mod b/gcc/m2/gm2-compiler/M2Range.mod
index 347012bf5f13..2a5bfabecd1c 100644
--- a/gcc/m2/gm2-compiler/M2Range.mod
+++ b/gcc/m2/gm2-compiler/M2Range.mod
@@ -1257,6 +1257,7 @@ END FoldAssignment ;
    CheckCancelled - check to see if the range has been cancelled and if so 
remove quad.
 *)
 
+(*
 PROCEDURE CheckCancelled (range: CARDINAL; quad: CARDINAL) ;
 BEGIN
    IF IsCancelled (range)
@@ -1264,6 +1265,7 @@ BEGIN
       SubQuad (quad)
    END
 END CheckCancelled ;
+*)
 
 
 (*
diff --git a/gcc/m2/gm2-compiler/M2System.mod b/gcc/m2/gm2-compiler/M2System.mod
index efd5d1183a3f..68ed9dc52ed5 100644
--- a/gcc/m2/gm2-compiler/M2System.mod
+++ b/gcc/m2/gm2-compiler/M2System.mod
@@ -61,7 +61,7 @@ FROM NameKey IMPORT Name, MakeKey, NulName ;
 FROM M2Batch IMPORT MakeDefinitionSource ;
 FROM M2Base IMPORT Cardinal, ZType ;
 FROM M2Size IMPORT Size, MakeSize ;
-FROM M2ALU IMPORT PushCard, PushIntegerTree, DivTrunc ;
+FROM M2ALU IMPORT PushCard, PushIntegerTree, PushRealTree, DivTrunc ;
 FROM M2Error IMPORT InternalError ;
 FROM Lists IMPORT List, InitList, IsItemInList, PutItemIntoList, 
GetItemFromList, NoOfItemsInList ;
 FROM SymbolKey IMPORT SymbolTree, InitTree, GetSymKey, PutSymKey ;
@@ -114,21 +114,32 @@ END Init ;
 
 
 (*
-   CreateMinMaxFor - creates the min and max values for, type, given gccType.
+   CreateMinMaxFor - creates the min and max values for type given gccType.
 *)
 
-PROCEDURE CreateMinMaxFor (type: CARDINAL; min, max: ARRAY OF CHAR; gccType: 
tree) ;
+PROCEDURE CreateMinMaxFor (type: CARDINAL; min, max: ARRAY OF CHAR;
+                           gccType: tree; realtype: BOOLEAN) ;
 VAR
    maxval, minval: CARDINAL ;
 BEGIN
    maxval := MakeConstVar (BuiltinTokenNo, MakeKey(max)) ;
-   PushIntegerTree (GetMaxFrom (BuiltinsLocation (), gccType)) ;
+   IF realtype
+   THEN
+      PushRealTree (GetMaxFrom (BuiltinsLocation (), gccType))
+   ELSE
+      PushIntegerTree (GetMaxFrom (BuiltinsLocation (), gccType))
+   END ;
    PopValue (maxval) ;
    PutVar (maxval, type) ;
    PutSymKey (MaxValues, GetSymName (type), maxval) ;
 
    minval := MakeConstVar (BuiltinTokenNo, MakeKey(min)) ;
-   PushIntegerTree (GetMinFrom (BuiltinsLocation (), gccType)) ;
+   IF realtype
+   THEN
+      PushRealTree (GetMinFrom (BuiltinsLocation (), gccType))
+   ELSE
+      PushIntegerTree (GetMinFrom (BuiltinsLocation (), gccType))
+   END ;
    PopValue (minval) ;
    PutVar (minval, type) ;
    PutSymKey (MinValues, GetSymName (type), minval)
@@ -136,31 +147,32 @@ END CreateMinMaxFor ;
 
 
 (*
-   MapType -
+   MapType - create a mapping of the M2 frontend type to gcctype.
 *)
 
 PROCEDURE MapType (type: CARDINAL;
                    name, min, max: ARRAY OF CHAR;
-                   needsExporting: BOOLEAN; t: tree) ;
+                   needsExporting: BOOLEAN;
+                   gcctype: tree; realtype: BOOLEAN) ;
 VAR
    n: Name ;
 BEGIN
-   PushIntegerTree(BuildSize(BuiltinsLocation(), t, FALSE)) ;
-   PopSize(type) ;
-   IF IsItemInList(SystemTypes, type)
+   PushIntegerTree (BuildSize (BuiltinsLocation (), gcctype, FALSE)) ;
+   PopSize (type) ;
+   IF IsItemInList (SystemTypes, type)
    THEN
       InternalError ('not expecting system type to already be declared')
    END ;
-   PutItemIntoList(SystemTypes, type) ;
+   PutItemIntoList (SystemTypes, type) ;
 
-   (* create min, max constants if type is ordinal *)
-   IF (NOT StrEqual(min, '')) AND (NOT StrEqual(max, ''))
+   (* Create min, max constants if type is ordinal or a floating point type.  
*)
+   IF (NOT StrEqual (min, '')) AND (NOT StrEqual (max, ''))
    THEN
-      CreateMinMaxFor(type, min, max, t)
+      CreateMinMaxFor (type, min, max, gcctype, realtype)
    END ;
    IF needsExporting AND DumpSystemExports
    THEN
-      n := GetSymName(type) ;
+      n := GetSymName (type) ;
       printf1('SYSTEM module creates type: %a\n', n)
    END
 END MapType ;
@@ -171,7 +183,8 @@ END MapType ;
 *)
 
 PROCEDURE CreateType (name, min, max: ARRAY OF CHAR;
-                      needsExporting: BOOLEAN; gccType: tree) : CARDINAL ;
+                      needsExporting: BOOLEAN; gccType: tree;
+                      realtype: BOOLEAN) : CARDINAL ;
 VAR
    type: CARDINAL ;
 BEGIN
@@ -183,7 +196,7 @@ BEGIN
       (* Create base type.  *)
       type := MakeType (BuiltinTokenNo, MakeKey (name)) ;
       PutType (type, NulSym) ;  (* a Base Type *)
-      MapType (type, name, min, max, needsExporting, gccType) ;
+      MapType (type, name, min, max, needsExporting, gccType, realtype) ;
       RETURN type
    END
 END CreateType ;
@@ -195,9 +208,11 @@ END CreateType ;
 *)
 
 PROCEDURE AttemptToCreateType (name, min, max: ARRAY OF CHAR;
-                               needsExporting: BOOLEAN; gccType: tree) ;
+                               needsExporting: BOOLEAN; gccType: tree;
+                               realtype: BOOLEAN) ;
 BEGIN
-   Assert (IsLegal (CreateType (name, min, max, needsExporting, gccType)))
+   Assert (IsLegal (CreateType (name, min, max, needsExporting,
+                                gccType, realtype)))
 END AttemptToCreateType ;
 
 
@@ -226,7 +241,7 @@ BEGIN
       subrange := MakeSubrange (BuiltinTokenNo, NulName) ;
       PutSubrange (subrange, low, high, Cardinal) ;
       PutSet (type, subrange, FALSE) ;
-      MapType (type, name, '', '', needsExporting, gccType) ;
+      MapType (type, name, '', '', needsExporting, gccType, FALSE) ;
       RETURN type
    END
 END CreateSetType ;
@@ -251,33 +266,33 @@ END AttemptToCreateSetType ;
 
 PROCEDURE MakeFixedSizedTypes ;
 BEGIN
-   AttemptToCreateType ('INTEGER8', 'MinInteger8', 'MaxInteger8', TRUE, 
GetM2Integer8 ()) ;
-   AttemptToCreateType ('INTEGER16', 'MinInteger16', 'MaxInteger16', TRUE, 
GetM2Integer16 ()) ;
-   AttemptToCreateType ('INTEGER32', 'MinInteger32', 'MaxInteger32', TRUE, 
GetM2Integer32 ()) ;
-   AttemptToCreateType ('INTEGER64', 'MinInteger64', 'MaxInteger64', TRUE, 
GetM2Integer64 ()) ;
+   AttemptToCreateType ('INTEGER8', 'MinInteger8', 'MaxInteger8', TRUE, 
GetM2Integer8 (), FALSE) ;
+   AttemptToCreateType ('INTEGER16', 'MinInteger16', 'MaxInteger16', TRUE, 
GetM2Integer16 (), FALSE) ;
+   AttemptToCreateType ('INTEGER32', 'MinInteger32', 'MaxInteger32', TRUE, 
GetM2Integer32 (), FALSE) ;
+   AttemptToCreateType ('INTEGER64', 'MinInteger64', 'MaxInteger64', TRUE, 
GetM2Integer64 (), FALSE) ;
 
-   AttemptToCreateType ('CARDINAL8', 'MinCardinal8', 'MaxCardinal8', TRUE, 
GetM2Cardinal8 ()) ;
-   AttemptToCreateType ('CARDINAL16', 'MinCardinal16', 'MaxCardinal16', TRUE, 
GetM2Cardinal16 ()) ;
-   AttemptToCreateType ('CARDINAL32', 'MinCardinal32', 'MaxCardinal32', TRUE, 
GetM2Cardinal32 ()) ;
-   AttemptToCreateType ('CARDINAL64', 'MinCardinal64', 'MaxCardinal64', TRUE, 
GetM2Cardinal64 ()) ;
+   AttemptToCreateType ('CARDINAL8', 'MinCardinal8', 'MaxCardinal8', TRUE, 
GetM2Cardinal8 (), FALSE) ;
+   AttemptToCreateType ('CARDINAL16', 'MinCardinal16', 'MaxCardinal16', TRUE, 
GetM2Cardinal16 (), FALSE) ;
+   AttemptToCreateType ('CARDINAL32', 'MinCardinal32', 'MaxCardinal32', TRUE, 
GetM2Cardinal32 (), FALSE) ;
+   AttemptToCreateType ('CARDINAL64', 'MinCardinal64', 'MaxCardinal64', TRUE, 
GetM2Cardinal64 (), FALSE) ;
 
-   AttemptToCreateType ('WORD16', '', '', TRUE, GetM2Word16 ()) ;
-   AttemptToCreateType ('WORD32', '', '', TRUE, GetM2Word32 ()) ;
-   AttemptToCreateType ('WORD64', '', '', TRUE, GetM2Word64 ()) ;
+   AttemptToCreateType ('WORD16', '', '', TRUE, GetM2Word16 (), FALSE) ;
+   AttemptToCreateType ('WORD32', '', '', TRUE, GetM2Word32 (), FALSE) ;
+   AttemptToCreateType ('WORD64', '', '', TRUE, GetM2Word64 (), FALSE) ;
 
    AttemptToCreateSetType ('BITSET8' , '7' , TRUE, GetM2Bitset8 ()) ;
    AttemptToCreateSetType ('BITSET16', '15', TRUE, GetM2Bitset16 ()) ;
    AttemptToCreateSetType ('BITSET32', '31', TRUE, GetM2Bitset32 ()) ;
 
-   AttemptToCreateType ('REAL32', '', '', TRUE, GetM2Real32 ()) ;
-   AttemptToCreateType ('REAL64', '', '', TRUE, GetM2Real64 ()) ;
-   AttemptToCreateType ('REAL96', '', '', TRUE, GetM2Real96 ()) ;
-   AttemptToCreateType ('REAL128', '', '', TRUE, GetM2Real128 ()) ;
+   AttemptToCreateType ('REAL32', 'MinReal32', 'MaxReal32', TRUE, GetM2Real32 
(), TRUE) ;
+   AttemptToCreateType ('REAL64', 'MinReal64', 'MaxReal64', TRUE, GetM2Real64 
(), TRUE) ;
+   AttemptToCreateType ('REAL96', 'MinReal96', 'MaxReal96', TRUE, GetM2Real96 
(), TRUE) ;
+   AttemptToCreateType ('REAL128', 'MinReal128', 'MaxReal128', TRUE, 
GetM2Real128 (), TRUE) ;
 
-   AttemptToCreateType ('COMPLEX32', '', '', TRUE, GetM2Complex32 ()) ;
-   AttemptToCreateType ('COMPLEX64', '', '', TRUE, GetM2Complex64 ()) ;
-   AttemptToCreateType ('COMPLEX96', '', '', TRUE, GetM2Complex96 ()) ;
-   AttemptToCreateType ('COMPLEX128', '', '', TRUE, GetM2Complex128 ())
+   AttemptToCreateType ('COMPLEX32', '', '', TRUE, GetM2Complex32 (), TRUE) ;
+   AttemptToCreateType ('COMPLEX64', '', '', TRUE, GetM2Complex64 (), TRUE) ;
+   AttemptToCreateType ('COMPLEX96', '', '', TRUE, GetM2Complex96 (), TRUE) ;
+   AttemptToCreateType ('COMPLEX128', '', '', TRUE, GetM2Complex128 (), TRUE)
 END MakeFixedSizedTypes ;
 
 
@@ -287,16 +302,16 @@ END MakeFixedSizedTypes ;
 
 PROCEDURE InitPIMTypes ;
 BEGIN
-   Loc := CreateType ('LOC', '', '', TRUE, GetISOLocType()) ;
+   Loc := CreateType ('LOC', '', '', TRUE, GetISOLocType(), FALSE) ;
    InitSystemTypes(BuiltinsLocation(), Loc) ;
-   Word := CreateType ('WORD', '', '', TRUE, GetWordType()) ;
-   Byte := CreateType ('BYTE', '', '', TRUE, GetByteType()) ;
+   Word := CreateType ('WORD', '', '', TRUE, GetWordType(), FALSE) ;
+   Byte := CreateType ('BYTE', '', '', TRUE, GetByteType(), FALSE) ;
 
    (* ADDRESS = POINTER TO BYTE *)
 
    Address := MakePointer (BuiltinTokenNo, MakeKey('ADDRESS')) ;
    PutPointer (Address, Byte) ;                (* Base Type       *)
-   MapType (Address, 'ADDRESS', '', '', TRUE, GetPointerType())
+   MapType (Address, 'ADDRESS', '', '', TRUE, GetPointerType(), FALSE)
 END InitPIMTypes ;
 
 
@@ -306,17 +321,15 @@ END InitPIMTypes ;
 
 PROCEDURE InitISOTypes ;
 BEGIN
-   Loc := CreateType ('LOC', 'MinLoc', 'MaxLoc', TRUE, GetISOLocType ()) ;
+   Loc := CreateType ('LOC', 'MinLoc', 'MaxLoc', TRUE, GetISOLocType (), 
FALSE) ;
    InitSystemTypes (BuiltinsLocation (), Loc) ;
 
    Address := MakePointer (BuiltinTokenNo, MakeKey ('ADDRESS')) ;
    PutPointer (Address, Loc) ;                (* Base Type       *)
-   MapType (Address, 'ADDRESS', '', '', TRUE, GetPointerType()) ;
-
-   Byte := CreateType ('BYTE', '', '', TRUE, GetISOByteType()) ;
-   Word := CreateType ('WORD', '', '', TRUE, GetISOWordType()) ;
+   MapType (Address, 'ADDRESS', '', '', TRUE, GetPointerType(), FALSE) ;
 
-   (* CreateMinMaxFor(Loc, 'MinLoc', 'MaxLoc', GetISOLocType()) *)
+   Byte := CreateType ('BYTE', '', '', TRUE, GetISOByteType(), FALSE) ;
+   Word := CreateType ('WORD', '', '', TRUE, GetISOWordType(), FALSE) ;
 END InitISOTypes ;
 
 
@@ -327,9 +340,9 @@ END InitISOTypes ;
 
 PROCEDURE MakeExtraSystemTypes ;
 BEGIN
-   CSizeT  := CreateType ('CSIZE_T' , '', '', TRUE, GetCSizeTType ()) ;
-   CSSizeT := CreateType ('CSSIZE_T', '', '', TRUE, GetCSSizeTType ()) ;
-   COffT := CreateType ('COFF_T', '', '', TRUE, GetCOffTType ()) ;
+   CSizeT  := CreateType ('CSIZE_T' , '', '', TRUE, GetCSizeTType (), FALSE) ;
+   CSSizeT := CreateType ('CSSIZE_T', '', '', TRUE, GetCSSizeTType (), FALSE) ;
+   COffT := CreateType ('COFF_T', '', '', TRUE, GetCOffTType (), FALSE)
 END MakeExtraSystemTypes ;
 
 
@@ -425,9 +438,9 @@ BEGIN
                           MakeKey('THROW')) ;       (* Procedure       *)
    PutProcedureNoReturn (Throw, DefProcedure, TRUE) ;
 
-   CreateMinMaxFor(Word, 'MinWord', 'MaxWord', GetWordType()) ;
-   CreateMinMaxFor(Address, 'MinAddress', 'MaxAddress', GetPointerType()) ;
-   CreateMinMaxFor(Byte, 'MinByte', 'MaxByte', GetByteType()) ;
+   CreateMinMaxFor(Word, 'MinWord', 'MaxWord', GetWordType(), FALSE) ;
+   CreateMinMaxFor(Address, 'MinAddress', 'MaxAddress', GetPointerType(), 
FALSE) ;
+   CreateMinMaxFor(Byte, 'MinByte', 'MaxByte', GetByteType(), FALSE) ;
 
    MakeFixedSizedTypes ;
    MakeExtraSystemTypes ;
diff --git a/gcc/m2/gm2-gcc/m2pp.cc b/gcc/m2/gm2-gcc/m2pp.cc
index 6ec8aaa88ea0..7d4adb8ff71f 100644
--- a/gcc/m2/gm2-gcc/m2pp.cc
+++ b/gcc/m2/gm2-gcc/m2pp.cc
@@ -2367,7 +2367,6 @@ m2pp_asm_expr (pretty *state, tree node)
 static void
 m2pp_nop_expr (pretty *state, tree t)
 {
-  enum tree_code code = TREE_CODE (t);
   m2pp_begin (state);
   m2pp_print (state, "(* NOP for debug location *)");
   m2pp_needspace (state);
diff --git a/gcc/m2/gm2-gcc/m2type.cc b/gcc/m2/gm2-gcc/m2type.cc
index e82857d252df..e486f12004fe 100644
--- a/gcc/m2/gm2-gcc/m2type.cc
+++ b/gcc/m2/gm2-gcc/m2type.cc
@@ -1891,6 +1891,22 @@ m2type_GetDefaultType (location_t location, char *name, 
tree type)
     return id;
 }
 
+/* IsGccRealType return true if type is a GCC realtype.  */
+  
+static
+bool
+IsGccRealType (tree type)
+{
+  return (type == m2_real_type_node || type == m2type_GetRealType () ||
+         type == m2_long_real_type_node || type == m2type_GetLongRealType () ||
+         type == m2_short_real_type_node || type == m2type_GetShortRealType () 
||
+         type == m2type_GetM2Real32 () ||
+         type == m2type_GetM2Real64 () ||
+         type == m2type_GetM2Real96 () ||
+         type == m2type_GetM2Real128 ());
+}
+
+static
 tree
 do_min_real (tree type)
 {
@@ -1911,11 +1927,7 @@ m2type_GetMinFrom (location_t location, tree type)
 {
   m2assert_AssertLocation (location);
 
-  if (type == m2_real_type_node || type == m2type_GetRealType ())
-    return do_min_real (type);
-  if (type == m2_long_real_type_node || type == m2type_GetLongRealType ())
-    return do_min_real (type);
-  if (type == m2_short_real_type_node || type == m2type_GetShortRealType ())
+  if (IsGccRealType (type))
     return do_min_real (type);
   if (type == ptr_type_node)
     return m2expr_GetPointerZero (location);
@@ -1923,6 +1935,7 @@ m2type_GetMinFrom (location_t location, tree type)
   return TYPE_MIN_VALUE (m2tree_skip_type_decl (type));
 }
 
+static      
 tree
 do_max_real (tree type)
 {
@@ -1943,11 +1956,7 @@ m2type_GetMaxFrom (location_t location, tree type)
 {
   m2assert_AssertLocation (location);
 
-  if (type == m2_real_type_node || type == m2type_GetRealType ())
-    return do_max_real (type);
-  if (type == m2_long_real_type_node || type == m2type_GetLongRealType ())
-    return do_max_real (type);
-  if (type == m2_short_real_type_node || type == m2type_GetShortRealType ())
+  if (IsGccRealType (type))
     return do_max_real (type);
   if (type == ptr_type_node)
     return fold (m2expr_BuildSub (location, m2expr_GetPointerZero (location),
diff --git a/gcc/testsuite/gm2/pim/pass/minmaxreal.mod 
b/gcc/testsuite/gm2/pim/pass/minmaxreal.mod
new file mode 100644
index 000000000000..2871f46f8485
--- /dev/null
+++ b/gcc/testsuite/gm2/pim/pass/minmaxreal.mod
@@ -0,0 +1,7 @@
+MODULE minmaxreal ;  
+
+CONST
+   min = MIN (REAL) ;
+   max = MAX (REAL) ;
+
+END minmaxreal.
diff --git a/gcc/testsuite/gm2/pim/pass/minmaxreal2.mod 
b/gcc/testsuite/gm2/pim/pass/minmaxreal2.mod
new file mode 100644
index 000000000000..120c1b711bf1
--- /dev/null
+++ b/gcc/testsuite/gm2/pim/pass/minmaxreal2.mod
@@ -0,0 +1,8 @@
+MODULE minmaxreal2 ;  
+
+VAR
+   min, max: REAL ;
+BEGIN
+   min := MIN (REAL) ;
+   max := MAX (REAL)
+END minmaxreal2.
diff --git a/gcc/testsuite/gm2/pim/pass/minmaxreal3.mod 
b/gcc/testsuite/gm2/pim/pass/minmaxreal3.mod
new file mode 100644
index 000000000000..30b5d1b3b1dc
--- /dev/null
+++ b/gcc/testsuite/gm2/pim/pass/minmaxreal3.mod
@@ -0,0 +1,10 @@
+MODULE minmaxreal3 ;  
+
+FROM SYSTEM  IMPORT REAL64 ;
+
+VAR
+   min, max: REAL64 ;
+BEGIN
+   min := MIN (REAL64) ;
+   max := MAX (REAL64)
+END minmaxreal3.

Reply via email to