{-# LINE 1 "System\\Win32\\Automation\\Input.hsc" #-}{-# LANGUAGE CPP #-}{- |
 Module : System.Win32.Automation.Input
 Copyright : 2013 shelarcy
 License : BSD-style
 Maintainer : shelarcy@gmail.com
 Stability : Provisional
 Portability : Non-portable (Win32 API)
 Provide sendInput function and INPUT types.
-}moduleSystem.Win32.Automation.Input(sendInput,sendInputPtr,makeKeyboardInput,PINPUT,LPINPUT,INPUT(..),PHARDWAREINPUT,HARDWAREINPUT(..),getMessageExtraInfo,setMessageExtraInfo,moduleSystem.Win32.Automation.Input.Key,moduleSystem.Win32.Automation.Input.Mouse)whereimportData.Bits((.|.))importForeign.Ptr(Ptr)importForeign.Storable(Storable(..))importForeign.Marshal.Array(withArrayLen)importForeign.C.Types(CIntPtr(..))importGraphics.Win32.Key(VKey,c_MapVirtualKey)importSystem.Win32.Automation.Input.KeyimportSystem.Win32.Automation.Input.Mouse(MOUSEINPUT)importSystem.Win32.Automation.Input.Mousehiding(MOUSEINPUT(..))importSystem.Win32.Types(UINT,LPARAM,failIfZero)importSystem.Win32.Word(DWORD,WORD)
#include "windows_cconv.h"
sendInput::[INPUT]->IOUINTsendInputinput=withArrayLeninput$\lenc_input->sendInputPtrlenc_input{-# INLINEsendInputPtr#-}-- | Raw pointer of array version of 'sendInput'.
-- Use this function to support non-list sequence.
sendInputPtr::Int->PtrINPUT->IOUINTsendInputPtrlenc_input=failIfZero"SendInput"$c_SendInput(fromIntegrallen)c_input$sizeOf(undefined::INPUT)foreignimportWINDOWS_CCONVunsafe"windows.h SendInput"c_SendInput::UINT->LPINPUT->Int->IOUINTmakeKeyboardInput::VKey->MaybeDWORD->IOINPUTmakeKeyboardInputvkeyflag=doletflag'=maybekEYEVENTF_EXTENDEDKEY(kEYEVENTF_EXTENDEDKEY.|.)flagscan<-c_MapVirtualKeyvkey0dwExtraInfo'<-getMessageExtraInforeturn$Keyboard$KEYBDINPUT{wVk=fromIntegralvkey,wScan=fromIntegralscan,dwFlags=flag',time=0,dwExtraInfo=fromIntegral$dwExtraInfo'}typePINPUT=PtrINPUTtypeLPINPUT=PtrINPUTdataINPUT=MouseMOUSEINPUT|KeyboardKEYBDINPUT|OtherHardwareHARDWAREINPUTderivingShowinstanceStorableINPUTwheresizeOf=const(40){-# LINE 83 "System\\Win32\\Automation\\Input.hsc" #-}alignment_=8{-# LINE 84 "System\\Win32\\Automation\\Input.hsc" #-}pokebuf(Mousemouse)=do((\hsc_ptr->pokeByteOffhsc_ptr0))buf(0::DWORD){-# LINE 87 "System\\Win32\\Automation\\Input.hsc" #-}((\hsc_ptr->pokeByteOffhsc_ptr8))bufmouse{-# LINE 88 "System\\Win32\\Automation\\Input.hsc" #-}pokebuf(Keyboardkey)=do((\hsc_ptr->pokeByteOffhsc_ptr0))buf(1::DWORD){-# LINE 90 "System\\Win32\\Automation\\Input.hsc" #-}((\hsc_ptr->pokeByteOffhsc_ptr8))bufkey{-# LINE 91 "System\\Win32\\Automation\\Input.hsc" #-}pokebuf(OtherHardwarehard)=do((\hsc_ptr->pokeByteOffhsc_ptr0))buf(2::DWORD){-# LINE 93 "System\\Win32\\Automation\\Input.hsc" #-}((\hsc_ptr->pokeByteOffhsc_ptr8))bufhard{-# LINE 94 "System\\Win32\\Automation\\Input.hsc" #-}peekbuf=dotype'<-((\hsc_ptr->peekByteOffhsc_ptr0))buf::IODWORD{-# LINE 97 "System\\Win32\\Automation\\Input.hsc" #-}casetype'of0->{-# LINE 99 "System\\Win32\\Automation\\Input.hsc" #-}Mouse`fmap`((\hsc_ptr->peekByteOffhsc_ptr8))buf{-# LINE 100 "System\\Win32\\Automation\\Input.hsc" #-}1->{-# LINE 101 "System\\Win32\\Automation\\Input.hsc" #-}Keyboard`fmap`((\hsc_ptr->peekByteOffhsc_ptr8))buf{-# LINE 102 "System\\Win32\\Automation\\Input.hsc" #-}_->OtherHardware`fmap`((\hsc_ptr->peekByteOffhsc_ptr8))buf{-# LINE 103 "System\\Win32\\Automation\\Input.hsc" #-}typePHARDWAREINPUT=PtrHARDWAREINPUTdataHARDWAREINPUT=HARDWAREINPUT{uMsg::DWORD,wParamL::WORD,wParamH::WORD}derivingShowinstanceStorableHARDWAREINPUTwheresizeOf=const(8){-# LINE 115 "System\\Win32\\Automation\\Input.hsc" #-}alignment_=4{-# LINE 116 "System\\Win32\\Automation\\Input.hsc" #-}pokebufinput=do((\hsc_ptr->pokeByteOffhsc_ptr0))buf(uMsginput){-# LINE 118 "System\\Win32\\Automation\\Input.hsc" #-}((\hsc_ptr->pokeByteOffhsc_ptr4))buf(wParamLinput){-# LINE 119 "System\\Win32\\Automation\\Input.hsc" #-}((\hsc_ptr->pokeByteOffhsc_ptr6))buf(wParamHinput){-# LINE 120 "System\\Win32\\Automation\\Input.hsc" #-}peekbuf=douMsg'<-((\hsc_ptr->peekByteOffhsc_ptr0))buf{-# LINE 122 "System\\Win32\\Automation\\Input.hsc" #-}wParamL'<-((\hsc_ptr->peekByteOffhsc_ptr4))buf{-# LINE 123 "System\\Win32\\Automation\\Input.hsc" #-}wParamH'<-((\hsc_ptr->peekByteOffhsc_ptr6))buf{-# LINE 124 "System\\Win32\\Automation\\Input.hsc" #-}return$HARDWAREINPUTuMsg'wParamL'wParamH'foreignimportWINDOWS_CCONVunsafe"windows.h GetMessageExtraInfo"getMessageExtraInfo::IOLPARAMforeignimportWINDOWS_CCONVunsafe"windows.h SetMessageExtraInfo"setMessageExtraInfo::LPARAM->IOLPARAM

AltStyle によって変換されたページ (->オリジナル) /