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