{-# LINE 1 "libraries\\Win32\\Graphics\\Win32\\Window\\HotKey.hsc" #-}
{-# LANGUAGE CPP #-}
{- |

   Module      :  Graphics.Win32.Window.HotKey

   Copyright   :  2013 shelarcy

   License     :  BSD-style



   Maintainer  :  [email protected]

   Stability   :  Provisional

   Portability :  Non-portable (Win32 API)



   An FFI binding to the hot key part of the Win32 API.

-}
module Graphics.Win32.Window.HotKey where

import Data.Bits                 ( (.|.) )
import Graphics.Win32.GDI.Types  ( HWND, MbHWND )
import Graphics.Win32.Key        ( VKey )
import Graphics.Win32.Message    ( WindowMessage )
import System.Win32.Types        ( UINT, BOOL, maybePtr, failIfFalse_ )
import System.Win32.Exception.Unsupported ( unsupportedVal, upgradeWindowsOS )
import System.Win32.Info.Version ( is7OrLater )


#include "windows_cconv.h"


type FsModifiers = [FsModifier]
type FsModifier  = UINT

mOD_ALT       :: FsModifier
mOD_ALT       =  1
mOD_CONTROL   :: FsModifier
mOD_CONTROL   =  2
mOD_SHIFT     :: FsModifier
mOD_SHIFT     =  4
mOD_WIN       :: FsModifier
mOD_WIN       =  8

{-# LINE 35 "libraries\\Win32\\Graphics\\Win32\\Window\\HotKey.hsc" #-}

-- | This parameter requires to use Windows 7 or later.

mOD_NOREPEAT :: FsModifier
mOD_NOREPEAT
  = unsupportedVal "MOD_NOREPEAT"
      is7OrLater (upgradeWindowsOS "Windows 7") 0x4000
{-

 , mOD_NOREPEAT = MOD_NOREPEAT

-}

wM_HOTKEY :: WindowMessage
wM_HOTKEY = 786
{-# LINE 47 "libraries\\Win32\\Graphics\\Win32\\Window\\HotKey.hsc" #-}

joinModifiers :: FsModifiers -> FsModifier
joinModifiers = foldr (.|.) 0

registerHotKey :: MbHWND -> Int -> FsModifier -> VKey -> IO ()
registerHotKey mb_wnd kid md vkey =
  failIfFalse_ (unwords ["RegisterHotKey", show mb_wnd, show kid, show md, show vkey])
    $ c_RegisterHotKey (maybePtr mb_wnd) kid md vkey

foreign import WINDOWS_CCONV "windows.h RegisterHotKey"
  c_RegisterHotKey :: HWND -> Int -> UINT -> VKey -> IO BOOL

unregisterHotKey :: MbHWND -> Int -> IO ()
unregisterHotKey mb_wnd kid =
  failIfFalse_ (unwords ["UnregisterHotKey", show mb_wnd, show kid])
    $ c_UnregisterHotKey (maybePtr mb_wnd) kid

foreign import WINDOWS_CCONV "windows.h UnregisterHotKey"
  c_UnregisterHotKey :: HWND -> Int -> IO BOOL