Search code examples
haskellconsolefunctional-programmingterminalioctl

Get Terminal width Haskell


How to get the width of the terminal in Haskell?

Things I tried

System.Posix.IOCtl (could not figure out how to get it to work) 

This only has to work unix.

Thanks


Solution

  • If you don't want a dependency on ncurses, here's a wrapper of the appropriate ioctl() request using the FFI, based on the accepted answer of Getting terminal width in C?

    TermSize.hsc

    {-# LANGUAGE ForeignFunctionInterface #-}
    
    module TermSize (getTermSize) where
    
    import Foreign
    import Foreign.C.Error
    import Foreign.C.Types
    
    #include <sys/ioctl.h>
    #include <unistd.h>
    
    -- Trick for calculating alignment of a type, taken from
    -- http://www.haskell.org/haskellwiki/FFICookBook#Working_with_structs
    #let alignment t = "%lu", (unsigned long)offsetof(struct {char x__; t (y__); }, y__)
    
    -- The ws_xpixel and ws_ypixel fields are unused, so I've omitted them here.
    data WinSize = WinSize { wsRow, wsCol :: CUShort }
    
    instance Storable WinSize where
      sizeOf _ = (#size struct winsize)
      alignment _ = (#alignment struct winsize) 
      peek ptr = do
        row <- (#peek struct winsize, ws_row) ptr
        col <- (#peek struct winsize, ws_col) ptr
        return $ WinSize row col
      poke ptr (WinSize row col) = do
        (#poke struct winsize, ws_row) ptr row
        (#poke struct winsize, ws_col) ptr col
    
    foreign import ccall "sys/ioctl.h ioctl"
      ioctl :: CInt -> CInt -> Ptr WinSize -> IO CInt
    
    -- | Return current number of (rows, columns) of the terminal.
    getTermSize :: IO (Int, Int)
    getTermSize = 
      with (WinSize 0 0) $ \ws -> do
        throwErrnoIfMinus1 "ioctl" $
          ioctl (#const STDOUT_FILENO) (#const TIOCGWINSZ) ws
        WinSize row col <- peek ws
        return (fromIntegral row, fromIntegral col)
    

    This uses the hsc2hs preprocessor to figure out the correct constants and offsets based on the C headers rather than hardcoding them. I think it's packaged with either GHC or the Haskell Platform, so chances are you'll have it already.

    If you're using Cabal, you can add TermSize.hs to your .cabal file and it'll automatically know how to generate it from TermSize.hsc. Otherwise, you can run hsc2hs TermSize.hsc manually to generate a .hs file which you can then compile with GHC.