BIOS.I386.PCI.Mod 19 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564
  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, Objects, KernelLog;
  5. CONST
  6. Trace = TRUE;
  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: LONGINT
  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: LONGINT;
  50. PROCEDURE BiosServiceDirectory(sadr, sid, fs: LONGINT; VAR badr: ADDRESS; VAR len, entry: LONGINT): CHAR;
  51. CODE {SYSTEM.i386}
  52. PUSH ECX
  53. MOV AX, CS
  54. PUSH EAX
  55. MOV EAX, [EBP+sid]
  56. MOV EBX, [EBP+fs]
  57. MOV EDX, [EBP+sadr]
  58. CALL EDX
  59. MOV ESI, [EBP+badr]
  60. MOV [ESI], EBX
  61. MOV ESI, [EBP+len]
  62. MOV [ESI], ECX
  63. MOV ESI, [EBP+entry]
  64. MOV [ESI], EDX
  65. POP ECX
  66. END BiosServiceDirectory;
  67. PROCEDURE FindBios32Service*(serviceId, serviceFkt: LONGINT; VAR serviceAdr: ADDRESS; VAR serviceLen, entryOffset: LONGINT): LONGINT;
  68. VAR ch: CHAR; res: WORD; state: SET;
  69. BEGIN {EXCLUSIVE}
  70. IF bios32 THEN
  71. state := Machine.DisableInterrupts();
  72. ch := BiosServiceDirectory(Bios32Def.entry, serviceId, serviceFkt,
  73. serviceAdr, serviceLen, entryOffset);
  74. Machine.RestoreInterrupts(state);
  75. res := ORD(ch)
  76. ELSE
  77. res := NoBios32
  78. END;
  79. RETURN res
  80. END FindBios32Service;
  81. PROCEDURE DetectBios32;
  82. VAR adr, chksum, i: LONGINT; s: ARRAY 16 OF CHAR;
  83. BEGIN
  84. adr := 0E0000H; chksum := 0FFH;
  85. REPEAT
  86. SYSTEM.MOVE(adr, ADDRESSOF(s[0]), 16);
  87. IF (s[0] = "_") & (s[1] = "3") & (s[2] = "2") & (s[3] = "_") THEN
  88. chksum := 0; i := 0;
  89. WHILE i < 16 DO
  90. chksum := chksum + ORD(s[i]);
  91. IF FALSE & debug THEN KernelLog.Int(ORD(s[i]), 1); KernelLog.Char(" ") END;
  92. INC(i)
  93. END;
  94. chksum := chksum MOD 256;
  95. END;
  96. INC(adr, 16)
  97. UNTIL (chksum = 0) OR (adr = 0100000H);
  98. bios32 := chksum = 0;
  99. IF bios32 THEN
  100. SYSTEM.MOVE(ADDRESSOF(s[0]), ADDRESSOF(Bios32Def), 16);
  101. IF Trace THEN
  102. KernelLog.String("PCI Bios32 detected at: "); KernelLog.Hex(adr-16, 8); KernelLog.Ln;
  103. KernelLog.String(" Sig: ");
  104. KernelLog.Char(Bios32Def.sig[0]); KernelLog.Char(Bios32Def.sig[1]);
  105. KernelLog.Char(Bios32Def.sig[2]); KernelLog.Char(Bios32Def.sig[3]);
  106. KernelLog.String(", Entry: "); KernelLog.Hex(Bios32Def.entry, 8);
  107. KernelLog.String(", Revision: "); KernelLog.Int(ORD(Bios32Def.rev), 1);
  108. KernelLog.String(", Length: "); KernelLog.Int(ORD(Bios32Def.len)*16, 1);
  109. KernelLog.String(", Checksum: "); KernelLog.Int(ORD(Bios32Def.chksum), 1);
  110. KernelLog.Ln
  111. END
  112. ELSE
  113. IF Trace THEN
  114. KernelLog.String("No PCI BIOS32 detected"); KernelLog.Ln
  115. END;
  116. END
  117. END DetectBios32;
  118. PROCEDURE pcicall(entry:LONGINT; VAR eax,ebx,ecx,edx,esi,edi:LONGINT; VAR eflags: SET);
  119. CODE {SYSTEM.i386}
  120. PUSH ECX
  121. MOV EAX,CS
  122. PUSH EAX
  123. MOV EAX,[EBP+edi]
  124. MOV EDI,[EAX]
  125. MOV EAX,[EBP+esi]
  126. MOV ESI,[EAX]
  127. MOV EAX,[EBP+edx]
  128. MOV EDX,[EAX]
  129. MOV EAX,[EBP+ecx]
  130. MOV ECX,[EAX]
  131. MOV EAX,[EBP+ebx]
  132. MOV EBX,[EAX]
  133. MOV EAX,[EBP+eax]
  134. MOV EAX,[EAX]
  135. CALL DWORD [EBP+entry]
  136. PUSHFD
  137. PUSH EAX
  138. MOV EAX,[EBP+edi]
  139. MOV [EAX],EDI
  140. MOV EAX,[EBP+esi]
  141. MOV [EAX],ESI
  142. MOV EAX,[EBP+edx]
  143. MOV [EAX],EDX
  144. MOV EAX,[EBP+ecx]
  145. MOV [EAX],ECX
  146. MOV EAX,[EBP+ebx]
  147. MOV [EAX],EBX
  148. POP EBX
  149. MOV EAX,[EBP+eax]
  150. MOV [EAX],EBX
  151. POP EBX
  152. MOV EAX,[EBP+eflags]
  153. MOV [EAX],EBX
  154. POP ECX
  155. END pcicall;
  156. PROCEDURE OutRegs(eax, ebx, ecx, edx, esi, edi: LONGINT; eflags: SET);
  157. BEGIN
  158. IF debug THEN
  159. KernelLog.String(" eax: "); KernelLog.Hex(eax, 8); KernelLog.Ln;
  160. KernelLog.String(" ebx: "); KernelLog.Hex(ebx, 8); KernelLog.Ln;
  161. KernelLog.String(" ecx: "); KernelLog.Hex(ecx, 8); KernelLog.Ln;
  162. KernelLog.String(" edx: "); KernelLog.Hex(edx, 8); KernelLog.Ln;
  163. KernelLog.String(" esi: "); KernelLog.Hex(esi, 8); KernelLog.Ln;
  164. KernelLog.String(" edi: "); KernelLog.Hex(edi, 8); KernelLog.Ln;
  165. KernelLog.String(" eflags: "); KernelLog.Hex(SYSTEM.VAL(LONGINT, eflags), 8); KernelLog.Ln
  166. END
  167. END OutRegs;
  168. PROCEDURE PCIPresent*(VAR version, lastPCIbus, hwMech: LONGINT): LONGINT;
  169. VAR res, eax, ebx, ecx, edx, esi, edi: LONGINT; eflags, state: SET;
  170. BEGIN {EXCLUSIVE}
  171. IF pci THEN
  172. eax := PCIFunctionId + PCIBiosPresent;
  173. state := Machine.DisableInterrupts();
  174. pcicall(pciEntry, eax, ebx, ecx, edx, esi, edi, eflags);
  175. Machine.RestoreInterrupts(state);
  176. res := (eax DIV 100H) MOD 100H;
  177. IF (edx = PCIString) & ~(0 IN eflags) & (res = Done) THEN
  178. version := ebx MOD 10000H;
  179. lastPCIbus := ecx MOD 100H;
  180. hwMech := eax MOD 100H
  181. ELSIF res = 0 THEN res := NoPCI (* ; pci := FALSE (* <- hmm, not sure about that *) *)
  182. END;
  183. IF debug THEN
  184. KernelLog.String("PCIPresent:"); KernelLog.Ln;
  185. OutRegs(eax, ebx, ecx, edx, esi, edi, eflags)
  186. END
  187. ELSE
  188. res := NoPCI
  189. END;
  190. RETURN res
  191. END PCIPresent;
  192. PROCEDURE FindPCIDevice*(devId, vendId, idx: LONGINT; VAR busNr, devNr, fktNr: LONGINT): LONGINT;
  193. VAR res, eax, ebx, ecx, edx, esi, edi: LONGINT; eflags, state: SET;
  194. BEGIN {EXCLUSIVE}
  195. IF pci THEN
  196. eax := PCIFunctionId + findPCIDevice;
  197. ecx := devId; edx := vendId; esi := idx;
  198. state := Machine.DisableInterrupts();
  199. pcicall(pciEntry, eax, ebx, ecx, edx, esi, edi, eflags);
  200. Machine.RestoreInterrupts(state);
  201. res := (eax DIV 100H) MOD 100H; ASSERT(~((0 IN eflags) & (res=0)));
  202. IF ~(0 IN eflags) & (res = Done) THEN
  203. busNr := (ebx DIV 100H) MOD 100H;
  204. devNr := (ebx DIV 8) MOD 20H;
  205. fktNr := ebx MOD 8
  206. END;
  207. IF debug THEN
  208. KernelLog.String("FindPCIDevice:"); KernelLog.Ln;
  209. OutRegs(eax, ebx, ecx, edx, esi, edi, eflags)
  210. END
  211. ELSE
  212. res := NoPCI
  213. END;
  214. RETURN res
  215. END FindPCIDevice;
  216. PROCEDURE FindPCIClassCode*(classCode, idx: LONGINT; VAR busNr, devNr, fktNr: LONGINT): LONGINT;
  217. VAR res, eax, ebx, ecx, edx, esi, edi: LONGINT; eflags, state: SET;
  218. BEGIN {EXCLUSIVE}
  219. IF pci THEN
  220. eax := PCIFunctionId + findPCIClassCode;
  221. ecx := classCode; esi := idx;
  222. state := Machine.DisableInterrupts();
  223. pcicall(pciEntry, eax, ebx, ecx, edx, esi, edi, eflags);
  224. Machine.RestoreInterrupts(state);
  225. res := (eax DIV 100H) MOD 100H; ASSERT(~((0 IN eflags) & (res=0)));
  226. IF ~(0 IN eflags) & (res = Done) THEN
  227. busNr := (ebx DIV 100H) MOD 100H;
  228. devNr := (ebx DIV 8) MOD 20H;
  229. fktNr := ebx MOD 8
  230. END;
  231. IF debug THEN
  232. KernelLog.String("FindPCIClassCode:"); KernelLog.Ln;
  233. OutRegs(eax, ebx, ecx, edx, esi, edi, eflags)
  234. END
  235. ELSE
  236. res := NoPCI
  237. END;
  238. RETURN res
  239. END FindPCIClassCode;
  240. PROCEDURE GenerateSpecialCycle*(busNr, specCycleData: LONGINT): LONGINT;
  241. VAR res, eax, ebx, ecx, edx, esi, edi: LONGINT; eflags, state: SET;
  242. BEGIN {EXCLUSIVE}
  243. IF pci THEN
  244. eax := PCIFunctionId + generateSpecialCycle;
  245. ebx := busNr*100H; edx := specCycleData;
  246. state := Machine.DisableInterrupts();
  247. pcicall(pciEntry, eax, ebx, ecx, edx, esi, edi, eflags);
  248. Machine.RestoreInterrupts(state);
  249. res := (eax DIV 100H) MOD 100H; ASSERT(~((0 IN eflags) & (res=0)));
  250. IF debug THEN
  251. KernelLog.String("GenerateSpecialCycle:"); KernelLog.Ln;
  252. OutRegs(eax, ebx, ecx, edx, esi, edi, eflags)
  253. END
  254. ELSE
  255. res := NoPCI
  256. END;
  257. RETURN res
  258. END GenerateSpecialCycle;
  259. PROCEDURE GetIrqRoutingOptions*(VAR rt: RouteTable; VAR IrqBitmap: SET): LONGINT;
  260. CONST dbN = 16*8;
  261. VAR
  262. res, eax, ebx, ecx, edx, esi, edi, i: LONGINT; eflags, state: SET;
  263. rb: RouteBuffer; db: ARRAY dbN OF CHAR;
  264. last: RouteTable;
  265. BEGIN {EXCLUSIVE}
  266. IF pci THEN
  267. eax := PCIFunctionId + getIrqRoutingOptions;
  268. rb.BufferSize := dbN; rb.SegSelector := 0;
  269. rb.DataBufferAdr := ADDRESSOF(db[0]);
  270. ebx := 0H; edi := ADDRESSOF(rb);
  271. state := Machine.DisableInterrupts();
  272. pcicall(pciEntry, eax, ebx, ecx, edx, esi, edi, eflags);
  273. Machine.RestoreInterrupts(state);
  274. res := (eax DIV 100H) MOD 100H; ASSERT(~((0 IN eflags) & (res=0)));
  275. ASSERT(res # BufferTooSmall); (* Increase dbN on Trap *)
  276. IF ~(0 IN eflags) & (res = Done) THEN
  277. IrqBitmap := SYSTEM.VAL(SET, ebx);
  278. NEW(rt); rt.next := NIL; last := rt; i := 0;
  279. WHILE i < rb.BufferSize DO
  280. NEW(last.next); last := last.next; last.next := NIL;
  281. last.busNr := ORD(db[i]); INC(i);
  282. last.devNr := ORD(db[i]) DIV 8; INC(i);
  283. last.linkValIntA := db[i]; INC(i);
  284. last.IrqBitmapA := SYSTEM.VAL(SET, LONG(ORD(db[i])+ORD(db[i+1])*100H)); INC(i, 2);
  285. last.linkValIntB := db[i]; INC(i);
  286. last.IrqBitmapB := SYSTEM.VAL(SET, LONG(ORD(db[i])+ORD(db[i+1])*100H)); INC(i, 2);
  287. last.linkValIntC:= db[i]; INC(i);
  288. last.IrqBitmapC := SYSTEM.VAL(SET, LONG(ORD(db[i])+ORD(db[i+1])*100H)); INC(i, 2);
  289. last.linkValIntD := db[i]; INC(i);
  290. last.IrqBitmapD := SYSTEM.VAL(SET, LONG(ORD(db[i])+ORD(db[i+1])*100H)); INC(i, 2);
  291. last.slotNr := ORD(db[i]); INC(i);
  292. INC(i) (* reserved byte *)
  293. END;
  294. rt := rt.next
  295. END;
  296. IF debug THEN
  297. KernelLog.String("GetIrqRoutingOptions:"); KernelLog.Ln;
  298. OutRegs(eax, ebx, ecx, edx, esi, edi, eflags)
  299. END
  300. ELSE
  301. res := NoPCI
  302. END;
  303. RETURN res
  304. END GetIrqRoutingOptions;
  305. PROCEDURE SetPCIIrq*(IntPin, IrqNum, busNr, devNr, fktNr: LONGINT): LONGINT;
  306. VAR res, eax, ebx, ecx, edx, esi, edi: LONGINT; eflags, state: SET;
  307. BEGIN {EXCLUSIVE}
  308. IF pci THEN
  309. eax := PCIFunctionId + setPCIIrq;
  310. ecx := IrqNum*100H + IntPin; ebx := busNr*100H+devNr*8+fktNr;
  311. state := Machine.DisableInterrupts();
  312. pcicall(pciEntry, eax, ebx, ecx, edx, esi, edi, eflags);
  313. Machine.RestoreInterrupts(state);
  314. res := (eax DIV 100H) MOD 100H; ASSERT(~((0 IN eflags) & (res=0)));
  315. IF debug THEN
  316. KernelLog.String("SetPCIHwInt:"); KernelLog.Ln;
  317. OutRegs(eax, ebx, ecx, edx, esi, edi, eflags)
  318. END
  319. ELSE
  320. res := NoPCI
  321. END;
  322. RETURN res
  323. END SetPCIIrq;
  324. (** Set bits included in <mask> in the PCI command register if not set already *)
  325. PROCEDURE Enable*(mask : SET; busNr, devNr, fktNr : LONGINT) : LONGINT;
  326. VAR cmdReg : LONGINT; res : WORD;
  327. BEGIN
  328. res := ReadConfigWord(busNr, devNr, fktNr, CmdReg, cmdReg);
  329. IF (res = Done) THEN
  330. IF mask - SYSTEM.VAL(SET, cmdReg) # {} THEN
  331. cmdReg := SYSTEM.VAL(LONGINT, SYSTEM.VAL(SET, cmdReg) + mask);
  332. res := WriteConfigWord(busNr, devNr, fktNr, CmdReg, cmdReg);
  333. IF (res = Done) THEN (* maybe the device does not implement all bits writable... check! *)
  334. res := ReadConfigWord(busNr, devNr, fktNr, CmdReg, cmdReg);
  335. IF (res = Done) THEN
  336. IF mask - SYSTEM.VAL(SET, cmdReg) # {} THEN (* at least one bit is not set *)
  337. res := Error;
  338. END;
  339. END;
  340. END;
  341. END;
  342. END;
  343. RETURN res;
  344. END Enable;
  345. PROCEDURE ReadConfig(fkt, busNr, devNr, fktNr, regNr: LONGINT; mask: SET; VAR regVal: LONGINT): LONGINT;
  346. VAR res, eax, ebx, ecx, edx, esi, edi: LONGINT; eflags, state: SET;
  347. BEGIN {EXCLUSIVE}
  348. IF pci THEN
  349. eax := PCIFunctionId + fkt;
  350. ebx := busNr*100H+devNr*8+fktNr; edi := regNr;
  351. state := Machine.DisableInterrupts();
  352. pcicall(pciEntry, eax, ebx, ecx, edx, esi, edi, eflags);
  353. Machine.RestoreInterrupts(state);
  354. res := (eax DIV 100H) MOD 100H; ASSERT(~((0 IN eflags) & (res=0)));
  355. IF ~(0 IN eflags) & (res = Done) THEN
  356. regVal := SYSTEM.VAL(LONGINT, SYSTEM.VAL(SET, ecx)*mask)
  357. END;
  358. IF debug THEN
  359. KernelLog.String("ReadConfig ("); KernelLog.Int(fkt, 1); KernelLog.String("):"); KernelLog.Ln;
  360. OutRegs(eax, ebx, ecx, edx, esi, edi, eflags)
  361. END
  362. ELSE
  363. res := NoPCI
  364. END;
  365. RETURN res
  366. END ReadConfig;
  367. PROCEDURE ReadConfigByte*(busNr, devNr, fktNr, regNr: LONGINT; VAR regVal: LONGINT): LONGINT;
  368. BEGIN
  369. RETURN ReadConfig(readConfigByte, busNr, devNr, fktNr, regNr, {0..7}, regVal)
  370. END ReadConfigByte;
  371. PROCEDURE ReadConfigWord*(busNr, devNr, fktNr, regNr: LONGINT; VAR regVal: LONGINT): LONGINT;
  372. BEGIN
  373. ASSERT(regNr MOD 2 = 0);
  374. RETURN ReadConfig(readConfigWord, busNr, devNr, fktNr, regNr, {0..15}, regVal)
  375. END ReadConfigWord;
  376. PROCEDURE ReadConfigDword*(busNr, devNr, fktNr, regNr: LONGINT; VAR regVal: LONGINT): LONGINT;
  377. BEGIN
  378. ASSERT(regNr MOD 4 = 0);
  379. RETURN ReadConfig(readConfigDword, busNr, devNr, fktNr, regNr, {0..31}, regVal)
  380. END ReadConfigDword;
  381. PROCEDURE WriteConfig(fkt, busNr, devNr, fktNr, regNr, regVal: LONGINT): LONGINT;
  382. VAR res, eax, ebx, ecx, edx, esi, edi: LONGINT; eflags, state: SET;
  383. BEGIN {EXCLUSIVE}
  384. IF pci THEN
  385. eax := PCIFunctionId + fkt;
  386. ebx := busNr*100H+devNr*8+fktNr; ecx := regVal; edi := regNr;
  387. state := Machine.DisableInterrupts();
  388. pcicall(pciEntry, eax, ebx, ecx, edx, esi, edi, eflags);
  389. Machine.RestoreInterrupts(state);
  390. res := (eax DIV 100H) MOD 100H; ASSERT(~((0 IN eflags) & (res=0)));
  391. IF debug THEN
  392. KernelLog.String("WriteConfig ("); KernelLog.Int(fkt, 1); KernelLog.String("):"); KernelLog.Ln;
  393. OutRegs(eax, ebx, ecx, edx, esi, edi, eflags)
  394. END
  395. ELSE
  396. res := NoPCI
  397. END;
  398. RETURN res
  399. END WriteConfig;
  400. PROCEDURE WriteConfigByte*(busNr, devNr, fktNr, regNr, regVal: LONGINT): LONGINT;
  401. BEGIN
  402. RETURN WriteConfig(writeConfigByte, busNr, devNr, fktNr, regNr, regVal)
  403. END WriteConfigByte;
  404. PROCEDURE WriteConfigWord*(busNr, devNr, fktNr, regNr, regVal: LONGINT): LONGINT;
  405. BEGIN
  406. ASSERT(regNr MOD 2 = 0);
  407. RETURN WriteConfig(writeConfigWord, busNr, devNr, fktNr, regNr, regVal)
  408. END WriteConfigWord;
  409. PROCEDURE WriteConfigDword*(busNr, devNr, fktNr, regNr, regVal: LONGINT): LONGINT;
  410. BEGIN
  411. ASSERT(regNr MOD 4 = 0);
  412. RETURN WriteConfig(writeConfigDword, busNr, devNr, fktNr, regNr, regVal)
  413. END WriteConfigDword;
  414. PROCEDURE DetectPCI;
  415. VAR res, len, entry: LONGINT; adr: ADDRESS;
  416. BEGIN
  417. res := FindBios32Service(PCIServiceId, 0, adr, len, entry);
  418. pci := res = Done;
  419. IF pci THEN
  420. Machine.MapPhysical(adr, len, adr); (* map into virtual address space *)
  421. ASSERT(adr # Machine.NilAdr);
  422. pciEntry := adr+entry
  423. END
  424. END DetectPCI;
  425. PROCEDURE Show*;
  426. VAR version, lastPCIBus, hwMech, res : LONGINT;
  427. BEGIN
  428. IF ~PCIDisabled() THEN
  429. res := PCIPresent(version, lastPCIBus, hwMech);
  430. IF (res = Done) THEN
  431. KernelLog.Enter;
  432. KernelLog.String("PCI: "); KernelLog.Int(lastPCIBus + 1, 0); KernelLog.String(" bus(ses) found, PCI version: ");
  433. KernelLog.Hex(version DIV 256, -2); KernelLog.Char("."); KernelLog.Hex(version MOD 256, -2);
  434. KernelLog.Exit;
  435. ELSE
  436. KernelLog.Enter; KernelLog.String("PCI: No bus found."); KernelLog.Exit;
  437. END;
  438. ELSE
  439. KernelLog.Enter; KernelLog.String("PCI: Not available (Disabled by user)."); KernelLog.Exit;
  440. END;
  441. END Show;
  442. PROCEDURE StartIterate*(VAR pci: Pci);
  443. BEGIN pci.bus := 0; pci.device := 0; pci.function := 0
  444. END StartIterate;
  445. PROCEDURE Iterate*(VAR pci: Pci): BOOLEAN;
  446. VAR hdrType,res: LONGINT; multifunction: BOOLEAN;
  447. BEGIN
  448. IF pci.function = 0 THEN
  449. (* check if multi-function device *)
  450. res := ReadConfigDword(pci.bus, pci.device, pci.function, 0CH, hdrType);
  451. multifunction := 23 IN SYSTEM.VAL(SET, hdrType);
  452. ELSE multifunction := TRUE
  453. END;
  454. INC(pci.function);
  455. IF ~multifunction OR (pci.function >= 8) THEN
  456. pci.function := 0;
  457. INC(pci.device);
  458. IF pci.device >= 32 THEN
  459. pci.device := 0;
  460. INC(pci.bus);
  461. IF pci.bus > 255 THEN RETURN FALSE END;
  462. END;
  463. END;
  464. RETURN TRUE
  465. END Iterate;
  466. PROCEDURE PCIDisabled() : BOOLEAN;
  467. VAR string : ARRAY 2 OF CHAR;
  468. BEGIN
  469. Machine.GetConfig("DisablePCI", string);
  470. RETURN string = "1";
  471. END PCIDisabled;
  472. BEGIN
  473. pci := FALSE; bios32 := FALSE;
  474. IF ~PCIDisabled() THEN
  475. DetectBios32;
  476. DetectPCI;
  477. END;
  478. Show;
  479. END PCI.
  480. (**
  481. Notes
  482. 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.
  483. Example:
  484. VAR res, bus, dev, fkt: LONGINT;
  485. (* look for a 3Com 905B ethernet card *)
  486. res := PCI.FindPCIDevice(9055H, 10B7H, 0, bus, dev, fkt);
  487. IF res = PCI.Done THEN (* found at (bus, dev, fkt) *) END
  488. 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.
  489. Example:
  490. VAR res, adr: LONGINT;
  491. (* find the I/O base address of the ethernet controller *)
  492. res := PCI.ReadConfigDword(bus, dev, fkt, 10H, adr);
  493. IF res = PCI.Done THEN
  494. ASSERT(ODD(adr)); (* must be I/O mapped *)
  495. DEC(adr, adr MOD 4); (* strip lower 2 bits *)
  496. ...
  497. SYSTEM.PORTIN(adr+X, x) (* read some device register *)
  498. END
  499. To access a memory-mapped device, its address range has to be mapped into the virtual address space first.
  500. Example:
  501. CONST Size = 4096; (* the device has 4KB of registers *)
  502. VAR res, physAdr, virtAdr: LONGINT;
  503. (* find the base address of a memory-mapped device *)
  504. res := PCI.ReadConfigDword(bus, dev, fkt, 10H, physAdr);
  505. IF res = PCI.Done THEN
  506. ASSERT(~ODD(physAdr)); (* must be memory mapped *)
  507. DEC(physAdr, physAdr MOD 16); (* strip lower 4 bits *)
  508. Machine.MapPhysical(physAdr, Size, virtAdr);
  509. ...
  510. x := SYSTEM.GET32(virtAdr+X); (* read some device register *)
  511. ...
  512. Machine.UnmapPhysical(virtAdr, Size)
  513. END
  514. *)