{-# LINE 1 "libraries\\Win32\\System\\Win32\\Console\\Title.hsc" #-}
{-# LANGUAGE CPP #-}
module System.Win32.Console.Title
( getConsoleTitle
, setConsoleTitle
) where
import System.Win32.String ( LPTSTR, LPCTSTR
, withTStringBufferLen, withTString, peekTStringLen )
import System.Win32.Types ( BOOL, failIfFalse_, failIfZero )
import System.Win32.Word ( DWORD )
#include "windows_cconv.h"
getConsoleTitle :: IO String
getConsoleTitle =
withTStringBufferLen maxLength $ \(buf, len) -> do
len' <- failIfZero "GetConsoleTitle"
$ c_GetConsoleTitle buf (fromIntegral len)
peekTStringLen (buf, (fromIntegral len'))
where
maxLength = 260
{-# LINE 34 "libraries\\Win32\\System\\Win32\\Console\\Title.hsc" #-}
setConsoleTitle :: String -> IO ()
setConsoleTitle title =
withTString title $ \buf ->
failIfFalse_ (unwords ["SetConsoleTitle", title])
$ c_SetConsoleTitle buf
foreign import WINDOWS_CCONV "windows.h GetConsoleTitleW"
c_GetConsoleTitle :: LPTSTR -> DWORD -> IO DWORD
foreign import WINDOWS_CCONV "windows.h SetConsoleTitleW"
c_SetConsoleTitle :: LPCTSTR -> IO BOOL