{-# LINE 1 "libraries\\Win32\\System\\Win32\\WindowsString\\Console.hsc" #-}
module System.Win32.WindowsString.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.WindowsString.Types
import System.Win32.Console.Internal
import System.Win32.Console hiding (getArgs, commandLineToArgv)
import System.OsString.Windows
import Foreign.Storable (Storable(..))
import Foreign.Marshal.Array (peekArray)
import Foreign.Marshal.Alloc (alloca)
commandLineToArgv :: WindowsString -> IO [WindowsString]
commandLineToArgv arg
| arg == mempty = return []
| otherwise = withTString 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 [WindowsString]
getArgs = do
getCommandLineW >>= peekTString >>= commandLineToArgv