1--  GHDL Run Time (GRT) - common types.
2--  Copyright (C) 2002 - 2014 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>.
16--
17--  As a special exception, if other files instantiate generics from this
18--  unit, or you link this unit with other files to produce an executable,
19--  this unit does not by itself cause the resulting executable to be
20--  covered by the GNU General Public License. This exception does not
21--  however invalidate any other reasons why the executable file might be
22--  covered by the GNU Public License.
23with System; use System;
24with Ada.Unchecked_Conversion;
25with Ada.Unchecked_Deallocation;
26with Interfaces; use Interfaces;
27
28package Grt.Types is
29   pragma Preelaborate (Grt.Types);
30
31   type Ghdl_B1 is new Boolean;
32   type Ghdl_U8 is new Unsigned_8;
33   subtype Ghdl_E8 is Ghdl_U8;
34   type Ghdl_U32 is new Unsigned_32;
35   subtype Ghdl_E32 is Ghdl_U32;
36   type Ghdl_I32 is new Integer_32;
37   type Ghdl_I64 is new Integer_64;
38   type Ghdl_U64 is new Unsigned_64;
39   type Ghdl_F64 is new IEEE_Float_64;
40
41   function To_Ghdl_U64 is new Ada.Unchecked_Conversion
42     (Ghdl_I64, Ghdl_U64);
43
44   type Ghdl_Ptr is new Address;
45   type Ghdl_Index_Type is mod 2 ** 32;
46   subtype Ghdl_Real is Ghdl_F64;
47
48   type Ghdl_Dir_Type is (Dir_To, Dir_Downto);
49   for Ghdl_Dir_Type use (Dir_To => 0, Dir_Downto => 1);
50   for Ghdl_Dir_Type'Size use 8;
51
52   --  Access to an unconstrained string.
53   type String_Access is access String;
54   type String_Cst is access constant String;
55   procedure Unchecked_Deallocation is new Ada.Unchecked_Deallocation
56     (Name => String_Access, Object => String);
57
58   subtype Std_Integer is Ghdl_I32;
59
60   type Std_Integer_Acc is access Std_Integer;
61   pragma Convention (C, Std_Integer_Acc);
62
63   type Std_Time is new Ghdl_I64;
64   Bad_Time : constant Std_Time := Std_Time'First;
65
66   type Std_Integer_Trt is record
67      Left : Std_Integer;
68      Right : Std_Integer;
69      Dir : Ghdl_Dir_Type;
70      Length : Ghdl_Index_Type;
71   end record;
72
73   type Std_Integer_Range_Ptr is access Std_Integer_Trt;
74   pragma Convention (C, Std_Integer_Range_Ptr);
75
76   subtype Std_Character is Character;
77   type Std_String_Uncons is array (Ghdl_Index_Type range <>) of Std_Character;
78   subtype Std_String_Base is Std_String_Uncons (Ghdl_Index_Type);
79   type Std_String_Basep is access all Std_String_Base;
80   function To_Std_String_Basep is new Ada.Unchecked_Conversion
81     (Source => Address, Target => Std_String_Basep);
82
83   type Std_String_Bound is record
84      Dim_1 : Std_Integer_Trt;
85   end record;
86   type Std_String_Boundp is access all Std_String_Bound;
87   function To_Std_String_Boundp is new Ada.Unchecked_Conversion
88     (Source => Address, Target => Std_String_Boundp);
89
90   type Std_String is record
91      Base : Std_String_Basep;
92      Bounds : Std_String_Boundp;
93   end record;
94   type Std_String_Ptr is access all Std_String;
95   function To_Std_String_Ptr is new Ada.Unchecked_Conversion
96     (Source => Address, Target => Std_String_Ptr);
97
98   type Std_Bit is ('0', '1');
99   type Std_Bit_Vector_Uncons is array (Ghdl_Index_Type range <>) of Std_Bit;
100   subtype Std_Bit_Vector_Base is Std_Bit_Vector_Uncons (Ghdl_Index_Type);
101   type Std_Bit_Vector_Basep is access all Std_Bit_Vector_Base;
102
103   --  An unconstrained array.
104   --  It is in fact a fat pointer to the base and the bounds.
105   type Ghdl_Uc_Array is record
106      Base : Address;
107      Bounds : Address;
108   end record;
109   type Ghdl_Uc_Array_Acc is access Ghdl_Uc_Array;
110   function To_Ghdl_Uc_Array_Acc is new Ada.Unchecked_Conversion
111     (Source => Address, Target => Ghdl_Uc_Array_Acc);
112
113   --  Verilog types.
114
115   type Ghdl_Logic32 is record
116      Val : Ghdl_U32;
117      Xz : Ghdl_U32;
118   end record;
119   type Ghdl_Logic32_Ptr is access Ghdl_Logic32;
120   type Ghdl_Logic32_Vec is array (Ghdl_U32) of Ghdl_Logic32;
121   type Ghdl_Logic32_Vptr is access Ghdl_Logic32_Vec;
122
123   function To_Ghdl_Logic32_Vptr is new Ada.Unchecked_Conversion
124     (Source => Address, Target => Ghdl_Logic32_Vptr);
125
126   function To_Ghdl_Logic32_Ptr is new Ada.Unchecked_Conversion
127     (Source => Address, Target => Ghdl_Logic32_Ptr);
128
129   --  Mimics C strings (NUL ended).
130   --  Note: this is 1 based.
131   type Ghdl_C_String is access String (Positive);
132   NUL : constant Character := Character'Val (0);
133
134   Nl : constant Character := Character'Val (10);  -- LF, nl or '\n'.
135
136   function strlen (Str : Ghdl_C_String) return Natural;
137   pragma Import (C, strlen);
138
139   function Strcmp (L , R : Ghdl_C_String) return Integer;
140   pragma Import (C, Strcmp);
141
142   function To_Ghdl_C_String is new Ada.Unchecked_Conversion
143     (Source => Address, Target => Ghdl_C_String);
144   function To_Address is new Ada.Unchecked_Conversion
145     (Source => Ghdl_C_String, Target => Address);
146
147   --  Str_len.
148   type String_Ptr is access String (1 .. Natural'Last);
149   type Ghdl_Str_Len_Type is record
150      Len : Natural;
151      Str : String_Ptr;
152   end record;
153   --  Same as previous one, but using 'address.
154   type Ghdl_Str_Len_Address_Type is record
155      Len : Natural;
156      Str : Address;
157   end record;
158   type Ghdl_Str_Len_Ptr is access constant Ghdl_Str_Len_Type;
159   type Ghdl_Str_Len_Array is array (Natural) of Ghdl_Str_Len_Type;
160   type Ghdl_Str_Len_Array_Ptr is access all Ghdl_Str_Len_Array;
161
162   --  Location is used for errors/messages.
163   type Ghdl_Location is record
164      Filename : Ghdl_C_String;
165      Line : Integer;
166      Col : Integer;
167   end record;
168   type Ghdl_Location_Ptr is access Ghdl_Location;
169   function To_Ghdl_Location_Ptr is new Ada.Unchecked_Conversion
170     (Source => Address, Target => Ghdl_Location_Ptr);
171
172   type C_Boolean is new Boolean;
173   pragma Convention (C, C_Boolean);
174
175   --  Signal index.
176   type Sig_Table_Index is new Integer;
177
178   --  A range of signals.
179   type Sig_Table_Range is record
180      First, Last : Sig_Table_Index;
181   end record;
182
183   --  Simple values, used for signals.
184   type Mode_Type is
185     (Mode_B1, Mode_E8, Mode_E32, Mode_I32, Mode_I64, Mode_F64);
186
187   type Ghdl_B1_Array is array (Ghdl_Index_Type range <>) of Ghdl_B1;
188   subtype Ghdl_B1_Array_Base is Ghdl_B1_Array (Ghdl_Index_Type);
189   type Ghdl_B1_Array_Base_Ptr is access Ghdl_B1_Array_Base;
190   function To_Ghdl_B1_Array_Base_Ptr is new Ada.Unchecked_Conversion
191     (Source => Ghdl_Ptr, Target => Ghdl_B1_Array_Base_Ptr);
192
193   type Ghdl_E8_Array is array (Ghdl_Index_Type range <>) of Ghdl_E8;
194   subtype Ghdl_E8_Array_Base is Ghdl_E8_Array (Ghdl_Index_Type);
195   type Ghdl_E8_Array_Base_Ptr is access Ghdl_E8_Array_Base;
196   function To_Ghdl_E8_Array_Base_Ptr is new Ada.Unchecked_Conversion
197     (Source => Ghdl_Ptr, Target => Ghdl_E8_Array_Base_Ptr);
198
199   type Ghdl_E32_Array is array (Ghdl_Index_Type range <>) of Ghdl_E32;
200   subtype Ghdl_E32_Array_Base is Ghdl_E32_Array (Ghdl_Index_Type);
201   type Ghdl_E32_Array_Base_Ptr is access Ghdl_E32_Array_Base;
202   function To_Ghdl_E32_Array_Base_Ptr is new Ada.Unchecked_Conversion
203     (Source => Ghdl_Ptr, Target => Ghdl_E32_Array_Base_Ptr);
204
205   type Ghdl_I32_Array is array (Ghdl_Index_Type range <>) of Ghdl_I32;
206
207   type Value_Union (Mode : Mode_Type := Mode_B1) is record
208      case Mode is
209         when Mode_B1 =>
210            B1 : Ghdl_B1;
211         when Mode_E8 =>
212            E8 : Ghdl_E8;
213         when Mode_E32 =>
214            E32 : Ghdl_E32;
215         when Mode_I32 =>
216            I32 : Ghdl_I32;
217         when Mode_I64 =>
218            I64 : Ghdl_I64;
219         when Mode_F64 =>
220            F64 : Ghdl_F64;
221      end case;
222   end record;
223   pragma Unchecked_Union (Value_Union);
224
225   type Ghdl_Value_Ptr is access all Value_Union;
226   function To_Ghdl_Value_Ptr is new Ada.Unchecked_Conversion
227     (Source => Address, Target => Ghdl_Value_Ptr);
228
229   --  Ranges.
230   type Ghdl_Range_B1 is record
231      Left : Ghdl_B1;
232      Right : Ghdl_B1;
233      Dir : Ghdl_Dir_Type;
234      Len : Ghdl_Index_Type;
235   end record;
236
237   type Ghdl_Range_E8 is record
238      Left : Ghdl_E8;
239      Right : Ghdl_E8;
240      Dir : Ghdl_Dir_Type;
241      Len : Ghdl_Index_Type;
242   end record;
243
244   type Ghdl_Range_E32 is record
245      Left : Ghdl_E32;
246      Right : Ghdl_E32;
247      Dir : Ghdl_Dir_Type;
248      Len : Ghdl_Index_Type;
249   end record;
250
251   type Ghdl_Range_I32 is record
252      Left : Ghdl_I32;
253      Right : Ghdl_I32;
254      Dir : Ghdl_Dir_Type;
255      Len : Ghdl_Index_Type;
256   end record;
257
258   type Ghdl_Range_I64 is record
259      Left : Ghdl_I64;
260      Right : Ghdl_I64;
261      Dir : Ghdl_Dir_Type;
262      Len : Ghdl_Index_Type;
263   end record;
264
265   type Ghdl_Range_F64 is record
266      Left : Ghdl_F64;
267      Right : Ghdl_F64;
268      Dir : Ghdl_Dir_Type;
269   end record;
270
271   type Ghdl_Range_Type (K : Mode_Type := Mode_B1) is record
272      case K is
273         when Mode_B1 =>
274            B1 : Ghdl_Range_B1;
275         when Mode_E8 =>
276            E8 : Ghdl_Range_E8;
277         when Mode_E32 =>
278            E32 : Ghdl_Range_E32;
279         when Mode_I32 =>
280            I32 : Ghdl_Range_I32;
281         when Mode_I64 =>
282            P64 : Ghdl_Range_I64;
283         when Mode_F64 =>
284            F64 : Ghdl_Range_F64;
285      end case;
286   end record;
287   pragma Unchecked_Union (Ghdl_Range_Type);
288
289   type Ghdl_Range_Ptr is access all Ghdl_Range_Type;
290
291   function To_Ghdl_Range_Ptr is new Ada.Unchecked_Conversion
292     (Source => Address, Target => Ghdl_Range_Ptr);
293
294   type Ghdl_Range_Array is array (Ghdl_Index_Type range <>) of Ghdl_Range_Ptr;
295
296   type Ghdl_Indexes_Type is record
297      Value : Ghdl_Index_Type;
298      Signal : Ghdl_Index_Type;
299   end record;
300
301   type Ghdl_Indexes_Ptr is access all Ghdl_Indexes_Type;
302
303   function To_Ghdl_Indexes_Ptr is new Ada.Unchecked_Conversion
304     (Source => Address, Target => Ghdl_Indexes_Ptr);
305
306   --  For PSL counters.
307   type Ghdl_Index_Ptr is access all Ghdl_Index_Type;
308
309   function To_Ghdl_Index_Ptr is new Ada.Unchecked_Conversion
310     (Source => Address, Target => Ghdl_Index_Ptr);
311
312   --  Mode of a signal.
313   type Mode_Signal_Type is
314     (Mode_Signal,
315      Mode_Linkage, Mode_Buffer, Mode_Out, Mode_Inout, Mode_In,
316      Mode_Stable, Mode_Quiet, Mode_Delayed, Mode_Transaction, Mode_Guard,
317      Mode_Conv_In, Mode_Conv_Out,
318      Mode_End);
319
320   subtype Mode_Signal_Port is
321     Mode_Signal_Type range Mode_Linkage .. Mode_In;
322
323   --  Not implicit signals.
324   subtype Mode_Signal_User is
325     Mode_Signal_Type range Mode_Signal .. Mode_In;
326
327   --  Implicit signals.
328   subtype Mode_Signal_Implicit is
329     Mode_Signal_Type range Mode_Stable .. Mode_Guard;
330
331   subtype Mode_Signal_Forward is
332     Mode_Signal_Type range Mode_Stable .. Mode_Delayed;
333
334   --  Note: we could use system.storage_elements, but unfortunatly,
335   --  this doesn't work with pragma no_run_time (gnat 3.15p).
336   type Integer_Address is mod Memory_Size;
337
338   function To_Address is new Ada.Unchecked_Conversion
339     (Source => Integer_Address, Target => Address);
340
341   function To_Integer is new Ada.Unchecked_Conversion
342     (Source => Address, Target => Integer_Address);
343
344   --  The NOW value.
345   Current_Time : Std_Time;
346   --  The current delta cycle number.
347   Current_Delta : Integer;
348private
349   pragma Export (C, Current_Time, "__ghdl_now");
350end Grt.Types;
351