1% this file is prolog
2% It contains special comments
3%>> GENERIC
4:- lib(ic).
5:- lib(lists).
6
7:- [objects3].
8
9% The mapf predicate describes a single mapping entry of a controller
10% mapf(ControllerLabel, InPort, InMsg, OutPort, OutMsg)
11% Example:
12% mapf(msi_a, 100, nullMsg, 11, mem_write(110, 230))
13:- dynamic(mapf/5).
14
15% The controller predicate describes an instance of a controller
16% See below for details.
17% controller(ControllerLabel, ControllerClass, InputRange, OutputRange)
18:- dynamic(controller/4).
19
20% The int_dest_used predicate describes which interrupt sinks are currently
21% in use.
22% int_dest_used(CpuNumber,VectorNumber).
23:- dynamic(int_dest_used/2).
24
25% This is also defined in queries.pl
26:- dynamic(interrupt_override/4).
27
28
29%>> X86
30% X86 specific. To find an IOAPIC given a GSI, the system must know
31% which GSI base number belongs to a.
32% ioapic_gsi_base(Label, Base)
33:- dynamic(ioapic_gsi_base/2).
34
35% Link the PCI controller label with an addr(...)
36:- dynamic(pci_lbl_addr/2).
37
38% X86 int model with one argument with a single atom that indicates
39% the system is using one of the interrupt models.
40% atoms currently used is
41% pic, apic (pic and apic at the same time are not possible)
42% iommu, x2_apic_opt_out
43%:- dynamic(x86_interrupt_model/1).
44%
45
46
47% X86 specific. irte index links the Index used in the dmar_* predicates
48% to the corresponding irte and iommu controller label.
49% Example: irte_index(0, irte_a, iommu_a).
50:- dynamic(irte_index/3).
51:- dynamic(dmar/1).
52:- dynamic(dmar_device/5).
53% PCI specific, Links an ACPI PCI LNK name to a controller label
54% Example pcilnk_index("\\_SB_.GSIE", pcilnk_a)
55:- dynamic(pcilnk_index/2).
56%>> X86
57
58
59
60%>> GENERIC
61% Documentation
62% =============
63
64%% Examples:
65% Checking if a single mapping is valid for a given controller:
66% mapf_valid(msi_a, 100, nullMsg, 11, mem_write(110, 230)).    --> true
67% assert(mapf(msi_a, 100, nullMsg, 11, mem_write(110, 230))).   --> true
68% mapf_valid(msi_a, 101, nullMsg, 11, mem_write(110, 231)).     --> true
69% mapf_valid(msi_a, 101, nullMsg, 11, mem_write(110, 230)).     --> false
70
71% Example 1: Calculate an arbitrary destination for interrupt input 100.
72% route(100, nullMsg, Port, Msg, Li), term_variables(Li,List), labeling(List).
73
74% Example 2: Calculate a from interrupt input 100 to core=3
75% Port=3, route(100, nullMsg, Port, Msg, Li), term_variables(Li,List), labeling(List).
76
77% Example 3: Calculate, install and print the route
78% find_and_add_irq_route(100, 1).
79%
80% Example 4: Remove the route installed in Ex3
81% get_route(100,nullMsg,Li), remove_route(Li).
82
83
84%% Controller class
85% There are class labels that describe a controller class, such as
86% pic, msi, msix. Each controller class consists of the following predicates.
87% It must take care of ensuring the OutMsg has the right format, either a
88% IC constraint must be applied (ieL OutMsg :: [1..10]) or it must be unified to a
89% mem_write(_,_) term (ie: OutMsg = mem_write(A,B)).
90
91% mapf_valid_class(controller_class, controller_label, InPort, nullMsg, OutPort, OutMsg)
92
93%% Controller
94% Each controller gets a label (an atom, ie pic_a, belongs to a given
95% class (atom, such as pic), has a InPort range and a OutPort range.
96% controller_class(ControllerLabel, ControllerClass, InPortRange, OutPortRange).
97% controller_class(pic_a, pic, [0 .. 8], [100]).
98% This checks for a concrete instance if a mapping is legal.
99% mapf_valid(controller_label, InPort, nullMsg, OutPort, OutMsg)
100% Examples:
101% controller(pic_a, pic, [100 .. 116], [1]).
102% controller(msi_a, msi, [200 .. 204], [300]).
103% controller(msix_a, msix, [400 .. 416], [300]).
104% controller(msireceiver_a, msireceiver, [300], [1 .. 48]).
105% controller(irte_a, irte, [300], [301]).
106% controller(iommu_a, iommu, [301], [1 .. 48]).
107
108%% Words
109% It is not possible to directly set constraints on bit fields in IC
110% constrained integers.
111% Example how to use words:
112% Constrain bits 20 to 21 to contain the value 2:
113% assert_word(W,32), subword(W, Sw, 20..21), word_to_num(Sw,2).
114
115
116% Utility predicates
117% ==================
118% last element of list (from lib listut)
119last(Last, [Last]) :- !.
120last(Last, [_|List]) :-
121        last(Last, List).
122
123% This predicate gets the upper bound of a range
124get_max_range(Range, Hi) :-
125    X :: Range,
126    get_max(X, Hi).
127
128% This predicate gets the upper bound of a range
129get_min_range(Range, Lo) :-
130    X :: Range,
131    get_min(X, Lo).
132
133% Constrains word to be a N bit word
134assert_word(W, N) :-
135    dim(W,[N]), W :: [0 .. 1].
136
137% This beauty converts words (array of bit values) to a numeric representation.
138word_to_num(W, Num) :-
139    dim(W, [Len]),
140    (for(I,1,Len), fromto(0,In,Out,NumT), param(W) do
141        Out = W[I] * 2^(I-1) + In),
142    Num $= eval(NumT).
143
144% A part of word is etracted into Subword, Range specifies
145subword(Word,Subword, Range) :-
146    SW is Word[Range],
147    array_list(Subword,SW).
148
149
150
151
152
153%>> ARM
154% Controller constraints
155
156mapf_valid_class(gicv2, CtrlLabel, InPort, InMsg, OutPort, OutMsg) :-
157    OutMsg = InMsg.
158
159%>> X86
160% Controller constraints
161% ======================
162
163% The PCI controller simply forwards (or discards) nullMsg
164mapf_valid_class(pci, _, _, nullMsg, _, nullMsg) :-
165    true.
166
167%% A MSI controller must output to the same port, and there must be consecutive
168%% data words for all inputs.
169mapf_valid_class(msi, CtrlLabel, InPort, nullMsg, _, mem_write(OutAddr, OutData)) :-
170    % If there is a mapf for this controller, same OutPort and
171    % Consecutive data words
172    (mapf(CtrlLabel, EInPort, _, _, mem_write(EOutAddr, EOutData) )
173    -> ((EInPort - InPort) $= (EOutData - OutData), OutAddr = EOutAddr) ; true).
174
175% A MSIx controller must output a mem_write, otherwise no constraints.
176% For every source of MSIx interrupts, one of this controllers
177% should be instantiated (ie one for each PCI function)
178mapf_valid_class(msix, _, _, _, _, mem_write(_, _)) :-
179    true.
180
181% This one enables the MSI-X in the PCI conf header. Can only forward interrupts without
182% remap.
183mapf_valid_class(pci_msix, CtrlLabel, InPort, Msg, OutPort, Msg) :-
184    controller(CtrlLabel, _, InRange, OutRange),
185    get_min_range(InRange, InLo),
186    get_min_range(OutRange, OutLo),
187    (InPort - InLo) $= (OutPort - OutLo).
188
189
190% In systems without an IOMMU, the translation from memory
191% writes to CPU interrupts happens in the northbridge?
192% We model this (fixed) translation here.
193% The vector is encoded in the lower 8 bit of the data word,
194% The destination is encoded in the 12..19 bits of the address.
195mapf_valid_class(msireceiver, _, _, mem_write(Addr, Data), OutPort, OutMsg) :-
196    int_dest_port(OutPort),
197
198    % This forces the upper bits to be 0, which must not be true. See Vol. 3A 10-35
199    Data :: [ 16'10 .. 16'FE ],
200    Data = OutMsg,
201    Addr :: [ 16'FEE00000 .. 16'FEE0FFFF],
202    assert_word(AddrW, 32),
203    word_to_num(AddrW, Addr),
204    subword(AddrW,DestW, 13 .. 20), % The range is 1 based equals to 0 based 12 .. 19
205    word_to_num(DestW, OutPort).
206
207
208% The PIC has a fixed function. The lowest input port number must map
209% to vector 32 and consecutive
210mapf_valid_class(pic, CtrlLabel, InPort, nullMsg, _, OutMsg) :-
211    controller(CtrlLabel, _, InRange, _),
212    get_min_range(InRange, Xlo),
213    OutMsg $= InPort - Xlo + 32.
214
215% The IRTE mapper has a fixed function.
216mapf_valid_class(irte, _, _, mem_write(InAddr,InData), _, OutMsg) :-
217    InAddr :: [16'0FEE0000 .. 16'0FEEFFFF],
218    % Actually the InData is not constrained to 0..2^16, but only the
219    % lower 16 bits are considered for the index calculation.
220    InData :: [0 .. 2^16],
221    InAddrLo $= InAddr - 16'0FEE0000, %No bitwise operations with IC lib.
222    OutMsg $= InAddrLo + InData.
223
224% The mem write gets captured by the irte, hence the iommu is constrained by the number of slots.
225mapf_valid_class(iommu, _, _, InMsg, _, _) :-
226    InMsg :: [ 0 .. 2 ^ 16].
227
228% IOAPIC that is directly connected to CPU
229mapf_valid_class(ioapic, _, _, _, _, OutMsg) :-
230    OutMsg :: [ 32 .. 255 ].
231
232% The pci link device can install any mapping between
233% its in- and outport
234mapf_valid_class(pcilnk, _, _, nullMsg, _, nullMsg) :-
235    true.
236
237% IOAPIC that is connected to the iommu.
238% The fields of the ioredtbl are interpreted differently, depending on
239% the presence of an iommu.
240mapf_valid_class(ioapic_iommu, _, _, _, _, OutMsg) :-
241    OutMsg :: [ 0 .. 2^16 ].
242
243%>> GENERIC
244input_to_int_tuple((InPort,InMsg), OutInt) :- input_to_int(InPort, InMsg, OutInt).
245
246% delay if there is any variable in InPort or InMsg.
247delay input_to_int(InPort, InMsg, OutInt) if var(InPort); var(InMsg); (InMsg = mem_write(A,B), (var(A) ; var(B))).
248input_to_int(InPort, InMsg, OutInt) :-
249    (InMsg = nullMsg) -> OutInt is InPort ;
250    (InMsg = mem_write(A,B)) -> OutInt is A * 1024 + B ;
251    OutInt is InPort + InMsg * 1024.
252
253% The mapf validity check function for a controller instance.
254% It takes into account static constraints from the controller class
255% but also the runtime configuration. It will not allow to overrite
256% an already installed mapping.
257mapf_valid(ControllerLabel, InPort, Msg, OutPort, OutMsg) :-
258    % Constraint In and OutRange.
259    controller(ControllerLabel, _, InRange, OutRange),
260    InPort :: InRange,
261    OutPort :: OutRange,
262
263    % Check class constraints.
264    controller(ControllerLabel, ControllerClass, _, _),
265    mapf_valid_class(ControllerClass, ControllerLabel, InPort, Msg, OutPort, OutMsg),
266
267    ((findall((YIn,YMsg), mapf(ControllerLabel, YIn, YMsg, _, _), Li),
268    maplist(input_to_int_tuple, Li, Li2),
269    input_to_int(InPort, Msg, InInt),
270    append(Li2, [InInt], Li3),
271    flatten(Li3, Li4),
272    alldifferent(Li4)
273    )).
274
275    % ; (   % This section is commented out. It would allow to reuse an existing mapping,
276    %       % but as the int dest are not used, this makes not sense yet.
277    %% Option 2: Re-use an installed mapping.
278    %    mapf(ControllerLabel, InPort, Msg, OutPort, OutMsg)
279    %)),
280
281
282
283% Locate a controller given an inport
284find_controller(InPort, CtrlLabel) :-
285    controller(CtrlLabel, _, InRange, _),
286    InPort :: InRange.
287
288% Makes sure int_dest_used(OutPort,OutMsg) are unique.
289int_dest_unique(OutPort, OutMsg) :-
290    findall(X, int_dest_used(OutPort,X), Li),
291    append(Li, [OutMsg], Li2),
292    alldifferent(Li2).
293
294
295% Try to find a route (without installing the mapping) between InPort and OutPort and OutMsg
296route(InPort, InMsg, OutPort, OutMsg, List) :-
297    find_controller(InPort, CtrlLabel),
298    mapf_valid(CtrlLabel, InPort, InMsg, NOutPort, NOutMsg),
299    (
300        (int_dest_port(NOutPort),NOutPort = OutPort)  ->
301            (
302             NOutMsg = OutMsg,
303             int_dest_msg(OutMsg),
304             int_dest_unique(OutPort, OutMsg),
305             List = [mapf(CtrlLabel, InPort, InMsg, NOutPort, NOutMsg)]
306            ) ; (
307                route(NOutPort, NOutMsg, OutPort, OutMsg, NList),
308                append([mapf(CtrlLabel, InPort, InMsg, NOutPort, NOutMsg)], NList, List)
309            )
310    ).
311
312
313% Translate the port indices of a mapf entry to zero based entries
314to_mapf_local(mapf(Lbl,A,B,C,D), Out) :-
315    controller(Lbl, _, InRange, OutRange),
316    get_min_range(InRange, InLo),
317    get_min_range(OutRange, OutLo),
318    AOut #= A - InLo,
319    COut #= C - OutLo,
320    Out = mapf(Lbl,AOut,B,COut,D).
321
322
323
324% Given a list of mapf entries, it adds the terms to the database,
325% effectively installing the route. Also assert int_dest_used for the
326% last entry.
327add_route(Li) :-
328    (foreach(L, Li) do
329        assert(L)),
330    last(mapf(_,_,_,LastPort,LastMsg), Li),
331    assert(int_dest_used(LastPort,LastMsg)).
332
333% Removes a route. The opposite of add_route. To
334% get a route, use get_route first.
335remove_route(Li) :-
336    (foreach(L, Li) do
337        retract(L)),
338    last(mapf(_,_,_,LastPort,LastMsg), Li),
339    retract(int_dest_used(LastPort,LastMsg)).
340
341
342
343% Gets a list with consecutive mapf entries for a installed route
344% Same format as produced from route(..).
345get_route(InPort, InMsg, Li) :-
346    mapf(CtrlLbl, InPort, InMsg, NextPort, NextMsg) ->
347        ( get_route(NextPort, NextMsg, NLi),
348          append([mapf(CtrlLbl, InPort, InMsg, NextPort, NextMsg)], NLi, Li))
349        ; ( Li = []).
350
351
352% Given a list of mapf entries, print parseable list of entries.
353% All port numbers are  0 based with respect to the controller in- resp. out-port range.
354% The ouput is multiple lines, each describing the mapping for one controller.
355% The format of a line is:
356% controllerlabel,inport,inmessage,outport,outmessage
357% Except the last line, that denotes the vector triggered at the cpu, the line
358% follows the format
359% cpu,cpuid,vector
360print_route(Li) :-
361    (foreach(mapf(Lbl,A,B,C,D), Li) do (
362        to_mapf_local(mapf(Lbl,A,B,C,D), mapf(_,ALocal,_,CLocal,_)),
363        controller(Lbl, Class, _,_),
364        printf(output, "%s,%s,%d,%Kw,%d,%Kw\n",[Lbl,Class,ALocal,B,CLocal,D]))).
365    %% This adds an extra line indicating dest cpu and vector
366    %last(mapf(Lbl,A,B,C,D), Li),
367    %to_mapf_local(mapf(Lbl,A,B,C,D), mapf(_,_,_,CLocal,_)),
368    %printf(output, "cpu,%d,%d\n", [CLocal,D]).
369
370
371% Returns true if this PortNumber is a interrupt destination.
372% We use the Barrelfish CoreId as identifier
373% TODO: Upper bound of CoreId shouldnt be hardcoded (here).
374int_dest_port(Port) :-
375    %corename(Port, _, _). % Does not work bc synchronization issues
376    Port :: [0 .. 1000],
377    labeling([Port]).
378
379% Returns a list of integers representing the int destinations
380int_dest_port_list(Li) :-
381    findall(X, int_dest_port(X), Li).
382
383%>> X86
384% Returns true if this Msg is acceptable as being delivered to a destination
385int_dest_msg(Msg) :-
386    Msg :: [32 .. 255].
387
388
389% Scans all controller and sinkPortRange and returns the maximum used port number
390max_used_port(OutMax) :-
391    findall(Ri, controller(_,_,Ri,_), RangeList1),
392    findall(Ri, controller(_,_,_,Ri), RangeList2),
393    append(RangeList1, RangeList2, RangeList),
394    maplist(get_max_range, RangeList, MaxList2),
395    % Due to synchronization issues, we cant use the following two lines
396    %findall(Ri, int_dest_port(Ri), MaxList1),
397    %append(MaxList1, MaxList2, MaxList),
398    append([1000], MaxList2, MaxList),
399    ic:max(MaxList, OutMax).
400
401
402% Prints mapf routing entries for a given controller.
403print_controller_config(CtrlLbl) :-
404    findall( mapf(CtrlLbl, A, B, C, D), mapf(CtrlLbl, A, B, C, D), ML),
405    printf(output, "Printing controller config for %s\n", [CtrlLbl]),
406    (foreach(mapf(Lbl,A,B,C,D), ML) do (
407        to_mapf_local(mapf(Lbl,A,B,C,D), mapf(_,ALocal,_,CLocal,_)),
408        printf("%d,%Kw,%d,%Kw\n", [ALocal,B,CLocal,D]))).
409
410
411get_unused_range(Size, RangeOut) :-
412    max_used_port(MaxPort),
413    Lo is MaxPort + 1,
414    Hi is MaxPort + Size,
415    RangeOut = [Lo .. Hi].
416
417% Helper for maplist...
418sub_rev(A,B,C) :- C is B-A.
419
420
421%% Front-end functions
422% Routes the IntNr to a unused vector on CpuNr.
423% Prints controller configurations according to print_route
424find_and_add_irq_route(IntNr, CpuNr, VecNr) :-
425    route(IntNr, nullMsg, CpuNr, VecNr, Li),
426    term_variables(Li,List),
427    labeling(List),
428    add_route(Li),
429    print_route(Li).
430
431%>> X86
432x86_iommu_mode :-
433    dmar(X), Y is 1 /\ X, Y = 1.
434
435
436% Sets up default X86 controllers.
437% It uses facts that are added by the acpi and pci discovery, hence
438% it must be run when these facts are added.
439add_x86_controllers :-
440    % pic + iommu is not a valid combination...
441    (x86_interrupt_model(apic) ; not(x86_iommu_mode)),
442    int_dest_port_list(CpuPorts),
443
444    % iommu or msireceiver
445    (x86_iommu_mode -> (
446        % Then instantiate iommus.
447        findall(X, dmar_hardware_unit(X, _, _, _), Li),
448        (foreach(X, Li) do add_iommu_controller(_, X) )
449    ) ; (
450        % instantiate a MSI receiver
451        get_unused_range(1, MsiInRange),
452        assert_controller(msireceiver_a, msireceiver, MsiInRange, CpuPorts)
453    )),
454
455    % ioapic -> We assert them directly from the controller driver
456
457    %%findall((Id,GsiBase), ioapic(Id,_, GsiBase), IoapicLi),
458    %%(foreach((Id,GsiBase), IoapicLi) do
459    %%    add_ioapic_controller(_, Id, GsiBase)
460    %%),
461    (not(x86_interrupt_model(apic)) -> (
462        get_min_range(CpuPorts, MinCpu),
463        get_unused_range(16, PicInRange),
464        assert_controller(pic_a, pic, PicInRange, [MinCpu])
465    ) ; true).
466
467    % PIR to pcilnk controllers
468    % This is now added on the fly when all pir facts
469    % become available. ACPI calls
470    % add_pcilnk_controller_by_name(Name, Lbl)
471    % after adding all relevant PIR facts.
472    %findall(Name, pir(Name, _),Li),
473    %sort(Li,LiUnique),
474    %(foreach(Name,LiUnique) do (
475    %    findall(Gsi, pir(Name, Gsi), GSIListT),
476    %    sort(GSIListT,GSIList),
477    %    add_pcilnk_controller(GSIList, Name, _)
478    %)).
479
480
481
482%>> GENERIC
483
484% Base is atom, index integer, Out is atom that is not yet in use in
485% any controller predicate.
486get_unused_controller_label(Base, Index, Out) :-
487    atom_string(Base, BaseS),
488    append_strings(BaseS, "_", BaseSx),
489    number_string(Index, IndexS),
490    append_strings(BaseSx, IndexS, R),
491    atom_string(Xn, R),
492    (not(controller(Xn, _,_,_)) , Out = Xn) ;
493    ( NIndex is Index + 1, get_unused_controller_label(Base,NIndex, Out)).
494
495% Some classes of controller can be added at runtime. The
496% InSize specifies the number of input ports the controller has.
497% Type should be an atom, one of:
498% msi, msix, pcilnk
499
500%>> X86
501add_controller(InSize, msi, Lbl) :-
502    InSize :: [1,2,4,8,16],
503    get_unused_range(InSize, InRange),
504    get_unused_controller_label(msi, 0, Lbl),
505    (controller(_, irte, MsiOut, _) ; controller(_, msireceiver, MsiOut, _)),
506    assert_controller(Lbl, msi, InRange, MsiOut).
507
508% Deprecated, use add_pci_msix_controller
509%%add_controller(InSize, msix, Lbl) :-
510%%    InSize :: [1 .. 1024],
511%%    get_unused_range(InSize, InRange),
512%%    get_unused_controller_label(msix, 0, Lbl),
513%%    (controller(_, irte, MsiOut, _) ; controller(_, msireceiver, MsiOut, _)),
514%%    assert_controller(Lbl, msix, InRange, MsiOut).
515
516
517% Get the DmarIndex for a PCI address.
518% It checks for a direct entry, and if not, recurses up the PCI hierarchy
519% to find a bus entry.
520% DmarIndex = The DmarIndex, this is the output of the relation
521% EntryType = 1 for the first invocation, 2 for the recursive calls.
522% Add = The pci address to be looked up.
523dmar_device_pci(DmarIndex, EntryType, addr(Bus,Device, Function)) :-
524    % Check if there is a device specific entry.
525    dmar_device(DmarIndex, 0, EntryType, addr(_, Bus, Device, Function), _)
526    ; (
527        bridge(_,NewAddr, _, _, _, _, _, secondary(Bus)),
528        dmar_device_pci(DmarIndex, 2, NewAddr)
529    ).
530
531
532% Adds a MSI controller. It needs the Addr to find the correct I/OMMU
533add_msi_controller(Lbl, InSize, Type, addr(Bus, Device, Function)) :-
534    (Type = msi ; Type = msix),
535    % First Check if there is an endpoint device
536    (x86_iommu_mode -> (
537        dmar_device(DmarIndex, 1, addr(Bus,Device,Function)),
538        irte_index(DmarIndex, IrteLbl, _),
539        controller(IrteLbl, _, MSIOutRange, _)) ;
540        controller(_, msireceiver, MSIOutRange, _)
541    ),
542    get_unused_range(InSize, InRange),
543    get_unused_controller_label(Type, 0, Lbl),
544    assert_controller(Lbl, Type, InRange, MSIOutRange).
545
546
547%%%% Functions that map various interrupt numbers to internal representation
548
549% Convert ACPI PIR name to a internal base number.
550prt_entry_to_num(pir(Name), Nu) :-
551    pcilnk_index(Name, Lbl),
552    controller(Lbl, _, InRange, _),
553    get_min_range(InRange, Nu).
554
555% Convert GSI to internal number
556prt_entry_to_num(gsi(Gsi), Nu) :-
557    controller_for_gsi(Gsi, Lbl, Base),
558    Offset is Gsi - Base,
559    controller(Lbl, _, InRange, _),
560    get_min_range(InRange, InLo),
561    Nu is InLo + Offset.
562
563%>> GENERIC
564% Filter none atoms out of a list.
565filter_none([], []).
566filter_none([none | Xs], Out) :- filter_none(Xs, Out).
567filter_none([A | Xs], Out) :- filter_none(Xs, OutT), Out = [A | OutT].
568
569%>> X86
570% Calculate the PCI bus swizzle until a PRT entry is found
571% same algorithm as findgsi in the old irq_routing.pl
572find_prt_entry(Pin, Addr, PrtEntry) :-
573    (
574        % lookup routing table to see if we have an entry
575        prt(Addr, Pin, PrtEntry)
576    ;
577        % if not, compute standard swizzle through bridge
578        Addr = addr(Bus, Device, _),
579        NewPin is (Device + Pin) mod 4,
580
581        % recurse, looking up mapping for the bridge itself
582        bridge(_, BridgeAddr, _, _, _, _, _, secondary(Bus)),
583        find_prt_entry(NewPin, BridgeAddr, PrtEntry)
584    ).
585
586
587% when using legacy interrupts, the PCI card does not need a controller
588% however it needs to be aware of the int numbers to use.
589% This function returns always only one interrupt, but for compatibility,
590% it returns a Lo,Hi tuple
591% A = addr(Bus,Device,Function)
592% LiR = (Lo,Hi)
593get_pci_legacy_int_range(A, (Lo,Hi)) :-
594    device(_, A, _, _, _, _, _, Pin),
595    find_prt_entry(Pin, A, X),
596    prt_entry_to_num(X, IntNu),
597    Lo = IntNu,
598    Hi = IntNu.
599
600% Translates fixed x86 legacy interrupt numbers to internal interrupt source number.
601% It first translates Legacy to GSI, then GSI to internal.
602% The first translation involves the ACPI int override table
603isa_irq_to_int(Legacy, Nr) :-
604    (interrupt_override(0, Legacy, Gsi, _) ; Gsi = Legacy),
605    prt_entry_to_num(gsi(Gsi), Nr).
606
607
608
609%>> GENERIC
610% Add a dynamic controller and a octopus object
611assert_controller(Lbl, Class, InRange, MSIOutRange) :-
612    assert( controller(Lbl, Class, InRange, MSIOutRange)),
613    atom_string(Lbl,LblStr),
614    atom_string(Class, ClassStr),
615    add_seq_object('hw.int.controller.',
616        [val(label, LblStr), val(class, ClassStr)], []).
617
618% GSIList is a list of GSI that this pci link device can output.
619add_pcilnk_controller(GSIList, Name, Lbl) :-
620    length(GSIList, LiLe),
621    get_unused_range(LiLe, InRange),
622    get_unused_controller_label(pcilnk, 0, Lbl),
623
624    % Calculate OutRange. Subtract GSI Base, then add the minimum of the IoApic ctrl.
625    GSIList = [GSI0 | _],
626    !,
627    controller_for_gsi(GSI0, Ioapiclbl, GSIBase),
628    controller(Ioapiclbl, _, IoIn, _),
629    get_min_range(IoIn, IoApicIn),
630    maplist(sub_rev(GSIBase), GSIList, LocalList), maplist(+(IoApicIn), LocalList, OutRange),
631    assert(pcilnk_index(Name, Lbl)),
632    assert_controller(Lbl, pcilnk, InRange, OutRange).
633
634%>> X86
635% For a given (ACPI) pci link controller name, this looks
636% up all the GSI from the pir(..) facts and instantiates the controller
637add_pcilnk_controller_by_name(Name, Lbl) :-
638    findall(Gsi, pir(Name, Gsi), GSIListT),
639    sort(GSIListT,GSIList),
640    add_pcilnk_controller(GSIList, Name, Lbl).
641
642
643% The PCI controller can not route interrupts to different destinations,
644% however, it will enable/disable interrupts in the PCI conf space. This controller
645% is only instantiated for legacy interrupts.
646% A = addr(Bus,Device,Function)
647add_pci_controller(Lbl, A) :-
648    % get fresh inputs
649    get_unused_range(1, PciInRange),
650    get_unused_controller_label(pci, 0, Lbl),
651
652    % now, determine the output range, using the pci address
653    device(_, A, _, _, _, _, _, Pin),
654    find_prt_entry(Pin, A, X),
655    prt_entry_to_num(X, IntNu),
656    OutRange :: [IntNu, IntNu],
657
658    assert(pci_lbl_addr(Lbl, A)),
659
660    assert_controller(Lbl, pci, PciInRange, OutRange).
661
662% Instantiates two linke controllers:
663% * pci_msix: can not route interrupts to different destinations,
664%   however, it will enable/disable interrupts in the PCI conf space.
665% * msix: The MSIX vector table
666%
667% A = addr(Bus,Device,Function)
668add_pci_msix_controller(PciMsixLbl, MsixLbl, A) :-
669    TBLSIZE = 16, % TODO read TBLSIZE from conf space and pass in as argument
670    % First, build msix controller
671    get_unused_range(TBLSIZE, PciOutRange),
672    get_unused_controller_label(msix, 0, MsixLbl),
673    (controller(_, irte, MsiOut, _) ; controller(_, msireceiver, MsiOut, _)),
674    assert_controller(MsixLbl, msix, PciOutRange, MsiOut),
675
676    % Then pci_msix controller, that sits before the msix ctrl
677    get_unused_range(TBLSIZE, InRange),
678    get_unused_controller_label(pci_msix, 0, PciMsixLbl),
679    assert(pci_lbl_addr(PciMsixLbl, A)),
680    assert_controller(PciMsixLbl, pci_msix, InRange, PciOutRange).
681
682
683
684
685
686add_ioapic_controller(Lbl, IoApicId, GSIBase) :-
687    ((
688        % Check if there is a dmar_hardware_unit entry that covers this controller
689        % If so, we instantiate a ioapic_iommu controller
690        % that is connected directly to the iommu
691        % (not the irte), because the ioapic driver knows
692        % how to address an entry directly
693        dmar_device(DmarIndex, _, 3, _, IoApicId),
694        irte_index(DmarIndex, _, CtrlLbl),
695        controller(CtrlLbl, _, OutRange, _), % OutRange is the Input Range of the ioapic
696        CtrlClass = ioapic_iommu
697    ) ; (
698        % No IOMMU applicable
699        int_dest_port_list(OutRange),
700        CtrlClass = ioapic
701    )),
702    get_unused_range(24, IoApicInRange),
703    get_unused_controller_label(ioapic, 0, Lbl),
704    assert_controller(Lbl, CtrlClass, IoApicInRange, OutRange),
705    assert( ioapic_gsi_base(Lbl, GSIBase) ).
706
707add_iommu_controller(Lbl, DmarIndex) :-
708    int_dest_port_list(CpuPorts),
709    max_used_port(MaxPort),
710    Lo1 is MaxPort + 1,
711    Hi1 is MaxPort + 1,
712    Lo2 is MaxPort + 2,
713    Hi2 is MaxPort + 2,
714    IrteOutRange = [Lo1 .. Hi1],
715    IommuInRange = [Lo2 .. Hi2],
716    get_unused_controller_label(iommu, 0, IommuLbl),
717    get_unused_controller_label(irte, 0, IrteLbl),
718
719    assert_controller(IommuLbl, iommu, IrteOutRange, CpuPorts),
720    assert( irte_index(DmarIndex, IrteLbl, IommuLbl) ),
721    assert_controller(IrteLbl, irte, IommuInRange, IrteOutRange),
722    Lbl = IrteLbl.
723
724
725% iommu
726print_controller_class_details(Lbl, iommu) :-
727    irte_index(DmarIndex, _, Lbl),
728    dmar_hardware_unit(DmarIndex, Flags, Segment, Address),
729    printf(",%u,%u,%u", [Flags,Segment,Address]).
730
731% ioapic
732print_controller_class_details(Lbl, ioapic) :-
733    ioapic_gsi_base(Lbl, GSIBase),
734    ioapic(_, MemBase, GSIBase),
735    printf(",%u", [MemBase]).
736
737% ioapic-iommu
738print_controller_class_details(Lbl, ioapic_iommu) :-
739    print_controller_class_details(Lbl, ioapic).
740
741% Default, print nothing
742print_controller_class_details(_, _) :- true.
743
744%>> GENERIC
745% This predicate indicates which binary to start for a given controller class
746% If there is no such binary, no driver is started
747% controller_driver_binary(ioapic, "ioapic").
748% controller_driver_binary(ioapic_iommu, "ioapic").
749% controller_driver_binary(iommu, "iommu").
750
751find_int_controller_driver(Lbl) :-
752    controller(Lbl, Class, InRange, OutRange),
753    %Binary = "None",
754    controller_driver_binary(Class, Binary),
755    get_min_range(InRange,InLo),
756    get_max_range(InRange,InHi),
757    get_min_range(OutRange,OutLo),
758    get_max_range(OutRange,OutHi),
759
760    printf("%s,%w,%w,%u,%u,%u,%u", [Binary,Lbl, Class, InLo, InHi, OutLo, OutHi]),
761    print_controller_class_details(Lbl, Class),
762    printf("\n",[]).
763
764% This function prints a CSV file in the following format:
765% Lbl,Class,InRangeLow,InRangeHigh,OutRangeLow,OutRangeHigh
766% followed by controller specific details needed for controller
767% driver startup (such as a MMIO base address for the IOMMU)
768print_int_controller(Lbl) :-
769    controller(Lbl, Class, InRange, OutRange),
770    get_min_range(InRange,InLo),
771    get_max_range(InRange,InHi),
772    get_min_range(OutRange,OutLo),
773    get_max_range(OutRange,OutHi),
774    printf("%w,%w,%u,%u,%u,%u", [Lbl, Class, InLo, InHi, OutLo, OutHi]),
775    print_controller_class_details(Lbl, Class),
776    printf("\n",[]).
777
778print_controller_driver :-
779    findall(Lbl, controller(Lbl, _,_,_), Li),
780    (foreach(Lbl,Li) do
781        (find_int_controller_driver(Lbl);true)).
782
783
784%>> X86
785% Returns the controller label for a GSI
786% Can also be used to map GSI to internal interrupt source number.
787controller_for_gsi(GSI, Lbl, Base) :-
788    ioapic_gsi_base(Lbl, Base),
789    Base > GSI-24,
790    Base =< GSI.
791
792
793
794%>> GENERIC
795print_controller_dot_file_handle(Handle) :-
796    printf(Handle, "digraph controllergraph {\n", []),
797    findall( controller(CtrlLbl, CtrlClass, In, Out), controller(CtrlLbl, CtrlClass, In, Out), CtrlLi),
798    (foreach( controller(CtrlLbl, _, InRange, OutRange), CtrlLi), param(Handle) do (
799        % In Connections
800        InTemp :: InRange,
801        findall( InTemp, labeling([InTemp]), InLi),
802        (foreach(Y, InLi), param(CtrlLbl), param(Handle) do (
803            mapf(CtrlLbl, Y, _, _, _) -> printf(Handle, "%d -> %Kw [color=blue];\n", [Y, CtrlLbl]) ;
804            printf(Handle, "%d -> %Kw;\n", [Y, CtrlLbl])
805
806        )),
807        OutTemp :: OutRange,
808        findall( OutTemp, labeling([OutTemp]), OutLi),
809        (foreach(Y, OutLi), param(CtrlLbl), param(Handle) do (
810            int_dest_port(Y) -> (
811                mapf(CtrlLbl, _,_, Y, _) -> printf(Handle, "%Kw -> cpu_%d [color=blue];\n", [CtrlLbl, Y]);
812                printf(Handle, "%Kw -> cpu_%d;\n", [CtrlLbl, Y])
813            ) ; (
814                mapf(CtrlLbl, _,_, Y, _) -> printf(Handle, "%Kw -> %d [color=blue];\n", [CtrlLbl, Y]);
815                printf(Handle, "%Kw -> %d;\n", [CtrlLbl, Y])
816            )
817        ))
818    )),
819    printf(Handle, "}\n",[]).
820
821print_controller_dot_file_local :-
822    open("/home/luki/ETH/IRQ route/dot-test/out.dot", write, Handle),
823    print_controller_dot_file_handle(Handle),
824    close(Handle).
825
826print_controller_dot_file:-
827    print_controller_dot_file_handle(stdout).
828
829%%% DEBUG:  Some facts that are helpful for experimentation %%%
830%controller(pic_a, pic, [100 .. 116], [1]).
831%controller(msi_a, msi, [200 .. 204], [300]).
832%controller(msix_a, msix, [400 .. 416], [300]).
833%controller(msireceiver_a, msireceiver, [300], [1 .. 48]).
834%controller(irte_a, irte, [300], [301]).
835%controller(iommu_a, iommu, [301], [1 .. 48]).
836
837
838%%% DEBUG:  Some facts that are helpful for experimentation %%%
839%:- [debugfacts].
840%
841%:- add_x86_controllers.
842%:- add_ioapic_controller(Lbl,0), print_controller(Lbl).
843%:- add_ioapic_controller(Lbl,24), print_controller(Lbl).
844%:- add_pcilnk_controller([12,13,14,15], Lbl), print_controller(Lbl).
845%:- add_pcilnk_controller([16,17,18,19], Lbl), print_controller(Lbl).
846%:- add_pcilnk_controller([16,17,18,19], Lbl), print_controller(Lbl).
847%:- add_controller(4, msi, Lbl), print_controller(Lbl).
848%:- add_controller(5, msix, Lbl), print_controller(Lbl).
849%
850%% install route going from the first input of the ioapic_0 to the first CPU.
851%:- controller(ioapic_0,_,InRange,_), get_min_range(InRange,Lo), int_dest_port_list(PoLi), PoLi = [CPU|_], find_and_add_irq_route(Lo, CPU).
852%:- controller(pcilnk_1,_,InRange,_), get_min_range(InRange,Lo), int_dest_port_list(PoLi), PoLi = [CPU|_], find_and_add_irq_route(Lo, CPU).
853%:- controller(pcilnk_1,_,InRange,_), get_min_range(InRange,Lo), int_dest_port_list(PoLi), PoLi = [CPU|_], get_route(Lo, nullMsg, Li), print_route(Li).
854%:- controller(pcilnk_1,_,InRange,_), get_min_range(InRange,Lo), Lo1 is Lo + 1, int_dest_port_list(PoLi), PoLi = [CPU|_], find_and_add_irq_route(Lo1, CPU).
855%:- controller(msi_0,_,InRange,_), get_min_range(InRange,Lo), int_dest_port_list(PoLi), PoLi = [CPU|_], find_and_add_irq_route(Lo, CPU).
856%:- controller(msix_0,_,InRange,_), get_min_range(InRange,Lo), int_dest_port_list(PoLi), PoLi = [CPU|_], find_and_add_irq_route(Lo, CPU).
857%
858%%remove and re-install a route.
859%:- controller(msi_0,_,InRange,_), get_min_range(InRange,Lo), get_route(Lo, nullMsg, Li), remove_route(Li).
860%:- controller(msi_0,_,InRange,_), get_min_range(InRange,Lo), int_dest_port_list(PoLi), PoLi = [CPU|_], find_and_add_irq_route(Lo, CPU).
861%
862%:- print_controller_dot_file.
863%
864%:- print_controller_config(piclnk_1).
865
866
867
868
869
870
871% Other useful facts, not defined here but relevant.
872%
873
874
875