Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Get terminal window height and width without ncurses dependency
Based on answer by Andreas Hammar at http://stackoverflow.com/a/12807521/972985
Documentation
Terminal window width and height
Instances
Foldable Window Source # | |
Defined in System.Console.Terminal.Common 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 # elem :: Eq a => a -> Window a -> Bool # maximum :: Ord a => Window a -> a # minimum :: Ord a => Window a -> a # | |
Traversable Window Source # | |
Functor Window Source # | |
Generic1 Window Source # | |
Data a => Data (Window a) Source # | |
Defined in System.Console.Terminal.Common 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 # | |
Read a => Read (Window a) Source # | |
Show a => Show (Window a) Source # | |
Eq a => Eq (Window a) Source # | |
type Rep1 Window Source # | |
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 # | |
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})