effects-terminal
Safe HaskellNone
LanguageGHC2021

Effects.System.Terminal

Description

Provides the MonadTerminal typeclass.

Since: 0.1

Synopsis

Effect

class Monad m => MonadTerminal (m :: Type -> Type) where Source #

Represents a terminal.

Since: 0.1

Methods

putStr :: String -> m () Source #

Lifted putStr.

Since: 0.1

putStrLn :: String -> m () Source #

Lifted putStrLn.

Since: 0.1

putBinary :: ByteString -> m () Source #

Lifted putStr.

Since: 0.1

getChar :: m Char Source #

Lifted getChar.

Since: 0.1

getLine :: m String Source #

Lifted getLine.

Since: 0.1

getContents' :: m String Source #

Lifted getContents'.

Since: 0.1

getTerminalSize :: (HasCallStack, Integral a) => m (Window a) Source #

Retrieves the terminal size.

Since: 0.1

supportsPretty :: m Bool Source #

Lifted supportsPretty.

Since: 0.1

Functions

print :: (HasCallStack, MonadTerminal m, Show a) => a -> m () Source #

putStrLn and show.

Since: 0.1

Text

putText :: (HasCallStack, MonadTerminal m) => Text -> m () Source #

Text version of putStr.

Since: 0.1

putTextLn :: (HasCallStack, MonadTerminal m) => Text -> m () Source #

Text version of putStrLn.

Since: 0.1

getTextLine :: (HasCallStack, MonadTerminal m) => m Text Source #

Text version of getLine.

Since: 0.1

Window

getTerminalWidth :: (HasCallStack, Integral a, MonadTerminal m) => m a Source #

Retrieves the terminal width.

Since: 0.1

getTerminalHeight :: (HasCallStack, Integral a, MonadTerminal m) => m a Source #

Retrieves the terminal height.

Since: 0.1

Reexports

data Natural #

Natural number

Invariant: numbers <= 0xffffffffffffffff use the NS constructor

Instances

Instances details
PrintfArg Natural #

Since: base-4.8.0.0

Instance details

Defined in Text.Printf

NFData Natural #

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Natural -> () #

Enum Natural #

Since: base-4.8.0.0

Instance details

Defined in GHC.Internal.Enum

Num Natural #

Note that Natural's Num instance isn't a ring: no element but 0 has an additive inverse. It is a semiring though.

Since: base-4.8.0.0

Instance details

Defined in GHC.Internal.Num

Integral Natural #

Since: base-4.8.0.0

Instance details

Defined in GHC.Internal.Real

Real Natural #

Since: base-4.8.0.0

Instance details

Defined in GHC.Internal.Real

Show Natural #

Since: base-4.8.0.0

Instance details

Defined in GHC.Internal.Show

Eq Natural # 
Instance details

Defined in GHC.Num.Natural

Methods

(==) :: Natural -> Natural -> Bool #

(/=) :: Natural -> Natural -> Bool #

Ord Natural # 
Instance details

Defined in GHC.Num.Natural

KnownNat n => HasResolution (n :: Nat) #

For example, Fixed 1000 will give you a Fixed with a resolution of 1000.

Instance details

Defined in Data.Fixed

Methods

resolution :: p n -> Integer #

data Window a Source #

Terminal window width and height

Constructors

Window 

Fields

Instances

Instances details
Functor Window Source # 
Instance details

Defined in System.Console.Terminal.Common

Methods

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

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

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) #

Generic1 Window Source # 
Instance details

Defined in System.Console.Terminal.Common

Associated Types

type Rep1 Window 
Instance details

Defined in System.Console.Terminal.Common

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

Methods

from1 :: Window a -> Rep1 Window a #

to1 :: 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) 
Instance details

Defined in System.Console.Terminal.Common

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

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-3o6aIqERJTyEjqQfSsqCbc" '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-3o6aIqERJTyEjqQfSsqCbc" 'False) (C1 ('MetaCons "Window" 'PrefixI 'True) (S1 ('MetaSel ('Just "height") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Just "width") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a)))

data Text #

A space efficient, packed, unboxed Unicode text type.

Instances

Instances details
Pretty Text Source #

Instance of Pretty for Text

Instance details

Defined in System.Console.Pretty

type Item Text # 
Instance details

Defined in Data.Text

type Item Text = Char