{-# LINE 1 "libraries\\Win32\\System\\Win32\\Console.hsc" #-}
{-# LINE 2 "libraries\\Win32\\System\\Win32\\Console.hsc" #-}
{-# LANGUAGE Safe #-}
{-# LINE 6 "libraries\\Win32\\System\\Win32\\Console.hsc" #-}
module System.Win32.Console (
getConsoleMode,
setConsoleMode,
eNABLE_ECHO_INPUT,
eNABLE_EXTENDED_FLAGS,
eNABLE_INSERT_MODE,
eNABLE_LINE_INPUT,
eNABLE_MOUSE_INPUT,
eNABLE_PROCESSED_INPUT,
eNABLE_QUICK_EDIT_MODE,
eNABLE_WINDOW_INPUT,
eNABLE_VIRTUAL_TERMINAL_INPUT,
eNABLE_PROCESSED_OUTPUT,
eNABLE_WRAP_AT_EOL_OUTPUT,
eNABLE_VIRTUAL_TERMINAL_PROCESSING,
dISABLE_NEWLINE_AUTO_RETURN,
eNABLE_LVB_GRID_WORLDWIDE,
getConsoleCP,
setConsoleCP,
getConsoleOutputCP,
setConsoleOutputCP,
CtrlEvent, cTRL_C_EVENT, cTRL_BREAK_EVENT,
generateConsoleCtrlEvent,
commandLineToArgv,
getCommandLineW,
getArgs,
CONSOLE_SCREEN_BUFFER_INFO(..),
CONSOLE_SCREEN_BUFFER_INFOEX(..),
COORD(..),
SMALL_RECT(..),
COLORREF,
getConsoleScreenBufferInfo,
getCurrentConsoleScreenBufferInfo,
getConsoleScreenBufferInfoEx,
getCurrentConsoleScreenBufferInfoEx
) where
#include "windows_cconv.h"
import System.Win32.Types
import System.Win32.Console.Internal
import Graphics.Win32.Misc
import Graphics.Win32.GDI.Types (COLORREF)
import Foreign.C.String (withCWString)
import Foreign.Storable (Storable(..))
import Foreign.Marshal.Array (peekArray)
import Foreign.Marshal.Alloc (alloca)
getConsoleMode :: HANDLE -> IO DWORD
getConsoleMode h = alloca $ \ptr -> do
failIfFalse_ "GetConsoleMode" $ c_GetConsoleMode h ptr
peek ptr
setConsoleMode :: HANDLE -> DWORD -> IO ()
setConsoleMode h mode = failIfFalse_ "SetConsoleMode" $ c_SetConsoleMode h mode
eNABLE_ECHO_INPUT, eNABLE_EXTENDED_FLAGS, eNABLE_INSERT_MODE, eNABLE_LINE_INPUT,
eNABLE_MOUSE_INPUT, eNABLE_PROCESSED_INPUT, eNABLE_QUICK_EDIT_MODE,
eNABLE_WINDOW_INPUT, eNABLE_VIRTUAL_TERMINAL_INPUT, eNABLE_PROCESSED_OUTPUT,
eNABLE_WRAP_AT_EOL_OUTPUT, eNABLE_VIRTUAL_TERMINAL_PROCESSING,
dISABLE_NEWLINE_AUTO_RETURN, eNABLE_LVB_GRID_WORLDWIDE :: DWORD
eNABLE_ECHO_INPUT = 4
ULONG
eNABLE_EXTENDED_FLAGS = 128
eNABLE_INSERT_MODE = 32
eNABLE_LINE_INPUT = 2
eNABLE_MOUSE_INPUT = 16
eNABLE_PROCESSED_INPUT = 1
eNABLE_PROCESSED_INPUT :: ULONG
eNABLE_QUICK_EDIT_MODE = 64
eNABLE_WINDOW_INPUT = 8
eNABLE_VIRTUAL_TERMINAL_INPUT = 512
eNABLE_PROCESSED_OUTPUT = 1
eNABLE_WRAP_AT_EOL_OUTPUT = 2
eNABLE_VIRTUAL_TERMINAL_PROCESSING = 4
dISABLE_NEWLINE_AUTO_RETURN = 8
eNABLE_LVB_GRID_WORLDWIDE = 16
generateConsoleCtrlEvent :: CtrlEvent -> DWORD -> IO ()
generateConsoleCtrlEvent e p
= failIfFalse_
"generateConsoleCtrlEvent"
$ c_GenerateConsoleCtrlEvent e p
commandLineToArgv :: String -> IO [String]
commandLineToArgv [] = return []
commandLineToArgv :: String -> IO [String]
commandLineToArgv arg =
do withCWString arg $ \c_arg -> do
alloca $ \c_size -> do
res <- c_CommandLineToArgvW c_arg c_size
size <- peek c_size
args <- peekArray (fromIntegral size) res
_ <- localFree res
mapM peekTString args
getArgs :: IO [String]
getArgs = do
getCommandLineW >>= peekTString >>= commandLineToArgv
getConsoleScreenBufferInfo :: HANDLE -> IO CONSOLE_SCREEN_BUFFER_INFO
getConsoleScreenBufferInfo h = alloca $ \ptr -> do
failIfFalse_ "GetConsoleScreenBufferInfo" $ c_GetConsoleScreenBufferInfo h ptr
peek ptr
getCurrentConsoleScreenBufferInfo :: IO CONSOLE_SCREEN_BUFFER_INFO
getCurrentConsoleScreenBufferInfo = do
h <- failIf (== nullHANDLE) "getStdHandle" $ getStdHandle sTD_OUTPUT_HANDLE
getConsoleScreenBufferInfo h
getConsoleScreenBufferInfoEx :: HANDLE -> IO CONSOLE_SCREEN_BUFFER_INFOEX
getConsoleScreenBufferInfoEx h = alloca $ \ptr -> do
((\hsc_ptr -> pokeByteOff hsc_ptr 0)) ptr cbSize
{-# LINE 147 "libraries\\Win32\\System\\Win32\\Console.hsc" #-}
failIfFalse_ "GetConsoleScreenBufferInfoEx" $ c_GetConsoleScreenBufferInfoEx h ptr
peek ptr
where
cbSize :: ULONG
cbSize = (96)
{-# LINE 152 "libraries\\Win32\\System\\Win32\\Console.hsc" #-}
getCurrentConsoleScreenBufferInfoEx :: IO CONSOLE_SCREEN_BUFFER_INFOEX
getCurrentConsoleScreenBufferInfoEx = do
h <- failIf (== nullHANDLE) "getStdHandle" $ getStdHandle sTD_OUTPUT_HANDLE
getConsoleScreenBufferInfoEx h