BIOS.AMD64.PCI.Mod 19 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556
  1. MODULE PCI; (** non-portable *)
  2. (** AUTHOR "ryser"; PURPOSE "PCI bus interface (compatible with Native Oberon)"; *)
  3. (* Contributed by P. Ryser to the System 3 project *)
  4. IMPORT SYSTEM, Machine, KernelLog;
  5. CONST
  6. Trace = FALSE;
  7. (* PCI Configuration Registers *)
  8. DevReg* = 0H; CmdReg* = 4H; RevIdReg* = 8H; CLSReg* = 0CH;
  9. Adr0Reg* = 10H; Adr1Reg* = 14H; Adr2Reg* = 18H;
  10. Adr3Reg* = 1CH; Adr4Reg* = 20H; Adr5Reg* = 24H;
  11. CISReg* = 28H; SubvReg* = 2CH; ROMReg* = 30H; IntlReg* = 3CH;
  12. (* PCI Command register encoding, used as arguments for Enable *)
  13. IOSpace* = {0};
  14. MemorySpace* = {1};
  15. BusMaster* = {2};
  16. debug = FALSE;
  17. Done* = 0; NoPCI* = -1; NoBios32* = -1; Error* = -2;
  18. FuncNotSupported* = 81H; BadVendorId* = 83H; DeviceNotFound* = 86H;
  19. BadRegisterNumber* = 87H; SetFailed* = 88H; BufferTooSmall* = 89H;
  20. PCIServiceId = 49435024H; (* "$PCI" *)
  21. PCIString = 20494350H; (* " PCI" *)
  22. PCIFunctionId = 0B1H*256;
  23. PCIBiosPresent = 1H; findPCIDevice = 2H; findPCIClassCode = 3H; generateSpecialCycle = 6H;
  24. readConfigByte = 8H; readConfigWord = 9H; readConfigDword = 0AH;
  25. writeConfigByte = 0BH; writeConfigWord = 0CH; writeConfigDword = 0DH;
  26. getIrqRoutingOptions = 0EH; setPCIIrq = 0FH;
  27. TYPE
  28. RouteTable* = POINTER TO RouteTableDesc;
  29. RouteTableDesc* = RECORD
  30. busNr*, devNr*, slotNr*: LONGINT;
  31. linkValIntA*, linkValIntB*, linkValIntC*, linkValIntD*: CHAR;
  32. IrqBitmapA*, IrqBitmapB*, IrqBitmapC*, IrqBitmapD*: SET;
  33. next*: RouteTable
  34. END;
  35. RouteBuffer = RECORD
  36. BufferSize, SegSelector: INTEGER;
  37. DataBufferAdr: ADDRESS
  38. END;
  39. Pci* = RECORD bus*, device*, function*: LONGINT END;
  40. VAR
  41. Bios32Def: RECORD
  42. sig: ARRAY 4 OF CHAR;
  43. entry: LONGINT;
  44. rev, len, chksum: CHAR;
  45. res: ARRAY 5 OF CHAR;
  46. END;
  47. bios32: BOOLEAN;
  48. pci: BOOLEAN;
  49. pciEntry: ADDRESS;
  50. PROCEDURE BiosServiceDirectory(sadr: ADDRESS; sid, fsel: LONGINT; VAR badr: ADDRESS; VAR len, entry: LONGINT): CHAR;
  51. CODE {SYSTEM.AMD64}
  52. MOV EAX, [RBP + sid]
  53. MOV EBX, [RBP + fsel]
  54. PUSH QWORD [RBP + sadr]
  55. MOV WORD [RSP + 4], 3*8
  56. DB 0FFH, 01CH, 024h ; CALL FAR [RSP]
  57. MOV R8, [RBP + badr]
  58. MOV [R8], RBX
  59. MOV R8, [RBP + len]
  60. MOV [R8], ECX
  61. MOV R8, [RBP + entry]
  62. MOV [R8], EDX
  63. END BiosServiceDirectory;
  64. PROCEDURE FindBios32Service*(serviceId, serviceFkt: LONGINT; VAR serviceAdr: ADDRESS; VAR serviceLen, entryOffset: LONGINT): LONGINT;
  65. VAR ch: CHAR; res: WORD; state: SET;
  66. BEGIN {EXCLUSIVE}
  67. IF bios32 THEN
  68. state := Machine.DisableInterrupts();
  69. ch := BiosServiceDirectory(Bios32Def.entry, serviceId, serviceFkt,
  70. serviceAdr, serviceLen, entryOffset);
  71. Machine.RestoreInterrupts(state);
  72. res := ORD(ch)
  73. ELSE
  74. res := NoBios32
  75. END;
  76. RETURN res
  77. END FindBios32Service;
  78. PROCEDURE DetectBios32;
  79. VAR adr, chksum, i: LONGINT; s: ARRAY 16 OF CHAR;
  80. BEGIN
  81. adr := 0E0000H; chksum := 0FFH;
  82. REPEAT
  83. SYSTEM.MOVE(adr, ADDRESSOF(s[0]), 16);
  84. IF (s[0] = "_") & (s[1] = "3") & (s[2] = "2") & (s[3] = "_") THEN
  85. chksum := 0; i := 0;
  86. WHILE i < 16 DO
  87. chksum := chksum + ORD(s[i]);
  88. IF FALSE & debug THEN KernelLog.Int(ORD(s[i]), 1); KernelLog.Char(" ") END;
  89. INC(i)
  90. END;
  91. chksum := chksum MOD 256;
  92. END;
  93. INC(adr, 16)
  94. UNTIL (chksum = 0) OR (adr = 0100000H);
  95. bios32 := chksum = 0;
  96. IF bios32 THEN
  97. SYSTEM.MOVE(ADDRESSOF(s[0]), ADDRESSOF(Bios32Def), 16);
  98. IF Trace THEN
  99. KernelLog.String("PCI Bios32 detected at: "); KernelLog.Hex(adr-16, 8); KernelLog.Ln;
  100. KernelLog.String(" Sig: ");
  101. KernelLog.Char(Bios32Def.sig[0]); KernelLog.Char(Bios32Def.sig[1]);
  102. KernelLog.Char(Bios32Def.sig[2]); KernelLog.Char(Bios32Def.sig[3]);
  103. KernelLog.String(", Entry: "); KernelLog.Hex(Bios32Def.entry, 8);
  104. KernelLog.String(", Revision: "); KernelLog.Int(ORD(Bios32Def.rev), 1);
  105. KernelLog.String(", Length: "); KernelLog.Int(ORD(Bios32Def.len)*16, 1);
  106. KernelLog.String(", Checksum: "); KernelLog.Int(ORD(Bios32Def.chksum), 1);
  107. KernelLog.Ln
  108. END
  109. END
  110. END DetectBios32;
  111. PROCEDURE pcicall(entry:ADDRESS; VAR peax,pebx,pecx,pedx,pesi,pedi:LONGINT; VAR eflags: SET);
  112. CODE {SYSTEM.AMD64}
  113. MOV R8, [RBP + peax]
  114. MOV EAX, [R8]
  115. MOV R8, [RBP + pebx]
  116. MOV EBX, [R8]
  117. MOV R8, [RBP + pecx]
  118. MOV ECX, [R8]
  119. MOV R8, [RBP + pedx]
  120. MOV EDX, [R8]
  121. MOV R8, [RBP + pesi]
  122. MOV ESI, [R8]
  123. MOV R8, [RBP + pedi]
  124. MOV EDI, [R8]
  125. PUSH QWORD [RBP + entry]
  126. MOV WORD [RSP + 4], 3*8
  127. DB 0FFH, 01CH, 024h; FAR CALL [RSP]
  128. PUSHFQ
  129. MOV R8, [RBP + peax]
  130. MOV [R8], EAX
  131. MOV R8, [RBP + pebx]
  132. MOV [R8], EBX
  133. MOV R8, [RBP + pecx]
  134. MOV [R8], ECX
  135. MOV R8, [RBP + pedx]
  136. MOV [R8], EDX
  137. MOV R8, [RBP + pesi]
  138. MOV [R8], ESI
  139. MOV R8, [RBP + pedi]
  140. MOV [R8], EDI
  141. MOV R8, [RBP + eflags]
  142. POP R9
  143. MOV [R8], R9
  144. END pcicall;
  145. PROCEDURE OutRegs(eax, ebx, ecx, edx, esi, edi: LONGINT; eflags: SET);
  146. BEGIN
  147. IF debug THEN
  148. KernelLog.String(" eax: "); KernelLog.Hex(eax, 8); KernelLog.Ln;
  149. KernelLog.String(" ebx: "); KernelLog.Hex(ebx, 8); KernelLog.Ln;
  150. KernelLog.String(" ecx: "); KernelLog.Hex(ecx, 8); KernelLog.Ln;
  151. KernelLog.String(" edx: "); KernelLog.Hex(edx, 8); KernelLog.Ln;
  152. KernelLog.String(" esi: "); KernelLog.Hex(esi, 8); KernelLog.Ln;
  153. KernelLog.String(" edi: "); KernelLog.Hex(edi, 8); KernelLog.Ln;
  154. KernelLog.String(" eflags: "); KernelLog.Hex(SYSTEM.VAL(LONGINT, eflags), 8); KernelLog.Ln
  155. END
  156. END OutRegs;
  157. PROCEDURE PCIPresent*(VAR version, lastPCIbus, hwMech: LONGINT): LONGINT;
  158. VAR res, eax, ebx, ecx, edx, esi, edi: LONGINT; eflags, state: SET;
  159. BEGIN {EXCLUSIVE}
  160. IF pci THEN
  161. eax := PCIFunctionId + PCIBiosPresent;
  162. state := Machine.DisableInterrupts();
  163. pcicall(pciEntry, eax, ebx, ecx, edx, esi, edi, eflags);
  164. Machine.RestoreInterrupts(state);
  165. res := (eax DIV 100H) MOD 100H;
  166. IF (edx = PCIString) & ~(0 IN eflags) & (res = Done) THEN
  167. version := ebx MOD 10000H;
  168. lastPCIbus := ecx MOD 100H;
  169. hwMech := eax MOD 100H
  170. ELSIF res = 0 THEN res := NoPCI (* ; pci := FALSE (* <- hmm, not sure about that *) *)
  171. END;
  172. IF debug THEN
  173. KernelLog.String("PCIPresent:"); KernelLog.Ln;
  174. OutRegs(eax, ebx, ecx, edx, esi, edi, eflags)
  175. END
  176. ELSE
  177. res := NoPCI
  178. END;
  179. RETURN res
  180. END PCIPresent;
  181. PROCEDURE FindPCIDevice*(devId, vendId, idx: LONGINT; VAR busNr, devNr, fktNr: LONGINT): LONGINT;
  182. VAR res, eax, ebx, ecx, edx, esi, edi: LONGINT; eflags, state: SET;
  183. BEGIN {EXCLUSIVE}
  184. IF pci THEN
  185. eax := PCIFunctionId + findPCIDevice;
  186. ecx := devId; edx := vendId; esi := idx;
  187. state := Machine.DisableInterrupts();
  188. pcicall(pciEntry, eax, ebx, ecx, edx, esi, edi, eflags);
  189. Machine.RestoreInterrupts(state);
  190. res := (eax DIV 100H) MOD 100H; ASSERT(~((0 IN eflags) & (res=0)));
  191. IF ~(0 IN eflags) & (res = Done) THEN
  192. busNr := (ebx DIV 100H) MOD 100H;
  193. devNr := (ebx DIV 8) MOD 20H;
  194. fktNr := ebx MOD 8
  195. END;
  196. IF debug THEN
  197. KernelLog.String("FindPCIDevice:"); KernelLog.Ln;
  198. OutRegs(eax, ebx, ecx, edx, esi, edi, eflags)
  199. END
  200. ELSE
  201. res := NoPCI
  202. END;
  203. RETURN res
  204. END FindPCIDevice;
  205. PROCEDURE FindPCIClassCode*(classCode, idx: LONGINT; VAR busNr, devNr, fktNr: LONGINT): LONGINT;
  206. VAR res, eax, ebx, ecx, edx, esi, edi: LONGINT; eflags, state: SET;
  207. BEGIN {EXCLUSIVE}
  208. IF pci THEN
  209. eax := PCIFunctionId + findPCIClassCode;
  210. ecx := classCode; esi := idx;
  211. state := Machine.DisableInterrupts();
  212. pcicall(pciEntry, eax, ebx, ecx, edx, esi, edi, eflags);
  213. Machine.RestoreInterrupts(state);
  214. res := (eax DIV 100H) MOD 100H; ASSERT(~((0 IN eflags) & (res=0)));
  215. IF ~(0 IN eflags) & (res = Done) THEN
  216. busNr := (ebx DIV 100H) MOD 100H;
  217. devNr := (ebx DIV 8) MOD 20H;
  218. fktNr := ebx MOD 8
  219. END;
  220. IF debug THEN
  221. KernelLog.String("FindPCIClassCode:"); KernelLog.Ln;
  222. OutRegs(eax, ebx, ecx, edx, esi, edi, eflags)
  223. END
  224. ELSE
  225. res := NoPCI
  226. END;
  227. RETURN res
  228. END FindPCIClassCode;
  229. PROCEDURE GenerateSpecialCycle*(busNr, specCycleData: LONGINT): LONGINT;
  230. VAR res, eax, ebx, ecx, edx, esi, edi: LONGINT; eflags, state: SET;
  231. BEGIN {EXCLUSIVE}
  232. IF pci THEN
  233. eax := PCIFunctionId + generateSpecialCycle;
  234. ebx := busNr*100H; edx := specCycleData;
  235. state := Machine.DisableInterrupts();
  236. pcicall(pciEntry, eax, ebx, ecx, edx, esi, edi, eflags);
  237. Machine.RestoreInterrupts(state);
  238. res := (eax DIV 100H) MOD 100H; ASSERT(~((0 IN eflags) & (res=0)));
  239. IF debug THEN
  240. KernelLog.String("GenerateSpecialCycle:"); KernelLog.Ln;
  241. OutRegs(eax, ebx, ecx, edx, esi, edi, eflags)
  242. END
  243. ELSE
  244. res := NoPCI
  245. END;
  246. RETURN res
  247. END GenerateSpecialCycle;
  248. PROCEDURE GetIrqRoutingOptions*(VAR rt: RouteTable; VAR IrqBitmap: SET): LONGINT;
  249. CONST dbN = 16*8;
  250. VAR
  251. res, eax, ebx, ecx, edx, esi, edi, i: LONGINT; eflags, state: SET;
  252. rb: RouteBuffer; db: ARRAY dbN OF CHAR;
  253. last: RouteTable;
  254. BEGIN {EXCLUSIVE}
  255. IF pci THEN
  256. eax := PCIFunctionId + getIrqRoutingOptions;
  257. rb.BufferSize := dbN; rb.SegSelector := 0; rb.DataBufferAdr := ADDRESSOF(db[0]);
  258. ebx := 0H; edi := Machine.Ensure32BitAddress(SYSTEM.VAL (ADDRESS, rb));
  259. state := Machine.DisableInterrupts();
  260. pcicall(pciEntry, eax, ebx, ecx, edx, esi, edi, eflags);
  261. Machine.RestoreInterrupts(state);
  262. res := (eax DIV 100H) MOD 100H; ASSERT(~((0 IN eflags) & (res=0)));
  263. ASSERT(res # BufferTooSmall); (* Increase dbN on Trap *)
  264. IF ~(0 IN eflags) & (res = Done) THEN
  265. IrqBitmap := SYSTEM.VAL(SET, ebx);
  266. NEW(rt); rt.next := NIL; last := rt; i := 0;
  267. WHILE i < rb.BufferSize DO
  268. NEW(last.next); last := last.next; last.next := NIL;
  269. last.busNr := ORD(db[i]); INC(i);
  270. last.devNr := ORD(db[i]) DIV 8; INC(i);
  271. last.linkValIntA := db[i]; INC(i);
  272. last.IrqBitmapA := SYSTEM.VAL(SET, LONG(ORD(db[i])+ORD(db[i+1])*100H)); INC(i, 2);
  273. last.linkValIntB := db[i]; INC(i);
  274. last.IrqBitmapB := SYSTEM.VAL(SET, LONG(ORD(db[i])+ORD(db[i+1])*100H)); INC(i, 2);
  275. last.linkValIntC:= db[i]; INC(i);
  276. last.IrqBitmapC := SYSTEM.VAL(SET, LONG(ORD(db[i])+ORD(db[i+1])*100H)); INC(i, 2);
  277. last.linkValIntD := db[i]; INC(i);
  278. last.IrqBitmapD := SYSTEM.VAL(SET, LONG(ORD(db[i])+ORD(db[i+1])*100H)); INC(i, 2);
  279. last.slotNr := ORD(db[i]); INC(i);
  280. INC(i) (* reserved byte *)
  281. END;
  282. rt := rt.next
  283. END;
  284. IF debug THEN
  285. KernelLog.String("GetIrqRoutingOptions:"); KernelLog.Ln;
  286. OutRegs(eax, ebx, ecx, edx, esi, edi, eflags)
  287. END
  288. ELSE
  289. res := NoPCI
  290. END;
  291. RETURN res
  292. END GetIrqRoutingOptions;
  293. PROCEDURE SetPCIIrq*(IntPin, IrqNum, busNr, devNr, fktNr: LONGINT): LONGINT;
  294. VAR res, eax, ebx, ecx, edx, esi, edi: LONGINT; eflags, state: SET;
  295. BEGIN {EXCLUSIVE}
  296. IF pci THEN
  297. eax := PCIFunctionId + setPCIIrq;
  298. ecx := IrqNum*100H + IntPin; ebx := busNr*100H+devNr*8+fktNr;
  299. state := Machine.DisableInterrupts();
  300. pcicall(pciEntry, eax, ebx, ecx, edx, esi, edi, eflags);
  301. Machine.RestoreInterrupts(state);
  302. res := (eax DIV 100H) MOD 100H; ASSERT(~((0 IN eflags) & (res=0)));
  303. IF debug THEN
  304. KernelLog.String("SetPCIHwInt:"); KernelLog.Ln;
  305. OutRegs(eax, ebx, ecx, edx, esi, edi, eflags)
  306. END
  307. ELSE
  308. res := NoPCI
  309. END;
  310. RETURN res
  311. END SetPCIIrq;
  312. (** Set bits included in <mask> in the PCI command register if not set already *)
  313. PROCEDURE Enable*(mask : SET; busNr, devNr, fktNr : LONGINT) : LONGINT;
  314. VAR cmdReg : LONGINT; res : WORD;
  315. BEGIN
  316. res := ReadConfigWord(busNr, devNr, fktNr, CmdReg, cmdReg);
  317. IF (res = Done) THEN
  318. IF mask - SYSTEM.VAL(SET, cmdReg) # {} THEN
  319. cmdReg := SYSTEM.VAL(LONGINT, SYSTEM.VAL(SET, cmdReg) + mask);
  320. res := WriteConfigWord(busNr, devNr, fktNr, CmdReg, cmdReg);
  321. IF (res = Done) THEN (* maybe the device does not implement all bits writable... check! *)
  322. res := ReadConfigWord(busNr, devNr, fktNr, CmdReg, cmdReg);
  323. IF (res = Done) THEN
  324. IF mask - SYSTEM.VAL(SET, cmdReg) # {} THEN (* at least one bit is not set *)
  325. res := Error;
  326. END;
  327. END;
  328. END;
  329. END;
  330. END;
  331. RETURN res;
  332. END Enable;
  333. PROCEDURE ReadConfig(fkt, busNr, devNr, fktNr, regNr: LONGINT; mask: SET; VAR regVal: LONGINT): LONGINT;
  334. VAR res, eax, ebx, ecx, edx, esi, edi: LONGINT; eflags, state: SET;
  335. BEGIN {EXCLUSIVE}
  336. IF pci THEN
  337. eax := PCIFunctionId + fkt;
  338. ebx := busNr*100H+devNr*8+fktNr; edi := regNr;
  339. state := Machine.DisableInterrupts();
  340. pcicall(pciEntry, eax, ebx, ecx, edx, esi, edi, eflags);
  341. Machine.RestoreInterrupts(state);
  342. res := (eax DIV 100H) MOD 100H; ASSERT(~((0 IN eflags) & (res=0)));
  343. IF ~(0 IN eflags) & (res = Done) THEN
  344. regVal := SYSTEM.VAL(LONGINT, SYSTEM.VAL(SET, ecx)*mask)
  345. END;
  346. IF debug THEN
  347. KernelLog.String("ReadConfig ("); KernelLog.Int(fkt, 1); KernelLog.String("):"); KernelLog.Ln;
  348. OutRegs(eax, ebx, ecx, edx, esi, edi, eflags)
  349. END
  350. ELSE
  351. res := NoPCI
  352. END;
  353. RETURN res
  354. END ReadConfig;
  355. PROCEDURE ReadConfigByte*(busNr, devNr, fktNr, regNr: LONGINT; VAR regVal: LONGINT): LONGINT;
  356. BEGIN
  357. RETURN ReadConfig(readConfigByte, busNr, devNr, fktNr, regNr, {0..7}, regVal)
  358. END ReadConfigByte;
  359. PROCEDURE ReadConfigWord*(busNr, devNr, fktNr, regNr: LONGINT; VAR regVal: LONGINT): LONGINT;
  360. BEGIN
  361. ASSERT(regNr MOD 2 = 0);
  362. RETURN ReadConfig(readConfigWord, busNr, devNr, fktNr, regNr, {0..15}, regVal)
  363. END ReadConfigWord;
  364. PROCEDURE ReadConfigDword*(busNr, devNr, fktNr, regNr: LONGINT; VAR regVal: LONGINT): LONGINT;
  365. BEGIN
  366. ASSERT(regNr MOD 4 = 0);
  367. RETURN ReadConfig(readConfigDword, busNr, devNr, fktNr, regNr, {0..31}, regVal)
  368. END ReadConfigDword;
  369. PROCEDURE WriteConfig(fkt, busNr, devNr, fktNr, regNr, regVal: LONGINT): LONGINT;
  370. VAR res, eax, ebx, ecx, edx, esi, edi: LONGINT; eflags, state: SET;
  371. BEGIN {EXCLUSIVE}
  372. IF pci THEN
  373. eax := PCIFunctionId + fkt;
  374. ebx := busNr*100H+devNr*8+fktNr; ecx := regVal; edi := regNr;
  375. state := Machine.DisableInterrupts();
  376. pcicall(pciEntry, eax, ebx, ecx, edx, esi, edi, eflags);
  377. Machine.RestoreInterrupts(state);
  378. res := (eax DIV 100H) MOD 100H; ASSERT(~((0 IN eflags) & (res=0)));
  379. IF debug THEN
  380. KernelLog.String("WriteConfig ("); KernelLog.Int(fkt, 1); KernelLog.String("):"); KernelLog.Ln;
  381. OutRegs(eax, ebx, ecx, edx, esi, edi, eflags)
  382. END
  383. ELSE
  384. res := NoPCI
  385. END;
  386. RETURN res
  387. END WriteConfig;
  388. PROCEDURE WriteConfigByte*(busNr, devNr, fktNr, regNr, regVal: LONGINT): LONGINT;
  389. BEGIN
  390. RETURN WriteConfig(writeConfigByte, busNr, devNr, fktNr, regNr, regVal)
  391. END WriteConfigByte;
  392. PROCEDURE WriteConfigWord*(busNr, devNr, fktNr, regNr, regVal: LONGINT): LONGINT;
  393. BEGIN
  394. ASSERT(regNr MOD 2 = 0);
  395. RETURN WriteConfig(writeConfigWord, busNr, devNr, fktNr, regNr, regVal)
  396. END WriteConfigWord;
  397. PROCEDURE WriteConfigDword*(busNr, devNr, fktNr, regNr, regVal: LONGINT): LONGINT;
  398. BEGIN
  399. ASSERT(regNr MOD 4 = 0);
  400. RETURN WriteConfig(writeConfigDword, busNr, devNr, fktNr, regNr, regVal)
  401. END WriteConfigDword;
  402. PROCEDURE DetectPCI;
  403. VAR res, len, entry: LONGINT; adr: ADDRESS;
  404. BEGIN
  405. res := FindBios32Service(PCIServiceId, 0, adr, len, entry);
  406. pci := res = Done;
  407. IF pci THEN
  408. Machine.MapPhysical(adr, len, adr); (* map into virtual address space *)
  409. ASSERT(adr # Machine.NilAdr);
  410. pciEntry := adr+entry
  411. END
  412. END DetectPCI;
  413. PROCEDURE Show*;
  414. VAR version, lastPCIBus, hwMech, res : LONGINT;
  415. BEGIN
  416. IF ~PCIDisabled() THEN
  417. res := PCIPresent(version, lastPCIBus, hwMech);
  418. IF (res = Done) THEN
  419. KernelLog.Enter;
  420. KernelLog.String("PCI: "); KernelLog.Int(lastPCIBus + 1, 0); KernelLog.String(" bus(ses) found, PCI version: ");
  421. KernelLog.Hex(version DIV 256, -2); KernelLog.Char("."); KernelLog.Hex(version MOD 256, -2);
  422. KernelLog.Exit;
  423. ELSE
  424. KernelLog.Enter; KernelLog.String("PCI: No bus found."); KernelLog.Exit;
  425. END;
  426. ELSE
  427. KernelLog.Enter; KernelLog.String("PCI: Not available (Disabled by user)."); KernelLog.Exit;
  428. END;
  429. END Show;
  430. PROCEDURE StartIterate*(VAR pci: Pci);
  431. BEGIN pci.bus := 0; pci.device := 0; pci.function := 0
  432. END StartIterate;
  433. PROCEDURE Iterate*(VAR pci: Pci): BOOLEAN;
  434. VAR hdrType,res: LONGINT; multifunction: BOOLEAN;
  435. BEGIN
  436. IF pci.function = 0 THEN
  437. (* check if multi-function device *)
  438. res := ReadConfigDword(pci.bus, pci.device, pci.function, 0CH, hdrType);
  439. multifunction := 23 IN SYSTEM.VAL(SET, hdrType);
  440. ELSE multifunction := TRUE
  441. END;
  442. INC(pci.function);
  443. IF ~multifunction OR (pci.function >= 8) THEN
  444. pci.function := 0;
  445. INC(pci.device);
  446. IF pci.device >= 32 THEN
  447. pci.device := 0;
  448. INC(pci.bus);
  449. IF pci.bus > 255 THEN RETURN FALSE END;
  450. END;
  451. END;
  452. RETURN TRUE
  453. END Iterate;
  454. PROCEDURE PCIDisabled() : BOOLEAN;
  455. VAR string : ARRAY 2 OF CHAR;
  456. BEGIN
  457. Machine.GetConfig("DisablePCI", string);
  458. RETURN string = "1";
  459. END PCIDisabled;
  460. BEGIN
  461. pci := FALSE; bios32 := FALSE;
  462. IF ~PCIDisabled() THEN
  463. DetectBios32;
  464. DetectPCI;
  465. END;
  466. Show;
  467. END PCI.
  468. (**
  469. Notes
  470. PCI devices are uniquely identified by their vendor ID and device ID. For example, a 3Com 905B Etherlink XL ethernet card has vendor ID 10B7H (3Com) and device ID 9055H. To get access to this card, use the FindPCIDevice call. The third parameter (idx) is used to find multiple instances of the card. If set to 0, the first card is returned; if set to 1, the second; etc. The last three parameters return the bus number, device number and function number of the card, respectively. This triple can be used with the other calls (e.g., ReadConfig..., WriteConfig...) to address a specific card.
  471. Example:
  472. VAR res, bus, dev, fkt: LONGINT;
  473. (* look for a 3Com 905B ethernet card *)
  474. res := PCI.FindPCIDevice(9055H, 10B7H, 0, bus, dev, fkt);
  475. IF res = PCI.Done THEN (* found at (bus, dev, fkt) *) END
  476. The PCI configuration area is a standardized set of registers provided by every PCI device. It can be accessed using the ReadConfig... and WriteConfig... calls. Typically, registers 10H, 14H, ..., 24H specify the base addresses of a card. Bit 0 is 1 if the address is in the I/O space, and 0 if it is in the physical memory space. For I/O addresses, the bottom two bits should be masked off, and for physical memory addresses, the bottom 4 bits should be masked off.
  477. Example:
  478. VAR res, adr: LONGINT;
  479. (* find the I/O base address of the ethernet controller *)
  480. res := PCI.ReadConfigDword(bus, dev, fkt, 10H, adr);
  481. IF res = PCI.Done THEN
  482. ASSERT(ODD(adr)); (* must be I/O mapped *)
  483. DEC(adr, adr MOD 4); (* strip lower 2 bits *)
  484. ...
  485. SYSTEM.PORTIN(adr+X, x) (* read some device register *)
  486. END
  487. To access a memory-mapped device, its address range has to be mapped into the virtual address space first.
  488. Example:
  489. CONST Size = 4096; (* the device has 4KB of registers *)
  490. VAR res, physAdr, virtAdr: LONGINT;
  491. (* find the base address of a memory-mapped device *)
  492. res := PCI.ReadConfigDword(bus, dev, fkt, 10H, physAdr);
  493. IF res = PCI.Done THEN
  494. ASSERT(~ODD(physAdr)); (* must be memory mapped *)
  495. DEC(physAdr, physAdr MOD 16); (* strip lower 4 bits *)
  496. Machine.MapPhysical(physAdr, Size, virtAdr);
  497. ...
  498. x := SYSTEM.GET32(virtAdr+X); (* read some device register *)
  499. ...
  500. Machine.UnmapPhysical(virtAdr, Size)
  501. END
  502. *)