]> code.delx.au - gnu-emacs/blobdiff - src/w32fns.c
Merge from origin/emacs-25
[gnu-emacs] / src / w32fns.c
index c57b5a188b238832858815a76a548db49c8dc8cf..ede8f6be2925da56aa327bc7c9cdb0a43f020da5 100644 (file)
@@ -20,6 +20,9 @@ along with GNU Emacs.  If not, see <http://www.gnu.org/licenses/>.  */
 /* Added by Kevin Gallo */
 
 #include <config.h>
+/* Override API version to get the latest functionality.  */
+#undef _WIN32_WINNT
+#define _WIN32_WINNT 0x0600
 
 #include <signal.h>
 #include <stdio.h>
@@ -41,6 +44,7 @@ along with GNU Emacs.  If not, see <http://www.gnu.org/licenses/>.  */
 #include "coding.h"
 
 #include "w32common.h"
+#include "w32inevt.h"
 
 #ifdef WINDOWSNT
 #include <mbstring.h>
@@ -52,6 +56,8 @@ along with GNU Emacs.  If not, see <http://www.gnu.org/licenses/>.  */
 #include "w32.h"
 #endif
 
+#include <basetyps.h>
+#include <unknwn.h>
 #include <commctrl.h>
 #include <commdlg.h>
 #include <shellapi.h>
@@ -251,6 +257,38 @@ HINSTANCE hinst = NULL;
 static unsigned int sound_type = 0xFFFFFFFF;
 #define MB_EMACS_SILENT (0xFFFFFFFF - 1)
 
+/* Special virtual key code for indicating "any" key.  */
+#define VK_ANY 0xFF
+
+#ifndef WM_WTSSESSION_CHANGE
+/* 32-bit MinGW does not define these constants.  */
+# define WM_WTSSESSION_CHANGE  0x02B1
+# define WTS_SESSION_LOCK      0x7
+#endif
+
+/* Keyboard hook state data.  */
+static struct
+{
+  int hook_count; /* counter, if several windows are created */
+  HHOOK hook;     /* hook handle */
+  HWND console;   /* console window handle */
+
+  int lwindown;      /* Left Windows key currently pressed (and hooked) */
+  int rwindown;      /* Right Windows key currently pressed (and hooked) */
+  int winsdown;      /* Number of handled keys currently pressed */
+  int send_win_up;   /* Pass through the keyup for this Windows key press? */
+  int suppress_lone; /* Suppress simulated Windows keydown-keyup for this press? */
+  int winseen;       /* Windows keys seen during this press? */
+
+  char alt_hooked[256];  /* hook Alt+[this key]? */
+  char lwin_hooked[256]; /* hook left Win+[this key]? */
+  char rwin_hooked[256]; /* hook right Win+[this key]? */
+} kbdhook;
+typedef HWND (WINAPI *GetConsoleWindow_Proc) (void);
+
+/* stdin, from w32console.c */
+extern HANDLE keyboard_handle;
+
 /* Let the user specify a display with a frame.
    nil stands for the selected frame--or, if that is not a w32 frame,
    the first display on the list.  */
@@ -2074,6 +2112,350 @@ my_post_msg (W32Msg * wmsg, HWND hwnd, UINT msg, WPARAM wParam, LPARAM lParam)
   post_msg (wmsg);
 }
 
