1--  Semantic utilities.
2--  Copyright (C) 2018 Tristan Gingold
3--
4--  This program is free software: you can redistribute it and/or modify
5--  it under the terms of the GNU General Public License as published by
6--  the Free Software Foundation, either version 2 of the License, or
7--  (at your option) any later version.
8--
9--  This program is distributed in the hope that it will be useful,
10--  but WITHOUT ANY WARRANTY; without even the implied warranty of
11--  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
12--  GNU General Public License for more details.
13--
14--  You should have received a copy of the GNU General Public License
15--  along with this program.  If not, see <gnu.org/licenses>.
16with Ada.Unchecked_Conversion;
17with Types; use Types;
18with Flags; use Flags;
19with Vhdl.Errors; use Vhdl.Errors;
20with Vhdl.Nodes_Utils; use Vhdl.Nodes_Utils;
21with Vhdl.Utils; use Vhdl.Utils;
22with Vhdl.Ieee.Std_Logic_1164;
23with Std_Names;
24with Vhdl.Std_Package; use Vhdl.Std_Package;
25
26package body Vhdl.Sem_Utils is
27   procedure Compute_Subprogram_Hash (Subprg : Iir)
28   is
29      type Hash_Type is mod 2**32;
30      function To_Hash is new Ada.Unchecked_Conversion
31        (Source => Iir, Target => Hash_Type);
32      function To_Int32 is new Ada.Unchecked_Conversion
33        (Source => Hash_Type, Target => Iir_Int32);
34
35      Kind : Iir_Kind;
36      Hash : Hash_Type;
37      Sig : Hash_Type;
38      Inter : Iir;
39      Itype : Iir;
40   begin
41      Kind := Get_Kind (Subprg);
42      if Kind = Iir_Kind_Function_Declaration
43        or else Kind = Iir_Kind_Enumeration_Literal
44      then
45         Itype := Get_Base_Type (Get_Return_Type (Subprg));
46         Hash := To_Hash (Itype);
47         Sig := 8;
48      else
49         Sig := 1;
50         Hash := 0;
51      end if;
52
53      if Kind /= Iir_Kind_Enumeration_Literal then
54         Inter := Get_Interface_Declaration_Chain (Subprg);
55         while Inter /= Null_Iir loop
56            if Get_Kind (Inter) in Iir_Kinds_Interface_Object_Declaration then
57               Itype := Get_Base_Type (Get_Type (Inter));
58               Sig := Sig + 1;
59               Hash := Hash * 7 + To_Hash (Itype);
60               Hash := Hash + Hash / 2**28;
61            else
62               --  Non-object parameter are not allowed.
63               pragma Assert (Flags.Flag_Force_Analysis);
64               null;
65            end if;
66            Inter := Get_Chain (Inter);
67         end loop;
68      end if;
69      Set_Subprogram_Hash (Subprg, To_Int32 (Hash + Sig));
70   end Compute_Subprogram_Hash;
71
72   --  LRM93 7.2.2
73   --  A discrete array is a one-dimensional array whose elements are of a
74   --  discrete type.
75   function Is_Discrete_Array (Def : Iir) return Boolean
76   is
77   begin
78      case Get_Kind (Def) is
79         when Iir_Kind_Array_Type_Definition
80           | Iir_Kind_Array_Subtype_Definition =>
81            null;
82         when others =>
83            raise Internal_Error;
84            -- return False;
85      end case;
86      if not Is_One_Dimensional_Array_Type (Def) then
87         return False;
88      end if;
89      if Get_Kind (Get_Element_Subtype (Def))
90        not in Iir_Kinds_Discrete_Type_Definition
91      then
92         return False;
93      end if;
94      return True;
95   end Is_Discrete_Array;
96
97   function Create_Anonymous_Interface (Atype : Iir)
98     return Iir_Interface_Constant_Declaration
99   is
100      Inter : Iir_Interface_Constant_Declaration;
101   begin
102      Inter := Create_Iir (Iir_Kind_Interface_Constant_Declaration);
103      Location_Copy (Inter, Atype);
104      Set_Identifier (Inter, Null_Identifier);
105      Set_Mode (Inter, Iir_In_Mode);
106      Set_Type (Inter, Atype);
107      return Inter;
108   end Create_Anonymous_Interface;
109
110   --  Create an implicit/predefined function for DECL.
111   function Create_Implicit_Function (Name : Name_Id;
112                                      Decl : Iir;
113                                      Def : Iir_Predefined_Functions;
114                                      Interface_Chain : Iir;
115                                      Return_Type : Iir)
116                                     return Iir
117   is
118      Operation : Iir_Function_Declaration;
119   begin
120      Operation := Create_Iir (Iir_Kind_Function_Declaration);
121      Location_Copy (Operation, Decl);
122      Set_Parent (Operation, Get_Parent (Decl));
123      Set_Interface_Declaration_Chain (Operation, Interface_Chain);
124      Set_Return_Type (Operation, Return_Type);
125      Set_Implicit_Definition (Operation, Def);
126      Set_Identifier (Operation, Name);
127      Set_Visible_Flag (Operation, True);
128      Compute_Subprogram_Hash (Operation);
129      return Operation;
130   end Create_Implicit_Function;
131
132   procedure Create_Implicit_File_Primitives
133     (Decl : Iir_Type_Declaration; Type_Definition : Iir_File_Type_Definition)
134   is
135      Type_Mark : constant Iir := Get_File_Type_Mark (Type_Definition);
136      Type_Mark_Type : constant Iir := Get_Type (Type_Mark);
137      Proc: Iir_Procedure_Declaration;
138      Func: Iir_Function_Declaration;
139      Inter: Iir;
140      Loc : Location_Type;
141      File_Interface_Kind : Iir_Kind;
142      First_Interface, Last_Interface : Iir;
143      Last : Iir;
144   begin
145      Last := Decl;
146      Loc := Get_Location (Decl);
147
148      if Flags.Vhdl_Std >= Vhdl_93 then
149         for I in 1 .. 2 loop
150            --  Create the implicit file_open (form 1) declaration.
151            --  Create the implicit file_open (form 2) declaration.
152            Proc := Create_Iir (Iir_Kind_Procedure_Declaration);
153            Set_Location (Proc, Loc);
154            Set_Parent (Proc, Get_Parent (Decl));
155            Set_Identifier (Proc, Std_Names.Name_File_Open);
156            Set_Visible_Flag (Proc, True);
157            Set_Wait_State (Proc, False);
158            Chain_Init (First_Interface, Last_Interface);
159            case I is
160               when 1 =>
161                  Set_Implicit_Definition (Proc, Iir_Predefined_File_Open);
162               when 2 =>
163                  Set_Implicit_Definition (Proc,
164                                           Iir_Predefined_File_Open_Status);
165                  --  status : out file_open_status.
166                  Inter :=
167                    Create_Iir (Iir_Kind_Interface_Variable_Declaration);
168                  Set_Location (Inter, Loc);
169                  Set_Identifier (Inter, Std_Names.Name_Status);
170                  Set_Type (Inter,
171                            Std_Package.File_Open_Status_Type_Definition);
172                  Set_Mode (Inter, Iir_Out_Mode);
173                  Set_Visible_Flag (Inter, True);
174                  Chain_Append (First_Interface, Last_Interface, Inter);
175            end case;
176            --  File F : FT
177            Inter := Create_Iir (Iir_Kind_Interface_File_Declaration);
178            Set_Location (Inter, Loc);
179            Set_Identifier (Inter, Std_Names.Name_F);
180            Set_Type (Inter, Type_Definition);
181            Set_Mode (Inter, Iir_Inout_Mode);
182            Set_Visible_Flag (Inter, True);
183            Chain_Append (First_Interface, Last_Interface, Inter);
184            --  External_Name : in STRING
185            Inter := Create_Iir (Iir_Kind_Interface_Constant_Declaration);
186            Set_Location (Inter, Loc);
187            Set_Identifier (Inter, Std_Names.Name_External_Name);
188            Set_Type (Inter, Std_Package.String_Type_Definition);
189            Set_Mode (Inter, Iir_In_Mode);
190            Set_Visible_Flag (Inter, True);
191            Chain_Append (First_Interface, Last_Interface, Inter);
192            --  Open_Kind : in File_Open_Kind := Read_Mode.
193            Inter := Create_Iir (Iir_Kind_Interface_Constant_Declaration);
194            Set_Location (Inter, Loc);
195            Set_Identifier (Inter, Std_Names.Name_Open_Kind);
196            Set_Type (Inter, Std_Package.File_Open_Kind_Type_Definition);
197            Set_Mode (Inter, Iir_In_Mode);
198            Set_Default_Value
199              (Inter,
200               Build_Simple_Name (Std_Package.File_Open_Kind_Read_Mode, Loc));
201            Set_Visible_Flag (Inter, True);
202            Chain_Append (First_Interface, Last_Interface, Inter);
203            Set_Interface_Declaration_Chain (Proc, First_Interface);
204            Compute_Subprogram_Hash (Proc);
205            -- Add it to the list.
206            Insert_Incr (Last, Proc);
207         end loop;
208
209         --  Create the implicit file_close declaration.
210         Proc := Create_Iir (Iir_Kind_Procedure_Declaration);
211         Set_Identifier (Proc, Std_Names.Name_File_Close);
212         Set_Location (Proc, Loc);
213         Set_Parent (Proc, Get_Parent (Decl));
214         Set_Implicit_Definition (Proc, Iir_Predefined_File_Close);
215         Set_Visible_Flag (Proc, True);
216         Set_Wait_State (Proc, False);
217         Inter := Create_Iir (Iir_Kind_Interface_File_Declaration);
218         Set_Identifier (Inter, Std_Names.Name_F);
219         Set_Location (Inter, Loc);
220         Set_Type (Inter, Type_Definition);
221         Set_Mode (Inter, Iir_Inout_Mode);
222         Set_Visible_Flag (Inter, True);
223         Set_Interface_Declaration_Chain (Proc, Inter);
224         Compute_Subprogram_Hash (Proc);
225         -- Add it to the list.
226         Insert_Incr (Last, Proc);
227      end if;
228
229      if Flags.Vhdl_Std = Vhdl_87 then
230         File_Interface_Kind := Iir_Kind_Interface_Variable_Declaration;
231      else
232         File_Interface_Kind := Iir_Kind_Interface_File_Declaration;
233      end if;
234
235      -- Create the implicit procedure read declaration.
236      Proc := Create_Iir (Iir_Kind_Procedure_Declaration);
237      Set_Identifier (Proc, Std_Names.Name_Read);
238      Set_Location (Proc, Loc);
239      Set_Parent (Proc, Get_Parent (Decl));
240      Set_Visible_Flag (Proc, True);
241      Set_Wait_State (Proc, False);
242      Chain_Init (First_Interface, Last_Interface);
243      Inter := Create_Iir (File_Interface_Kind);
244      Set_Identifier (Inter, Std_Names.Name_F);
245      Set_Location (Inter, Loc);
246      Set_Type (Inter, Type_Definition);
247      Set_Mode (Inter, Iir_In_Mode);
248      Set_Visible_Flag (Inter, True);
249      Chain_Append (First_Interface, Last_Interface, Inter);
250      Inter := Create_Iir (Iir_Kind_Interface_Variable_Declaration);
251      Set_Identifier (Inter, Std_Names.Name_Value);
252      Set_Location (Inter, Loc);
253      Set_Subtype_Indication (Inter, Build_Simple_Name (Decl, Loc));
254      Set_Type (Inter, Type_Mark_Type);
255      Set_Mode (Inter, Iir_Out_Mode);
256      Set_Visible_Flag (Inter, True);
257      Chain_Append (First_Interface, Last_Interface, Inter);
258      if Get_Kind (Type_Mark_Type) in Iir_Kinds_Array_Type_Definition
259        and then Get_Constraint_State (Type_Mark_Type) /= Fully_Constrained
260      then
261         Inter := Create_Iir (Iir_Kind_Interface_Variable_Declaration);
262         Set_Identifier (Inter, Std_Names.Name_Length);
263         Set_Location (Inter, Loc);
264         Set_Type (Inter, Std_Package.Natural_Subtype_Definition);
265         Set_Mode (Inter, Iir_Out_Mode);
266         Set_Visible_Flag (Inter, True);
267         Chain_Append (First_Interface, Last_Interface, Inter);
268         Set_Implicit_Definition (Proc, Iir_Predefined_Read_Length);
269      else
270         Set_Implicit_Definition (Proc, Iir_Predefined_Read);
271      end if;
272      Set_Interface_Declaration_Chain (Proc, First_Interface);
273      Compute_Subprogram_Hash (Proc);
274      -- Add it to the list.
275      Insert_Incr (Last, Proc);
276
277      -- Create the implicit procedure write declaration.
278      Proc := Create_Iir (Iir_Kind_Procedure_Declaration);
279      Set_Identifier (Proc, Std_Names.Name_Write);
280      Set_Location (Proc, Loc);
281      Set_Parent (Proc, Get_Parent (Decl));
282      Set_Visible_Flag (Proc, True);
283      Set_Wait_State (Proc, False);
284      Chain_Init (First_Interface, Last_Interface);
285      Inter := Create_Iir (File_Interface_Kind);
286      Set_Identifier (Inter, Std_Names.Name_F);
287      Set_Location (Inter, Loc);
288      Set_Type (Inter, Type_Definition);
289      Set_Mode (Inter, Iir_Out_Mode);
290      Set_Name_Staticness (Inter, Locally);
291      Set_Expr_Staticness (Inter, None);
292      Set_Visible_Flag (Inter, True);
293      Chain_Append (First_Interface, Last_Interface, Inter);
294      Inter := Create_Iir (Iir_Kind_Interface_Constant_Declaration);
295      Set_Identifier (Inter, Std_Names.Name_Value);
296      Set_Location (Inter, Loc);
297      Set_Subtype_Indication (Inter, Build_Simple_Name (Decl, Loc));
298      Set_Type (Inter, Type_Mark_Type);
299      Set_Mode (Inter, Iir_In_Mode);
300      Set_Visible_Flag (Inter, True);
301      Chain_Append (First_Interface, Last_Interface, Inter);
302      Set_Implicit_Definition (Proc, Iir_Predefined_Write);
303      Set_Interface_Declaration_Chain (Proc, First_Interface);
304      Compute_Subprogram_Hash (Proc);
305      -- Add it to the list.
306      Insert_Incr (Last, Proc);
307
308      --  Create the implicit procedure flush declaration
309      if Flags.Vhdl_Std >= Vhdl_08 then
310         Proc := Create_Iir (Iir_Kind_Procedure_Declaration);
311         Set_Identifier (Proc, Std_Names.Name_Flush);
312         Set_Location (Proc, Loc);
313         Set_Parent (Proc, Get_Parent (Decl));
314         Set_Visible_Flag (Proc, True);
315         Set_Wait_State (Proc, False);
316         Inter := Create_Iir (File_Interface_Kind);
317         Set_Identifier (Inter, Std_Names.Name_F);
318         Set_Location (Inter, Loc);
319         Set_Type (Inter, Type_Definition);
320         Set_Name_Staticness (Inter, Locally);
321         Set_Expr_Staticness (Inter, None);
322         Set_Visible_Flag (Inter, True);
323         Set_Implicit_Definition (Proc, Iir_Predefined_Flush);
324         Set_Interface_Declaration_Chain (Proc, Inter);
325         Compute_Subprogram_Hash (Proc);
326         -- Add it to the list.
327         Insert_Incr (Last, Proc);
328      end if;
329
330      -- Create the implicit function endfile declaration.
331      Func := Create_Iir (Iir_Kind_Function_Declaration);
332      Set_Identifier (Func, Std_Names.Name_Endfile);
333      Set_Location (Func, Loc);
334      Set_Parent (Func, Get_Parent (Decl));
335      Set_Visible_Flag (Func, True);
336      Inter := Create_Iir (File_Interface_Kind);
337      Set_Identifier (Inter, Std_Names.Name_F);
338      Set_Location (Inter, Loc);
339      Set_Type (Inter, Type_Definition);
340      Set_Mode (Inter, Iir_In_Mode);
341      Set_Visible_Flag (Inter, True);
342      Set_Return_Type (Func, Std_Package.Boolean_Type_Definition);
343      Set_Implicit_Definition (Func, Iir_Predefined_Endfile);
344      Set_Interface_Declaration_Chain (Func, Inter);
345      Compute_Subprogram_Hash (Func);
346      -- Add it to the list.
347      Insert_Incr (Last, Func);
348
349   end Create_Implicit_File_Primitives;
350
351   procedure Create_Implicit_Operations
352     (Decl : Iir; Is_Std_Standard : Boolean := False)
353   is
354      use Std_Names;
355      Binary_Chain : Iir;
356      Unary_Chain : Iir;
357      Type_Definition : Iir;
358      Last : Iir;
359
360      procedure Add_Operation (Name : Name_Id;
361                               Def : Iir_Predefined_Functions;
362                               Interface_Chain : Iir;
363                               Return_Type : Iir)
364      is
365         Operation : Iir_Function_Declaration;
366      begin
367         Operation := Create_Implicit_Function
368           (Name, Decl, Def, Interface_Chain, Return_Type);
369         Insert_Incr (Last, Operation);
370      end Add_Operation;
371
372      procedure Add_Relational (Name : Name_Id; Def : Iir_Predefined_Functions)
373      is
374      begin
375         Add_Operation
376           (Name, Def, Binary_Chain, Std_Package.Boolean_Type_Definition);
377      end Add_Relational;
378
379      procedure Add_Binary (Name : Name_Id; Def : Iir_Predefined_Functions) is
380      begin
381         Add_Operation (Name, Def, Binary_Chain, Type_Definition);
382      end Add_Binary;
383
384      procedure Add_Unary (Name : Name_Id; Def : Iir_Predefined_Functions) is
385      begin
386         Add_Operation (Name, Def, Unary_Chain, Type_Definition);
387      end Add_Unary;
388
389      procedure Add_To_String (Def : Iir_Predefined_Functions) is
390      begin
391         Add_Operation (Name_To_String, Def,
392                        Unary_Chain, String_Type_Definition);
393      end Add_To_String;
394
395      procedure Add_Min_Max (Name : Name_Id; Def : Iir_Predefined_Functions)
396      is
397         Left, Right : Iir;
398      begin
399         Left := Create_Anonymous_Interface (Type_Definition);
400         Set_Identifier (Left, Name_L);
401         Right := Create_Anonymous_Interface (Type_Definition);
402         Set_Identifier (Right, Name_R);
403         Set_Chain (Left, Right);
404         Add_Operation (Name, Def, Left, Type_Definition);
405      end Add_Min_Max;
406
407      procedure Add_Vector_Min_Max
408        (Name : Name_Id; Def : Iir_Predefined_Functions)
409      is
410         Left : Iir;
411      begin
412         Left := Create_Anonymous_Interface (Type_Definition);
413         Set_Identifier (Left, Name_L);
414         Add_Operation
415           (Name, Def, Left, Get_Element_Subtype (Type_Definition));
416      end Add_Vector_Min_Max;
417
418      procedure Add_Shift_Operators
419      is
420         Inter_Chain : Iir_Interface_Constant_Declaration;
421         Inter_Int : Iir;
422      begin
423         Inter_Chain := Create_Anonymous_Interface (Type_Definition);
424
425         Inter_Int := Create_Iir (Iir_Kind_Interface_Constant_Declaration);
426         Location_Copy (Inter_Int, Decl);
427         Set_Identifier (Inter_Int, Null_Identifier);
428         Set_Mode (Inter_Int, Iir_In_Mode);
429         Set_Type (Inter_Int, Std_Package.Integer_Subtype_Definition);
430
431         Set_Chain (Inter_Chain, Inter_Int);
432
433         Add_Operation
434           (Name_Sll, Iir_Predefined_Array_Sll, Inter_Chain, Type_Definition);
435         Add_Operation
436           (Name_Srl, Iir_Predefined_Array_Srl, Inter_Chain, Type_Definition);
437         Add_Operation
438           (Name_Sla, Iir_Predefined_Array_Sla, Inter_Chain, Type_Definition);
439         Add_Operation
440           (Name_Sra, Iir_Predefined_Array_Sra, Inter_Chain, Type_Definition);
441         Add_Operation
442           (Name_Rol, Iir_Predefined_Array_Rol, Inter_Chain, Type_Definition);
443         Add_Operation
444           (Name_Ror, Iir_Predefined_Array_Ror, Inter_Chain, Type_Definition);
445      end Add_Shift_Operators;
446   begin
447      Last := Decl;
448
449      Type_Definition := Get_Base_Type (Get_Type_Definition (Decl));
450      if Get_Kind (Type_Definition) /= Iir_Kind_File_Type_Definition then
451         Unary_Chain := Create_Anonymous_Interface (Type_Definition);
452         Binary_Chain := Create_Anonymous_Interface (Type_Definition);
453         Set_Chain (Binary_Chain, Unary_Chain);
454      end if;
455
456      case Get_Kind (Type_Definition) is
457         when Iir_Kind_Enumeration_Type_Definition =>
458            Add_Relational (Name_Op_Equality, Iir_Predefined_Enum_Equality);
459            Add_Relational
460              (Name_Op_Inequality, Iir_Predefined_Enum_Inequality);
461            Add_Relational (Name_Op_Greater, Iir_Predefined_Enum_Greater);
462            Add_Relational
463              (Name_Op_Greater_Equal, Iir_Predefined_Enum_Greater_Equal);
464            Add_Relational (Name_Op_Less, Iir_Predefined_Enum_Less);
465            Add_Relational
466              (Name_Op_Less_Equal, Iir_Predefined_Enum_Less_Equal);
467
468            if Flags.Vhdl_Std >= Vhdl_08 then
469               --  LRM08 5.2.6 Predefined operations on scalar types
470               --  Given a type declaration that declares a scalar type T, the
471               --  following operations are implicitely declared immediately
472               --  following the type declaration (except for the TO_STRING
473               --  operations in package STANDARD [...])
474               Add_Min_Max (Name_Minimum, Iir_Predefined_Enum_Minimum);
475               Add_Min_Max (Name_Maximum, Iir_Predefined_Enum_Maximum);
476               if not Is_Std_Standard then
477                  Add_To_String (Iir_Predefined_Enum_To_String);
478               end if;
479
480               --  LRM08 9.2.3 Relational operators
481               --  The matching relational operators are predefined for the
482               --  [predefined type BIT and for the] type STD_ULOGIC defined
483               --  in package STD_LOGIC_1164.
484               if Type_Definition = Ieee.Std_Logic_1164.Std_Ulogic_Type then
485                  Add_Binary (Name_Op_Match_Equality,
486                              Iir_Predefined_Std_Ulogic_Match_Equality);
487                  Add_Binary (Name_Op_Match_Inequality,
488                              Iir_Predefined_Std_Ulogic_Match_Inequality);
489                  Add_Binary (Name_Op_Match_Less,
490                              Iir_Predefined_Std_Ulogic_Match_Less);
491                  Add_Binary (Name_Op_Match_Less_Equal,
492                              Iir_Predefined_Std_Ulogic_Match_Less_Equal);
493                  Add_Binary (Name_Op_Match_Greater,
494                              Iir_Predefined_Std_Ulogic_Match_Greater);
495                  Add_Binary (Name_Op_Match_Greater_Equal,
496                              Iir_Predefined_Std_Ulogic_Match_Greater_Equal);
497               end if;
498            end if;
499
500         when Iir_Kind_Array_Type_Definition
501           | Iir_Kind_Array_Subtype_Definition =>
502            declare
503               Element_Type : Iir;
504
505               Element_Array_Inter_Chain : Iir;
506               Array_Element_Inter_Chain : Iir;
507               Element_Element_Inter_Chain : Iir;
508            begin
509               Add_Relational
510                 (Name_Op_Equality, Iir_Predefined_Array_Equality);
511               Add_Relational
512                 (Name_Op_Inequality, Iir_Predefined_Array_Inequality);
513               if Is_Discrete_Array (Type_Definition) then
514                  Add_Relational
515                    (Name_Op_Greater, Iir_Predefined_Array_Greater);
516                  Add_Relational
517                    (Name_Op_Greater_Equal,
518                     Iir_Predefined_Array_Greater_Equal);
519                  Add_Relational
520                    (Name_Op_Less, Iir_Predefined_Array_Less);
521                  Add_Relational
522                    (Name_Op_Less_Equal, Iir_Predefined_Array_Less_Equal);
523
524                  --  LRM08 5.3.2.4 Predefined operations on array types
525                  --  Given a type declaration that declares a discrete array
526                  --  type T, the following operatons are implicitly declared
527                  --  immediately following the type declaration:
528                  --   function MINIMUM (L, R : T) return T;
529                  --   function MAXIMUM (L, R : T) return T;
530                  if Vhdl_Std >= Vhdl_08 then
531                     Add_Min_Max (Name_Maximum, Iir_Predefined_Array_Maximum);
532                     Add_Min_Max (Name_Minimum, Iir_Predefined_Array_Minimum);
533                  end if;
534               end if;
535
536               Element_Type := Get_Element_Subtype (Type_Definition);
537
538               if Is_One_Dimensional_Array_Type (Type_Definition) then
539                  --  LRM93 7.2.4 Adding operators
540                  --  The concatenation operator & is predefined for any
541                  --  one-dimensional array type.
542                  Add_Operation (Name_Op_Concatenation,
543                                 Iir_Predefined_Array_Array_Concat,
544                                 Binary_Chain,
545                                 Type_Definition);
546
547                  Element_Array_Inter_Chain :=
548                    Create_Anonymous_Interface (Element_Type);
549                  Set_Chain (Element_Array_Inter_Chain, Unary_Chain);
550                  Add_Operation (Name_Op_Concatenation,
551                                 Iir_Predefined_Element_Array_Concat,
552                                 Element_Array_Inter_Chain,
553                                 Type_Definition);
554
555                  Array_Element_Inter_Chain :=
556                    Create_Anonymous_Interface (Type_Definition);
557                  Set_Chain (Array_Element_Inter_Chain,
558                             Create_Anonymous_Interface (Element_Type));
559                  Add_Operation (Name_Op_Concatenation,
560                                 Iir_Predefined_Array_Element_Concat,
561                                 Array_Element_Inter_Chain,
562                                 Type_Definition);
563
564                  Element_Element_Inter_Chain :=
565                    Create_Anonymous_Interface (Element_Type);
566                  Set_Chain (Element_Element_Inter_Chain,
567                             Create_Anonymous_Interface (Element_Type));
568                  Add_Operation (Name_Op_Concatenation,
569                                 Iir_Predefined_Element_Element_Concat,
570                                 Element_Element_Inter_Chain,
571                                 Type_Definition);
572
573                  --  LRM08 5.3.2.4 Predefined operations on array types
574                  --  In addition, given a type declaration that declares a
575                  --  one-dimensional array type T whose elements are of a
576                  --  sclar type E, the following operations are implicitly
577                  --  declared immediately following the type declaration:
578                  --   function MINIMUM (L : T) return E;
579                  --   function MAXIMUM (L : T) return E;
580                  if Vhdl_Std >= Vhdl_08
581                    and then (Get_Kind (Element_Type) in
582                                Iir_Kinds_Scalar_Type_And_Subtype_Definition)
583                  then
584                     Add_Vector_Min_Max
585                       (Name_Maximum, Iir_Predefined_Vector_Maximum);
586                     Add_Vector_Min_Max
587                       (Name_Minimum, Iir_Predefined_Vector_Minimum);
588                  end if;
589
590                  if Element_Type = Std_Package.Boolean_Type_Definition
591                    or else Element_Type = Std_Package.Bit_Type_Definition
592                  then
593                     --  LRM93 7.2.1 Logical operators
594                     --  LRM08 9.2.2 Logical operators
595                     --  The binary logical operators AND, OR, NAND, NOR, XOR,
596                     --  and XNOR, and the unary logical operator NOT are
597                     --  defined for predefined types BIT and BOOLEAN.  They
598                     --  are also defined for any one-dimensional array type
599                     --  whose element type is BIT or BOOLEAN.
600
601                     Add_Unary (Name_Not, Iir_Predefined_TF_Array_Not);
602
603                     Add_Binary (Name_And, Iir_Predefined_TF_Array_And);
604                     Add_Binary (Name_Or, Iir_Predefined_TF_Array_Or);
605                     Add_Binary (Name_Nand, Iir_Predefined_TF_Array_Nand);
606                     Add_Binary (Name_Nor, Iir_Predefined_TF_Array_Nor);
607                     Add_Binary (Name_Xor, Iir_Predefined_TF_Array_Xor);
608                     if Flags.Vhdl_Std > Vhdl_87 then
609                        Add_Binary (Name_Xnor, Iir_Predefined_TF_Array_Xnor);
610
611                        --  LRM93 7.2.3 Shift operators
612                        --  The shift operators SLL, SRL, SLA, SRA, ROL and
613                        --  ROR are defined for any one-dimensional array type
614                        --  whose element type is either of the predefined
615                        --  types BIT or BOOLEAN.
616                        Add_Shift_Operators;
617                     end if;
618
619                     --  LRM08 9.2.2 Logical operators
620                     --  For the binary operators AND, OR, NAND, NOR, XOR and
621                     --  XNOR, the operands shall both be [of the same base
622                     --  type,] or one operand shall be of a scalar type and
623                     --  the other operand shall be a one-dimensional array
624                     --  whose element type is the scalar type.  The result
625                     --  type is the same as the base type of the operands if
626                     --  [both operands are scalars of the same base type or]
627                     --  both operands are arrays, or the same as the base type
628                     --  of the array operand if one operand is a scalar and
629                     --  the other operand is an array.
630                     if Flags.Vhdl_Std >= Vhdl_08 then
631                        Add_Operation
632                          (Name_And, Iir_Predefined_TF_Element_Array_And,
633                           Element_Array_Inter_Chain, Type_Definition);
634                        Add_Operation
635                          (Name_And, Iir_Predefined_TF_Array_Element_And,
636                           Array_Element_Inter_Chain, Type_Definition);
637                        Add_Operation
638                          (Name_Or, Iir_Predefined_TF_Element_Array_Or,
639                           Element_Array_Inter_Chain, Type_Definition);
640                        Add_Operation
641                          (Name_Or, Iir_Predefined_TF_Array_Element_Or,
642                           Array_Element_Inter_Chain, Type_Definition);
643                        Add_Operation
644                          (Name_Nand, Iir_Predefined_TF_Element_Array_Nand,
645                           Element_Array_Inter_Chain, Type_Definition);
646                        Add_Operation
647                          (Name_Nand, Iir_Predefined_TF_Array_Element_Nand,
648                           Array_Element_Inter_Chain, Type_Definition);
649                        Add_Operation
650                          (Name_Nor, Iir_Predefined_TF_Element_Array_Nor,
651                           Element_Array_Inter_Chain, Type_Definition);
652                        Add_Operation
653                          (Name_Nor, Iir_Predefined_TF_Array_Element_Nor,
654                           Array_Element_Inter_Chain, Type_Definition);
655                        Add_Operation
656                          (Name_Xor, Iir_Predefined_TF_Element_Array_Xor,
657                           Element_Array_Inter_Chain, Type_Definition);
658                        Add_Operation
659                          (Name_Xor, Iir_Predefined_TF_Array_Element_Xor,
660                           Array_Element_Inter_Chain, Type_Definition);
661                        Add_Operation
662                          (Name_Xnor, Iir_Predefined_TF_Element_Array_Xnor,
663                           Element_Array_Inter_Chain, Type_Definition);
664                        Add_Operation
665                          (Name_Xnor, Iir_Predefined_TF_Array_Element_Xnor,
666                           Array_Element_Inter_Chain, Type_Definition);
667                     end if;
668
669                     if Flags.Vhdl_Std >= Vhdl_08 then
670                        --  LRM08 9.2.2 Logical operations
671                        --  The unary logical operators AND, OR, NAND, NOR,
672                        --  XOR, and XNOR are referred to as logical reduction
673                        --  operators.  The logical reduction operators are
674                        --  predefined for any one-dimensional array type whose
675                        --  element type is BIT or BOOLEAN.  The result type
676                        --  for the logical reduction operators is the same as
677                        --  the element type of the operand.
678                        Add_Operation
679                          (Name_And, Iir_Predefined_TF_Reduction_And,
680                           Unary_Chain, Element_Type);
681                        Add_Operation
682                          (Name_Or, Iir_Predefined_TF_Reduction_Or,
683                           Unary_Chain, Element_Type);
684                        Add_Operation
685                          (Name_Nand, Iir_Predefined_TF_Reduction_Nand,
686                           Unary_Chain, Element_Type);
687                        Add_Operation
688                          (Name_Nor, Iir_Predefined_TF_Reduction_Nor,
689                           Unary_Chain, Element_Type);
690                        Add_Operation
691                          (Name_Xor, Iir_Predefined_TF_Reduction_Xor,
692                           Unary_Chain, Element_Type);
693                        Add_Operation
694                          (Name_Xnor, Iir_Predefined_TF_Reduction_Xnor,
695                           Unary_Chain, Element_Type);
696                     end if;
697                  end if;
698
699                  --  LRM08 9.2.3 Relational operators
700                  --  The matching equality and matching inequality operatotrs
701                  --  are also defined for any one-dimensional array type
702                  --  whose element type is BIT or STD_ULOGIC.
703                  if Flags.Vhdl_Std >= Vhdl_08 then
704                     if Element_Type = Std_Package.Bit_Type_Definition then
705                        Add_Operation
706                          (Name_Op_Match_Equality,
707                           Iir_Predefined_Bit_Array_Match_Equality,
708                           Binary_Chain, Element_Type);
709                        Add_Operation
710                          (Name_Op_Match_Inequality,
711                           Iir_Predefined_Bit_Array_Match_Inequality,
712                           Binary_Chain, Element_Type);
713                     elsif Element_Type = Ieee.Std_Logic_1164.Std_Ulogic_Type
714                     then
715                        Add_Operation
716                          (Name_Op_Match_Equality,
717                           Iir_Predefined_Std_Ulogic_Array_Match_Equality,
718                           Binary_Chain, Element_Type);
719                        Add_Operation
720                          (Name_Op_Match_Inequality,
721                           Iir_Predefined_Std_Ulogic_Array_Match_Inequality,
722                           Binary_Chain, Element_Type);
723                     end if;
724                  end if;
725
726                  --  LRM08 5.3.2.4  Predefined operations on array type
727                  --
728                  --  Given a type declaration that declares a one-dimensional
729                  --  array type T whose element type is a character type that
730                  --  contains only character literals, the following operation
731                  --  is implicitely declared immediately following the type
732                  --  declaration
733                  if Vhdl_Std >= Vhdl_08
734                    and then String_Type_Definition /= Null_Iir
735                    and then (Get_Kind (Element_Type)
736                                = Iir_Kind_Enumeration_Type_Definition)
737                    and then Get_Only_Characters_Flag (Element_Type)
738                  then
739                     Add_Operation (Name_To_String,
740                                    Iir_Predefined_Array_Char_To_String,
741                                    Unary_Chain,
742                                    String_Type_Definition);
743                  end if;
744               end if;
745            end;
746
747         when Iir_Kind_Access_Type_Definition =>
748            Add_Relational (Name_Op_Equality, Iir_Predefined_Access_Equality);
749            Add_Relational
750              (Name_Op_Inequality, Iir_Predefined_Access_Inequality);
751            declare
752               Deallocate_Proc: Iir_Procedure_Declaration;
753               Var_Interface: Iir_Interface_Variable_Declaration;
754            begin
755               Deallocate_Proc :=
756                 Create_Iir (Iir_Kind_Procedure_Declaration);
757               Location_Copy (Deallocate_Proc, Decl);
758               Set_Identifier (Deallocate_Proc, Std_Names.Name_Deallocate);
759               Set_Implicit_Definition
760                 (Deallocate_Proc, Iir_Predefined_Deallocate);
761               Set_Parent (Deallocate_Proc, Get_Parent (Decl));
762
763               Var_Interface :=
764                 Create_Iir (Iir_Kind_Interface_Variable_Declaration);
765               Location_Copy (Var_Interface, Decl);
766               Set_Identifier (Var_Interface, Std_Names.Name_P);
767               Set_Parent (Var_Interface, Deallocate_Proc);
768               Set_Type (Var_Interface, Type_Definition);
769               Set_Mode (Var_Interface, Iir_Inout_Mode);
770               --Set_Purity_State (Deallocate_Proc, Impure);
771               Set_Wait_State (Deallocate_Proc, False);
772               Set_Visible_Flag (Deallocate_Proc, True);
773
774               Set_Interface_Declaration_Chain
775                 (Deallocate_Proc, Var_Interface);
776               Compute_Subprogram_Hash (Deallocate_Proc);
777               Insert_Incr (Last, Deallocate_Proc);
778            end;
779
780         when Iir_Kind_Record_Type_Definition =>
781            Add_Relational (Name_Op_Equality, Iir_Predefined_Record_Equality);
782            Add_Relational
783              (Name_Op_Inequality, Iir_Predefined_Record_Inequality);
784
785         when Iir_Kind_Integer_Type_Definition =>
786            Add_Relational (Name_Op_Equality, Iir_Predefined_Integer_Equality);
787            Add_Relational
788              (Name_Op_Inequality, Iir_Predefined_Integer_Inequality);
789            Add_Relational (Name_Op_Greater, Iir_Predefined_Integer_Greater);
790            Add_Relational
791              (Name_Op_Greater_Equal, Iir_Predefined_Integer_Greater_Equal);
792            Add_Relational (Name_Op_Less, Iir_Predefined_Integer_Less);
793            Add_Relational
794              (Name_Op_Less_Equal, Iir_Predefined_Integer_Less_Equal);
795
796            Add_Binary (Name_Op_Plus, Iir_Predefined_Integer_Plus);
797            Add_Binary (Name_Op_Minus, Iir_Predefined_Integer_Minus);
798
799            Add_Unary (Name_Op_Minus, Iir_Predefined_Integer_Negation);
800            Add_Unary (Name_Op_Plus, Iir_Predefined_Integer_Identity);
801
802            Add_Binary (Name_Op_Mul, Iir_Predefined_Integer_Mul);
803            Add_Binary (Name_Op_Div, Iir_Predefined_Integer_Div);
804            Add_Binary (Name_Mod, Iir_Predefined_Integer_Mod);
805            Add_Binary (Name_Rem, Iir_Predefined_Integer_Rem);
806
807            Add_Unary (Name_Abs, Iir_Predefined_Integer_Absolute);
808
809            declare
810               Inter_Chain : Iir;
811            begin
812               Inter_Chain := Create_Anonymous_Interface (Type_Definition);
813               Set_Chain
814                 (Inter_Chain,
815                  Create_Anonymous_Interface (Integer_Type_Definition));
816               Add_Operation (Name_Op_Exp, Iir_Predefined_Integer_Exp,
817                              Inter_Chain, Type_Definition);
818            end;
819
820            if Vhdl_Std >= Vhdl_08 then
821               --  LRM08 5.2.6 Predefined operations on scalar types
822               --  Given a type declaration that declares a scalar type T, the
823               --  following operations are implicitely declared immediately
824               --  following the type declaration (except for the TO_STRING
825               --  operations in package STANDARD [...])
826               Add_Min_Max (Name_Minimum, Iir_Predefined_Integer_Minimum);
827               Add_Min_Max (Name_Maximum, Iir_Predefined_Integer_Maximum);
828               if not Is_Std_Standard then
829                  Add_To_String (Iir_Predefined_Integer_To_String);
830               end if;
831            end if;
832
833         when Iir_Kind_Floating_Type_Definition =>
834            Add_Relational
835              (Name_Op_Equality, Iir_Predefined_Floating_Equality);
836            Add_Relational
837              (Name_Op_Inequality, Iir_Predefined_Floating_Inequality);
838            Add_Relational
839              (Name_Op_Greater, Iir_Predefined_Floating_Greater);
840            Add_Relational
841              (Name_Op_Greater_Equal, Iir_Predefined_Floating_Greater_Equal);
842            Add_Relational
843              (Name_Op_Less, Iir_Predefined_Floating_Less);
844            Add_Relational
845              (Name_Op_Less_Equal, Iir_Predefined_Floating_Less_Equal);
846
847            Add_Binary (Name_Op_Plus, Iir_Predefined_Floating_Plus);
848            Add_Binary (Name_Op_Minus, Iir_Predefined_Floating_Minus);
849
850            Add_Unary (Name_Op_Minus, Iir_Predefined_Floating_Negation);
851            Add_Unary (Name_Op_Plus, Iir_Predefined_Floating_Identity);
852
853            Add_Binary (Name_Op_Mul, Iir_Predefined_Floating_Mul);
854            Add_Binary (Name_Op_Div, Iir_Predefined_Floating_Div);
855
856            Add_Unary (Name_Abs, Iir_Predefined_Floating_Absolute);
857
858            declare
859               Inter_Chain : Iir;
860            begin
861               Inter_Chain := Create_Anonymous_Interface (Type_Definition);
862               Set_Chain
863                 (Inter_Chain,
864                  Create_Anonymous_Interface (Integer_Type_Definition));
865               Add_Operation (Name_Op_Exp, Iir_Predefined_Floating_Exp,
866                              Inter_Chain, Type_Definition);
867            end;
868
869            if Vhdl_Std >= Vhdl_08 then
870               --  LRM08 5.2.6 Predefined operations on scalar types
871               --  Given a type declaration that declares a scalar type T, the
872               --  following operations are implicitely declared immediately
873               --  following the type declaration (except for the TO_STRING
874               --  operations in package STANDARD [...])
875               Add_Min_Max (Name_Minimum, Iir_Predefined_Floating_Minimum);
876               Add_Min_Max (Name_Maximum, Iir_Predefined_Floating_Maximum);
877               if not Is_Std_Standard then
878                  Add_To_String (Iir_Predefined_Floating_To_String);
879               end if;
880            end if;
881
882         when Iir_Kind_Physical_Type_Definition =>
883            Add_Relational
884              (Name_Op_Equality, Iir_Predefined_Physical_Equality);
885            Add_Relational
886              (Name_Op_Inequality, Iir_Predefined_Physical_Inequality);
887            Add_Relational
888              (Name_Op_Greater, Iir_Predefined_Physical_Greater);
889            Add_Relational
890              (Name_Op_Greater_Equal, Iir_Predefined_Physical_Greater_Equal);
891            Add_Relational
892              (Name_Op_Less, Iir_Predefined_Physical_Less);
893            Add_Relational
894              (Name_Op_Less_Equal, Iir_Predefined_Physical_Less_Equal);
895
896            Add_Binary (Name_Op_Plus, Iir_Predefined_Physical_Plus);
897            Add_Binary (Name_Op_Minus, Iir_Predefined_Physical_Minus);
898
899            Add_Unary (Name_Op_Minus, Iir_Predefined_Physical_Negation);
900            Add_Unary (Name_Op_Plus, Iir_Predefined_Physical_Identity);
901
902            declare
903               Inter_Chain : Iir;
904            begin
905               Inter_Chain := Create_Anonymous_Interface (Type_Definition);
906               Set_Chain
907                 (Inter_Chain,
908                  Create_Anonymous_Interface (Integer_Type_Definition));
909               Add_Operation (Name_Op_Mul, Iir_Predefined_Physical_Integer_Mul,
910                              Inter_Chain, Type_Definition);
911               Add_Operation (Name_Op_Div, Iir_Predefined_Physical_Integer_Div,
912                              Inter_Chain, Type_Definition);
913            end;
914
915            declare
916               Inter_Chain : Iir;
917            begin
918               Inter_Chain :=
919                 Create_Anonymous_Interface (Integer_Type_Definition);
920               Set_Chain (Inter_Chain, Unary_Chain);
921               Add_Operation (Name_Op_Mul, Iir_Predefined_Integer_Physical_Mul,
922                              Inter_Chain, Type_Definition);
923            end;
924
925            declare
926               Inter_Chain : Iir;
927            begin
928               Inter_Chain := Create_Anonymous_Interface (Type_Definition);
929               Set_Chain (Inter_Chain,
930                          Create_Anonymous_Interface (Real_Type_Definition));
931               Add_Operation (Name_Op_Mul, Iir_Predefined_Physical_Real_Mul,
932                              Inter_Chain, Type_Definition);
933               Add_Operation (Name_Op_Div, Iir_Predefined_Physical_Real_Div,
934                              Inter_Chain, Type_Definition);
935            end;
936
937            declare
938               Inter_Chain : Iir;
939            begin
940               Inter_Chain :=
941                 Create_Anonymous_Interface (Real_Type_Definition);
942               Set_Chain (Inter_Chain, Unary_Chain);
943               Add_Operation (Name_Op_Mul, Iir_Predefined_Real_Physical_Mul,
944                              Inter_Chain, Type_Definition);
945            end;
946            Add_Operation (Name_Op_Div, Iir_Predefined_Physical_Physical_Div,
947                           Binary_Chain,
948                           Std_Package.Convertible_Integer_Type_Definition);
949
950            Add_Unary (Name_Abs, Iir_Predefined_Physical_Absolute);
951
952            if Vhdl_Std >= Vhdl_08 then
953               --  LRM08 5.2.6 Predefined operations on scalar types
954               --  Given a type declaration that declares a scalar type T, the
955               --  following operations are implicitely declared immediately
956               --  following the type declaration (except for the TO_STRING
957               --  operations in package STANDARD [...])
958               Add_Min_Max (Name_Minimum, Iir_Predefined_Physical_Minimum);
959               Add_Min_Max (Name_Maximum, Iir_Predefined_Physical_Maximum);
960               if not Is_Std_Standard then
961                  Add_To_String (Iir_Predefined_Physical_To_String);
962               end if;
963            end if;
964
965         when Iir_Kind_File_Type_Definition =>
966            Create_Implicit_File_Primitives (Decl, Type_Definition);
967
968         when Iir_Kind_Protected_Type_Declaration =>
969            null;
970
971         when others =>
972            Error_Kind ("create_predefined_operations", Type_Definition);
973      end case;
974
975      if not Is_Std_Standard then
976         return;
977      end if;
978      if Decl = Std_Package.Boolean_Type_Declaration then
979         Add_Binary (Name_And, Iir_Predefined_Boolean_And);
980         Add_Binary (Name_Or, Iir_Predefined_Boolean_Or);
981         Add_Binary (Name_Nand, Iir_Predefined_Boolean_Nand);
982         Add_Binary (Name_Nor, Iir_Predefined_Boolean_Nor);
983         Add_Binary (Name_Xor, Iir_Predefined_Boolean_Xor);
984         if Flags.Vhdl_Std > Vhdl_87 then
985            Add_Binary (Name_Xnor, Iir_Predefined_Boolean_Xnor);
986         end if;
987         Add_Unary (Name_Not, Iir_Predefined_Boolean_Not);
988      elsif Decl = Std_Package.Bit_Type_Declaration then
989         Add_Binary (Name_And, Iir_Predefined_Bit_And);
990         Add_Binary (Name_Or, Iir_Predefined_Bit_Or);
991         Add_Binary (Name_Nand, Iir_Predefined_Bit_Nand);
992         Add_Binary (Name_Nor, Iir_Predefined_Bit_Nor);
993         Add_Binary (Name_Xor, Iir_Predefined_Bit_Xor);
994         if Flags.Vhdl_Std > Vhdl_87 then
995            Add_Binary (Name_Xnor, Iir_Predefined_Bit_Xnor);
996         end if;
997         Add_Unary (Name_Not, Iir_Predefined_Bit_Not);
998         if Flags.Vhdl_Std >= Vhdl_08 then
999            Add_Binary (Name_Op_Match_Equality,
1000                        Iir_Predefined_Bit_Match_Equality);
1001            Add_Binary (Name_Op_Match_Inequality,
1002                        Iir_Predefined_Bit_Match_Inequality);
1003            Add_Binary (Name_Op_Match_Less,
1004                        Iir_Predefined_Bit_Match_Less);
1005            Add_Binary (Name_Op_Match_Less_Equal,
1006                        Iir_Predefined_Bit_Match_Less_Equal);
1007            Add_Binary (Name_Op_Match_Greater,
1008                        Iir_Predefined_Bit_Match_Greater);
1009            Add_Binary (Name_Op_Match_Greater_Equal,
1010                        Iir_Predefined_Bit_Match_Greater_Equal);
1011
1012            --  LRM08 9.2.9 Condition operator
1013            --  The unary operator ?? is predefined for type BIT defined in
1014            --  package STANDARD.
1015            Add_Operation (Name_Op_Condition, Iir_Predefined_Bit_Condition,
1016                           Unary_Chain, Std_Package.Boolean_Type_Definition);
1017
1018         end if;
1019      elsif Decl = Std_Package.Universal_Real_Type_Declaration then
1020         declare
1021            Inter_Chain : Iir;
1022         begin
1023            Inter_Chain := Create_Anonymous_Interface (Type_Definition);
1024            Set_Chain
1025              (Inter_Chain,
1026               Create_Anonymous_Interface (Universal_Integer_Type_Definition));
1027            Add_Operation (Name_Op_Mul, Iir_Predefined_Universal_R_I_Mul,
1028                           Inter_Chain, Type_Definition);
1029            Add_Operation (Name_Op_Div, Iir_Predefined_Universal_R_I_Div,
1030                           Inter_Chain, Type_Definition);
1031         end;
1032
1033         declare
1034            Inter_Chain : Iir;
1035         begin
1036            Inter_Chain :=
1037              Create_Anonymous_Interface (Universal_Integer_Type_Definition);
1038            Set_Chain (Inter_Chain, Unary_Chain);
1039            Add_Operation (Name_Op_Mul, Iir_Predefined_Universal_I_R_Mul,
1040                           Inter_Chain, Type_Definition);
1041         end;
1042      end if;
1043   end Create_Implicit_Operations;
1044end Vhdl.Sem_Utils;
1045