terminal-size-0.3.4: Get terminal window height and width
Safe HaskellSafe-Inferred
LanguageHaskell2010

System.Console.Terminal.Size

Description

Get terminal window height and width without ncurses dependency

Based on answer by Andreas Hammar at http://stackoverflow.com/a/12807521/972985

Synopsis

Documentation

data Window a Source #

Terminal window width and height

Constructors

Window 

Fields

Instances

Instances details
Foldable Window Source # 
Instance details

Defined in System.Console.Terminal.Common

Methods

fold :: Monoid m => Window m -> m #

foldMap :: Monoid m => (a -> m) -> Window a -> m #

foldMap' :: Monoid m => (a -> m) -> Window a -> m #

foldr :: (a -> b -> b) -> b -> Window a -> b #

foldr' :: (a -> b -> b) -> b -> Window a -> b #

foldl :: (b -> a -> b) -> b -> Window a -> b #

foldl' :: (b -> a -> b) -> b -> Window a -> b #

foldr1 :: (a -> a -> a) -> Window a -> a #

foldl1 :: (a -> a -> a) -> Window a -> a #

toList :: Window a -> [a] #

null :: Window a -> Bool #

length :: Window a -> Int #

elem :: Eq a => a -> Window a -> Bool #

maximum :: Ord a => Window a -> a #

minimum :: Ord a => Window a -> a #

sum :: Num a => Window a -> a #

product :: Num a => Window a -> a #

Traversable Window Source # 
Instance details

Defined in System.Console.Terminal.Common

Methods

traverse :: Applicative f => (a -> f b) -> Window a -> f (Window b) #

sequenceA :: Applicative f => Window (f a) -> f (Window a) #

mapM :: Monad m => (a -> m b) -> Window a -> m (Window b) #

sequence :: Monad m => Window (m a) -> m (Window a) #

Functor Window Source # 
Instance details

Defined in System.Console.Terminal.Common

Methods

fmap :: (a -> b) -> Window a -> Window b #

(<$) :: a -> Window b -> Window a #

Generic1 Window Source # 
Instance details

Defined in System.Console.Terminal.Common

Associated Types

type Rep1 Window :: k -> Type #

Methods

from1 :: forall (a :: k). Window a -> Rep1 Window a #

to1 :: forall (a :: k). Rep1 Window a -> Window a #

Data a => Data (Window a) Source # 
Instance details

Defined in System.Console.Terminal.Common

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Window a -> c (Window a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Window a) #

toConstr :: Window a -> Constr #

dataTypeOf :: Window a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Window a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Window a)) #

gmapT :: (forall b. Data b => b -> b) -> Window a -> Window a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Window a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Window a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Window a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Window a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Window a -> m (Window a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Window a -> m (Window a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Window a -> m (Window a) #

Generic (Window a) Source # 
Instance details

Defined in System.Console.Terminal.Common

Associated Types

type Rep (Window a) :: Type -> Type #

Methods

from :: Window a -> Rep (Window a) x #

to :: Rep (Window a) x -> Window a #

Read a => Read (Window a) Source # 
Instance details

Defined in System.Console.Terminal.Common

Show a => Show (Window a) Source # 
Instance details

Defined in System.Console.Terminal.Common

Methods

showsPrec :: Int -> Window a -> ShowS #

show :: Window a -> String #

showList :: [Window a] -> ShowS #

Eq a => Eq (Window a) Source # 
Instance details

Defined in System.Console.Terminal.Common

Methods

(==) :: Window a -> Window a -> Bool #

(/=) :: Window a -> Window a -> Bool #

type Rep1 Window Source # 
Instance details

Defined in System.Console.Terminal.Common

type Rep1 Window = D1 ('MetaData "Window" "System.Console.Terminal.Common" "terminal-size-0.3.4-KESmCkrM9R1FZsTYT6AjQH" 'False) (C1 ('MetaCons "Window" 'PrefixI 'True) (S1 ('MetaSel ('Just "height") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) Par1 :*: S1 ('MetaSel ('Just "width") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) Par1))
type Rep (Window a) Source # 
Instance details

Defined in System.Console.Terminal.Common

type Rep (Window a) = D1 ('MetaData "Window" "System.Console.Terminal.Common" "terminal-size-0.3.4-KESmCkrM9R1FZsTYT6AjQH" 'False) (C1 ('MetaCons "Window" 'PrefixI 'True) (S1 ('MetaSel ('Just "height") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Just "width") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a)))

size :: Integral n => IO (Maybe (Window n)) Source #

Get terminal window width and height for stdout.

>>> import System.Console.Terminal.Size
>>> size
Just (Window {height = 60, width = 112})

fdSize :: Integral n => Fd -> IO (Maybe (Window n)) Source #

Not available on Windows: 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

hSize :: Integral n => Handle -> IO (Maybe (Window n)) Source #

Same as fdSize, but takes Handle instead of Fd (file descriptor).

Note that on Windows with shells that use the native console API (cmd.exe, PowerShell) this works only for output handles like stdout and stderr; for input handles like stdin it always returns Nothing.

>>> import System.Console.Terminal.Size
>>> import System.IO
>>> hSize stdout
Just (Window {height = 56, width = 85})