{-# LINE 1 "libraries\\Win32\\System\\Win32\\Console\\Internal.hsc" #-}

{-# LINE 2 "libraries\\Win32\\System\\Win32\\Console\\Internal.hsc" #-}
{-# LANGUAGE Safe #-}

{-# LINE 6 "libraries\\Win32\\System\\Win32\\Console\\Internal.hsc" #-}
-----------------------------------------------------------------------------

-- |

-- Module      :  System.Win32.Console.Internal

-- Copyright   :  (c) University of Glasgow 2023

-- License     :  BSD-style (see the file LICENSE)

--

-- Maintainer  :  Esa Ilari Vuokko <ei@vuokko.info>

-- Stability   :  provisional

-- Portability :  portable

--

-- Internals for Console modules.

--

-----------------------------------------------------------------------------


module System.Win32.Console.Internal where



#include "windows_cconv.h"


import System.Win32.Types
import Graphics.Win32.GDI.Types (COLORREF)

import Foreign.C.Types (CInt(..))
import Foreign.C.String (CWString)
import Foreign.Ptr (Ptr, plusPtr)
import Foreign.Storable (Storable(..))
import Foreign.Marshal.Array (peekArray, pokeArray)

foreign import WINDOWS_CCONV unsafe "windows.h GetConsoleMode"
        c_GetConsoleMode :: HANDLE -> LPDWORD -> IO BOOL

foreign import WINDOWS_CCONV unsafe "windows.h SetConsoleMode"
        c_SetConsoleMode :: HANDLE -> DWORD -> IO BOOL

foreign import WINDOWS_CCONV unsafe "windows.h GetConsoleCP"
        getConsoleCP :: IO UINT

foreign import WINDOWS_CCONV unsafe "windows.h SetConsoleCP"
        setConsoleCP :: UINT -> IO ()

foreign import WINDOWS_CCONV unsafe "windows.h GetConsoleOutputCP"
        getConsoleOutputCP :: IO UINT

foreign import WINDOWS_CCONV unsafe "windows.h SetConsoleOutputCP"
        setConsoleOutputCP :: UINT -> IO ()

type CtrlEvent = DWORD
cTRL_C_EVENT       :: CtrlEvent
cTRL_C_EVENT       =  0
cTRL_BREAK_EVENT   :: CtrlEvent
cTRL_BREAK_EVENT   =  1

{-# LINE 59 "libraries\\Win32\\System\\Win32\\Console\\Internal.hsc" #-}

foreign import WINDOWS_CCONV safe "windows.h GenerateConsoleCtrlEvent"
    c_GenerateConsoleCtrlEvent :: CtrlEvent -> DWORD -> IO BOOL

foreign import WINDOWS_CCONV unsafe "Shellapi.h CommandLineToArgvW"
     c_CommandLineToArgvW :: CWString -> Ptr CInt -> IO (Ptr CWString)

foreign import WINDOWS_CCONV unsafe "processenv.h GetCommandLineW"
        getCommandLineW :: IO LPWSTR

data CONSOLE_SCREEN_BUFFER_INFO = CONSOLE_SCREEN_BUFFER_INFO
    { dwSize              :: COORD
    , dwCursorPosition    :: COORD
    , wAttributes         :: WORD
    , srWindow            :: SMALL_RECT
    , dwMaximumWindowSize :: COORD
    } deriving (Show, Eq)

instance Storable CONSOLE_SCREEN_BUFFER_INFO where
    sizeOf = const (22)
{-# LINE 79 "libraries\\Win32\\System\\Win32\\Console\\Internal.hsc" #-}
    alignment _ = 2
{-# LINE 80 "libraries\\Win32\\System\\Win32\\Console\\Internal.hsc" #-}
    peek buf = do
        dwSize'              <- ((\hsc_ptr -> peekByteOff hsc_ptr 0)) buf
{-# LINE 82 "libraries\\Win32\\System\\Win32\\Console\\Internal.hsc" #-}
        dwCursorPosition'    <- ((\hsc_ptr -> peekByteOff hsc_ptr 4)) buf
{-# LINE 83 "libraries\\Win32\\System\\Win32\\Console\\Internal.hsc" #-}
        wAttributes'         <- ((\hsc_ptr -> peekByteOff hsc_ptr 8)) buf
{-# LINE 84 "libraries\\Win32\\System\\Win32\\Console\\Internal.hsc" #-}
        srWindow'            <- ((\hsc_ptr -> peekByteOff hsc_ptr 10)) buf
{-# LINE 85 "libraries\\Win32\\System\\Win32\\Console\\Internal.hsc" #-}
        dwMaximumWindowSize' <- ((\hsc_ptr -> peekByteOff hsc_ptr 18)) buf
{-# LINE 86 "libraries\\Win32\\System\\Win32\\Console\\Internal.hsc" #-}
        return $ CONSOLE_SCREEN_BUFFER_INFO dwSize' dwCursorPosition' wAttributes' srWindow' dwMaximumWindowSize'
    poke buf info = do
        ((\hsc_ptr -> pokeByteOff hsc_ptr 0)) buf (dwSize info)
{-# LINE 89 "libraries\\Win32\\System\\Win32\\Console\\Internal.hsc" #-}
        ((\hsc_ptr -> pokeByteOff hsc_ptr 4)) buf (dwCursorPosition info)
{-# LINE 90 "libraries\\Win32\\System\\Win32\\Console\\Internal.hsc" #-}
        ((\hsc_ptr -> pokeByteOff hsc_ptr 8)) buf (wAttributes info)
{-# LINE 91 "libraries\\Win32\\System\\Win32\\Console\\Internal.hsc" #-}
        ((\hsc_ptr -> pokeByteOff hsc_ptr 10)) buf (srWindow info)
{-# LINE 92 "libraries\\Win32\\System\\Win32\\Console\\Internal.hsc" #-}
        ((\hsc_ptr -> pokeByteOff hsc_ptr 18)) buf (dwMaximumWindowSize info)
{-# LINE 93 "libraries\\Win32\\System\\Win32\\Console\\Internal.hsc" #-}

data CONSOLE_SCREEN_BUFFER_INFOEX = CONSOLE_SCREEN_BUFFER_INFOEX
    { dwSizeEx              :: COORD
    , dwCursorPositionEx    :: COORD
    , wAttributesEx         :: WORD
    , srWindowEx            :: SMALL_RECT
    , dwMaximumWindowSizeEx :: COORD
    , wPopupAttributes      :: WORD
    , bFullscreenSupported  :: BOOL
    , colorTable            :: [COLORREF]
      -- ^ Only the first 16 'COLORREF' values passed to the Windows Console

      -- API. If fewer than 16 values, the remainder are padded with @0@ when

      -- passed to the API.

    } deriving (Show, Eq)

instance Storable CONSOLE_SCREEN_BUFFER_INFOEX where
    sizeOf = const (96)
{-# LINE 110 "libraries\\Win32\\System\\Win32\\Console\\Internal.hsc" #-}
    alignment = const 4
{-# LINE 111 "libraries\\Win32\\System\\Win32\\Console\\Internal.hsc" #-}
    peek buf = do
        dwSize'               <- ((\hsc_ptr -> peekByteOff hsc_ptr 4)) buf
{-# LINE 113 "libraries\\Win32\\System\\Win32\\Console\\Internal.hsc" #-}
        dwCursorPosition'     <- ((\hsc_ptr -> peekByteOff hsc_ptr 8)) buf
{-# LINE 114 "libraries\\Win32\\System\\Win32\\Console\\Internal.hsc" #-}
        wAttributes'          <- ((\hsc_ptr -> peekByteOff hsc_ptr 12)) buf
{-# LINE 115 "libraries\\Win32\\System\\Win32\\Console\\Internal.hsc" #-}
        srWindow'             <- ((\hsc_ptr -> peekByteOff hsc_ptr 14)) buf
{-# LINE 116 "libraries\\Win32\\System\\Win32\\Console\\Internal.hsc" #-}
        dwMaximumWindowSize'  <- ((\hsc_ptr -> peekByteOff hsc_ptr 22)) buf
{-# LINE 117 "libraries\\Win32\\System\\Win32\\Console\\Internal.hsc" #-}
        wPopupAttributes'     <- ((\hsc_ptr -> peekByteOff hsc_ptr 26)) buf
{-# LINE 118 "libraries\\Win32\\System\\Win32\\Console\\Internal.hsc" #-}
        bFullscreenSupported' <- ((\hsc_ptr -> peekByteOff hsc_ptr 28)) buf
{-# LINE 119 "libraries\\Win32\\System\\Win32\\Console\\Internal.hsc" #-}
        colorTable'           <- peekArray 16 (((\hsc_ptr -> hsc_ptr `plusPtr` 32)) buf)
{-# LINE 120 "libraries\\Win32\\System\\Win32\\Console\\Internal.hsc" #-}
        return $ CONSOLE_SCREEN_BUFFER_INFOEX dwSize' dwCursorPosition'
          wAttributes' srWindow' dwMaximumWindowSize' wPopupAttributes'
          bFullscreenSupported' colorTable'
    poke buf info = do
        ((\hsc_ptr -> pokeByteOff hsc_ptr 0)) buf cbSize
{-# LINE 125 "libraries\\Win32\\System\\Win32\\Console\\Internal.hsc" #-}
        ((\hsc_ptr -> pokeByteOff hsc_ptr 4)) buf (dwSizeEx info)
{-# LINE 126 "libraries\\Win32\\System\\Win32\\Console\\Internal.hsc" #-}
        ((\hsc_ptr -> pokeByteOff hsc_ptr 8)) buf (dwCursorPositionEx info)
{-# LINE 127 "libraries\\Win32\\System\\Win32\\Console\\Internal.hsc" #-}
        ((\hsc_ptr -> pokeByteOff hsc_ptr 12)) buf (wAttributesEx info)
{-# LINE 128 "libraries\\Win32\\System\\Win32\\Console\\Internal.hsc" #-}
        ((\hsc_ptr -> pokeByteOff hsc_ptr 14)) buf (srWindowEx info)
{-# LINE 129 "libraries\\Win32\\System\\Win32\\Console\\Internal.hsc" #-}
        ((\hsc_ptr -> pokeByteOff hsc_ptr 22)) buf (dwMaximumWindowSizeEx info)
{-# LINE 130 "libraries\\Win32\\System\\Win32\\Console\\Internal.hsc" #-}
        ((\hsc_ptr -> pokeByteOff hsc_ptr 26)) buf (wPopupAttributes info)
{-# LINE 131 "libraries\\Win32\\System\\Win32\\Console\\Internal.hsc" #-}
        ((\hsc_ptr -> pokeByteOff hsc_ptr 28)) buf (bFullscreenSupported info)
{-# LINE 132 "libraries\\Win32\\System\\Win32\\Console\\Internal.hsc" #-}
        pokeArray (((\hsc_ptr -> hsc_ptr `plusPtr` 32)) buf) colorTable'
{-# LINE 133 "libraries\\Win32\\System\\Win32\\Console\\Internal.hsc" #-}
      where
        cbSize :: ULONG
        cbSize = (96)
{-# LINE 136 "libraries\\Win32\\System\\Win32\\Console\\Internal.hsc" #-}
        colorTable' = take 16 $ colorTable info ++ repeat 0

data COORD = COORD
    { xPos :: SHORT
    , yPos :: SHORT
    } deriving (Show, Eq)

instance Storable COORD where
    sizeOf = const (4)
{-# LINE 145 "libraries\\Win32\\System\\Win32\\Console\\Internal.hsc" #-}
    alignment _ = 2
{-# LINE 146 "libraries\\Win32\\System\\Win32\\Console\\Internal.hsc" #-}
    peek buf = do
        x' <- ((\hsc_ptr -> peekByteOff hsc_ptr 0)) buf
{-# LINE 148 "libraries\\Win32\\System\\Win32\\Console\\Internal.hsc" #-}
        y' <- ((\hsc_ptr -> peekByteOff hsc_ptr 2)) buf
{-# LINE 149 "libraries\\Win32\\System\\Win32\\Console\\Internal.hsc" #-}
        return $ COORD x' y'
    poke buf coord = do
        ((\hsc_ptr -> pokeByteOff hsc_ptr 0)) buf (xPos coord)
{-# LINE 152 "libraries\\Win32\\System\\Win32\\Console\\Internal.hsc" #-}
        ((\hsc_ptr -> pokeByteOff hsc_ptr 2)) buf (yPos coord)
{-# LINE 153 "libraries\\Win32\\System\\Win32\\Console\\Internal.hsc" #-}

data SMALL_RECT = SMALL_RECT
    { leftPos   :: SHORT
    , topPos    :: SHORT
    , rightPos  :: SHORT
    , bottomPos :: SHORT
    } deriving (Show, Eq)

instance Storable SMALL_RECT where
    sizeOf _ = (8)
{-# LINE 163 "libraries\\Win32\\System\\Win32\\Console\\Internal.hsc" #-}
    alignment _ = 2
{-# LINE 164 "libraries\\Win32\\System\\Win32\\Console\\Internal.hsc" #-}
    peek buf = do
        left'   <- ((\hsc_ptr -> peekByteOff hsc_ptr 0)) buf
{-# LINE 166 "libraries\\Win32\\System\\Win32\\Console\\Internal.hsc" #-}
        top'    <- ((\hsc_ptr -> peekByteOff hsc_ptr 2)) buf
{-# LINE 167 "libraries\\Win32\\System\\Win32\\Console\\Internal.hsc" #-}
        right'  <- ((\hsc_ptr -> peekByteOff hsc_ptr 4)) buf
{-# LINE 168 "libraries\\Win32\\System\\Win32\\Console\\Internal.hsc" #-}
        bottom' <- ((\hsc_ptr -> peekByteOff hsc_ptr 6)) buf
{-# LINE 169 "libraries\\Win32\\System\\Win32\\Console\\Internal.hsc" #-}
        return $ SMALL_RECT left' top' right' bottom'
    poke buf small_rect = do
        ((\hsc_ptr -> pokeByteOff hsc_ptr 0)) buf (leftPos small_rect)
{-# LINE 172 "libraries\\Win32\\System\\Win32\\Console\\Internal.hsc" #-}
        ((\hsc_ptr -> pokeByteOff hsc_ptr 2)) buf (topPos small_rect)
{-# LINE 173 "libraries\\Win32\\System\\Win32\\Console\\Internal.hsc" #-}
        ((\hsc_ptr -> pokeByteOff hsc_ptr 4)) buf (rightPos small_rect)
{-# LINE 174 "libraries\\Win32\\System\\Win32\\Console\\Internal.hsc" #-}
        ((\hsc_ptr -> pokeByteOff hsc_ptr 6)) buf (bottomPos small_rect)
{-# LINE 175 "libraries\\Win32\\System\\Win32\\Console\\Internal.hsc" #-}

foreign import WINDOWS_CCONV safe "windows.h GetConsoleScreenBufferInfo"
    c_GetConsoleScreenBufferInfo :: HANDLE -> Ptr CONSOLE_SCREEN_BUFFER_INFO -> IO BOOL

foreign import WINDOWS_CCONV safe "windows.h GetConsoleScreenBufferInfoEx"
    c_GetConsoleScreenBufferInfoEx :: HANDLE -> Ptr CONSOLE_SCREEN_BUFFER_INFOEX -> IO BOOL