1--  GHDL Run Time (GRT) - VCD generator.
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.
23
24-------------------------------------------------------------------------------
25
26-- TODO:
27-- * Fix the following issues :
28--    + Currently both the top level signals and signals in packages aren't
29--      visible on the tree view (SST) of gtkwave, but both of them are visible
30--      when no item is selected in the tree view and are mixed together.
31--      (Same issue with FST waves.)
32--    + After calling Vcd_Put_Hierarchy (Pack, Match_List), Avhpi_Error is
33--      raised several times when no signal paths are provided in a wave option
34--      file. It has no consequences other than a printed message.
35--      (Same issue with FST waves.)
36
37with System; use System;
38with Interfaces;
39with Grt.Stdio; use Grt.Stdio;
40with Grt.Errors; use Grt.Errors;
41with Grt.Signals; use Grt.Signals;
42with Grt.Table;
43with Grt.Astdio; use Grt.Astdio;
44with Grt.C; use Grt.C;
45with Grt.Hooks; use Grt.Hooks;
46with Grt.Rtis; use Grt.Rtis;
47with Grt.Rtis_Addr; use Grt.Rtis_Addr;
48with Grt.Rtis_Utils; use Grt.Rtis_Utils;
49with Grt.Rtis_Types; use Grt.Rtis_Types;
50with Grt.To_Strings;
51with Grt.Wave_Opt; use Grt.Wave_Opt;
52with Grt.Wave_Opt.Design; use Grt.Wave_Opt.Design;
53with Grt.Fcvt;
54with Grt.Options;
55pragma Elaborate_All (Grt.Table);
56
57package body Grt.Vcd is
58   --  If TRUE, put $date in vcd file.
59   --  Can be set to FALSE to make vcd comparaison easier.
60   Flag_Vcd_Date : Boolean := True;
61
62   Stream : FILEs;
63
64   procedure My_Vcd_Put (Str : String)
65   is
66      R : size_t;
67      pragma Unreferenced (R);
68   begin
69      R := fwrite (Str'Address, Str'Length, 1, Stream);
70   end My_Vcd_Put;
71
72   procedure My_Vcd_Putc (C : Character)
73   is
74      R : int;
75      pragma Unreferenced (R);
76   begin
77      R := fputc (Character'Pos (C), Stream);
78   end My_Vcd_Putc;
79
80   procedure My_Vcd_Close is
81   begin
82      fclose (Stream);
83      Stream := NULL_Stream;
84   end My_Vcd_Close;
85
86   --  VCD filename.
87   --  Stream corresponding to the VCD filename.
88   --Vcd_Stream : FILEs;
89
90   --  Index type of the table of vcd variables to dump.
91   type Vcd_Index_Type is new Integer;
92
93   --  Return TRUE if OPT is an option for VCD.
94   function Vcd_Option (Opt : String) return Boolean
95   is
96      F : constant Natural := Opt'First;
97      Mode : constant String := "wt" & NUL;
98      Vcd_Filename : String_Access;
99   begin
100      if Opt'Length < 5 or else Opt (F .. F + 4) /= "--vcd" then
101         return False;
102      end if;
103      if Opt'Length = 12 and then Opt (F + 5 .. F + 11) = "-nodate" then
104         Flag_Vcd_Date := False;
105         return True;
106      end if;
107      if Opt'Length > 6 and then Opt (F + 5) = '=' then
108         if Vcd_Close /= null then
109            Error ("--vcd: file already set");
110            return True;
111         end if;
112
113         --  Add an extra NUL character.
114         Vcd_Filename := new String (1 .. Opt'Length - 6 + 1);
115         Vcd_Filename (1 .. Opt'Length - 6) := Opt (F + 6 .. Opt'Last);
116         Vcd_Filename (Vcd_Filename'Last) := NUL;
117
118         if Vcd_Filename.all = "-" & NUL then
119            Stream := stdout;
120         else
121            Stream := fopen (Vcd_Filename.all'Address, Mode'Address);
122            if Stream = NULL_Stream then
123               Error_S ("cannot open ");
124               Error_E (Vcd_Filename (Vcd_Filename'First
125                                      .. Vcd_Filename'Last - 1));
126               return True;
127            end if;
128         end if;
129         Vcd_Putc := My_Vcd_Putc'Access;
130         Vcd_Put := My_Vcd_Put'Access;
131         Vcd_Close := My_Vcd_Close'Access;
132         return True;
133      else
134         return False;
135      end if;
136   end Vcd_Option;
137
138   procedure Vcd_Help is
139   begin
140      Put_Line (" --vcd=FILENAME     dump signal values into a VCD file");
141      Put_Line (" --vcd-nodate       do not write date in VCD file");
142   end Vcd_Help;
143
144   procedure Vcd_Newline is
145   begin
146      Vcd_Putc (Nl);
147   end Vcd_Newline;
148
149   procedure Vcd_Putline (Str : String) is
150   begin
151      Vcd_Put (Str);
152      Vcd_Newline;
153   end Vcd_Putline;
154
155--    procedure Vcd_Put (Str : Ghdl_Str_Len_Type)
156--    is
157--    begin
158--       Put_Str_Len (Vcd_Stream, Str);
159--    end Vcd_Put;
160
161   procedure Vcd_Put_I32 (V : Ghdl_I32)
162   is
163      Str : String (1 .. 11);
164      First : Natural;
165   begin
166      To_Strings.To_String (Str, First, V);
167      Vcd_Put (Str (First .. Str'Last));
168   end Vcd_Put_I32;
169
170   procedure Vcd_Put_Idcode (N : Vcd_Index_Type)
171   is
172      Str : String (1 .. 8);
173      V, R : Vcd_Index_Type;
174      L : Natural;
175   begin
176      L := 0;
177      V := N;
178      loop
179         R := V mod 93;
180         V := V / 93;
181         L := L + 1;
182         Str (L) := Character'Val (33 + R);
183         exit when V = 0;
184      end loop;
185      Vcd_Put (Str (1 .. L));
186   end Vcd_Put_Idcode;
187
188   procedure Vcd_Put_Name (Obj : VhpiHandleT)
189   is
190      Name : String (1 .. 128);
191      Name_Len : Integer;
192   begin
193      Vhpi_Get_Str (VhpiNameP, Obj, Name, Name_Len);
194      if Name_Len <= Name'Last then
195         Vcd_Put (Name (1 .. Name_Len));
196      else
197         --  Truncate.
198         Vcd_Put (Name);
199      end if;
200   end Vcd_Put_Name;
201
202   procedure Vcd_Put_End is
203   begin
204      Vcd_Putline ("$end");
205   end Vcd_Put_End;
206
207   --  Called before elaboration.
208   procedure Vcd_Init
209   is
210   begin
211      if Vcd_Close = null then
212         return;
213      end if;
214      if Flag_Vcd_Date then
215         Vcd_Putline ("$date");
216         Vcd_Put ("  ");
217         declare
218            type time_t is new Interfaces.Integer_64;
219            Cur_Time : time_t;
220
221            function time (Addr : Address) return time_t;
222            pragma Import (C, time);
223
224            function ctime (Timep: Address) return Ghdl_C_String;
225            pragma Import (C, ctime);
226
227            Ct : Ghdl_C_String;
228         begin
229            Cur_Time := time (Null_Address);
230            Ct := ctime (Cur_Time'Address);
231            for I in Positive loop
232               exit when Ct (I) = NUL;
233               Vcd_Putc (Ct (I));
234            end loop;
235            -- Note: ctime already append a LF.
236         end;
237         Vcd_Put_End;
238      end if;
239      Vcd_Putline ("$version");
240      Vcd_Putline ("  GHDL v0");
241      Vcd_Put_End;
242      Vcd_Putline ("$timescale");
243      case Options.Time_Resolution_Scale is
244         when 5 =>
245            Vcd_Putline ("  1 fs");
246         when 4 =>
247            Vcd_Putline ("  1 ps");
248         when 3 =>
249            Vcd_Putline ("  1 ns");
250         when 2 =>
251            Vcd_Putline ("  1 us");
252         when 1 =>
253            Vcd_Putline ("  1 ms");
254         when 0 =>
255            Vcd_Putline ("  1 sec");
256      end case;
257      Vcd_Put_End;
258   end Vcd_Init;
259
260   package Vcd_Table is new Grt.Table
261     (Table_Component_Type => Verilog_Wire_Info,
262      Table_Index_Type => Vcd_Index_Type,
263      Table_Low_Bound => 0,
264      Table_Initial => 32);
265
266   procedure Avhpi_Error (Err : AvhpiErrorT)
267   is
268      pragma Unreferenced (Err);
269   begin
270      Put_Line ("Vcd.Avhpi_Error!");
271      null;
272   end Avhpi_Error;
273
274   function Rti_To_Vcd_Kind (Rti : Ghdl_Rti_Access) return Vcd_Var_Type is
275   begin
276      case Rti.Kind is
277         when Ghdl_Rtik_Subtype_Scalar =>
278            return Rti_To_Vcd_Kind
279              (To_Ghdl_Rtin_Subtype_Scalar_Acc (Rti).Basetype);
280         when Ghdl_Rtik_Type_B1 =>
281            if Rti = Std_Standard_Boolean_RTI_Ptr then
282               return Vcd_Bool;
283            elsif Rti = Std_Standard_Bit_RTI_Ptr then
284               return Vcd_Bit;
285            else
286               return Vcd_Bad;
287            end if;
288         when Ghdl_Rtik_Type_I32 =>
289            return Vcd_Integer32;
290         when Ghdl_Rtik_Type_F64 =>
291            return Vcd_Float64;
292         when Ghdl_Rtik_Type_E8 =>
293            if Rti = Ieee_Std_Logic_1164_Std_Ulogic_RTI_Ptr then
294               return Vcd_Stdlogic;
295            else
296               return Vcd_Enum8;
297            end if;
298         when others =>
299            return Vcd_Bad;
300      end case;
301   end Rti_To_Vcd_Kind;
302
303   function Rti_To_Vcd_Kind (Rti : Ghdl_Rtin_Type_Array_Acc)
304                            return Vcd_Var_Type
305   is
306      It : Ghdl_Rti_Access;
307   begin
308      --  Support only one-dimensional arrays...
309      if Rti.Nbr_Dim /= 1 then
310         return Vcd_Bad;
311      end if;
312
313      --  ... whose index is a scalar...
314      It := Rti.Indexes (0);
315      if It.Kind /= Ghdl_Rtik_Subtype_Scalar then
316         return Vcd_Bad;
317      end if;
318
319      --  ... integer.
320      if To_Ghdl_Rtin_Subtype_Scalar_Acc (It).Basetype.Kind
321        /= Ghdl_Rtik_Type_I32
322      then
323         return Vcd_Bad;
324      end if;
325
326      case Rti_To_Vcd_Kind (Rti.Element) is
327         when Vcd_Bit =>
328            return Vcd_Bitvector;
329         when Vcd_Stdlogic =>
330            return Vcd_Stdlogic_Vector;
331         when others =>
332            return Vcd_Bad;
333      end case;
334   end Rti_To_Vcd_Kind;
335
336   procedure Get_Verilog_Wire (Sig : VhpiHandleT; Info : out Verilog_Wire_Info)
337   is
338      Sig_Type : VhpiHandleT;
339      Rti : Ghdl_Rti_Access;
340      Error : AvhpiErrorT;
341      Sig_Addr : Address;
342      Base : Address;
343      Bounds : Address;
344
345      Kind : Vcd_Var_Type;
346      Irange : Ghdl_Range_Ptr;
347      Val : Vcd_Value_Kind;
348   begin
349      --  Extract type of the signal.
350      Vhpi_Handle (VhpiSubtype, Sig, Sig_Type, Error);
351      if Error /= AvhpiErrorOk then
352         Avhpi_Error (Error);
353         return;
354      end if;
355
356      Rti := Avhpi_Get_Rti (Sig_Type);
357      Sig_Addr := Avhpi_Get_Address (Sig);
358      Object_To_Base_Bounds (Rti, Sig_Addr, Base, Bounds);
359      Sig_Addr := Base;
360
361      case Rti.Kind is
362         when Ghdl_Rtik_Type_B1
363           | Ghdl_Rtik_Type_E8
364           | Ghdl_Rtik_Subtype_Scalar =>
365            Kind := Rti_To_Vcd_Kind (Rti);
366            Irange := null;
367         when Ghdl_Rtik_Subtype_Array =>
368            declare
369               St : constant Ghdl_Rtin_Subtype_Composite_Acc :=
370                 To_Ghdl_Rtin_Subtype_Composite_Acc (Rti);
371               Arr_Rti : constant Ghdl_Rtin_Type_Array_Acc :=
372                 To_Ghdl_Rtin_Type_Array_Acc (St.Basetype);
373               Idx_Rti : constant Ghdl_Rti_Access :=
374                 Get_Base_Type (Arr_Rti.Indexes (0));
375            begin
376               Kind := Rti_To_Vcd_Kind (Arr_Rti);
377               Bounds := Loc_To_Addr (St.Common.Depth, St.Layout,
378                                      Avhpi_Get_Context (Sig));
379               Bounds := Array_Layout_To_Bounds (Bounds);
380               Extract_Range (Bounds, Idx_Rti, Irange);
381            end;
382         when Ghdl_Rtik_Type_Array =>
383            declare
384               Arr_Rti : constant Ghdl_Rtin_Type_Array_Acc :=
385                 To_Ghdl_Rtin_Type_Array_Acc (Rti);
386               Idx_Rti : constant Ghdl_Rti_Access :=
387                 Get_Base_Type (Arr_Rti.Indexes (0));
388            begin
389               Kind := Rti_To_Vcd_Kind (Arr_Rti);
390               Extract_Range (Bounds, Idx_Rti, Irange);
391            end;
392         when others =>
393            Kind := Vcd_Bad;
394      end case;
395
396      --  Do not allow null-array.
397      if Kind = Vcd_Bad
398        or else (Irange /= null and then Irange.I32.Len = 0)
399      then
400         Info := (Vtype => Vcd_Bad, Val => Vcd_Effective, Ptr => Null_Address);
401         return;
402      end if;
403
404      case Vhpi_Get_Kind (Sig) is
405         when VhpiPortDeclK =>
406            case Vhpi_Get_Mode (Sig) is
407               when VhpiInMode
408                 | VhpiInoutMode
409                 | VhpiBufferMode
410                 | VhpiLinkageMode =>
411                  Val := Vcd_Effective;
412               when VhpiOutMode =>
413                  Val := Vcd_Driving;
414               when VhpiErrorMode =>
415                  Kind := Vcd_Bad;
416            end case;
417         when VhpiSigDeclK =>
418            Val := Vcd_Effective;
419         when VhpiGenericDeclK
420           | VhpiConstDeclK =>
421            Val := Vcd_Variable;
422         when others =>
423            Info := (Vtype => Vcd_Bad,
424                     Val => Vcd_Effective, Ptr => Null_Address);
425            return;
426      end case;
427
428      case Kind is
429         when Vcd_Bad =>
430            Info := (Vcd_Bad, Vcd_Effective, Null_Address);
431         when Vcd_Enum8 =>
432            Info := (Vcd_Enum8, Val, Sig_Addr, Rti);
433         when Vcd_Bool =>
434            Info := (Vcd_Bool, Val, Sig_Addr);
435         when Vcd_Integer32 =>
436            Info := (Vcd_Integer32, Val, Sig_Addr);
437         when Vcd_Float64 =>
438            Info := (Vcd_Float64, Val, Sig_Addr);
439         when Vcd_Bit =>
440            Info := (Vcd_Bit, Val, Sig_Addr);
441         when Vcd_Stdlogic =>
442            Info := (Vcd_Stdlogic, Val, Sig_Addr);
443         when Vcd_Bitvector =>
444            Info := (Vcd_Bitvector, Val, Sig_Addr, Irange);
445         when Vcd_Stdlogic_Vector =>
446            Info := (Vcd_Stdlogic_Vector, Val, Sig_Addr, Irange);
447      end case;
448   end Get_Verilog_Wire;
449
450   function Get_Wire_Length (Info : Verilog_Wire_Info)
451                            return Ghdl_Index_Type is
452   begin
453      if Info.Vtype in Vcd_Var_Vectors then
454         return Info.Irange.I32.Len;
455      else
456         return 1;
457      end if;
458   end Get_Wire_Length;
459
460   function Verilog_Wire_Val (Info : Verilog_Wire_Info)
461                             return Ghdl_Value_Ptr is
462   begin
463      case Info.Val is
464         when Vcd_Effective =>
465            return To_Signal_Arr_Ptr (Info.Ptr)(0).Value_Ptr;
466         when Vcd_Driving =>
467            return To_Signal_Arr_Ptr (Info.Ptr)(0).Driving_Value'Access;
468         when Vcd_Variable =>
469            return To_Ghdl_Value_Ptr (Info.Ptr);
470      end case;
471   end Verilog_Wire_Val;
472
473   function Verilog_Wire_Val (Info : Verilog_Wire_Info; Idx : Ghdl_Index_Type)
474                             return Ghdl_Value_Ptr is
475   begin
476      case Info.Val is
477         when Vcd_Effective =>
478            return To_Signal_Arr_Ptr (Info.Ptr)(Idx).Value_Ptr;
479         when Vcd_Driving =>
480            return To_Signal_Arr_Ptr (Info.Ptr)(Idx).Driving_Value'Access;
481         when Vcd_Variable =>
482            --  TODO
483            Internal_Error ("verilog_wire_val");
484      end case;
485   end Verilog_Wire_Val;
486
487   procedure Add_Signal (Sig : VhpiHandleT)
488   is
489      N : Vcd_Index_Type;
490      Vcd_El : Verilog_Wire_Info;
491   begin
492      Get_Verilog_Wire (Sig, Vcd_El);
493
494      if Vcd_El.Vtype = Vcd_Bad
495        or else Vcd_El.Vtype = Vcd_Enum8
496      then
497         Vcd_Put ("$comment ");
498         Vcd_Put_Name (Sig);
499         Vcd_Put (" is not handled");
500         --Vcd_Put (Ghdl_Type_Kind'Image (Desc.Kind));
501         Vcd_Putc (' ');
502         Vcd_Put_End;
503         return;
504      else
505         Vcd_Table.Increment_Last;
506         N := Vcd_Table.Last;
507
508         Vcd_Table.Table (N) := Vcd_El;
509         Vcd_Put ("$var ");
510         case Vcd_El.Vtype is
511            when Vcd_Integer32 =>
512               Vcd_Put ("integer 32");
513            when Vcd_Float64 =>
514               Vcd_Put ("real 64");
515            when Vcd_Bool
516              | Vcd_Bit
517              | Vcd_Stdlogic =>
518               Vcd_Put ("reg 1");
519            when Vcd_Bitvector
520              | Vcd_Stdlogic_Vector =>
521               Vcd_Put ("reg ");
522               Vcd_Put_I32 (Ghdl_I32 (Vcd_El.Irange.I32.Len));
523            when Vcd_Bad
524              | Vcd_Enum8 =>
525               null;
526         end case;
527         Vcd_Putc (' ');
528         Vcd_Put_Idcode (N);
529         Vcd_Putc (' ');
530         Vcd_Put_Name (Sig);
531         if Vcd_El.Vtype in Vcd_Var_Vectors then
532            Vcd_Putc ('[');
533            Vcd_Put_I32 (Vcd_El.Irange.I32.Left);
534            Vcd_Putc (':');
535            Vcd_Put_I32 (Vcd_El.Irange.I32.Right);
536            Vcd_Putc (']');
537         end if;
538         Vcd_Putc (' ');
539         Vcd_Put_End;
540         if Boolean'(False) then
541            Vcd_Put ("$comment ");
542            Vcd_Put_Name (Sig);
543            Vcd_Put (" is ");
544            case Vcd_El.Val is
545               when Vcd_Effective =>
546                  Vcd_Put ("effective ");
547               when Vcd_Driving =>
548                  Vcd_Put ("driving ");
549               when Vcd_Variable =>
550                  Vcd_Put ("variable ");
551            end case;
552            Vcd_Put_End;
553         end if;
554      end if;
555   end Add_Signal;
556
557   procedure Vcd_Put_Hierarchy
558     (Inst : VhpiHandleT; Match_List : Design.Match_List)
559   is
560      Decl_It : VhpiHandleT;
561      Decl : VhpiHandleT;
562      Error : AvhpiErrorT;
563      Match_List_Child : Design.Match_List;
564   begin
565      Vhpi_Iterator (VhpiDecls, Inst, Decl_It, Error);
566      if Error /= AvhpiErrorOk then
567         Avhpi_Error (Error);
568         return;
569      end if;
570
571      Vcd_Put ("$scope module ");
572      Vcd_Put_Name (Inst);
573      Vcd_Putc (' ');
574      Vcd_Put_End;
575
576      --  Extract signals.
577      loop
578         Vhpi_Scan (Decl_It, Decl, Error);
579         exit when Error = AvhpiErrorIteratorEnd;
580         if Error /= AvhpiErrorOk then
581            Avhpi_Error (Error);
582            return;
583         end if;
584
585         case Vhpi_Get_Kind (Decl) is
586            when VhpiPortDeclK
587              | VhpiSigDeclK =>
588               Match_List_Child := Get_Cursor
589                 (Match_List, Avhpi_Get_Base_Name (Decl), Is_Signal => True);
590               if Is_Displayed (Match_List_Child) then
591                  Add_Signal (Decl);
592               end if;
593            when others =>
594               null;
595         end case;
596      end loop;
597
598      --  Extract sub-scopes.
599      if Vhpi_Get_Kind (Inst) /= VhpiPackInstK then
600         Vhpi_Iterator (VhpiInternalRegions, Inst, Decl_It, Error);
601         if Error /= AvhpiErrorOk then
602            Avhpi_Error (Error);
603            return;
604         end if;
605
606         loop
607            Vhpi_Scan (Decl_It, Decl, Error);
608            exit when Error = AvhpiErrorIteratorEnd;
609            if Error /= AvhpiErrorOk then
610               Avhpi_Error (Error);
611               return;
612            end if;
613            case Vhpi_Get_Kind (Decl) is
614               when VhpiIfGenerateK
615                 | VhpiForGenerateK
616                 | VhpiBlockStmtK
617                 | VhpiCompInstStmtK =>
618                  Match_List_Child := Get_Cursor
619                    (Match_List, Avhpi_Get_Base_Name (Decl));
620                  if Is_Displayed (Match_List_Child) then
621                     Vcd_Put_Hierarchy (Decl, Match_List_Child);
622                  end if;
623               when others =>
624                  null;
625            end case;
626         end loop;
627      end if;
628
629      Vcd_Put ("$upscope ");
630      Vcd_Put_End;
631   end Vcd_Put_Hierarchy;
632
633   procedure Vcd_Put_Bit (V : Ghdl_B1)
634   is
635      C : Character;
636   begin
637      if V then
638         C := '1';
639      else
640         C := '0';
641      end if;
642      Vcd_Putc (C);
643   end Vcd_Put_Bit;
644
645   procedure Vcd_Put_Stdlogic (V : Ghdl_E8)
646   is
647      type Map_Type is array (Ghdl_E8 range 0 .. 8) of Character;
648      --                             "UX01ZWLH-"
649   -- Map_Vlg : constant Map_Type := "xx01zz01x";
650      Map_Std : constant Map_Type := "UX01ZWLH-";
651   begin
652      if V not in Map_Type'Range then
653         Vcd_Putc ('?');
654      else
655         Vcd_Putc (Map_Std (V));
656      end if;
657   end Vcd_Put_Stdlogic;
658
659   procedure Vcd_Put_Integer32 (V : Ghdl_U32)
660   is
661      Val : Ghdl_U32;
662      N : Natural;
663   begin
664      Val := V;
665      N := 32;
666      while N > 1 loop
667         exit when (Val and 16#8000_0000#) /= 0;
668         Val := Val * 2;
669         N := N - 1;
670      end loop;
671
672      while N > 0 loop
673         if (Val and 16#8000_0000#) /= 0 then
674            Vcd_Putc ('1');
675         else
676            Vcd_Putc ('0');
677         end if;
678         Val := Val * 2;
679         N := N - 1;
680      end loop;
681   end Vcd_Put_Integer32;
682
683   procedure Vcd_Put_Float64 (V : Ghdl_F64)
684   is
685      Str : String (1 .. 32);
686      Len : Natural;
687   begin
688      --  IEEE1364 18.2 Format of the four state VCD file
689      --  A real number if dumped using a %.16g printf() format.  This
690      --  preserves the precision of that number by outputting all 53 bits in
691      --  the mantissa of a 64-bit IEEE std 754-1985 double-precision number.
692      --  Application programs can read a real number using a %g format to
693      --  scanf().
694
695      --  ISO-C 7.19.6.1 The fprintf function
696      --  [...], the maximum number of significant digits for the g and G
697      --  conversions, [...]
698
699      --  Note: the code always uses the 'e' format, with a full precision.
700      Grt.Fcvt.Format_Image (Str, Len, Interfaces.IEEE_Float_64 (V));
701
702      Vcd_Put (Str (1 .. Len));
703   end Vcd_Put_Float64;
704
705   procedure Vcd_Put_Var (I : Vcd_Index_Type)
706   is
707      V : Verilog_Wire_Info renames Vcd_Table.Table (I);
708      Len : constant Ghdl_Index_Type := Get_Wire_Length (V);
709   begin
710      case V.Vtype is
711         when Vcd_Bit
712           | Vcd_Bool =>
713            Vcd_Put_Bit (Verilog_Wire_Val (V).B1);
714         when Vcd_Stdlogic =>
715            Vcd_Put_Stdlogic (Verilog_Wire_Val (V).E8);
716         when Vcd_Integer32 =>
717            Vcd_Putc ('b');
718            Vcd_Put_Integer32 (Verilog_Wire_Val (V).E32);
719            Vcd_Putc (' ');
720         when Vcd_Float64 =>
721            Vcd_Putc ('r');
722            Vcd_Put_Float64 (Verilog_Wire_Val (V).F64);
723            Vcd_Putc (' ');
724         when Vcd_Bitvector =>
725            Vcd_Putc ('b');
726            for J in 0 .. Len - 1 loop
727               Vcd_Put_Bit (Verilog_Wire_Val (V, J).B1);
728            end loop;
729            Vcd_Putc (' ');
730         when Vcd_Stdlogic_Vector =>
731            Vcd_Putc ('b');
732            for J in 0 .. Len - 1 loop
733               Vcd_Put_Stdlogic (Verilog_Wire_Val (V, J).E8);
734            end loop;
735            Vcd_Putc (' ');
736         when Vcd_Bad
737           | Vcd_Enum8 =>
738            null;
739      end case;
740      Vcd_Put_Idcode (I);
741      Vcd_Newline;
742   end Vcd_Put_Var;
743
744   function Verilog_Wire_Changed (Info : Verilog_Wire_Info; Last : Std_Time)
745                                 return Boolean is
746   begin
747      case Vcd_Value_Signals (Info.Val) is
748         when Vcd_Effective =>
749            case Info.Vtype is
750               when Vcd_Bit
751                 | Vcd_Bool
752                 | Vcd_Enum8
753                 | Vcd_Stdlogic
754                 | Vcd_Integer32
755                 | Vcd_Float64 =>
756                  if To_Signal_Arr_Ptr (Info.Ptr)(0).Last_Event = Last then
757                     return True;
758                  end if;
759               when Vcd_Bitvector
760                 | Vcd_Stdlogic_Vector =>
761                  for J in 0 .. Info.Irange.I32.Len - 1 loop
762                     if To_Signal_Arr_Ptr (Info.Ptr)(J).Last_Event = Last then
763                        return True;
764                     end if;
765                  end loop;
766               when Vcd_Bad =>
767                  null;
768            end case;
769         when Vcd_Driving =>
770            case Info.Vtype is
771               when Vcd_Bit
772                 | Vcd_Bool
773                 | Vcd_Enum8
774                 | Vcd_Stdlogic
775                 | Vcd_Integer32
776                 | Vcd_Float64 =>
777                  if To_Signal_Arr_Ptr (Info.Ptr)(0).Last_Active = Last then
778                     return True;
779                  end if;
780               when Vcd_Bitvector
781                 | Vcd_Stdlogic_Vector =>
782                  for J in 0 .. Info.Irange.I32.Len - 1 loop
783                     if To_Signal_Arr_Ptr (Info.Ptr)(J).Last_Active = Last then
784                        return True;
785                     end if;
786                  end loop;
787               when Vcd_Bad =>
788                  null;
789            end case;
790      end case;
791      return False;
792   end Verilog_Wire_Changed;
793
794   function Verilog_Wire_Event (Info : Verilog_Wire_Info) return Boolean is
795   begin
796      case Info.Vtype is
797         when Vcd_Bit
798           | Vcd_Bool
799           | Vcd_Enum8
800           | Vcd_Stdlogic
801           | Vcd_Integer32
802           | Vcd_Float64 =>
803            if To_Signal_Arr_Ptr (Info.Ptr)(0).Event then
804               return True;
805            end if;
806         when Vcd_Bitvector
807           | Vcd_Stdlogic_Vector =>
808            for J in 0 .. Info.Irange.I32.Len - 1 loop
809               if To_Signal_Arr_Ptr (Info.Ptr)(J).Event then
810                  return True;
811               end if;
812            end loop;
813         when Vcd_Bad =>
814            null;
815      end case;
816      return False;
817   end Verilog_Wire_Event;
818
819   procedure Vcd_Put_Time
820   is
821      Str : String (1 .. 21);
822      First : Natural;
823   begin
824      Vcd_Putc ('#');
825      To_Strings.To_String (Str, First, Ghdl_I64 (Current_Time));
826      Vcd_Put (Str (First .. Str'Last));
827      Vcd_Newline;
828   end Vcd_Put_Time;
829
830   procedure Vcd_Cycle;
831
832   --  Called after elaboration.
833   procedure Vcd_Start
834   is
835      Pack_It : VhpiHandleT;
836      Pack : VhpiHandleT;
837      Error : AvhpiErrorT;
838      Root : VhpiHandleT;
839      Match_List : Design.Match_List;
840   begin
841      --  Do nothing if there is no VCD file to generate.
842      if Vcd_Close = null then
843         return;
844      end if;
845
846      --  Be sure the RTI of std_ulogic is set.
847      Search_Types_RTI;
848
849      --  Put hierarchy.
850
851      --  First packages.
852      Get_Package_Inst (Pack_It);
853      loop
854         Vhpi_Scan (Pack_It, Pack, Error);
855         exit when Error = AvhpiErrorIteratorEnd;
856         if Error /= AvhpiErrorOk then
857            Avhpi_Error (Error);
858            return;
859         end if;
860         Match_List := Get_Top_Cursor (Pkg, Avhpi_Get_Base_Name (Pack));
861         if Is_Displayed (Match_List) then
862            Vcd_Put_Hierarchy (Pack, Match_List);
863         end if;
864      end loop;
865
866      --  Then top entity.
867      Get_Root_Inst (Root);
868      Match_List := Get_Top_Cursor (Entity, Avhpi_Get_Base_Name (Root));
869      if Is_Displayed (Match_List) then
870         Vcd_Put_Hierarchy (Root, Match_List);
871      end if;
872      Wave_Opt.Design.Last_Checks;
873
874      --  End of header.
875      Vcd_Put ("$enddefinitions ");
876      Vcd_Put_End;
877
878      Register_Cycle_Hook (Vcd_Cycle'Access);
879   end Vcd_Start;
880
881   --  Called before each non delta cycle.
882   procedure Vcd_Cycle is
883   begin
884      --  Disp values.
885      Vcd_Put_Time;
886      if Current_Time = 0 then
887         --  Disp all values.
888         for I in Vcd_Table.First .. Vcd_Table.Last loop
889            Vcd_Put_Var (I);
890         end loop;
891      else
892         --  Disp only values changed.
893         for I in Vcd_Table.First .. Vcd_Table.Last loop
894            if Verilog_Wire_Changed (Vcd_Table.Table (I), Current_Time) then
895               Vcd_Put_Var (I);
896            end if;
897         end loop;
898      end if;
899   end Vcd_Cycle;
900
901   --  Called at the end of the simulation.
902   procedure Vcd_End is
903   begin
904      if Vcd_Close /= null then
905         Vcd_Close.all;
906      end if;
907   end Vcd_End;
908
909   Vcd_Hooks : aliased constant Hooks_Type :=
910     (Desc => new String'("vcd: save waveforms in vcf file format"),
911      Option => Vcd_Option'Access,
912      Help => Vcd_Help'Access,
913      Init => Vcd_Init'Access,
914      Start => Vcd_Start'Access,
915      Finish => Vcd_End'Access);
916
917   procedure Register is
918   begin
919      Register_Hooks (Vcd_Hooks'Access);
920   end Register;
921end Grt.Vcd;
922