+#ifdef WINDOWSNT
+/* The Windows keyboard hook callback.  */
+static LRESULT CALLBACK
+funhook (int code, WPARAM w, LPARAM l)
+{
+  INPUT inputs[2];
+  HWND focus = GetFocus ();
+  int console = 0;
+  KBDLLHOOKSTRUCT const *hs = (KBDLLHOOKSTRUCT*)l;
+
+  if (code < 0 || (hs->flags & LLKHF_INJECTED))
+    return CallNextHookEx (0, code, w, l);
+
+  /* The keyboard hook sees keyboard input on all processes (except
+     elevated ones, when Emacs itself is not elevated).  As such,
+     care must be taken to only filter out keyboard input when Emacs
+     itself is on the foreground.
+
+     GetFocus returns a non-NULL window if another application is active,
+     and always for a console Emacs process.  For a console Emacs, determine
+     focus by checking if the current foreground window is the process's
+     console window.  */
+  if (focus == NULL && kbdhook.console != NULL)
+    {
+      if (GetForegroundWindow () == kbdhook.console)
+       {
+         focus = kbdhook.console;
+         console = 1;
+       }
+    }
+
+  /* First, check hooks for the left and right Windows keys.  */
+  if (hs->vkCode == VK_LWIN || hs->vkCode == VK_RWIN)
+    {
+      if (focus != NULL && (w == WM_KEYDOWN || w == WM_SYSKEYDOWN))
+       {
+         /* The key is being pressed in an Emacs window.  */
+         if (hs->vkCode == VK_LWIN && !kbdhook.lwindown)
+           {
+             kbdhook.lwindown = 1;
+             kbdhook.winseen = 1;
+             kbdhook.winsdown++;
+           }
+         else if (hs->vkCode == VK_RWIN && !kbdhook.rwindown)
+           {
+             kbdhook.rwindown = 1;
+             kbdhook.winseen = 1;
+             kbdhook.winsdown++;
+           }
+         /* Returning 1 here drops the keypress without further processing.
+            If the keypress was allowed to go through, the normal Windows
+            hotkeys would take over.  */
+         return 1;
+       }
+      else if (kbdhook.winsdown > 0 && (w == WM_KEYUP || w == WM_SYSKEYUP))
+       {
+         /* A key that has been captured earlier is being released now.  */
+         if (hs->vkCode == VK_LWIN && kbdhook.lwindown)
+           {
+             kbdhook.lwindown = 0;
+             kbdhook.winsdown--;
+           }
+         else if (hs->vkCode == VK_RWIN && kbdhook.rwindown)
+           {
+             kbdhook.rwindown = 0;
+             kbdhook.winsdown--;
+           }
+         if (kbdhook.winsdown == 0 && kbdhook.winseen)
+           {
+             if (!kbdhook.suppress_lone)
+               {
+                 /* The Windows key was pressed, then released,
+                    without any other key pressed simultaneously.
+                    Normally, this opens the Start menu, but the user
+                    can prevent this by setting the
+                    w32-pass-[lr]window-to-system variable to
+                    NIL.  */
+                 if (hs->vkCode == VK_LWIN && !NILP (Vw32_pass_lwindow_to_system) ||
+                     hs->vkCode == VK_RWIN && !NILP (Vw32_pass_rwindow_to_system))
+                   {
+                     /* Not prevented - Simulate the keypress to the system.  */
+                     memset (inputs, 0, sizeof (inputs));
+                     inputs[0].type = INPUT_KEYBOARD;
+                     inputs[0].ki.wVk = hs->vkCode;
+                     inputs[0].ki.wScan = hs->vkCode;
+                     inputs[0].ki.dwFlags = KEYEVENTF_EXTENDEDKEY;
+                     inputs[0].ki.time = 0;
+                     inputs[1].type = INPUT_KEYBOARD;
+                     inputs[1].ki.wVk = hs->vkCode;
+                     inputs[1].ki.wScan = hs->vkCode;
+                     inputs[1].ki.dwFlags
+                       = KEYEVENTF_EXTENDEDKEY | KEYEVENTF_KEYUP;
+                     inputs[1].ki.time = 0;
+                     SendInput (2, inputs, sizeof (INPUT));
+                   }
+                 else if (focus != NULL)
+                   {
+                     /* When not passed to system, must simulate privately to Emacs.    */
+                     PostMessage (focus, WM_SYSKEYDOWN, hs->vkCode, 0);
+                     PostMessage (focus, WM_SYSKEYUP, hs->vkCode, 0);
+                   }
+               }
+           }
+         if (kbdhook.winsdown == 0)
+           {
+             /* No Windows keys pressed anymore - clear the state flags.  */
+             kbdhook.suppress_lone = 0;
+             kbdhook.winseen = 0;
+           }
+         if (!kbdhook.send_win_up)
+           {
+             /* Swallow this release message, as not to confuse
+                applications who did not get to see the original
+                WM_KEYDOWN message either.  */
+             return 1;
+           }
+         kbdhook.send_win_up = 0;
+       }
+    }
+  else if (kbdhook.winsdown > 0)
+    {
+      /* Some other key was pressed while a captured Win key is down.
+        This is either an Emacs registered hotkey combination, or a
+        system hotkey.  */
+      if (kbdhook.lwindown && kbdhook.lwin_hooked[hs->vkCode] ||
+         kbdhook.rwindown && kbdhook.rwin_hooked[hs->vkCode])
+       {
+         /* Hooked Win-x combination, do not pass the keypress to Windows.  */
+         kbdhook.suppress_lone = 1;
+       }
+      else if (!kbdhook.suppress_lone)
+       {
+         /* Unhooked S-x combination; simulate the combination now
+            (will be seen by the system).  */
+         memset (inputs, 0, sizeof (inputs));
+         inputs[0].type = INPUT_KEYBOARD;
+         inputs[0].ki.wVk = kbdhook.lwindown ? VK_LWIN : VK_RWIN;
+         inputs[0].ki.wScan = kbdhook.lwindown ? VK_LWIN : VK_RWIN;
+         inputs[0].ki.dwFlags = KEYEVENTF_EXTENDEDKEY;
+         inputs[0].ki.time = 0;
+         inputs[1].type = INPUT_KEYBOARD;
+         inputs[1].ki.wVk = hs->vkCode;
+         inputs[1].ki.wScan = hs->scanCode;
+         inputs[1].ki.dwFlags =
+           (hs->flags & LLKHF_EXTENDED) ? KEYEVENTF_EXTENDEDKEY : 0;
+         inputs[1].ki.time = 0;
+         SendInput (2, inputs, sizeof (INPUT));
+         /* Stop processing of this Win sequence here; the
+            corresponding keyup messages will come through the normal
+            channel when the keys are released.  */
+         kbdhook.suppress_lone = 1;
+         kbdhook.send_win_up = 1;
+         /* Swallow the original keypress (as we want the Win key
+            down message simulated above to precede this real message).  */
+         return 1;
+       }
+    }
+
+  /* Next, handle the registered Alt-* combinations.  */
+  if ((w == WM_SYSKEYDOWN || w == WM_KEYDOWN)
+      && kbdhook.alt_hooked[hs->vkCode]
+      && focus != NULL
+      && (GetAsyncKeyState (VK_MENU) & 0x8000))
+    {
+      /* Prevent the system from getting this Alt-* key - suppress the
+        message and post as a normal keypress to Emacs.  */
+      if (console)
+       {
+         INPUT_RECORD rec;
+         DWORD n;
+         rec.EventType = KEY_EVENT;
+         rec.Event.KeyEvent.bKeyDown = TRUE;
+         rec.Event.KeyEvent.wVirtualKeyCode = hs->vkCode;
+         rec.Event.KeyEvent.wVirtualScanCode = hs->scanCode;
+         rec.Event.KeyEvent.uChar.UnicodeChar = 0;
+         rec.Event.KeyEvent.dwControlKeyState =
+           ((GetAsyncKeyState (VK_LMENU) & 0x8000) ? LEFT_ALT_PRESSED : 0)
+           | ((GetAsyncKeyState (VK_RMENU) & 0x8000) ? RIGHT_ALT_PRESSED : 0)
+           | ((GetAsyncKeyState (VK_LCONTROL) & 0x8000) ? LEFT_CTRL_PRESSED : 0)
+           | ((GetAsyncKeyState (VK_RCONTROL) & 0x8000) ? RIGHT_CTRL_PRESSED : 0)
+           | ((GetAsyncKeyState (VK_SHIFT) & 0x8000) ? SHIFT_PRESSED : 0)
+           | ((hs->flags & LLKHF_EXTENDED) ? ENHANCED_KEY : 0);
+         if (w32_console_unicode_input)
+           WriteConsoleInputW (keyboard_handle, &rec, 1, &n);
+         else
+           WriteConsoleInputA (keyboard_handle, &rec, 1, &n);
+       }
+      else
+       PostMessage (focus, w, hs->vkCode, 1 | (1<<29));
+      return 1;
+    }
+
+  /* The normal case - pass the message through.  */
+  return CallNextHookEx (0, code, w, l);
+}
+
+/* Set up the hook; can be called several times, with matching
+   remove_w32_kbdhook calls.  */
+void
+setup_w32_kbdhook (void)
+{
+  kbdhook.hook_count++;
+
+  /* Hooking is only available on NT architecture systems, as
+     indicated by the w32_kbdhook_active variable.  */
+  if (kbdhook.hook_count == 1 && w32_kbdhook_active)
+    {
+      /* Get the handle of the Emacs console window.  As the
+        GetConsoleWindow function is only available on Win2000+, a
+        hackish workaround described in Microsoft KB article 124103
+        (https://support.microsoft.com/en-us/kb/124103) is used for
+        NT 4 systems.  */
+      GetConsoleWindow_Proc get_console = (GetConsoleWindow_Proc)
+       GetProcAddress (GetModuleHandle ("kernel32.dll"), "GetConsoleWindow");
+
+      if (get_console != NULL)
+       kbdhook.console = get_console ();
+      else
+        {
+         GUID guid;
+         wchar_t *oldTitle = malloc (1024 * sizeof(wchar_t));
+         wchar_t newTitle[64];
+         int i;
+
+         CoCreateGuid (&guid);
+         StringFromGUID2 (&guid, newTitle, 64);
+         if (newTitle != NULL)
+           {
+             GetConsoleTitleW (oldTitle, 1024);
+             SetConsoleTitleW (newTitle);
+             for (i = 0; i < 25; i++)
+               {
+                 Sleep (40);
+                 kbdhook.console = FindWindowW (NULL, newTitle);
+                 if (kbdhook.console != NULL)
+                   break;
+               }
+             SetConsoleTitleW (oldTitle);
+           }
+         free (oldTitle);
+       }
+
+      /* Set the hook.  */
+      kbdhook.hook = SetWindowsHookEx (WH_KEYBOARD_LL, funhook,
+                                      GetModuleHandle (NULL), 0);
+    }
+}
+
+/* Remove the hook.  */
+void
+remove_w32_kbdhook (void)
+{
+  kbdhook.hook_count--;
+  if (kbdhook.hook_count == 0 && w32_kbdhook_active)
+    {
+      UnhookWindowsHookEx (kbdhook.hook);
+      kbdhook.hook = NULL;
+    }
+}
+#endif /* WINDOWSNT */
+
+/* Mark a specific key combination as hooked, preventing it to be
+   handled by the system.  */
+void
+hook_w32_key (int hook, int modifier, int vkey)
+{
+  char *tbl = NULL;
+
+  switch (modifier)
+    {
+    case VK_MENU:
+      tbl = kbdhook.alt_hooked;
+      break;
+    case VK_LWIN:
+      tbl = kbdhook.lwin_hooked;
+      break;
+    case VK_RWIN:
+      tbl = kbdhook.rwin_hooked;
+      break;
+    }
+
+  if (tbl != NULL && vkey >= 0 && vkey <= 255)
+    {
+       /* VK_ANY hooks all keys for this modifier */
+       if (vkey == VK_ANY)
+        memset (tbl, (char)hook, 256);
+       else
+        tbl[vkey] = (char)hook;
+       /* Alt-<modifier>s should go through */
+       kbdhook.alt_hooked[VK_MENU] = 0;
+       kbdhook.alt_hooked[VK_LMENU] = 0;
+       kbdhook.alt_hooked[VK_RMENU] = 0;
+       kbdhook.alt_hooked[VK_CONTROL] = 0;
+       kbdhook.alt_hooked[VK_LCONTROL] = 0;
+       kbdhook.alt_hooked[VK_RCONTROL] = 0;
+       kbdhook.alt_hooked[VK_SHIFT] = 0;
+       kbdhook.alt_hooked[VK_LSHIFT] = 0;
+       kbdhook.alt_hooked[VK_RSHIFT] = 0;
+    }
+}
+
+/* Check the current Win key pressed state.  */
+int
+check_w32_winkey_state (int vkey)
+{
+  /* The hook code handles grabbing of the Windows keys and Alt-* key
+     combinations reserved by the system.  Handling Alt is a bit
+     easier, as Windows intends Alt-* shortcuts for application use in
+     Windows; hotkeys such as Alt-tab and Alt-escape are special
+     cases.  Win-* hotkeys, on the other hand, are primarily meant for
+     system use.
+
+     As a result, when we want Emacs to be able to grab the Win-*
+     keys, we must swallow all Win key presses in a low-level keyboard
+     hook.  Unfortunately, this means that the Emacs window procedure
+     (and console input handler) never see the keypresses either.
+     Thus, to check the modifier states properly, Emacs code must use
+     the check_w32_winkey_state function that uses the flags directly
+     updated by the hook callback.  */
+  switch (vkey)
+    {
+    case VK_LWIN:
+      return kbdhook.lwindown;
+    case VK_RWIN:
+      return kbdhook.rwindown;
+    }
+  return 0;
+}
+
+/* Reset the keyboard hook state.  Locking the workstation with Win-L
+   leaves the Win key(s) "down" from the hook's point of view - the
+   keyup event is never seen.  Thus, this function must be called when
+   the system is locked.  */
+void
+reset_w32_kbdhook_state (void)
+{
+  kbdhook.lwindown = 0;
+  kbdhook.rwindown = 0;
+  kbdhook.winsdown = 0;
+  kbdhook.send_win_up = 0;
+  kbdhook.suppress_lone = 0;
+  kbdhook.winseen = 0;
+}
+
 /* GetKeyState and MapVirtualKey on Windows 95 do not actually distinguish
    between left and right keys as advertised.  We test for this
    support dynamically, and set a flag when the support is absent.  If
@@ -2248,6 +2630,8 @@ modifier_set (int vkey)
       else
        return (GetKeyState (vkey) & 0x1);
     }
+  if (w32_kbdhook_active && (vkey == VK_LWIN || vkey == VK_RWIN))
+    return check_w32_winkey_state (vkey);
 
   if (!modifiers_recorded)
     return (GetKeyState (vkey) & 0x8000);
@@ -2390,7 +2774,9 @@ map_keypad_keys (unsigned int virt_key, unsigned int extended)
 /* List of special key combinations which w32 would normally capture,
    but Emacs should grab instead.  Not directly visible to lisp, to
    simplify synchronization.  Each item is an integer encoding a virtual
-   key code and modifier combination to capture.  */
+   key code and modifier combination to capture.
+   Note: This code is not used if keyboard hooks are active
+   (Windows 2000 and later).  */
 static Lisp_Object w32_grabbed_keys;
 
 #define HOTKEY(vk, mods)      make_number (((vk) & 255) | ((mods) << 8))
