{- |
   Module      :  System.Win32.Console.HWND
   Copyright   :  2009 Balazs Komuves, 2013 shelarcy
   License     :  BSD-style

   Maintainer  :  shelarcy@gmail.com
   Stability   :  Provisional
   Portability :  Non-portable (Win32 API)

   Get the handle of the current console window.
-}
module System.Win32.Console.HWND (getConsoleHWND) where
import Control.Concurrent           ( threadDelay )
import Control.Exception            ( bracket )
import Foreign.Ptr                  ( nullPtr )
import Graphics.Win32.Window        ( c_FindWindow )
import Graphics.Win32.GDI.Types     ( HWND )
import System.Win32.Console.Title   ( getConsoleTitle, setConsoleTitle )
import System.Win32.Process ( getCurrentProcessId )
import System.Win32.String          ( withTString )
import System.Win32.Time            ( getTickCount )

-- | Get the handle of the current console window by using window's title.

-- See: <http://support.microsoft.com/kb/124103>

getConsoleHWND :: IO HWND
getConsoleHWND :: IO HWND
getConsoleHWND
  = IO String -> (String -> IO ()) -> (String -> IO HWND) -> IO HWND
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket IO String
getConsoleTitle String -> IO ()
setConsoleTitle ((String -> IO HWND) -> IO HWND) -> (String -> IO HWND) -> IO HWND
forall a b. (a -> b) -> a -> b
$ \String
_ -> do
        DWORD
time   <- IO DWORD
getTickCount
        DWORD
pid    <- IO DWORD
getCurrentProcessId
        let unique :: String
unique = DWORD -> String
forall a. Show a => a -> String
show DWORD
time String -> String -> String
forall a. [a] -> [a] -> [a]
++ DWORD -> String
forall a. Show a => a -> String
show DWORD
pid
        String -> IO ()
setConsoleTitle String
unique
        Int -> IO ()
threadDelay (Int
42Int -> Int -> Int
forall a. Num a => a -> a -> a
*Int
1000)
        String -> (LPTSTR -> IO HWND) -> IO HWND
forall a. String -> (LPTSTR -> IO a) -> IO a
withTString String
unique ((LPTSTR -> IO HWND) -> IO HWND) -> (LPTSTR -> IO HWND) -> IO HWND
forall a b. (a -> b) -> a -> b
$ \LPTSTR
punique ->
            LPTSTR -> LPTSTR -> IO HWND
c_FindWindow LPTSTR
forall a. Ptr a
nullPtr LPTSTR
punique