6cd96208d43e03bf512c2b17e84433cee5934dc7
[libxhcidbg.git] / src / hw-dbc.adb
1 --
2 -- Copyright (C) 2016-2017 secunet Security Networks AG
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
15 with System;
16
17 with HW.Time;
18 with HW.Debug;
19
20 with HW.DbC.Intel_Quirk;
21 with HW.DbC.DMA_Buffers;
22 with HW.DbC.Transfer_Info;
23 with HW.DbC.Transfer_Rings;
24 with HW.DbC.Transfers;
25 with HW.DbC.Contexts;
26 with HW.DbC.Events;
27 with HW.DbC.TRBs;
28
29 package body HW.DbC
30 with
31    Refined_State => (State => (Connected, Running,
32                                DbC_Run_Deadline, DbC_Poll_Deadline,
33                                DbC_Stat_Deadline, Events.State,
34                                Transfer_Info.State, Transfer_Rings.State),
35                      DMA   => (ERST, DbC_Context, Desc_Strings, Events.DMA,
36                                Transfer_Rings.DMA))
37 is
38
39    Apply_Intel_Quirk : constant Boolean := True;
40    Debug_xCap        : constant Boolean := False;
41
42    Connected         : Boolean := False;
43    Running           : Boolean := False;
44    DbC_Run_Deadline  : Time.T  := Time.T_First;
45    DbC_Poll_Deadline : Time.T  := Time.T_First;
46    DbC_Stat_Deadline : Time.T  := Time.T_First;
47
48    ----------------------------------------------------------------------------
49
50    ERST : Events.ERST_Entry
51    with
52       Address => System'To_Address (DMA_Buffers.Event_Ring_Segment_Table_Base);
53
54    DbC_Context : Contexts.DbC_Context
55    with
56       Address => System'To_Address (DMA_Buffers.DbC_Context_Base);
57
58    ----------------------------------------------------------------------------
59
60    subtype Desc_Str_Range is Natural range 0 .. 14;
61    type Desc_Str is array (Desc_Str_Range) of Word16 with Pack;
62    type String_Descriptor is record
63       bLength           : Byte;
64       bDescriptor_Type  : Byte;
65       wData             : Desc_Str;
66    end record with Pack;
67
68    Null_String_Desc : constant String_Descriptor
69      := (bLength          => 0,
70          bDescriptor_Type => 0,
71          wData            => (others => 0));
72
73    type Desc_Strings_Type is (String0, Manufacturer, Product, Serial_Number);
74    type Desc_Strings_Array is
75       array (Desc_Strings_Type) of String_Descriptor with Pack;
76    Desc_Strings : Desc_Strings_Array := (others => Null_String_Desc)
77    with
78       Address => System'To_Address (DMA_Buffers.Descriptor_Strings_Base);
79
80    procedure String_To_Desc (Dst : out String_Descriptor; Src : in String)
81    is
82       use type Byte;
83    begin
84       Dst.bLength := 2 + 2 * Byte'Min (Dst.wData'Length, Src'Length);
85       Dst.bDescriptor_Type := 16#03#;
86       for I in Desc_Str_Range loop
87          if I < Src'Last then
88             Dst.wData (I) := Character'Pos (Src (I + 1));
89          else
90             Dst.wData (I) := 16#0000#;
91          end if;
92       end loop;
93    end String_To_Desc;
94
95    ----------------------------------------------------------------------------
96
97    procedure Find_Next_xCap (Cap_Id : in Word8; Success : out Boolean)
98    is
99       use type Word8;
100       use type Word32;
101       Current_Id : Word8;
102       Temp_Offset : Word32;
103    begin
104       Success := False;
105       if xCap_Regs.Byte_Offset = 0 then
106          Cap_Regs.Read (Temp_Offset, XHCI_Extended_Caps);
107       else
108          xCap_Regs.Read (Temp_Offset, Next_xCap);
109       end if;
110       loop
111          Temp_Offset := Shift_Left (Temp_Offset, 2);
112          pragma Debug (Debug_xCap, Debug.Put_Reg32
113            ("Find_Next_xCap Offset", Temp_Offset));
114          exit when
115             Temp_Offset = 0 or else
116             xCap_Regs.Byte_Offset > MMIO_Size - Natural (Temp_Offset) - 2;
117
118          xCap_Regs.Byte_Offset := xCap_Regs.Byte_Offset + Natural (Temp_Offset);
119
120          xCap_Regs.Read (Current_Id, Capability_ID);
121          Success := Current_Id = Cap_Id;
122          pragma Debug (Debug_xCap, Debug.Put_Reg8
123            ("Find_Next_xCap Cap_Id", Current_Id));
124          exit when Success;
125
126          xCap_Regs.Read (Temp_Offset, Next_xCap);
127       end loop;
128    end Find_Next_xCap;
129
130    ----------------------------------------------------------------------------
131
132    procedure BIOS_Handover (Success : out Boolean)
133    is
134       use type Word8;
135       BIOS_Owned  : Word8;
136       Deadline    : Time.T;
137    begin
138       xCap_Regs.Byte_Offset := 0;
139       Find_Next_xCap (1, Success);
140       if Success then
141          Legacy_Support_Regs.Byte_Offset := xCap_Regs.Byte_Offset;
142          -- See if the BIOS claims ownership
143          Legacy_Support_Regs.Read (BIOS_Owned, HC_BIOS_Owned_Semaphore);
144          if BIOS_Owned = 1 then
145             pragma Debug (Debug.Put_Line ("DbC: BIOS claims ownership."));
146
147             Legacy_Support_Regs.Write (HC_OS_Owned_Semaphore, Word8'(1));
148
149             Deadline := Time.MS_From_Now (5_000);
150             loop
151                Legacy_Support_Regs.Read (BIOS_Owned, HC_BIOS_Owned_Semaphore);
152                exit when BIOS_Owned = 0;
153                declare
154                   Timeout : constant Boolean := Time.Timed_Out (Deadline);
155                begin
156                   Success := not Timeout;
157                end;
158                exit when not Success;
159                pragma Warnings (GNATprove, Off, "statement has no effect");
160                for I in 0 .. 1234 loop
161                   null; -- Busy loop to reduce pressure on HC BIOS Owned
162                         -- Semaphore. It shouldn't generate an SMI but
163                         -- might congest the xHC?
164                end loop;
165                pragma Warnings (GNATprove, On, "statement has no effect");
166             end loop;
167
168             pragma Debug (not Success, Debug.Put_Line
169               ("ERROR: BIOS didn't hand over xHC within 5s."));
170             pragma Debug (Success, Debug.Put_Line
171               ("DbC: BIOS hand-over succeeded."));
172          end if;
173       end if;
174    end BIOS_Handover;
175
176    procedure Reset (Initial_Reset : Boolean := False);
177
178    procedure Init
179    is
180       use type Word8;
181       CNR : Word8;
182       Deadline : Time.T;
183       Success : Boolean;
184       Cap_Length : Word8;
185    begin
186       Cap_Regs.Read (Cap_Length, Capability_Registers_Length);
187       Op_Regs.Byte_Offset := Natural (Cap_Length);
188
189       Op_Regs.Read (CNR, Controller_Not_Ready);
190       Success := CNR = 0;
191
192       if not Success then
193          pragma Debug (Debug.Put_Line ("WARNING: xHCI not ready!"));
194          Deadline := Time.MS_From_Now (1_000);
195          Success := True;
196          loop
197             Op_Regs.Read (CNR, Controller_Not_Ready);
198             exit when CNR = 0;
199             declare
200                Timed_Out : constant Boolean := Time.Timed_Out (Deadline);
201             begin
202                Success := not Timed_Out;
203             end;
204             exit when not Success;
205          end loop;
206          pragma Debug (not Success, Debug.Put_Line
207            ("ERROR: xHC not ready after 1s."));
208       end if;
209
210       if Success then
211          BIOS_Handover (Success);
212       end if;
213
214       if Success then
215          xCap_Regs.Byte_Offset := 0;
216          Find_Next_xCap (10, Success);
217       end if;
218
219       pragma Debug (not Success, Debug.Put_Line
220                     ("ERROR: Couldn't find xHCI debug capability."));
221
222       if Success then
223          Regs.Byte_Offset := xCap_Regs.Byte_Offset;
224
225          ERST := Events.ERST_Entry'
226            (Segment_Base   => DMA_Buffers.Event_Ring_Base,
227             Segment_Size   => TRBs.TRBs_Per_Ring,
228             Reserved_Z     => 0);
229
230          Desc_Strings (String0).bLength            := 16#04#;
231          Desc_Strings (String0).bDescriptor_Type   := 16#03#;
232          Desc_Strings (String0).wData := (0 => 16#0409#, others => 16#0000#);
233          String_To_Desc (Desc_Strings (Manufacturer), "secunet");
234          String_To_Desc (Desc_Strings (Product), "HW.DbC");
235          String_To_Desc (Desc_Strings (Serial_Number), "1");
236
237          Reset (Initial_Reset => True);
238       end if;
239    end Init;
240
241    ----------------------------------------------------------------------------
242
243    procedure Reset (Initial_Reset : Boolean := False)
244    is
245       use type Word8;
246       use type Word16;
247       use type Word64;
248       DCE,
249       MBS : Word8;
250    begin
251       if Regs.Byte_Offset /= 0 then
252          Regs.Write (DbC_Enable, Word8'(0));
253          loop
254             Regs.Read (DCE, DbC_Enable);
255             exit when DCE = 0;
256          end loop;
257
258          Transfers.Reset (Initial_Reset);
259
260          Regs.Write (ERST_Size, Word16'(1));
261          Regs.Write (ERST_Base_Lo, Word32
262            (DMA_Buffers.Event_Ring_Segment_Table_Base mod 16#1_0000_0000#));
263          Regs.Write (ERST_Base_Hi, Word32
264            (DMA_Buffers.Event_Ring_Segment_Table_Base  /  16#1_0000_0000#));
265          Events.Reset_Ring;
266
267          Regs.Write (ER_Dequeue_Ptr_Lo, Word32
268            (DMA_Buffers.Event_Ring_Base mod 16#1_0000_0000#));
269          Regs.Write (ER_Dequeue_Ptr_Hi, Word32
270            (DMA_Buffers.Event_Ring_Base  /  16#1_0000_0000#));
271
272          Regs.Write (Context_Pointer_Lo, Word32
273            (DMA_Buffers.DbC_Context_Base mod 16#1_0000_0000#));
274          Regs.Write (Context_Pointer_Hi, Word32
275            (DMA_Buffers.DbC_Context_Base  /  16#1_0000_0000#));
276
277          Contexts.Clear_DbC_Context (DbC_Context);
278          DbC_Context.DbC_Info :=
279            (String_0_Address              => DMA_Buffers.Descriptor_Strings_Base,
280             Manufacturer_String_Address   => DMA_Buffers.Descriptor_Strings_Base
281                                              + 1 * String_Descriptor'Size / 8,
282             Product_String_Address        => DMA_Buffers.Descriptor_Strings_Base
283                                              + 2 * String_Descriptor'Size / 8,
284             Serial_Number_String_Address  => DMA_Buffers.Descriptor_Strings_Base
285                                              + 3 * String_Descriptor'Size / 8,
286             String_0_Length               => Desc_Strings (String0).bLength,
287             Manufacturer_String_Length    => Desc_Strings (Manufacturer).bLength,
288             Product_String_Length         => Desc_Strings (Product).bLength,
289             Serial_Number_String_Length   => Desc_Strings (Serial_Number).bLength,
290             Reserved_Z                    => 0,
291             others                        => 0);
292
293          Regs.Read (MBS, Debug_Max_Burst_Size);
294          DbC_Context.OUT_EP.EP_Type                := Contexts.Bulk_O;
295          DbC_Context.OUT_EP.Max_Burst_Size         := MBS;
296          DbC_Context.OUT_EP.Max_Packet_Size        := 1024;
297          DbC_Context.OUT_EP.TR_Dequeue_Pointer_Lo  := Word28
298            (Shift_Right (Transfer_Rings.Physical (2),  4) and 16#0fff_ffff#);
299          DbC_Context.OUT_EP.TR_Dequeue_Pointer_Hi  := Word32
300            (Shift_Right (Transfer_Rings.Physical (2), 32) and 16#ffff_ffff#);
301          DbC_Context.OUT_EP.Dequeue_Cycle_State    := 1;
302          DbC_Context.OUT_EP.Average_TRB_Length     := Max_Bulk_Size / 2;
303          DbC_Context.IN_EP.EP_Type                 := Contexts.Bulk_I;
304          DbC_Context.IN_EP.Max_Burst_Size          := MBS;
305          DbC_Context.IN_EP.Max_Packet_Size         := 1024;
306          DbC_Context.IN_EP.TR_Dequeue_Pointer_Lo   := Word28
307            (Shift_Right (Transfer_Rings.Physical (3),  4) and 16#0fff_ffff#);
308          DbC_Context.IN_EP.TR_Dequeue_Pointer_Hi   := Word32
309            (Shift_Right (Transfer_Rings.Physical (3), 32) and 16#ffff_ffff#);
310          DbC_Context.IN_EP.Dequeue_Cycle_State     := 1;
311          DbC_Context.IN_EP.Average_TRB_Length      := Max_Bulk_Size / 2;
312
313          Regs.Write (DbC_Protocol, Word16'(0));  -- Debug Target vendor defined.
314          Regs.Write (Vendor_ID, Word16 (16#ffff#));
315          Regs.Write (Product_ID, Word16 (16#dbc1#));
316          Regs.Write (Device_Revision, Word16 (16#0001#));
317
318          Regs.Write (DbC_Enable, Word8'(1));
319          loop
320             Regs.Read (DCE, DbC_Enable);
321             exit when DCE = 1;
322          end loop;
323
324          if Apply_Intel_Quirk then
325             Intel_Quirk.Reset_Port;
326          end if;
327
328          Running := False;
329          Connected := False;
330          DbC_Poll_Deadline := Time.Now;
331          DbC_Stat_Deadline := Time.MS_From_Now (12_345);
332       end if;
333    end Reset;
334
335    procedure Poll (Now : Boolean := False)
336    is
337       use type Word8;
338
339       Temp8 : Word8;
340       Timed_Out : Boolean;
341    begin
342       if Regs.Byte_Offset /= 0 then
343          Timed_Out := Time.Timed_Out (DbC_Poll_Deadline);
344          if Now or else Timed_Out then
345             Regs.Read (Temp8, DbC_Enable);
346             if Temp8 = 1 then
347                Regs.Read (Temp8, Current_Connect_Status);
348                if Temp8 = 1 then
349                   -- Something is connected...
350                   DbC_Poll_Deadline := Time.MS_From_Now (10);
351                   if not Connected then
352                      pragma Debug (Debug.Put_Line ("DbC connected."));
353                      DbC_Run_Deadline := Time.MS_From_Now (333);
354                      Connected := True;
355                   end if;
356                   Regs.Read (Temp8, DbC_Run);
357                   if Temp8 = 1 then
358                      -- ...configured too
359                      if not Running then
360                         pragma Debug (Debug.Put_Line ("DbC configured."));
361                         Transfers.Start;
362                         Running := True;
363                      end if;
364                   elsif Running then
365                      pragma Debug (Debug.Put_Line
366                        ("DbC still connected but deconfigured."));
367                      DbC_Run_Deadline := Time.MS_From_Now (333);
368                      Running := False;
369                   else
370                      Timed_Out := Time.Timed_Out (DbC_Run_Deadline);
371                      if Timed_Out then
372                         pragma Debug (Debug.Put_Line
373                           ("DbC connection timed out."));
374                         Reset;
375                      end if;
376                   end if;
377                else
378                   -- Nothing connected
379                   DbC_Poll_Deadline := Time.MS_From_Now (333);
380                   if Connected then
381                      pragma Debug (Debug.Put_Line ("DbC disconnected."));
382                      Connected := False;
383                      Running := False;
384                   end if;
385                end if;
386             else
387                pragma Debug (Debug.Put_Line ("DbC got disabled, huh?"));
388                Reset;
389             end if;
390             Events.Handle_Events;
391             Timed_Out := Time.Timed_Out (DbC_Stat_Deadline);
392             if Timed_Out then
393                pragma Debug (Transfer_Info.Dump_Stats);
394                DbC_Stat_Deadline := Time.MS_From_Now (12_345);
395             end if;
396          end if;
397       end if;
398    end Poll;
399
400    procedure Receive (Buf : in out Buffer; Len : in out Natural)
401    is
402    begin
403       Poll (Now => True);
404
405       Transfers.Receive (Buf, Len);
406    end Receive;
407
408    procedure Send (Buf : Buffer; Len : in out Natural; Success : out Boolean)
409    is
410    begin
411       Poll (Now => True);
412
413       Transfers.Send
414         (Buf         => Buf,
415          Len         => Len,
416          Start_Now   => Running,
417          Success     => Success);
418    end Send;
419
420    procedure Ring_Doorbell (EP : Endpoint_Range)
421    is
422       use type Word8;
423    begin
424       Regs.Write (Doorbell_Target, Word8 (EP) - 2);
425    end Ring_Doorbell;
426
427 end HW.DbC;
428
429 --  vim: set ts=8 sts=3 sw=3 et: