{-# LINE 1 "src/unix/System/Terminal.hsc" #-}
{-# LANGUAGE ForeignFunctionInterface #-}
module System.Terminal
( fixCodePage
, getTerminalWidth
, hIsTerminalDeviceOrMinTTY
) where

import           Foreign
import           Foreign.C.Types
import           RIO (MonadIO, Handle, hIsTerminalDevice)





newtype WindowWidth = WindowWidth CUShort
    deriving (Eq, Ord, Show)

instance Storable WindowWidth where
  sizeOf _ = ((8))
{-# LINE 21 "src/unix/System/Terminal.hsc" #-}
  alignment _ = (2)
{-# LINE 22 "src/unix/System/Terminal.hsc" #-}
  peek p = WindowWidth <$> ((\hsc_ptr -> peekByteOff hsc_ptr 2)) p
{-# LINE 23 "src/unix/System/Terminal.hsc" #-}
  poke p (WindowWidth w) = do
    ((\hsc_ptr -> pokeByteOff hsc_ptr 2)) p w
{-# LINE 25 "src/unix/System/Terminal.hsc" #-}

foreign import ccall "sys/ioctl.h ioctl"
  ioctl :: CInt -> CInt -> Ptr WindowWidth -> IO CInt

getTerminalWidth :: IO (Maybe Int)
getTerminalWidth =
    alloca $ \p -> do
        errno <- ioctl (1) (21523) p
{-# LINE 33 "src/unix/System/Terminal.hsc" #-}
        if errno < 0
        then return Nothing
        else do
            WindowWidth w <- peek p
            return . Just . fromIntegral $ w

fixCodePage :: x -> y -> a -> a
fixCodePage _ _ = id

-- | hIsTerminaDevice does not recognise handles to mintty terminals as terminal
-- devices, but isMinTTYHandle does.
hIsTerminalDeviceOrMinTTY :: MonadIO m => Handle -> m Bool
hIsTerminalDeviceOrMinTTY = hIsTerminalDevice