ARM.UsbKeyboard.Mod 28 KB

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