{-# LINE 1 "src/System/Console/Terminal/Size.hsc" #-}
{- |
{-# LINE 2 "src/System/Console/Terminal/Size.hsc" #-}
Get terminal window height and width without ncurses dependency

Only tested to work on GNU/Linux systems

Based on answer by Andreas Hammar at <http://stackoverflow.com/a/12807521/972985>
-}
module System.Console.Terminal.Size
  ( Window(..), size, fdSize, hSize
  ) where

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 23 "src/System/Console/Terminal/Size.hsc" #-}
import System.Posix.Types (Fd(Fd))


{-# LINE 26 "src/System/Console/Terminal/Size.hsc" #-}

{-# LINE 27 "src/System/Console/Terminal/Size.hsc" #-}



{-# LINE 30 "src/System/Console/Terminal/Size.hsc" #-}


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

instance Storable CWin where
  sizeOf _ = ((8))
{-# LINE 37 "src/System/Console/Terminal/Size.hsc" #-}
  alignment _ = (2)
{-# LINE 38 "src/System/Console/Terminal/Size.hsc" #-}
  peek ptr = do
    row <- ((\hsc_ptr -> peekByteOff hsc_ptr 0)) ptr
{-# LINE 40 "src/System/Console/Terminal/Size.hsc" #-}
    col <- ((\hsc_ptr -> peekByteOff hsc_ptr 2)) ptr
{-# LINE 41 "src/System/Console/Terminal/Size.hsc" #-}
    return $ CWin row col
  poke ptr (CWin row col) = do
    ((\hsc_ptr -> pokeByteOff hsc_ptr 0)) ptr row
{-# LINE 44 "src/System/Console/Terminal/Size.hsc" #-}
    ((\hsc_ptr -> pokeByteOff hsc_ptr 2)) ptr col
{-# LINE 45 "src/System/Console/Terminal/Size.hsc" #-}


-- | Terminal window width and height
data Window a = Window
  { height :: !a
  , width  :: !a
  } deriving (Show, Read)

instance Functor Window where
  fmap f (Window { height = h, width = w }) = Window { height = f h, width = f w }

-- | Get terminal window width and height for a specified file descriptor. If
-- it's not attached to a terminal then 'Nothing' is returned.
--
-- >>> import System.Console.Terminal.Size
-- >>> import System.Posix
-- >>> fdSize stdOutput
-- Just (Window {height = 56, width = 85})
-- >>> fd <- openFd "foo" ReadWrite (Just stdFileMode) defaultFileFlags
-- >>> fdSize fd
-- Nothing
fdSize :: Integral n => Fd -> IO (Maybe (Window n))
fdSize (Fd fd) = with (CWin 0 0) $ \ws -> do
  throwErrnoIfMinus1 "ioctl" $
    ioctl fd (21523) ws
{-# LINE 70 "src/System/Console/Terminal/Size.hsc" #-}
  CWin row col <- peek ws
  return . Just $ Window (fromIntegral row) (fromIntegral col)
 `catch`
  handler
 where
  handler :: IOError -> IO (Maybe (Window h))
  handler _ = return Nothing

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

-- | Get terminal window width and height for @stdout@.
--
-- >>> import System.Console.Terminal.Size
-- >>> size
-- Just (Window {height = 60, width = 112})
size :: Integral n => IO (Maybe (Window n))
size = fdSize (Fd (1))
{-# LINE 88 "src/System/Console/Terminal/Size.hsc" #-}

-- | Same as 'fdSize', but takes 'Handle' instead of 'Fd' (file descriptor).
--
-- >>> import System.Console.Terminal.Size
-- >>> import System.IO
-- >>> hSize stdout
-- Just (Window {height = 56, width = 85})
hSize :: Integral n => Handle -> IO (Maybe (Window n))
hSize h = withHandle_ "hSize" h $ \Handle__ { haDevice = dev } ->
  case cast dev of
    Nothing -> return Nothing
    Just FD { fdFD = fd } -> fdSize (Fd fd)