AMD64.UsbKeyboard.Mod 29 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761
  1. MODULE UsbKeyboard; (** AUTHOR "cplattner; staubesv"; PURPOSE "Bluebottle USB Keyboard Driver" *) (** non-portable **)
  2. (**
  3. * Bluebottle USB Keyboard Driver (HID boot protocol)
  4. *
  5. * Usage:
  6. *
  7. * UsbKeyboard.Install ~ loads this driver System.Free UsbKeyboard ~ unloads it
  8. *
  9. * UsbKeyboard.SetLayout dev file ~ sets the keyboard layout
  10. * UsbKeyboard.SetLayout UsbKeyboard00 KeyCH.Bin ~ sets the CH keyboard layout, for example
  11. *
  12. * References:
  13. *
  14. * Device Class Definition for Human Interface Devices (HID), version 1.11
  15. * HID Usage Tables, version 1.11
  16. *
  17. * References are available at http://www.usb.org
  18. *
  19. * History:
  20. *
  21. * 30.09.2000 cp first release
  22. * 18.10.2000 cp fix size of interrupt endpoint and add warning message if keyboard fails
  23. * 27.02.2006 Correct handling for modifier keys (also generate event if only a modifier key is pressed) (staubesv)
  24. * 01.03.2006 Added SetLayout & KeyboardDriver.SetLayout (staubesv)
  25. * 22.01.2007 Splitted up Keyboard Driver for HID compatibility (ottigerm)
  26. *)
  27. IMPORT SYSTEM, Machine, Files, Inputs, Commands, KernelLog, Streams, Plugins, Modules, Usb, Usbdi, UsbHid;
  28. CONST
  29. Name = "UsbKeyboard";
  30. Description = "USB Keyboard Driver";
  31. Priority = 10;
  32. NumLock* = 0;
  33. CapsLock* = 1;
  34. ScrollLock* = 2;
  35. (* Compose & kana not yet implemented *)
  36. Compose = 3;
  37. Kana = 4;
  38. (* If you press a key and hold it down, the following will happen: *)
  39. (* 1. A Inputs.KeyboardMsg is sent *)
  40. (* 2. No further messages are sent until the period KeyDeadTime expires *)
  41. (* 3. Further messages are sent with the interval KeyDeadTimeRepeat *)
  42. (* *)
  43. (* A release event is sent when you release the key. *)
  44. (* The values KeyDeadTime and KeyDeadTimeRepeat are set in milliseconds. *)
  45. (* *)
  46. KeyDeadTime* = 100;
  47. KeyDeadTimeRepeat* = 0; (* 10 <= value < infinity && value mod 10 = 0 *)
  48. TraceKeys* = FALSE; (* Displays scan code of pressed key on KernelLog if TRUE *)
  49. Debug* = TRUE;
  50. TYPE
  51. Key* = RECORD
  52. ch* : CHAR;
  53. keysym* : LONGINT;
  54. counter* : LONGINT;
  55. repeat* : BOOLEAN;
  56. updated* : BOOLEAN;
  57. END;
  58. TYPE
  59. KeyboardBase*=OBJECT
  60. VAR
  61. msg*, lastMsg : Inputs.KeyboardMsg;
  62. lastFlags : SET;
  63. numKeyVal : LONGINT;
  64. deadKey* : LONGINT;
  65. dkHack* : LONGINT; (* deadKey value should persist Release events ... *)
  66. (* Status of NumLock,ScrollLock,CapsLock,Compose & Kana *)
  67. leds*, lastLeds* : SET;
  68. ledBuffer* : Usbdi.BufferPtr;
  69. keyboardFileTable : POINTER TO ARRAY OF CHAR;
  70. keytable* : ADDRESS; (* used as pointer to keyboardFileTable[0] *)
  71. keyDeadTime*, keyDeadTimeRepeat* : LONGINT;
  72. PROCEDURE HandleKey*(c : CHAR);
  73. VAR k : LONGINT;
  74. BEGIN
  75. (* map USB Usage ID to keysym: Only non-alphanumeric keys are mapped by Keysym() *)
  76. msg.keysym := KeySym(c, leds);
  77. IF TraceKeys THEN KernelLog.String("USB Usage ID: "); KernelLog.Hex(ORD(c), -3); END;
  78. (* map USB Usage ID to Oberon key code *)
  79. SYSTEM.GET(UsbScanTab() + ORD(c), c);
  80. IF TraceKeys THEN KernelLog.String(" -> Oberon key code: "); KernelLog.Hex(ORD(c), -3) END;
  81. IF c = CHR(58) THEN leds := leds / {CapsLock};
  82. ELSIF c = CHR(69) THEN leds := leds / {NumLock};
  83. ELSIF c = CHR(70) THEN leds := leds / {ScrollLock};
  84. ELSE
  85. k := Translate(msg.flags, leds, c, keytable, deadKey, numKeyVal);
  86. IF TraceKeys THEN KernelLog.String(" translated into: "); KernelLog.Char(CHR(k)); END;
  87. (* if c is an ASCII character, then map c to keysym *)
  88. IF (k >= 1) & (k <= 126) & (msg.keysym = Inputs.KsNil) THEN msg.keysym := k; END;
  89. IF k >= 0 THEN msg.ch := CHR(k) ELSE msg.ch := 0X END;
  90. IF TraceKeys THEN
  91. KernelLog.String(" Aos Keysym: "); IF msg.keysym = Inputs.KsNil THEN KernelLog.String("No Key"); ELSE KernelLog.Hex(msg.keysym, 9); END;
  92. KernelLog.Ln; ShowFlags(msg.flags, leds); KernelLog.Ln;
  93. END;
  94. (* build up message for this event *)
  95. IF (msg.flags # lastMsg.flags) OR (msg.ch # 0X) OR (msg.keysym # Inputs.KsNil) THEN
  96. Inputs.keyboard.Handle(msg);
  97. END;
  98. lastMsg := msg;
  99. END;
  100. END HandleKey;
  101. PROCEDURE HandleModifiers*(flags : SET);
  102. VAR i : LONGINT;
  103. BEGIN
  104. IF flags # lastFlags THEN
  105. msg.flags := {}; msg.ch := 0X; msg.keysym := Inputs.KsNil;
  106. FOR i := 0 TO MAX(SET) DO
  107. IF (i IN flags) & ~(i IN lastFlags) THEN (* modifier key pressed for the first time *)
  108. msg.flags := {i}; msg.keysym := GetModifierKeysym(i);
  109. Inputs.keyboard.Handle(msg);
  110. ELSIF ~(i IN flags) & (i IN lastFlags) THEN (* modifier key released *)
  111. msg.flags := {Inputs.Release}; msg.keysym := GetModifierKeysym(i);
  112. Inputs.keyboard.Handle(msg);
  113. END;
  114. END;
  115. END;
  116. lastFlags := flags;
  117. END HandleModifiers;
  118. PROCEDURE TableFromFile*(CONST name: ARRAY OF CHAR): ADDRESS;
  119. VAR f: Files.File; r: Files.Rider; len: LONGINT;
  120. BEGIN
  121. KernelLog.String("UsbKeyboard: "); KernelLog.String(" Loading layout "); KernelLog.String(name); KernelLog.Ln;
  122. f := Files.Old(name);
  123. IF f # NIL THEN
  124. len := f.Length();
  125. IF len MOD 4 = 0 THEN
  126. NEW(keyboardFileTable, len+1);
  127. f.Set(r, 0); f.ReadBytes(r, keyboardFileTable^, 0, len);
  128. IF r.res = 0 THEN
  129. keyboardFileTable[len] := 0FFX;
  130. RETURN ADDRESSOF(keyboardFileTable[0])
  131. ELSIF Debug THEN KernelLog.String("UsbKeyboard: TableFromFile: Error: res="); KernelLog.Int(r.res, 1); KernelLog.Ln;
  132. END
  133. ELSIF Debug THEN KernelLog.String("UsbKeyboard: TableFromFile: Error: len="); KernelLog.Int(len, 1); KernelLog.Ln;
  134. END
  135. ELSIF Debug THEN KernelLog.String("UsbKeyboard: TableFromFile: Error: File not found."); KernelLog.Ln;
  136. END;
  137. RETURN -1;
  138. END TableFromFile;
  139. PROCEDURE SetLayout*(CONST name : ARRAY OF CHAR);
  140. VAR adr : ADDRESS;
  141. BEGIN
  142. IF name = "KeyUS.Bin" THEN adr := TableUS();
  143. ELSE adr := TableFromFile(name);
  144. END;
  145. IF adr = -1 THEN (* Leave the current setting *)
  146. ELSE SYSTEM.PUT(ADDRESSOF(keytable), adr);
  147. END;
  148. END SetLayout;
  149. END KeyboardBase;
  150. KeyboardDriver = OBJECT (UsbHid.HidDriver)
  151. VAR
  152. pipe : Usbdi.Pipe;
  153. (* buffer[0] : modifier byte *)
  154. (* buffer[1] : reserved *)
  155. (* buffer[2]-buffer[7] : 6 one byte key codes *)
  156. buffer : Usbdi.BufferPtr;
  157. base : KeyboardBase;
  158. (*for keeping the pressed keys in mind*)
  159. pressed* : ARRAY 6 OF Key;
  160. PROCEDURE &Init*;
  161. BEGIN
  162. NEW(base);
  163. END Init;
  164. PROCEDURE EventHandler(status : Usbdi.Status; actLen : LONGINT);
  165. VAR
  166. i, j : LONGINT;
  167. c : CHAR;
  168. modifiers, flags : SET;
  169. res : BOOLEAN;
  170. tempPressed : ARRAY 6 OF Key;
  171. found, kill : BOOLEAN;
  172. BEGIN
  173. IF (status=Usbdi.Ok) OR ((status = Usbdi.ShortPacket) & (actLen >= 8)) THEN
  174. (* evaluate modifier keys *)
  175. base.msg.flags := {};
  176. modifiers := SYSTEM.VAL(SET, buffer[0]);
  177. IF modifiers * {0} # {} THEN INCL(base.msg.flags, Inputs.LeftCtrl) END;
  178. IF modifiers * {1} # {} THEN INCL(base.msg.flags, Inputs.LeftShift) END;
  179. IF modifiers * {2} # {} THEN INCL(base.msg.flags, Inputs.LeftAlt) END;
  180. IF modifiers * {3} # {} THEN INCL(base.msg.flags, Inputs.LeftMeta) END;
  181. IF modifiers * {4} # {} THEN INCL(base.msg.flags, Inputs.RightCtrl) END;
  182. IF modifiers * {5} # {} THEN INCL(base.msg.flags, Inputs.RightShift) END;
  183. IF modifiers * {6} # {} THEN INCL(base.msg.flags, Inputs.RightAlt) END;
  184. IF modifiers * {7} # {} THEN INCL(base.msg.flags, Inputs.RightMeta) END;
  185. flags := base.msg.flags;
  186. (* evaluate the six keycodes *)
  187. FOR i := 2 TO 7 DO
  188. c := buffer[i];
  189. IF c # CHR(0) THEN (* buffer[i] contains key code *)
  190. (* check whether the key is pressed for the first time, is still being pressed or has been released *)
  191. FOR j := 0 TO 5 DO
  192. IF pressed[j].ch = c THEN (* key is still pressed *)
  193. found := TRUE;
  194. pressed[j].updated := TRUE;
  195. tempPressed[i-2].counter := pressed[j].counter + 1;
  196. tempPressed[i-2].ch := pressed[j].ch;
  197. tempPressed[i-2].keysym := pressed[j].keysym;
  198. tempPressed[i-2].updated := FALSE;
  199. tempPressed[i-2].repeat := pressed[j].repeat;
  200. IF pressed[j].repeat THEN
  201. IF (base.keyDeadTimeRepeat # 0) & (tempPressed[i-2].counter MOD base.keyDeadTimeRepeat # 0) THEN (* don't send key event *) kill := TRUE; END;
  202. ELSE
  203. IF tempPressed[i-2].counter MOD base.keyDeadTime # 0 THEN (* don't send key event *)
  204. kill := TRUE;
  205. ELSE
  206. tempPressed[i-2].repeat := TRUE;
  207. END;
  208. END;
  209. END;
  210. END;
  211. END;
  212. IF ~found THEN (* the key has not been pressed down before *)
  213. tempPressed[i-2].ch := c;
  214. tempPressed[i-2].repeat := FALSE;
  215. tempPressed[i-2].updated := FALSE;
  216. tempPressed[i-2].counter := 1;
  217. END;
  218. (* kill : Key is pressed but do not generate key event this time -> repeat rate ... *)
  219. IF (c # CHR(0)) & ~kill THEN
  220. base.HandleKey(c);
  221. tempPressed[i-2].keysym := base.msg.keysym; (* base.msg.keysym asigned by HandleKey() ... *)
  222. END;
  223. END; (* FOR LOOP *)
  224. (* update pressed array. generate keyboard.base.msg's for released keys *)
  225. FOR i := 0 TO 5 DO
  226. IF (pressed[i].updated = FALSE) & (pressed[i].ch # CHR(0)) THEN (* this key has been released *)
  227. base.msg.flags := {};
  228. INCL(base.msg.flags, Inputs.Release);
  229. base.msg.ch := pressed[i].ch;
  230. base.msg.keysym := pressed[i].keysym;
  231. base.dkHack := base.deadKey; (* value of deadKey should persist the key release event *)
  232. base.HandleKey(c);
  233. base.deadKey := base.dkHack;
  234. END;
  235. pressed[i].counter := tempPressed[i].counter;
  236. pressed[i].ch := tempPressed[i].ch;
  237. pressed[i].keysym := tempPressed[i].keysym;
  238. pressed[i].repeat := tempPressed[i].repeat;
  239. pressed[i].updated := FALSE;
  240. END;
  241. (* Generate events for modifiers *)
  242. base.HandleModifiers(flags);
  243. (* update status of the LEDs of the keyboad if necessary *)
  244. IF base.lastLeds # base.leds THEN (* LED status has changed *)
  245. base.ledBuffer[0] := SYSTEM.VAL(CHAR, base.leds); base.lastLeds := base.leds;
  246. res := SetReport(UsbHid.ReportOutput, 0, base.ledBuffer^, 1); (* ignore res *)
  247. END;
  248. status := pipe.Transfer(pipe.maxPacketSize, 0, buffer^);
  249. ELSE
  250. IF Debug THEN KernelLog.String("UsbKeyboard: Error. Disabling keyboard "); KernelLog.String(name); KernelLog.Ln; END;
  251. END;
  252. END EventHandler;
  253. PROCEDURE Connect*(): BOOLEAN;
  254. VAR status : Usbdi.Status; endpoint: LONGINT; i: ADDRESS; k : ARRAY 32 OF CHAR;
  255. BEGIN
  256. IF ~SetProtocol(0) THEN
  257. IF Debug THEN KernelLog.String("UsbKeyboard: Error: Cannot set keyboard into boot protocol mode."); KernelLog.Ln; END;
  258. RETURN FALSE
  259. END;
  260. IF ~SetIdle(0,10) THEN
  261. IF Debug THEN KernelLog.String("UsbKeyboard: Error: Cannot set idle the keyboard."); KernelLog.Ln; END;
  262. RETURN FALSE
  263. END;
  264. endpoint := SYSTEM.VAL(LONGINT, SYSTEM.VAL(SET, interface.endpoints[0].bEndpointAddress) * {0,1,2,3,7});
  265. pipe := device.GetPipe(endpoint);
  266. IF pipe = NIL THEN
  267. IF Debug THEN KernelLog.String("UsbKeyboard: Could not get pipe."); KernelLog.Ln; END;
  268. RETURN FALSE;
  269. END;
  270. (* Get *)
  271. Machine.GetConfig("Keyboard", k);
  272. i := -1;
  273. IF k # "" THEN i := base.TableFromFile(k); END;
  274. IF i = -1 THEN (* Fallback to default *) i := TableUS(); END;
  275. SYSTEM.PUT(ADDRESSOF(base.keytable), i);
  276. (* Apply Numlock boot up state *)
  277. Machine.GetConfig("NumLock", k);
  278. IF k[0] = "1" THEN INCL(base.leds, NumLock) END;
  279. base.keyDeadTime := KeyDeadTime DIV 10;
  280. base.keyDeadTimeRepeat := KeyDeadTimeRepeat DIV 10;
  281. NEW(base.ledBuffer, 1);
  282. NEW(buffer, pipe.maxPacketSize);
  283. pipe.SetTimeout(0);
  284. pipe.SetCompletionHandler(EventHandler);
  285. status := pipe.Transfer(pipe.maxPacketSize, 0, buffer^); (* ignore status *)
  286. RETURN TRUE;
  287. END Connect;
  288. PROCEDURE Disconnect*;
  289. BEGIN
  290. KernelLog.String("UsbKeyboard: USB Keyboard disconnected."); KernelLog.Ln;
  291. END Disconnect;
  292. END KeyboardDriver;
  293. VAR
  294. (* Translation table format:
  295. *
  296. * table = { scancode unshifted-code shifted-code flags } 0FFX .
  297. * scancode = <scancode byte from keyboard, bit 7 set for "grey" extended keys>
  298. * unshifted-code = <CHAR produced by this scancode, without shift>
  299. * shifted-code = <CHAR produced by this scancode, with shift>
  300. * flags = <bit-mapped flag byte indicating special behaviour>
  301. *
  302. * flag bit function
  303. * 0 01 DeadKey: Set dead key flag according to translated key code (1-7)
  304. * 1 02 NumLock: if set, the state of NumLock will reverse the action of shift (for num keypad)
  305. * 2 04 CapsLock: if set, the state of CapsLock will reverse the action of shift (for alpha keys)
  306. * 3 08 LAlt: \ the state of these two flags in the table and the current state of the two...
  307. * 4 10 RAlt: / ...Alt keys must match exactly, otherwise the search is continued.
  308. * 5 20 \
  309. * 6 40 > dead key number (0-7), must match current dead key flag
  310. * 7 80 /
  311. *
  312. * The table is scanned sequentially (speed not critical). Ctrl-Break, Ctrl-F10 and Ctrl-Alt-Del
  313. * are always defined and are not in the table. The control keys are also always defined.
  314. *)
  315. (* TableUS - US keyboard translation table (dead keys: ^=1, '=2, `=3, ~=4, "=5) *)
  316. PROCEDURE TableUS*(): ADDRESS;
  317. CODE {SYSTEM.AMD64}
  318. LEA RAX, [RIP + L2 - L1];
  319. L1:
  320. LEAVE
  321. RET
  322. L2:
  323. ; alphabet
  324. DB 1EH, 'a', 'A', 4H, 30H, 'b', 'B', 4H, 2EH, 'c', 'C', 4H, 20H, 'd', 'D', 4H
  325. DB 12H, 'e', 'E', 4H, 21H, 'f', 'F', 4H, 22H, 'g', 'G', 4H, 23H, 'h', 'H', 4H
  326. DB 17H, 'i', 'I', 4H, 24H, 'j', 'J', 4H, 25H, 'k', 'K', 4H, 26H, 'l', 'L', 4H
  327. DB 32H, 'm', 'M', 4H, 31H, 'n', 'N', 4H, 18H, 'o', 'O', 4H, 19H, 'p', 'P', 4H
  328. DB 10H, 'q', 'Q', 4H, 13H, 'r', 'R', 4H, 1FH, 's', 'S', 4H, 14H, 't', 'T', 4H
  329. DB 16H, 'u', 'U', 4H, 2FH, 'v', 'V', 4H, 11H, 'w', 'W', 4H, 2DH, 'x', 'X', 4H
  330. DB 15H, 'y', 'Y', 4H, 2CH, 'z', 'Z', 4H
  331. ; Oberon accents (LAlt & RAlt)
  332. ; DB 1EH, 'ä', 'Ä', 0CH, 12H, 'ë', 0FFH, 0CH, 18H, 'ö', 'Ö', 0CH, 16H, 'ü', 'Ü', 0CH
  333. ; DB 17H, 'ï', 0FFH, 0CH, 1FH, 'ß', 0FFH, 0CH, 2EH, 'ç', 0FFH, 0CH, 31H, 'ñ', 0FFH, 0CH
  334. ; DB 1EH, 'ä', 'Ä', 14H, 12H, 'ë', 0FFH, 14H, 18H, 'ö', 'Ö', 14H, 16H, 'ü', 'Ü', 14H
  335. ; DB 17H, 'ï', 0FFH, 14H, 1FH, 'ß', 0FFH, 14H, 2EH, 'ç', 0FFH, 14H, 31H, 'ñ', 0FFH, 14H
  336. ; dead keys (LAlt & RAlt)
  337. DB 07H, 0FFH, 1H, 9H, 28H, 2H, 5H, 9H, 29H, 3H, 4H, 9H,
  338. DB 07H, 0FFH, 1H, 11H, 28H, 2H, 5H, 11H, 29H, 3H, 4H, 11H,
  339. ; following keys
  340. ; DB 1EH, 'â', 0FFH, 20H, 12H, 'ê', 0FFH, 20H, 17H, 'î', 0FFH, 20H, 18H, 'ô', 0FFH, 20H
  341. ; DB 16H, 'û', 0FFH, 20H, 1EH, 'à', 0FFH, 60H, 12H, 'è', 0FFH, 60H, 17H, 'ì', 0FFH, 60H
  342. ; DB 18H, 'ò', 0FFH, 60H, 16H, 'ù', 0FFH, 60H, 1EH, 'á', 0FFH, 40H, 12H, 'é', 0FFH, 40H
  343. ; DB 1EH, 'ä', 'Ä', 0A4H, 12H, 'ë', 0FFH, 0A0H, 17H, 'ï', 0FFH, 0A0H, 18H, 'ö', 'Ö', 0A4H
  344. ; DB 16H, 'ü', 'Ü', 0A4H, 31H, 'ñ', 0FFH, 80H
  345. ; numbers at top
  346. DB 0BH, '0', ')', 0H, 02H, '1', '!', 0H, 03H, '2', '@', 0H, 04H, '3', '#', 0H
  347. DB 05H, '4', '$', 0H, 06H, '5', '%', 0H, 07H, '6', '^', 0H, 08H, '7', '&', 0H
  348. DB 09H, '8', '*', 0H, 0AH, '9', '(', 0H
  349. ; symbol keys
  350. DB 28H, 27H, 22H, 0H, 33H, ',', '<', 0H, 0CH, '-', '_', 0H, 34H, '.', '>', 0H
  351. DB 35H, '/', '?', 0H, 27H, ';', ':', 0H, 0DH, '=', '+', 0H, 1AH, '[', '{', 0H
  352. DB 2BH, '\', '|', 0H, 1BH, ']', '}', 0H, 29H, '`', '~', 0H
  353. ; control keys
  354. DB 0EH, 7FH, 7FH, 0H ; backspace
  355. DB 0FH, 09H, 09H, 0H ; tab
  356. DB 1CH, 0DH, 0DH, 0H ; enter
  357. DB 39H, 20H, 20H, 0H ; space
  358. DB 01H, 0FEH, 1BH, 0H ; esc
  359. ; keypad
  360. DB 4FH, 0A9H, '1', 2H ; end/1
  361. DB 50H, 0C2H, '2', 2H ; down/2
  362. DB 51H, 0A3H, '3', 2H ; pgdn/3
  363. DB 4BH, 0C4H, '4', 2H ; left/4
  364. DB 4CH, 0FFH, '5', 2H ; center/5
  365. DB 4DH, 0C3H, '6', 2H ; right/6
  366. DB 47H, 0A8H, '7', 2H ; home/7
  367. DB 48H, 0C1H, '8', 2H ; up/8
  368. DB 49H, 0A2H, '9', 2H ; pgup/9
  369. DB 52H, 0A0H, '0', 2H ; insert/0
  370. DB 53H, 0A1H, 2EH, 2H ; del/.
  371. ; gray keys
  372. DB 4AH, '-', '-', 0H ; gray -
  373. DB 4EH, '+', '+', 0H ; gray +
  374. DB 0B5H, '/', '/', 0H ; gray /
  375. DB 37H, '*', '*', 0H ; gray *
  376. DB 0D0H, 0C2H, 0C2H, 0H ; gray down
  377. DB 0CBH, 0C4H, 0C4H, 0H ; gray left
  378. DB 0CDH, 0C3H, 0C3H, 0H ; gray right
  379. DB 0C8H, 0C1H, 0C1H, 0H ; gray up
  380. DB 09CH, 0DH, 0DH, 0H ; gray enter
  381. DB 0D2H, 0A0H, 0A0H, 0H ; gray ins
  382. DB 0D3H, 0A1H, 0A1H, 0H ; gray del
  383. DB 0C9H, 0A2H, 0A2H, 0H ; gray pgup
  384. DB 0D1H, 0A3H, 0A3H, 0H ; gray pgdn
  385. DB 0C7H, 0A8H, 0A8H, 0H ; gray home
  386. DB 0CFH, 0A9H, 0A9H, 0H ; gray end
  387. ; function keys
  388. DB 3BH, 0A4H, 0FFH, 0H ; F1
  389. DB 3CH, 0A5H, 0FFH, 0H ; F2
  390. DB 3DH, 1BH, 0FFH, 0H ; F3
  391. DB 3EH, 0A7H, 0FFH, 0H ; F4
  392. DB 3FH, 0F5H, 0FFH, 0H ; F5
  393. DB 40H, 0F6H, 0FFH, 0H ; F6
  394. DB 41H, 0F7H, 0FFH, 0H ; F7
  395. DB 42H, 0F8H, 0FFH, 0H ; F8
  396. DB 43H, 0F9H, 0FFH, 0H ; F9
  397. DB 44H, 0FAH, 0FFH, 0H ; F10
  398. DB 57H, 0FBH, 0FFH, 0H ; F11
  399. DB 58H, 0FCH, 0FFH, 0H ; F12
  400. DB 0FFH
  401. END TableUS;
  402. (* maps USB usage ID's to Oberon character code *)
  403. PROCEDURE UsbScanTab*() : ADDRESS;
  404. CODE {SYSTEM.AMD64}
  405. LEA RAX, [RIP + L2 - L1];
  406. L1:
  407. LEAVE
  408. RET
  409. L2:
  410. ; Keyboard table stolen from Linux Usb keyboard driver, and corrected for Oberon
  411. DB 000, 000, 000, 000, 030, 048, 046, 032, 018, 033, 034, 035, 023, 036, 037, 038
  412. DB 050, 049, 024, 025, 016, 019, 031, 020, 022, 047, 017, 045, 021 ,044, 002, 003
  413. DB 004, 005, 006, 007, 008, 009, 010, 011, 028, 001, 014, 015 ,057, 012, 013, 026
  414. DB 027, 043, 043, 039, 040, 041, 051, 052, 053, 058, 059, 060, 061, 062, 063, 064
  415. DB 065, 066, 067, 068, 087, 088, 099, 070, 119, 210, 199, 201, 211, 207, 209, 205
  416. DB 203, 208, 200, 069, 181, 055, 074, 078, 156, 079, 080, 081, 075, 076, 077, 071
  417. DB 072, 073, 082, 083, 086, 127, 116, 117, 085, 089, 090, 091, 092, 093, 094, 095
  418. DB 120, 121, 122, 123, 134, 138, 130, 132, 128, 129, 131, 137, 133, 135, 136, 113
  419. DB 115, 114, 000, 000, 000, 000, 000, 124, 000, 000, 000, 000, 000, 000, 000, 000
  420. DB 000, 000, 000, 000, 000, 000, 000, 000, 000, 000, 000, 000, 000, 000, 000, 000
  421. DB 000, 000, 000, 000, 000, 000, 000, 000, 000, 000, 000, 000, 000, 000, 000, 000
  422. DB 000, 000, 000, 000, 000, 000, 000, 000, 000, 000, 000, 000, 000, 000, 000, 000
  423. DB 000, 000, 000, 000, 000, 000, 000, 000, 000, 000, 000, 000, 000, 000, 000, 000
  424. DB 000, 000, 000, 000, 000, 000, 000, 000, 000, 000, 000, 000, 000, 000, 000, 000
  425. DB 029, 042, 056, 125, 097, 054, 100, 126, 164, 166, 165, 163, 161, 115, 114, 113
  426. DB 150, 158, 159, 128, 136, 177, 178, 176, 142, 152, 173, 140, 000, 000, 000, 000
  427. END UsbScanTab;
  428. (* Maps USB key code to X11 keysym (/usr/include/X11/keysymdef.h). *)
  429. PROCEDURE KeySym*(VAR ch : CHAR; VAR leds : SET): LONGINT;
  430. VAR res: WORD;
  431. BEGIN
  432. CASE ch OF
  433. 028X: res := Inputs.KsReturn (* Return *)
  434. |029X: res := Inputs.KsEscape (* Escape *)
  435. |02AX: res := Inputs.KsBackSpace (* Delete (Backspace) *)
  436. |02BX: res := Inputs.KsTab (* Tab *)
  437. |03AX: res := Inputs.KsF1 (* f1 *)
  438. |03BX: res := Inputs.KsF2 (* f2 *)
  439. |03CX: res := Inputs.KsF3 (* f3 *)
  440. |03DX: res := Inputs.KsF4 (* f4 *)
  441. |03EX: res := Inputs.KsF5 (* f5 *)
  442. |03FX: res := Inputs.KsF6 (* f6 *)
  443. |040X: res := Inputs.KsF7 (* f7 *)
  444. |041X: res := Inputs.KsF8 (* f8 *)
  445. |042X: res := Inputs.KsF9 (* f9 *)
  446. |043X: res := Inputs.KsF10 (* f10 *)
  447. |044X: res := Inputs.KsF11 (* f11 *)
  448. |045X: res := Inputs.KsF12 (* f12 *)
  449. |046X: res := Inputs.KsPrint (* Printscreen *)
  450. |047X: res := Inputs.KsScrollLock (* ScrollLock *)
  451. |048X: res := Inputs.KsPause (* Pause *)
  452. |049X: res := Inputs.KsInsert (* insert *)
  453. |04AX: res := Inputs.KsHome (* home *)
  454. |04BX: res := Inputs.KsPageUp (* pgup *)
  455. |04CX: res := Inputs.KsDelete (* delete *)
  456. |04DX: res := Inputs.KsEnd (* end *)
  457. |04EX: res := Inputs.KsPageDown (* pgdn *)
  458. |04FX: res := Inputs.KsRight (* right *)
  459. |050X: res := Inputs.KsLeft (* left *)
  460. |051X: res := Inputs.KsDown (* down *)
  461. |052X: res := Inputs.KsUp (* up *)
  462. |053X: res := Inputs.KsNumLock; (* Keypad NumLock *)
  463. |054X: res := Inputs.KsKPDivide (* Keypad / *)
  464. |055X: res := Inputs.KsKPMultiply (* Keypad * *)
  465. |056X: res := Inputs.KsKPSubtract (* Keypad - *)
  466. |057X: res := Inputs.KsKPAdd (* Keypad + *)
  467. |058X: res := Inputs.KsReturn (* Keypad Enter: Should be KsKPEnter *)
  468. |059X: IF ~(NumLock IN leds) THEN res := Inputs.KsEnd; ELSE res := Inputs.KsNil END; (* Keypad 1 and End *)
  469. |05AX: IF ~(NumLock IN leds) THEN res := Inputs.KsDown; ELSE res := Inputs.KsNil END; (* Keypad 2 and Down Arrow *)
  470. |05BX: IF ~(NumLock IN leds) THEN res := Inputs.KsPageDown; ELSE res := Inputs.KsNil END; (* Keypad 3 and PageDown *)
  471. |05CX: IF ~(NumLock IN leds) THEN res := Inputs.KsLeft; ELSE res := Inputs.KsNil END; (* Keypad 4 and Left Arrow *)
  472. |05DX: IF ~(NumLock IN leds) THEN ch := 0X; res := Inputs.KsNil; ELSE res := Inputs.KsNil END; (* don't report key event !! *)
  473. |05EX: IF ~(NumLock IN leds) THEN res := Inputs.KsRight; ELSE res := Inputs.KsNil END; (* Keypad 6 and Right Arrow *)
  474. |05FX: IF ~(NumLock IN leds) THEN res := Inputs.KsHome; ELSE res := Inputs.KsNil END; (* Keypad 7 and Home *)
  475. |060X: IF ~(NumLock IN leds) THEN res := Inputs.KsUp; ELSE res := Inputs.KsNil END; (* Keypad 8 and Up Arrow *)
  476. |061X: IF ~(NumLock IN leds) THEN res := Inputs.KsPageUp; ELSE res := Inputs.KsNil END; (* Keypad 9 and Page Up *)
  477. |062X: IF ~(NumLock IN leds) THEN res := Inputs.KsInsert; ELSE res := Inputs.KsNil END; (* Keypad 0 and Insert *)
  478. |063X: IF ~(NumLock IN leds) THEN res := Inputs.KsDelete; ELSE res := Inputs.KsNil END; (* Keypad . and Delete *)
  479. |067X: IF ~(NumLock IN leds) THEN ch := 028X; res := Inputs.KsKPEnter; ELSE res := Inputs.KsNil END; (* Keypad =; remap to KpEnter *)
  480. |0B0X: ch := 0X; res := Inputs.KsNil; (* Keypad 00; don't map *)
  481. |0B1X: ch := 0X; res := Inputs.KsNil; (* Keypad 000; don't map *)
  482. |09AX: res := Inputs.KsSysReq (* SysReq / Attention *)
  483. |0E0X: res := Inputs.KsControlL (* Left Control *)
  484. |0E1X: res := Inputs.KsShiftL (* Left Shift *)
  485. |0E2X: res := Inputs.KsAltL (* Left Alt *)
  486. |0E3X: res := Inputs.KsMetaL (* Left GUI *)
  487. |0E4X: res := Inputs.KsControlR (* Right Control *)
  488. |0E5X: res := Inputs.KsShiftR (* Right Shift *)
  489. |0E6X: res := Inputs.KsAltR (* Right Alt *)
  490. |0E7X: res := Inputs.KsMetaR (* Right GUI *)
  491. |076X: res := Inputs.KsMenu (* Windows Menu *)
  492. |0FFX: res := Inputs.KsBreak (* Break *)
  493. ELSE
  494. (* if res=Inputs.KsNil, the KeySym will be assigned later (see HandleKey) *)
  495. res := Inputs.KsNil (* no key *)
  496. END;
  497. RETURN res
  498. END KeySym;
  499. PROCEDURE GetModifierKeysym(modifier : LONGINT) : LONGINT;
  500. VAR res : WORD;
  501. BEGIN
  502. CASE modifier OF
  503. |Inputs.LeftCtrl: res := Inputs.KsControlL;
  504. |Inputs.LeftShift: res := Inputs.KsShiftL;
  505. |Inputs.LeftAlt: res := Inputs.KsAltL;
  506. |Inputs.LeftMeta: res := Inputs.KsMetaL;
  507. |Inputs.RightCtrl: res := Inputs.KsControlR;
  508. |Inputs.RightShift: res := Inputs.KsShiftR;
  509. |Inputs.RightAlt: res := Inputs.KsAltR;
  510. |Inputs.RightMeta: res := Inputs.KsMetaR;
  511. ELSE
  512. res := Inputs.KsNil;
  513. END;
  514. RETURN res;
  515. END GetModifierKeysym;
  516. (* Translate - Translate scan code "c" to key. *)
  517. PROCEDURE Translate(flags, leds: SET; c: CHAR; keyboardTable : ADDRESS; VAR keyboardDeadKey, keyboardKeyVal : LONGINT): LONGINT;
  518. CONST
  519. (* The flags stored in the keytable are not the same as the ones defined in Inputs.
  520. The parameter flags and leds use the Inputs constants.
  521. The constants below are for the use of the flags stored in the keytable (variable s) *)
  522. OScrollLock = 0;
  523. ONumLock = 1;
  524. OCapsLock = 2;
  525. LAlt = 3;
  526. RAlt = 4;
  527. LCtrl = 5;
  528. RCtrl = 6;
  529. LShift = 7;
  530. RShift = 8;
  531. GreyEsc = 9;
  532. LMeta = 13;
  533. RMeta = 14;
  534. Alt = {LAlt, RAlt};
  535. Ctrl = {LCtrl, RCtrl};
  536. Shift = {LShift, RShift};
  537. DeadKey = 0;
  538. VAR
  539. a: ADDRESS;
  540. s1: CHAR;
  541. s : SET;
  542. k: INTEGER;
  543. dkn: SHORTINT;
  544. BEGIN
  545. IF (c = 46X) & (flags * Inputs.Ctrl # {}) THEN RETURN -2 END; (* Ctrl-Break - break *)
  546. IF (c = 44X) & (flags * Inputs.Ctrl # {}) THEN RETURN 0FFH END; (* Ctrl-F10 - exit *)
  547. IF (c = 53X) & (flags * Inputs.Ctrl # {}) & (flags * Inputs.Alt # {}) THEN RETURN 0FFH END; (* Ctrl-Alt-Del - exit *)
  548. a := keyboardTable;
  549. (* this loop linearly searches the keytable for an entry for the character c *)
  550. LOOP
  551. SYSTEM.GET(a, s1);
  552. IF s1 = 0FFX THEN (* end of table -> unmapped key *)
  553. (* reset key and dead key state *)
  554. k := -1; keyboardDeadKey := 0; EXIT;
  555. ELSIF s1 = c THEN (* found scan code in table *)
  556. k := 0;
  557. SYSTEM.GET(a+3, SYSTEM.VAL(CHAR, s)); (* flags from table *)
  558. dkn := SHORT(SHORT(SYSTEM.VAL(LONGINT, LSH(s * {5..7}, -5))));
  559. s := s * {DeadKey, ONumLock, OCapsLock, LAlt, RAlt, LCtrl, RCtrl};
  560. IF ((s * Alt = LSH(flags * Inputs.Alt,-2)) OR (ONumLock IN s) OR (s1>03BX)) & (dkn = keyboardDeadKey) THEN (* Alt & dead keys match exactly *)
  561. (* check if shift pressed *)
  562. IF flags * Inputs.Shift # {} THEN INCL(s, LShift) END;
  563. (* handle CapsLock *)
  564. IF (OCapsLock IN s) & (CapsLock IN leds) THEN s := s / {LShift} END;
  565. (* handle NumLock *)
  566. IF ONumLock IN s THEN
  567. IF flags * Inputs.Alt # {} THEN INCL(s, LShift)
  568. ELSIF NumLock IN leds THEN s := s / {LShift}
  569. END
  570. END;
  571. (* get key code *)
  572. IF LShift IN s THEN SYSTEM.GET(a+2, SYSTEM.VAL(CHAR, k)) (* shifted value *)
  573. ELSE SYSTEM.GET(a+1, SYSTEM.VAL(CHAR, k)) (* unshifted value *)
  574. END;
  575. IF (DeadKey IN s) & (k <= 7) THEN (* dead key *)
  576. keyboardDeadKey := SHORT(k); k := -1 (* set new dead key state *)
  577. ELSIF k = 0FFH THEN (* unmapped key *)
  578. k := -1; keyboardDeadKey := 0 (* reset dead key state *)
  579. ELSE (* mapped key *)
  580. IF flags * Inputs.Ctrl # {} THEN
  581. IF ((k >= 64) & (k <= 95)) OR ((k >= 97) & (k <= 122)) THEN
  582. k := SHORT(SYSTEM.VAL(LONGINT, SYSTEM.VAL(SET, k) * {0..4})) (* control *)
  583. ELSIF k = 13 THEN (* Ctrl-Enter *)
  584. k := 10
  585. END
  586. END;
  587. IF flags * Inputs.Alt # {} THEN (* Alt-keypad *)
  588. IF (k >= ORD("0")) & (k <= ORD("9")) & (NumLock IN s) THEN (* keypad num *)
  589. IF keyboardKeyVal = -1 THEN keyboardKeyVal := k-ORD("0")
  590. ELSE keyboardKeyVal := (10*keyboardKeyVal + (k-ORD("0"))) MOD 1000;
  591. END;
  592. k := -1
  593. END
  594. END;
  595. keyboardDeadKey := 0 (* reset dead key state *)
  596. END;
  597. EXIT
  598. END
  599. END;
  600. INC(a, 4)
  601. END; (* LOOP *)
  602. RETURN k
  603. END Translate;
  604. (* Displays textual representation of the set flags to KernelLog *)
  605. PROCEDURE ShowFlags(flags, leds : SET);
  606. BEGIN
  607. KernelLog.String("Flags: ");
  608. IF Inputs.LeftAlt IN flags THEN KernelLog.String("[Left Alt]"); END;
  609. IF Inputs.RightAlt IN flags THEN KernelLog.String("[Right Alt]"); END;
  610. IF Inputs.LeftCtrl IN flags THEN KernelLog.String("[Left Ctrl]"); END;
  611. IF Inputs.RightCtrl IN flags THEN KernelLog.String("[Rigth Ctrl]"); END;
  612. IF Inputs.LeftShift IN flags THEN KernelLog.String("[Left Shift]"); END;
  613. IF Inputs.RightShift IN flags THEN KernelLog.String("[Right Shift]"); END;
  614. IF Inputs.LeftMeta IN flags THEN KernelLog.String("[Left Meta]"); END;
  615. IF Inputs.RightMeta IN flags THEN KernelLog.String("[Rigth Meta]"); END;
  616. IF Inputs.Release IN flags THEN KernelLog.String("[Released]"); END;
  617. IF ScrollLock IN leds THEN KernelLog.String("[ScrollLock]"); END;
  618. IF NumLock IN leds THEN KernelLog.String("[NumLock]"); END;
  619. IF CapsLock IN leds THEN KernelLog.String("[CapsLock]"); END;
  620. IF Compose IN leds THEN KernelLog.String("[Compose]"); END;
  621. IF Kana IN leds THEN KernelLog.String("[Kana]"); END;
  622. END ShowFlags;
  623. PROCEDURE Probe(dev : Usbdi.UsbDevice; if : Usbdi.InterfaceDescriptor) : Usbdi.Driver;
  624. VAR driver : KeyboardDriver;
  625. BEGIN
  626. IF if.bInterfaceClass # 3 THEN RETURN NIL END; (* HID class *)
  627. IF if.bInterfaceSubClass # 1 THEN RETURN NIL END; (* Boot protocol subclass *)
  628. IF if.bInterfaceProtocol # 1 THEN RETURN NIL END; (* Keyboard *)
  629. IF if.bNumEndpoints # 1 THEN RETURN NIL END;
  630. KernelLog.String("UsbKeyboard: USB Keyboard found."); KernelLog.Ln;
  631. NEW(driver);
  632. RETURN driver;
  633. END Probe;
  634. PROCEDURE SetLayout*(context : Commands.Context); (** dev file ~ *)
  635. VAR
  636. string : ARRAY 64 OF CHAR;
  637. plugin : Plugins.Plugin; kd : KeyboardDriver;
  638. BEGIN
  639. IF context.arg.GetString(string) THEN
  640. plugin := Usb.usbDrivers.Get(string);
  641. IF plugin # NIL THEN
  642. IF plugin IS KeyboardDriver THEN
  643. kd := plugin (KeyboardDriver);
  644. ELSE context.error.String("UsbKeyboard: Device "); context.error.String(string); context.error.String(" is not a keyboard."); context.error.Ln;
  645. END;
  646. ELSE context.error.String("UsbKeyboard: Device "); context.error.String(string); context.error.String(" not found."); context.error.Ln;
  647. END;
  648. ELSE context.error.String("UsbKeyboard: Expected <dev> parameter."); context.error.Ln;
  649. END;
  650. IF kd # NIL THEN
  651. IF context.arg.GetString(string) THEN
  652. kd.base.SetLayout(string);
  653. context.out.String("Layout set to "); context.out.String(string); context.out.Ln;
  654. END;
  655. END;
  656. END SetLayout;
  657. PROCEDURE Install*;
  658. END Install;
  659. PROCEDURE Cleanup;
  660. BEGIN
  661. Usbdi.drivers.Remove(Name);
  662. END Cleanup;
  663. BEGIN
  664. Modules.InstallTermHandler(Cleanup);
  665. Usbdi.drivers.Add(Probe, Name, Description, Priority);
  666. END UsbKeyboard.
  667. UsbKeyboard.Install ~ System.Free UsbKeyboard ~
  668. UsbKeyboard.SetLayout UsbKeyboard00 KeyBE.Bin ~
  669. UsbKeyboard.SetLayout UsbKeyboard00 KeyCA.Bin ~
  670. UsbKeyboard.SetLayout UsbKeyboard00 KeyCH.Bin ~
  671. UsbKeyboard.SetLayout UsbKeyboard00 KeyD.Bin ~
  672. UsbKeyboard.SetLayout UsbKeyboard00 KeyDV.Bin ~
  673. UsbKeyboard.SetLayout UsbKeyboard00 KeyFR.Bin ~
  674. UsbKeyboard.SetLayout UsbKeyboard00 KeyIT.Bin ~
  675. UsbKeyboard.SetLayout UsbKeyboard00 KeyN.Bin ~
  676. UsbKeyboard.SetLayout UsbKeyboard00 KeyPL.Bin ~
  677. UsbKeyboard.SetLayout UsbKeyboard00 KeySF.Bin ~
  678. UsbKeyboard.SetLayout UsbKeyboard00 KeyTR.Bin ~
  679. UsbKeyboard.SetLayout UsbKeyboard00 KeyUK.Bin ~
  680. UsbKeyboard.SetLayout UsbKeyboard00 KeyUS.Bin ~
  681. WMKeyCode.Open ~ System.Free WMKeyCode ~