@@ -3476,7 +3862,7 @@ w32_wnd_proc (HWND hwnd, UINT msg, WPARAM wParam, LPARAM lParam)
       switch (wParam)
        {
        case VK_LWIN:
-         if (NILP (Vw32_pass_lwindow_to_system))
+         if (!w32_kbdhook_active && NILP (Vw32_pass_lwindow_to_system))
            {
              /* Prevent system from acting on keyup (which opens the
                 Start menu if no other key was pressed) by simulating a
@@ -3495,7 +3881,7 @@ w32_wnd_proc (HWND hwnd, UINT msg, WPARAM wParam, LPARAM lParam)
            return 0;
          break;
        case VK_RWIN:
-         if (NILP (Vw32_pass_rwindow_to_system))
+         if (!w32_kbdhook_active && NILP (Vw32_pass_rwindow_to_system))
            {
              if (GetAsyncKeyState (wParam) & 1)
                {
@@ -4352,10 +4738,12 @@ w32_wnd_proc (HWND hwnd, UINT msg, WPARAM wParam, LPARAM lParam)
     case WM_SETFOCUS:
       dpyinfo->faked_key = 0;
       reset_modifiers ();
-      register_hot_keys (hwnd);
+      if (!w32_kbdhook_active)
+       register_hot_keys (hwnd);
       goto command;
     case WM_KILLFOCUS:
-      unregister_hot_keys (hwnd);
+      if (!w32_kbdhook_active)
+       unregister_hot_keys (hwnd);
       button_state = 0;
       ReleaseCapture ();
       /* Relinquish the system caret.  */
@@ -4384,10 +4772,24 @@ w32_wnd_proc (HWND hwnd, UINT msg, WPARAM wParam, LPARAM lParam)
       my_post_msg (&wmsg, hwnd, msg, wParam, lParam);
       goto dflt;
 
+#ifdef WINDOWSNT
+    case WM_CREATE:
+      setup_w32_kbdhook ();
+      goto dflt;
+#endif
+
     case WM_DESTROY:
+#ifdef WINDOWSNT
+      remove_w32_kbdhook ();
+#endif
       CoUninitialize ();
       return 0;
 
+    case WM_WTSSESSION_CHANGE:
+      if (wParam == WTS_SESSION_LOCK)
+        reset_w32_kbdhook_state ();
+      goto dflt;
+
     case WM_CLOSE:
       wmsg.dwModifiers = w32_get_modifiers ();
       my_post_msg (&wmsg, hwnd, msg, wParam, lParam);
@@ -4880,7 +5282,8 @@ x_default_font_parameter (struct frame *f, Lisp_Object parms)
     {
       /* Remember the explicit font parameter, so we can re-apply it after
         we've applied the `default' face settings.  */
-      x_set_frame_parameters (f, Fcons (Fcons (Qfont_param, font_param), Qnil));
+      x_set_frame_parameters (f, Fcons (Fcons (Qfont_parameter, font_param),
+                                       Qnil));
     }
   x_default_parameter (f, parms, Qfont, font, "font", "Font", RES_TYPE_STRING);
 }
@@ -6056,8 +6459,6 @@ no value of TYPE (always string in the MS Windows case).  */)
                                Tool tips
  ***********************************************************************/
 
-static Lisp_Object x_create_tip_frame (struct w32_display_info *,
-                                      Lisp_Object, Lisp_Object);
 static void compute_tip_xy (struct frame *, Lisp_Object, Lisp_Object,
                            Lisp_Object, int, int, int *, int *);
 
@@ -6092,8 +6493,7 @@ unwind_create_tip_frame (Lisp_Object frame)
 
 
 /* Create a frame for a tooltip on the display described by DPYINFO.
-   PARMS is a list of frame parameters.  TEXT is the string to
-   display in the tip frame.  Value is the frame.
+   PARMS is a list of frame parameters.  Value is the frame.
 
    Note that functions called here, esp. x_default_parameter can
    signal errors, for instance when a specified color name is
@@ -6101,8 +6501,7 @@ unwind_create_tip_frame (Lisp_Object frame)
    when this happens.  */
 
 static Lisp_Object
