{-# LINE 1 "lib/System/Console/Terminal/Posix.hsc" #-}
{-# LANGUAGE CApiFFI #-}

module System.Console.Terminal.Posix
  ( size, fdSize, hSize
  ) where

import System.Console.Terminal.Common
import Control.Exception (catch)
import Data.Typeable (cast)
import Foreign
import Foreign.C.Error
import Foreign.C.Types
import GHC.IO.FD (FD(FD, fdFD))
import GHC.IO.Handle.Internals (withHandle_)
import GHC.IO.Handle.Types (Handle, Handle__(Handle__, haDevice))

{-# LINE 19 "lib/System/Console/Terminal/Posix.hsc" #-}
import System.Posix.Types (Fd(Fd))








-- Interesting part of @struct winsize@
data CWin = CWin CUShort CUShort

instance Storable CWin where
  sizeOf :: CWin -> Int
sizeOf CWin
_ = ((Int
8))
{-# LINE 33 "lib/System/Console/Terminal/Posix.hsc" #-}
  alignment _ = (2)
{-# LINE 34 "lib/System/Console/Terminal/Posix.hsc" #-}
  peek ptr = do
    row <- ((\hsc_ptr -> peekByteOff hsc_ptr 0)) ptr
{-# LINE 36 "lib/System/Console/Terminal/Posix.hsc" #-}
    col <- ((\hsc_ptr -> peekByteOff hsc_ptr 2)) ptr
{-# LINE 37 "lib/System/Console/Terminal/Posix.hsc" #-}
    return $ CWin row col
  poke :: Ptr CWin -> CWin -> IO ()
poke Ptr CWin
ptr (CWin CUShort
row CUShort
col) = do
    ((\Ptr CWin
hsc_ptr -> Ptr CWin -> Int -> CUShort -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr CWin
hsc_ptr Int
0)) Ptr CWin
ptr CUShort
row
{-# LINE 40 "lib/System/Console/Terminal/Posix.hsc" #-}
    ((\hsc_ptr -> pokeByteOff hsc_ptr 2)) ptr col
{-# LINE 41 "lib/System/Console/Terminal/Posix.hsc" #-}


fdSize :: Integral n => Fd -> IO (Maybe (Window n))
fdSize :: Fd -> IO (Maybe (Window n))
fdSize (Fd CInt
fd) = CWin
-> (Ptr CWin -> IO (Maybe (Window n))) -> IO (Maybe (Window n))
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with (CUShort -> CUShort -> CWin
CWin CUShort
0 CUShort
0) ((Ptr CWin -> IO (Maybe (Window n))) -> IO (Maybe (Window n)))
-> (Ptr CWin -> IO (Maybe (Window n))) -> IO (Maybe (Window n))
forall a b. (a -> b) -> a -> b
$ \Ptr CWin
ws -> do
  CInt
_ <- String -> IO CInt -> IO CInt
forall a. (Eq a, Num a) => String -> IO a -> IO a
throwErrnoIfMinus1 String
"ioctl" (IO CInt -> IO CInt) -> IO CInt -> IO CInt
forall a b. (a -> b) -> a -> b
$
    CInt -> CULong -> Ptr CWin -> IO CInt
ioctl CInt
fd (CULong
21523) Ptr CWin
ws
{-# LINE 47 "lib/System/Console/Terminal/Posix.hsc" #-}
  CWin row col <- peek ws
  Maybe (Window n) -> IO (Maybe (Window n))
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe (Window n) -> IO (Maybe (Window n)))
-> (Window n -> Maybe (Window n))
-> Window n
-> IO (Maybe (Window n))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Window n -> Maybe (Window n)
forall a. a -> Maybe a
Just (Window n -> IO (Maybe (Window n)))
-> Window n -> IO (Maybe (Window n))
forall a b. (a -> b) -> a -> b
$ n -> n -> Window n
forall a. a -> a -> Window a
Window (CUShort -> n
forall a b. (Integral a, Num b) => a -> b
fromIntegral CUShort
row) (CUShort -> n
forall a b. (Integral a, Num b) => a -> b
fromIntegral CUShort
col)
 IO (Maybe (Window n))
-> (IOError -> IO (Maybe (Window n))) -> IO (Maybe (Window n))
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
`catch`
  IOError -> IO (Maybe (Window n))
forall h. IOError -> IO (Maybe (Window h))
handler
 where
  handler :: IOError -> IO (Maybe (Window h))
  handler :: IOError -> IO (Maybe (Window h))
handler IOError
_ = Maybe (Window h) -> IO (Maybe (Window h))
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe (Window h)
forall a. Maybe a
Nothing

foreign import capi "sys/ioctl.h ioctl"
  ioctl :: CInt -> CULong -> Ptr CWin -> IO CInt

size :: Integral n => IO (Maybe (Window n))
size :: IO (Maybe (Window n))
size = Fd -> IO (Maybe (Window n))
forall n. Integral n => Fd -> IO (Maybe (Window n))
fdSize (CInt -> Fd
Fd (CInt
1))
{-# LINE 60 "lib/System/Console/Terminal/Posix.hsc" #-}

hSize :: Integral n => Handle -> IO (Maybe (Window n))
hSize :: Handle -> IO (Maybe (Window n))
hSize Handle
h = String
-> Handle
-> (Handle__ -> IO (Maybe (Window n)))
-> IO (Maybe (Window n))
forall a. String -> Handle -> (Handle__ -> IO a) -> IO a
withHandle_ String
"hSize" Handle
h ((Handle__ -> IO (Maybe (Window n))) -> IO (Maybe (Window n)))
-> (Handle__ -> IO (Maybe (Window n))) -> IO (Maybe (Window n))
forall a b. (a -> b) -> a -> b
$ \Handle__ { haDevice :: ()
haDevice = dev
dev } ->
  case dev -> Maybe FD
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast dev
dev of
    Maybe FD
Nothing -> Maybe (Window n) -> IO (Maybe (Window n))
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe (Window n)
forall a. Maybe a
Nothing
    Just FD { fdFD :: FD -> CInt
fdFD = CInt
fd } -> Fd -> IO (Maybe (Window n))
forall n. Integral n => Fd -> IO (Maybe (Window n))
fdSize (CInt -> Fd
Fd CInt
fd)