-x_create_tip_frame (struct w32_display_info *dpyinfo,
-                   Lisp_Object parms, Lisp_Object text)
+x_create_tip_frame (struct w32_display_info *dpyinfo, Lisp_Object parms)
 {
   struct frame *f;
   Lisp_Object frame;
@@ -6111,8 +6510,6 @@ x_create_tip_frame (struct w32_display_info *dpyinfo,
   ptrdiff_t count = SPECPDL_INDEX ();
   struct kboard *kb;
   bool face_change_before = face_change;
-  Lisp_Object buffer;
-  struct buffer *old_buffer;
   int x_width = 0, x_height = 0;
 
   /* Use this general default value to start with until we know if
@@ -6136,23 +6533,9 @@ x_create_tip_frame (struct w32_display_info *dpyinfo,
   frame = Qnil;
   /* Make a frame without minibuffer nor mode-line.  */
   f = make_frame (false);
-  f->wants_modeline = 0;
+  f->wants_modeline = false;
   XSETFRAME (frame, f);
 
-  AUTO_STRING (tip, " *tip*");
-  buffer = Fget_buffer_create (tip);
-  /* Use set_window_buffer instead of Fset_window_buffer (see
-     discussion of bug#11984, bug#12025, bug#12026).  */
-  set_window_buffer (FRAME_ROOT_WINDOW (f), buffer, false, false);
-  old_buffer = current_buffer;
-  set_buffer_internal_1 (XBUFFER (buffer));
-  bset_truncate_lines (current_buffer, Qnil);
-  specbind (Qinhibit_read_only, Qt);
-  specbind (Qinhibit_modification_hooks, Qt);
-  Ferase_buffer ();
-  Finsert (1, &text);
-  set_buffer_internal_1 (old_buffer);
-
   record_unwind_protect (unwind_create_tip_frame, frame);
 
   /* By setting the output method, we're essentially saying that
@@ -6186,7 +6569,7 @@ x_create_tip_frame (struct w32_display_info *dpyinfo,
     {
       fset_name (f, name);
       f->explicit_name = true;
-      /* use the frame's title when getting resources for this frame.  */
+      /* Use the frame's title when getting resources for this frame.  */
       specbind (Qx_resource_name, name);
     }
 
@@ -6216,14 +6599,10 @@ x_create_tip_frame (struct w32_display_info *dpyinfo,
        parms = Fcons (Fcons (Qinternal_border_width, value),
                       parms);
     }
+
   x_default_parameter (f, parms, Qinternal_border_width, make_number (1),
                       "internalBorderWidth", "internalBorderWidth",
                       RES_TYPE_NUMBER);
-  x_default_parameter (f, parms, Qright_divider_width, make_number (0),
-                      NULL, NULL, RES_TYPE_NUMBER);
-  x_default_parameter (f, parms, Qbottom_divider_width, make_number (0),
-                      NULL, NULL, RES_TYPE_NUMBER);
-
   /* Also do the stuff which must be set before the window exists.  */
   x_default_parameter (f, parms, Qforeground_color, build_string ("black"),
                       "foreground", "Foreground", RES_TYPE_STRING);
@@ -6250,6 +6629,9 @@ x_create_tip_frame (struct w32_display_info *dpyinfo,
   f->fringe_cols = 0;
   f->left_fringe_width = 0;
   f->right_fringe_width = 0;
+  /* No dividers on tip frame.  */
+  f->right_divider_width = 0;
+  f->bottom_divider_width = 0;
 
   block_input ();
   my_create_tip_window (f);
@@ -6276,7 +6658,6 @@ x_create_tip_frame (struct w32_display_info *dpyinfo,
   SET_FRAME_LINES (f, 0);
   adjust_frame_size (f, width * FRAME_COLUMN_WIDTH (f),
                     height * FRAME_LINE_HEIGHT (f), 0, true, Qtip_frame);
-
   /* Add `tooltip' frame parameter's default value. */
   if (NILP (Fframe_parameter (frame, Qtooltip)))
     Fmodify_frame_parameters (frame, Fcons (Fcons (Qtooltip, Qt), Qnil));
@@ -6294,8 +6675,6 @@ x_create_tip_frame (struct w32_display_info *dpyinfo,
     Lisp_Object fg = Fframe_parameter (frame, Qforeground_color);
     Lisp_Object colors = Qnil;
 
-    /* Set tip_frame here, so that */
-    tip_frame = frame;
     call2 (Qface_set_after_frame_default, frame, Qnil);
 
     if (!EQ (bg, Fframe_parameter (frame, Qbackground_color)))
@@ -6427,6 +6806,48 @@ compute_tip_xy (struct frame *f,
     *root_x = min_x;
 }
 
+/* Hide tooltip.  Delete its frame if DELETE is true.  */
+static Lisp_Object
+x_hide_tip (bool delete)
+{
+  if (!NILP (tip_timer))
+    {
+      call1 (Qcancel_timer, tip_timer);
+      tip_timer = Qnil;
+    }
+
+  if (NILP (tip_frame)
+      || (!delete && FRAMEP (tip_frame)
+         && !FRAME_VISIBLE_P (XFRAME (tip_frame))))
+    return Qnil;
+  else
+    {
+      ptrdiff_t count;
+      Lisp_Object was_open = Qnil;
+
+      count = SPECPDL_INDEX ();
+      specbind (Qinhibit_redisplay, Qt);
+      specbind (Qinhibit_quit, Qt);
+
+      if (FRAMEP (tip_frame))
+       {
+         if (delete)
+           {
+             delete_frame (tip_frame, Qnil);
+             tip_frame = Qnil;
+           }
+         else
+           x_make_frame_invisible (XFRAME (tip_frame));
+
+         was_open = Qt;
+       }
+      else
+       tip_frame = Qnil;
+
+      return unbind_to (count, was_open);
+    }
+}
+
 
 DEFUN ("x-show-tip", Fx_show_tip, Sx_show_tip, 1, 6, 0,
        doc: /* Show STRING in a \"tooltip\" window on frame FRAME.
@@ -6460,15 +6881,16 @@ A tooltip's maximum size is specified by `x-max-tooltip-size'.
 Text larger than the specified size is clipped.  */)
   (Lisp_Object string, Lisp_Object frame, Lisp_Object parms, Lisp_Object timeout, Lisp_Object dx, Lisp_Object dy)
 {
-  struct frame *f;
+  struct frame *f, *tip_f;
   struct window *w;
   int root_x, root_y;
   struct buffer *old_buffer;
   struct text_pos pos;
   int i, width, height;
-  bool seen_reversed_p;
   int old_windows_or_buffers_changed = windows_or_buffers_changed;
   ptrdiff_t count = SPECPDL_INDEX ();
+  ptrdiff_t count_1;
+  Lisp_Object window, size;
 
   specbind (Qinhibit_redisplay, Qt);
 
@@ -6492,91 +6914,155 @@ Text larger than the specified size is clipped.  */)
   if (NILP (last_show_tip_args))
     last_show_tip_args = Fmake_vector (make_number (3), Qnil);
 
-  if (!NILP (tip_frame))
+  if (FRAMEP (tip_frame) && FRAME_LIVE_P (XFRAME (tip_frame)))
     {
       Lisp_Object last_string = AREF (last_show_tip_args, 0);
       Lisp_Object last_frame = AREF (last_show_tip_args, 1);
       Lisp_Object last_parms = AREF (last_show_tip_args, 2);
 
-      if (EQ (frame, last_frame)
-         && !NILP (Fequal (last_string, string))
+      if (FRAME_VISIBLE_P (XFRAME (tip_frame))
+         && EQ (frame, last_frame)
+         && !NILP (Fequal_including_properties (last_string, string))
          && !NILP (Fequal (last_parms, parms)))
        {
-         struct frame *f = XFRAME (tip_frame);
-
          /* Only DX and DY have changed.  */
+         tip_f = XFRAME (tip_frame);
          if (!NILP (tip_timer))
            {
              Lisp_Object timer = tip_timer;
+
              tip_timer = Qnil;
              call1 (Qcancel_timer, timer);
            }
 
          block_input ();
-         compute_tip_xy (f, parms, dx, dy, FRAME_PIXEL_WIDTH (f),
-                         FRAME_PIXEL_HEIGHT (f), &root_x, &root_y);
+         compute_tip_xy (tip_f, parms, dx, dy, FRAME_PIXEL_WIDTH (tip_f),
+                         FRAME_PIXEL_HEIGHT (tip_f), &root_x, &root_y);
 
          /* Put tooltip in topmost group and in position.  */
-         SetWindowPos (FRAME_W32_WINDOW (f), HWND_TOPMOST,
+         SetWindowPos (FRAME_W32_WINDOW (tip_f), HWND_TOPMOST,
                        root_x, root_y, 0, 0,
                        SWP_NOSIZE | SWP_NOACTIVATE | SWP_NOOWNERZORDER);
 
          /* Ensure tooltip is on top of other topmost windows (eg menus).  */
-         SetWindowPos (FRAME_W32_WINDOW (f), HWND_TOP,
+         SetWindowPos (FRAME_W32_WINDOW (tip_f), HWND_TOP,
                        0, 0, 0, 0,
                        SWP_NOMOVE | SWP_NOSIZE
                        | SWP_NOACTIVATE | SWP_NOOWNERZORDER);
 
+         /* Let redisplay know that we have made the frame visible already.  */
+         SET_FRAME_VISIBLE (tip_f, 1);
+         ShowWindow (FRAME_W32_WINDOW (tip_f), SW_SHOWNOACTIVATE);
          unblock_input ();
+
          goto start_timer;
        }
-    }
+      else if (tooltip_reuse_hidden_frame && EQ (frame, last_frame))
+       {
+         bool delete = false;
+         Lisp_Object tail, elt, parm, last;
+
+         /* Check if every parameter in PARMS has the same value in
+            last_parms.  This may destruct last_parms which, however,
+            will be recreated below.  */
+         for (tail = parms; CONSP (tail); tail = XCDR (tail))
+           {
+             elt = XCAR (tail);
+             parm = Fcar (elt);
+             /* The left, top, right and bottom parameters are handled
+                by compute_tip_xy so they can be ignored here.  */
+             if (!EQ (parm, Qleft) && !EQ (parm, Qtop)
+                 && !EQ (parm, Qright) && !EQ (parm, Qbottom))
+               {
+                 last = Fassq (parm, last_parms);
+                 if (NILP (Fequal (Fcdr (elt), Fcdr (last))))
+                   {
+                     /* We lost, delete the old tooltip.  */
+                     delete = true;
+                     break;
+                   }
+                 else
+                   last_parms = call2 (Qassq_delete_all, parm, last_parms);
+               }
+             else
+               last_parms = call2 (Qassq_delete_all, parm, last_parms);
+           }
 
-  /* Hide a previous tip, if any.  */
-  Fx_hide_tip ();
+         /* Now check if there's a parameter left in last_parms with a
+            non-nil value.  */
+         for (tail = last_parms; CONSP (tail); tail = XCDR (tail))
+           {
+             elt = XCAR (tail);
+             parm = Fcar (elt);
+             if (!EQ (parm, Qleft) && !EQ (parm, Qtop) && !EQ (parm, Qright)
+                 && !EQ (parm, Qbottom) && !NILP (Fcdr (elt)))
+               {
+                 /* We lost, delete the old tooltip.  */
+                 delete = true;
+                 break;
+               }
+           }
+
+         x_hide_tip (delete);
+       }
+      else
+       x_hide_tip (true);
+    }
+  else
+    x_hide_tip (true);
 
   ASET (last_show_tip_args, 0, string);
   ASET (last_show_tip_args, 1, frame);
   ASET (last_show_tip_args, 2, parms);
 
-  /* Add default values to frame parameters.  */
-  if (NILP (Fassq (Qname, parms)))
-    parms = Fcons (Fcons (Qname, build_string ("tooltip")), parms);
-  if (NILP (Fassq (Qinternal_border_width, parms)))
-    parms = Fcons (Fcons (Qinternal_border_width, make_number (3)), parms);
-  if (NILP (Fassq (Qright_divider_width, parms)))
-    parms = Fcons (Fcons (Qright_divider_width, make_number (0)), parms);
-  if (NILP (Fassq (Qbottom_divider_width, parms)))
-    parms = Fcons (Fcons (Qbottom_divider_width, make_number (0)), parms);
-  if (NILP (Fassq (Qborder_width, parms)))
-    parms = Fcons (Fcons (Qborder_width, make_number (1)), parms);
-  if (NILP (Fassq (Qborder_color, parms)))
-    parms = Fcons (Fcons (Qborder_color, build_string ("lightyellow")), parms);
-  if (NILP (Fassq (Qbackground_color, parms)))
-    parms = Fcons (Fcons (Qbackground_color, build_string ("lightyellow")),
-                  parms);
-
   /* Block input until the tip has been fully drawn, to avoid crashes
      when drawing tips in menus.  */
   block_input ();
 
-  /* Create a frame for the tooltip, and record it in the global
-     variable tip_frame.  */
-  frame = x_create_tip_frame (FRAME_DISPLAY_INFO (f), parms, string);
-  f = XFRAME (frame);
+  if (!FRAMEP (tip_frame) || !FRAME_LIVE_P (XFRAME (tip_frame)))
+    {
+      /* Add default values to frame parameters.  */
+      if (NILP (Fassq (Qname, parms)))
+       parms = Fcons (Fcons (Qname, build_string ("tooltip")), parms);
+      if (NILP (Fassq (Qinternal_border_width, parms)))
+       parms = Fcons (Fcons (Qinternal_border_width, make_number (3)), parms);
+      if (NILP (Fassq (Qborder_width, parms)))
+       parms = Fcons (Fcons (Qborder_width, make_number (1)), parms);
+      if (NILP (Fassq (Qborder_color, parms)))
+       parms = Fcons (Fcons (Qborder_color, build_string ("lightyellow")), parms);
+      if (NILP (Fassq (Qbackground_color, parms)))
+       parms = Fcons (Fcons (Qbackground_color, build_string ("lightyellow")),
+                      parms);
+
+      /* Create a frame for the tooltip, and record it in the global
+        variable tip_frame.  */
+      if (NILP (tip_frame = x_create_tip_frame (FRAME_DISPLAY_INFO (f), parms)))
+       {
+         /* Creating the tip frame failed.  */
+         unblock_input ();
+         return unbind_to (count, Qnil);
+       }
+    }
+
+  tip_f = XFRAME (tip_frame);
+  window = FRAME_ROOT_WINDOW (tip_f);
+  AUTO_STRING (tip, " *tip*");
+  set_window_buffer (window, Fget_buffer_create (tip), false, false);
+  w = XWINDOW (window);
+  w->pseudo_window_p = true;
 
-  /* Set up the frame's root window.  */
-  w = XWINDOW (FRAME_ROOT_WINDOW (f));
+  /* Set up the frame's root window.  Note: The following code does not
+     try to size the window or its frame correctly.  Its only purpose is
+     to make the subsequent text size calculations work.  The right
+     sizes should get installed when the toolkit gets back to us.  */
   w->left_col = 0;
   w->top_line = 0;
   w->pixel_left = 0;
   w->pixel_top = 0;
 
   if (CONSP (Vx_max_tooltip_size)
-      && INTEGERP (XCAR (Vx_max_tooltip_size))
-      && XINT (XCAR (Vx_max_tooltip_size)) > 0
-      && INTEGERP (XCDR (Vx_max_tooltip_size))
-      && XINT (XCDR (Vx_max_tooltip_size)) > 0)
+      && RANGED_INTEGERP (1, XCAR (Vx_max_tooltip_size), INT_MAX)
+      && RANGED_INTEGERP (1, XCDR (Vx_max_tooltip_size), INT_MAX))
     {
       w->total_cols = XFASTINT (XCAR (Vx_max_tooltip_size));
       w->total_lines = XFASTINT (XCDR (Vx_max_tooltip_size));
@@ -6587,164 +7073,71 @@ Text larger than the specified size is clipped.  */)
       w->total_lines = 40;
     }
 
-  w->pixel_width = w->total_cols * FRAME_COLUMN_WIDTH (f);
-  w->pixel_height = w->total_lines * FRAME_LINE_HEIGHT (f);
-
-  FRAME_TOTAL_COLS (f) = WINDOW_TOTAL_COLS (w);
-  adjust_frame_glyphs (f);
-  w->pseudo_window_p = true;
+  w->pixel_width = w->total_cols * FRAME_COLUMN_WIDTH (tip_f);
+  w->pixel_height = w->total_lines * FRAME_LINE_HEIGHT (tip_f);
+  FRAME_TOTAL_COLS (tip_f) = WINDOW_TOTAL_COLS (w);
+  adjust_frame_glyphs (tip_f);
 
-  /* Display the tooltip text in a temporary buffer.  */
+  /* Insert STRING into the root window's buffer and fit the frame to
+     the buffer.  */
+  count_1 = SPECPDL_INDEX ();
   old_buffer = current_buffer;
-  set_buffer_internal_1 (XBUFFER (XWINDOW (FRAME_ROOT_WINDOW (f))->contents));
+  set_buffer_internal_1 (XBUFFER (w->contents));
   bset_truncate_lines (current_buffer, Qnil);
+  specbind (Qinhibit_read_only, Qt);
+  specbind (Qinhibit_modification_hooks, Qt);
+  specbind (Qinhibit_point_motion_hooks, Qt);
+  Ferase_buffer ();
+  Finsert (1, &string);
   clear_glyph_matrix (w->desired_matrix);
   clear_glyph_matrix (w->current_matrix);
   SET_TEXT_POS (pos, BEGV, BEGV_BYTE);
-  try_window (FRAME_ROOT_WINDOW (f), pos, TRY_WINDOW_IGNORE_FONTS_CHANGE);
-
-  /* Compute width and height of the tooltip.  */
-  width = height = 0;
-  seen_reversed_p = false;
-  for (i = 0; i < w->desired_matrix->nrows; ++i)
-    {
-      struct glyph_row *row = &w->desired_matrix->rows[i];
-      struct glyph *last;
-      int row_width;
-
-      /* Stop at the first empty row at the end.  */
-      if (!row->enabled_p || !MATRIX_ROW_DISPLAYS_TEXT_P (row))
-       break;
-
-      /* Let the row go over the full width of the frame.  */
-      row->full_width_p = true;
-
-      row_width = row->pixel_width;
-      if (row->used[TEXT_AREA])
-       {
-         if (!row->reversed_p)
-           {
-             /* There's a glyph at the end of rows that is used to
-                place the cursor there.  Don't include the width of
-                this glyph.  */
-             last = &row->glyphs[TEXT_AREA][row->used[TEXT_AREA] - 1];
-             if (NILP (last->object))
-               row_width -= last->pixel_width;
-           }
-         else
-           {
-             /* There could be a stretch glyph at the beginning of R2L
-                rows that is produced by extend_face_to_end_of_line.
-                Don't count that glyph.  */
-             struct glyph *g = row->glyphs[TEXT_AREA];
-
-             if (g->type == STRETCH_GLYPH && NILP (g->object))
-               {
-                 row_width -= g->pixel_width;
-                 seen_reversed_p = true;
-               }
-           }
-       }
-
-      height += row->height;
-      width = max (width, row_width);
-    }
-
-  /* If we've seen partial-length R2L rows, we need to re-adjust the
-     tool-tip frame width and redisplay it again, to avoid over-wide
-     tips due to the stretch glyph that extends R2L lines to full
-     width of the frame.  */
-  if (seen_reversed_p)
-    {
-      /* PXW: Why do we do the pixel-to-cols conversion only if
-        seen_reversed_p holds?  Don't we have to set other fields of
-        the window/frame structure?
-
-        w->total_cols and FRAME_TOTAL_COLS want the width in columns,
-        not in pixels.  */
-      w->pixel_width = width;
-      width /= WINDOW_FRAME_COLUMN_WIDTH (w);
-      w->total_cols = width;
-      FRAME_TOTAL_COLS (f) = width;
-      SET_FRAME_WIDTH (f, width);
-      adjust_frame_glyphs (f);
-      w->pseudo_window_p = 1;
-      clear_glyph_matrix (w->desired_matrix);
-      clear_glyph_matrix (w->current_matrix);
-      try_window (FRAME_ROOT_WINDOW (f), pos, TRY_WINDOW_IGNORE_FONTS_CHANGE);
-      width = height = 0;
-      /* Recompute width and height of the tooltip.  */
-      for (i = 0; i < w->desired_matrix->nrows; ++i)
-       {
-         struct glyph_row *row = &w->desired_matrix->rows[i];
-         struct glyph *last;
-         int row_width;
-
-         if (!row->enabled_p || !MATRIX_ROW_DISPLAYS_TEXT_P (row))
-           break;
-         row->full_width_p = true;
-         row_width = row->pixel_width;
-         if (row->used[TEXT_AREA] && !row->reversed_p)
-           {
-             last = &row->glyphs[TEXT_AREA][row->used[TEXT_AREA] - 1];
-             if (NILP (last->object))
-               row_width -= last->pixel_width;
-           }
-
-         height += row->height;
-         width = max (width, row_width);
-       }
-    }
-
-  /* Add the frame's internal border to the width and height the w32
-     window should have.  */
-  height += 2 * FRAME_INTERNAL_BORDER_WIDTH (f);
-  width += 2 * FRAME_INTERNAL_BORDER_WIDTH (f);
-
-  /* Move the tooltip window where the mouse pointer is.  Resize and
-     show it.
-
-     PXW: This should use the frame's pixel coordinates.  */
-  compute_tip_xy (f, parms, dx, dy, width, height, &root_x, &root_y);
-
+  try_window (window, pos, TRY_WINDOW_IGNORE_FONTS_CHANGE);
+  /* Calculate size of tooltip window.  */
+  size = Fwindow_text_pixel_size (window, Qnil, Qnil, Qnil,
+                                 make_number (w->pixel_height), Qnil);
+  /* Add the frame's internal border to calculated size.  */
+  width = XINT (Fcar (size)) + 2 * FRAME_INTERNAL_BORDER_WIDTH (tip_f);
+  height = XINT (Fcdr (size)) + 2 * FRAME_INTERNAL_BORDER_WIDTH (tip_f);
+  /* Calculate position of tooltip frame.  */
+  compute_tip_xy (tip_f, parms, dx, dy, width, height, &root_x, &root_y);
+
+  /* Show tooltip frame.  */
   {
-    /* Adjust Window size to take border into account.  */
     RECT rect;
+    int pad = (NUMBERP (Vw32_tooltip_extra_pixels)
+              ? max (0, XINT (Vw32_tooltip_extra_pixels))
+              : FRAME_COLUMN_WIDTH (tip_f));
+
     rect.left = rect.top = 0;
     rect.right = width;
     rect.bottom = height;
-    AdjustWindowRect (&rect, f->output_data.w32->dwStyle, false);
-
-    /* Position and size tooltip, and put it in the topmost group.
-       The add-on of FRAME_COLUMN_WIDTH to the 5th argument is a
-       peculiarity of w32 display: without it, some fonts cause the
-       last character of the tip to be truncated or wrapped around to
-       the next line.  */
-    SetWindowPos (FRAME_W32_WINDOW (f), HWND_TOPMOST,
+    AdjustWindowRect (&rect, tip_f->output_data.w32->dwStyle,
+                     FRAME_EXTERNAL_MENU_BAR (tip_f));
+
+    /* Position and size tooltip and put it in the topmost group.  */
+    SetWindowPos (FRAME_W32_WINDOW (tip_f), HWND_TOPMOST,
                  root_x, root_y,
-                 rect.right - rect.left + FRAME_COLUMN_WIDTH (f),
+                 rect.right - rect.left + pad,
                  rect.bottom - rect.top, SWP_NOACTIVATE | SWP_NOOWNERZORDER);
 
     /* Ensure tooltip is on top of other topmost windows (eg menus).  */
-    SetWindowPos (FRAME_W32_WINDOW (f), HWND_TOP,
+    SetWindowPos (FRAME_W32_WINDOW (tip_f), HWND_TOP,
                  0, 0, 0, 0,
                  SWP_NOMOVE | SWP_NOSIZE
                  | SWP_NOACTIVATE | SWP_NOOWNERZORDER);
 
     /* Let redisplay know that we have made the frame visible already.  */
-    SET_FRAME_VISIBLE (f, 1);
+    SET_FRAME_VISIBLE (tip_f, 1);
 
-    ShowWindow (FRAME_W32_WINDOW (f), SW_SHOWNOACTIVATE);
+    ShowWindow (FRAME_W32_WINDOW (tip_f), SW_SHOWNOACTIVATE);
   }
 
-  /* Draw into the window.  */
   w->must_be_updated_p = true;
   update_single_window (w);
-
-  unblock_input ();
-
-  /* Restore original current buffer.  */
   set_buffer_internal_1 (old_buffer);
+  unbind_to (count_1, Qnil);
+  unblock_input ();
   windows_or_buffers_changed = old_windows_or_buffers_changed;
 
  start_timer:
@@ -6761,31 +7154,7 @@ DEFUN ("x-hide-tip", Fx_hide_tip, Sx_hide_tip, 0, 0, 0,
 Value is t if tooltip was open, nil otherwise.  */)
   (void)
 {
-  ptrdiff_t count;
-  Lisp_Object deleted, frame, timer;
-
-  /* Return quickly if nothing to do.  */
-  if (NILP (tip_timer) && NILP (tip_frame))
-    return Qnil;
-
-  frame = tip_frame;
-  timer = tip_timer;
-  tip_frame = tip_timer = deleted = Qnil;
-
-  count = SPECPDL_INDEX ();
-  specbind (Qinhibit_redisplay, Qt);
-  specbind (Qinhibit_quit, Qt);
-
-  if (!NILP (timer))
-    call1 (Qcancel_timer, timer);
-
-  if (FRAMEP (frame))
-    {
-      delete_frame (frame, Qnil);
-      deleted = Qt;
-    }
-
-  return unbind_to (count, deleted);
+  return x_hide_tip (!tooltip_reuse_hidden_frame);
 }
 \f
 /***********************************************************************
@@ -7653,19 +8022,34 @@ lookup_vk_code (char *key)
        && strcmp (lispy_function_keys[i], key) == 0)
       return i;
 
+  if (w32_kbdhook_active)
+    {
+      /* Alphanumerics map to themselves.  */
+      if (key[1] == 0)
+      {
+       if (key[0] >= 'A' && key[0] <= 'Z' ||
+           key[0] >= '0' && key[0] <= '9')
+         return key[0];
+       if (key[0] >= 'a' && key[0] <= 'z')
+         return toupper(key[0]);
+      }
+    }
+
   return -1;
 }
 
 /* Convert a one-element vector style key sequence to a hot key
    definition.  */
 static Lisp_Object
-w32_parse_hot_key (Lisp_Object key)
+w32_parse_and_hook_hot_key (Lisp_Object key, int hook)
 {
   /* Copied from Fdefine_key and store_in_keymap.  */
   register Lisp_Object c;
   int vk_code;
   int lisp_modifiers;
   int w32_modifiers;
+  Lisp_Object res = Qnil;
+  char* vkname;
 
   CHECK_VECTOR (key);
 
@@ -7688,7 +8072,12 @@ w32_parse_hot_key (Lisp_Object key)
       c = Fcar (c);
       if (!SYMBOLP (c))
        emacs_abort ();
-      vk_code = lookup_vk_code (SSDATA (SYMBOL_NAME (c)));
+      vkname = SSDATA (SYMBOL_NAME (c));
+      /* [s-], [M-], [h-]: Register all keys for this modifier */
+      if (w32_kbdhook_active && vkname[0] == 0)
+        vk_code = VK_ANY;
+      else
+        vk_code = lookup_vk_code (vkname);
     }
   else if (INTEGERP (c))
     {
@@ -7712,34 +8101,75 @@ w32_parse_hot_key (Lisp_Object key)
 #define MOD_WIN         0x0008
 #endif
 
-  /* Convert lisp modifiers to Windows hot-key form.  */
-  w32_modifiers  = (lisp_modifiers & hyper_modifier)    ? MOD_WIN : 0;
-  w32_modifiers |= (lisp_modifiers & alt_modifier)      ? MOD_ALT : 0;
-  w32_modifiers |= (lisp_modifiers & ctrl_modifier)     ? MOD_CONTROL : 0;
-  w32_modifiers |= (lisp_modifiers & shift_modifier)    ? MOD_SHIFT : 0;
+  if (w32_kbdhook_active)
+    {
+      /* Register Alt-x combinations.  */
+      if (lisp_modifiers & alt_modifier)
+        {
+          hook_w32_key (hook, VK_MENU, vk_code);
+          res = Qt;
+        }
+      /* Register Win-x combinations based on modifier mappings.  */
+      if (((lisp_modifiers & hyper_modifier)
+          && EQ (Vw32_lwindow_modifier, Qhyper))
+         || ((lisp_modifiers & super_modifier)
+             && EQ (Vw32_lwindow_modifier, Qsuper)))
+        {
+          hook_w32_key (hook, VK_LWIN, vk_code);
+          res = Qt;
+        }
+      if (((lisp_modifiers & hyper_modifier)
+          && EQ (Vw32_rwindow_modifier, Qhyper))
+         || ((lisp_modifiers & super_modifier)
+             && EQ (Vw32_rwindow_modifier, Qsuper)))
+        {
+          hook_w32_key (hook, VK_RWIN, vk_code);
+          res = Qt;
+        }
+      return res;
+    }
+  else
+    {
+      /* Convert lisp modifiers to Windows hot-key form.  */
+      w32_modifiers  = (lisp_modifiers & hyper_modifier)    ? MOD_WIN : 0;
+      w32_modifiers |= (lisp_modifiers & alt_modifier)      ? MOD_ALT : 0;
+      w32_modifiers |= (lisp_modifiers & ctrl_modifier)     ? MOD_CONTROL : 0;
+      w32_modifiers |= (lisp_modifiers & shift_modifier)    ? MOD_SHIFT : 0;
 
-  return HOTKEY (vk_code, w32_modifiers);
+      return HOTKEY (vk_code, w32_modifiers);
+    }
 }
 
 DEFUN ("w32-register-hot-key", Fw32_register_hot_key,
        Sw32_register_hot_key, 1, 1, 0,
        doc: /* Register KEY as a hot-key combination.
-Certain key combinations like Alt-Tab are reserved for system use on
-Windows, and therefore are normally intercepted by the system.  However,
-most of these key combinations can be received by registering them as
-hot-keys, overriding their special meaning.
-
-KEY must be a one element key definition in vector form that would be
-acceptable to `define-key' (e.g. [A-tab] for Alt-Tab).  The meta
-modifier is interpreted as Alt if `w32-alt-is-meta' is t, and hyper
-is always interpreted as the Windows modifier keys.
-
-The return value is the hotkey-id if registered, otherwise nil.  */)
+Certain key combinations like Alt-Tab and Win-R are reserved for
+system use on Windows, and therefore are normally intercepted by the
+system.  These key combinations can be received by registering them
+as hot-keys, except for Win-L which always locks the computer.
+
+On Windows 98 and ME, KEY must be a one element key definition in
+vector form that would be acceptable to `define-key' (e.g. [A-tab] for
+Alt-Tab).  The meta modifier is interpreted as Alt if
+`w32-alt-is-meta' is t, and hyper is always interpreted as the Windows
+modifier keys.  The return value is the hotkey-id if registered, otherwise nil.
+
+On Windows versions since NT, KEY can also be specified as [M-], [s-] or
+[h-] to indicate that all combinations of that key should be processed
+by Emacs instead of the operating system.  The super and hyper
+modifiers are interpreted according to the current values of
+`w32-lwindow-modifier' and `w32-rwindow-modifier'.  For instance,
+setting `w32-lwindow-modifier' to `super' and then calling
+`(register-hot-key [s-])' grabs all combinations of the left Windows
+key to Emacs, but leaves the right Windows key free for the operating
+system keyboard shortcuts.  The return value is t if the call affected
+any key combinations, otherwise nil.  */)
   (Lisp_Object key)
 {
-  key = w32_parse_hot_key (key);
+  key = w32_parse_and_hook_hot_key (key, 1);
 
-  if (!NILP (key) && NILP (Fmemq (key, w32_grabbed_keys)))
+  if (!w32_kbdhook_active
+      && !NILP (key) && NILP (Fmemq (key, w32_grabbed_keys)))
     {
       /* Reuse an empty slot if possible.  */
       Lisp_Object item = Fmemq (Qnil, w32_grabbed_keys);
@@ -7767,7 +8197,10 @@ DEFUN ("w32-unregister-hot-key", Fw32_unregister_hot_key,
   Lisp_Object item;
 
   if (!INTEGERP (key))
-    key = w32_parse_hot_key (key);
+    key = w32_parse_and_hook_hot_key (key, 0);
+
+  if (w32_kbdhook_active)
+    return key;
 
   item = Fmemq (key, w32_grabbed_keys);
 
@@ -9315,12 +9748,13 @@ syms_of_w32fns (void)
   DEFSYM (Qctrl, "ctrl");
   DEFSYM (Qcontrol, "control");
   DEFSYM (Qshift, "shift");
-  DEFSYM (Qfont_param, "font-parameter");
+  DEFSYM (Qfont_parameter, "font-parameter");
   DEFSYM (Qgeometry, "geometry");
   DEFSYM (Qworkarea, "workarea");
   DEFSYM (Qmm_size, "mm-size");
   DEFSYM (Qframes, "frames");
   DEFSYM (Qtip_frame, "tip-frame");
+  DEFSYM (Qassq_delete_all, "assq-delete-all");
   DEFSYM (Qunicode_sip, "unicode-sip");
 #if defined WINDOWSNT && !defined HAVE_DBUS
   DEFSYM (QCicon, ":icon");
@@ -9333,10 +9767,10 @@ syms_of_w32fns (void)
 #endif
 
   /* Symbols used elsewhere, but only in MS-Windows-specific code.  */
-  DEFSYM (Qgnutls_dll, "gnutls");
-  DEFSYM (Qlibxml2_dll, "libxml2");
+  DEFSYM (Qgnutls, "gnutls");
+  DEFSYM (Qlibxml2, "libxml2");
   DEFSYM (Qserif, "serif");
-  DEFSYM (Qzlib_dll, "zlib");
+  DEFSYM (Qzlib, "zlib");
 
   Fput (Qundefined_color, Qerror_conditions,
        listn (CONSTYPE_PURE, 2, Qundefined_color, Qerror));
@@ -9374,11 +9808,15 @@ When non-nil, the Start menu is opened by tapping the key.
 If you set this to nil, the left \"Windows\" key is processed by Emacs
 according to the value of `w32-lwindow-modifier', which see.
 
-Note that some combinations of the left \"Windows\" key with other keys are
-caught by Windows at low level, and so binding them in Emacs will have no
-effect.  For example, <lwindow>-r always pops up the Windows Run dialog,
-<lwindow>-<Pause> pops up the "System Properties" dialog, etc.  However, see
-the doc string of `w32-phantom-key-code'.  */);
+Note that some combinations of the left \"Windows\" key with other
+keys are caught by Windows at low level.  For example, <lwindow>-r
+pops up the Windows Run dialog, <lwindow>-<Pause> pops up the "System
+Properties" dialog, etc.  On Windows 10, no \"Windows\" key
+combinations are normally handed to applications.  To enable Emacs to
+process \"Windows\" key combinations, use the function
+`w32-register-hot-key`.
+
+For Windows 98/ME, see the doc string of `w32-phantom-key-code'.  */);
   Vw32_pass_lwindow_to_system = Qt;
 
   DEFVAR_LISP ("w32-pass-rwindow-to-system",
@@ -9389,11 +9827,15 @@ When non-nil, the Start menu is opened by tapping the key.
 If you set this to nil, the right \"Windows\" key is processed by Emacs
 according to the value of `w32-rwindow-modifier', which see.
 
-Note that some combinations of the right \"Windows\" key with other keys are
-caught by Windows at low level, and so binding them in Emacs will have no
-effect.  For example, <rwindow>-r always pops up the Windows Run dialog,
-<rwindow>-<Pause> pops up the "System Properties" dialog, etc.  However, see
-the doc string of `w32-phantom-key-code'.  */);
+Note that some combinations of the right \"Windows\" key with other
+keys are caught by Windows at low level.  For example, <rwindow>-r
+pops up the Windows Run dialog, <rwindow>-<Pause> pops up the "System
+Properties" dialog, etc.  On Windows 10, no \"Windows\" key
+combinations are normally handed to applications.  To enable Emacs to
+process \"Windows\" key combinations, use the function
+`w32-register-hot-key`.
+
+For Windows 98/ME, see the doc string of `w32-phantom-key-code'.  */);
   Vw32_pass_rwindow_to_system = Qt;
 
   DEFVAR_LISP ("w32-phantom-key-code",
@@ -9403,7 +9845,11 @@ Value is a number between 0 and 255.
 
 Phantom key presses are generated in order to stop the system from
 acting on \"Windows\" key events when `w32-pass-lwindow-to-system' or
-`w32-pass-rwindow-to-system' is nil.  */);
+`w32-pass-rwindow-to-system' is nil.
+
+This variable is only used on Windows 98 and ME.  For other Windows
+versions, see the documentation of the `w32-register-hot-key`
+function.  */);
   /* Although 255 is technically not a valid key code, it works and
      means that this hack won't interfere with any real key code.  */
   XSETINT (Vw32_phantom_key_code, 255);
@@ -9433,7 +9879,9 @@ Any other value will cause the Scroll Lock key to be ignored.  */);
               doc: /* Modifier to use for the left \"Windows\" key.
 The value can be hyper, super, meta, alt, control or shift for the
 respective modifier, or nil to appear as the `lwindow' key.
-Any other value will cause the key to be ignored.  */);
+Any other value will cause the key to be ignored.
+
+Also see the documentation of the `w32-register-hot-key` function.  */);
   Vw32_lwindow_modifier = Qnil;
 
   DEFVAR_LISP ("w32-rwindow-modifier",
@@ -9441,7 +9889,9 @@ Any other value will cause the key to be ignored.  */);
               doc: /* Modifier to use for the right \"Windows\" key.
 The value can be hyper, super, meta, alt, control or shift for the
 respective modifier, or nil to appear as the `rwindow' key.
-Any other value will cause the key to be ignored.  */);
+Any other value will cause the key to be ignored.
+
+Also see the documentation of the `w32-register-hot-key` function.  */);
   Vw32_rwindow_modifier = Qnil;
 
   DEFVAR_LISP ("w32-apps-modifier",
@@ -9617,6 +10067,18 @@ Default is nil.
 This variable has effect only on Windows Vista and later.  */);
   w32_disable_new_uniscribe_apis = 0;
 
+  DEFVAR_LISP ("w32-tooltip-extra-pixels",
+              Vw32_tooltip_extra_pixels,
+              doc: /* Number of pixels added after tooltip text.
+On Windows some fonts may cause the last character of a tooltip be
+truncated or wrapped around to the next line.  Adding some extra space
+at the end of the toooltip works around this problem.
+
+This variable specifies the number of pixels that shall be added.  The
+default value t means to add the width of one canonical character of the
+tip frame.  */);
+  Vw32_tooltip_extra_pixels = Qt;
+
 #if 0 /* TODO: Port to W32 */
   defsubr (&Sx_change_window_property);
   defsubr (&Sx_delete_window_property);