-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Haskell bindings to the terminfo library. -- -- This library provides an interface to the terminfo database (via -- bindings to the curses library). Terminfo allows POSIX systems -- to interact with a variety of terminals using a standard set of -- capabilities. @package terminfo @version 0.4.1.5 -- | This module provides a low-level interface to the C functions of the -- terminfo library. -- -- NOTE: Since this library is built on top of the curses interface, it -- is not thread-safe. module System.Console.Terminfo.Base data Terminal -- | Initialize the terminfo library to the given terminal entry. -- -- Throws a SetupTermError if the terminfo database could not be -- read. -- --
-- >>> "Hello world" <> mempty -- "Hello world" --mempty :: Monoid a => a -- | An associative operation -- -- NOTE: This method is redundant and has the default -- implementation mappend = (<>) since -- base-4.11.0.0. Should it be implemented manually, since -- mappend is a synonym for (<>), it is expected that -- the two functions are defined the same way. In a future GHC release -- mappend will be removed from Monoid. mappend :: Monoid a => a -> a -> a -- | Fold a list using the monoid. -- -- For most types, the default definition for mconcat will be -- used, but the function is included in the class definition so that an -- optimized version can be provided for specific types. -- --
-- >>> mconcat ["Hello", " ", "Haskell", "!"] -- "Hello Haskell!" --mconcat :: Monoid a => [a] -> a -- | An operator version of mappend. (<#>) :: Monoid m => m -> m -> m infixl 2 <#> instance System.Console.Terminfo.Base.TermStr [GHC.Types.Char] instance System.Console.Terminfo.Base.TermStr System.Console.Terminfo.Base.TermOutput instance System.Console.Terminfo.Base.OutputCap [GHC.Types.Char] instance System.Console.Terminfo.Base.OutputCap System.Console.Terminfo.Base.TermOutput instance (GHC.Enum.Enum p, System.Console.Terminfo.Base.OutputCap f) => System.Console.Terminfo.Base.OutputCap (p -> f) instance GHC.Base.Semigroup System.Console.Terminfo.Base.TermOutput instance GHC.Base.Monoid System.Console.Terminfo.Base.TermOutput instance GHC.Base.Functor System.Console.Terminfo.Base.Capability instance GHC.Base.Applicative System.Console.Terminfo.Base.Capability instance GHC.Base.Monad System.Console.Terminfo.Base.Capability instance GHC.Base.Alternative System.Console.Terminfo.Base.Capability instance GHC.Base.MonadPlus System.Console.Terminfo.Base.Capability instance GHC.Show.Show System.Console.Terminfo.Base.SetupTermError instance GHC.Exception.Type.Exception System.Console.Terminfo.Base.SetupTermError module System.Console.Terminfo.Color -- | The maximum number of of colors on the screen. termColors :: Capability Int data Color Black :: Color Red :: Color Green :: Color Yellow :: Color Blue :: Color Magenta :: Color Cyan :: Color White :: Color ColorNumber :: Int -> Color -- | This capability temporarily sets the terminal's foreground color while -- outputting the given text, and then restores the terminal to its -- default foreground and background colors. withForegroundColor :: TermStr s => Capability (Color -> s -> s) -- | This capability temporarily sets the terminal's background color while -- outputting the given text, and then restores the terminal to its -- default foreground and background colors. withBackgroundColor :: TermStr s => Capability (Color -> s -> s) -- | Sets the foreground color of all further text output, using either the -- setaf or setf capability. setForegroundColor :: TermStr s => Capability (Color -> s) -- | Sets the background color of all further text output, using either the -- setab or setb capability. setBackgroundColor :: TermStr s => Capability (Color -> s) -- | Restores foreground/background colors to their original settings. restoreDefaultColors :: TermStr s => Capability s instance GHC.Classes.Ord System.Console.Terminfo.Color.Color instance GHC.Classes.Eq System.Console.Terminfo.Color.Color instance GHC.Show.Show System.Console.Terminfo.Color.Color -- | This module provides capabilities for moving the cursor on the -- terminal. module System.Console.Terminfo.Cursor termLines :: Capability Int termColumns :: Capability Int -- | This flag specifies that the cursor wraps automatically from the last -- column of one line to the first column of the next. autoRightMargin :: Capability Bool -- | This flag specifies that a backspace at column 0 wraps the cursor to -- the last column of the previous line. autoLeftMargin :: Capability Bool -- | This flag specifies that the terminal does not perform -- autoRightMargin-style wrapping when the character which would -- cause the wraparound is a control character. This is also known as the -- "newline glitch" or "magic wrap". -- -- For example, in an 80-column terminal with this behavior, the -- following will print single-spaced instead of double-spaced: -- --
-- replicateM_ 5 $ putStr $ replicate 80 'x' ++ "\n" --wraparoundGlitch :: Capability Bool -- | The cr capability, which moves the cursor to the first column -- of the current line. carriageReturn :: TermStr s => Capability s -- | The nel capability, which moves the cursor to the first -- column of the next line. It behaves like a carriage return followed by -- a line feed. -- -- If nel is not defined, this may be built out of other -- capabilities. newline :: TermStr s => Capability s scrollForward :: TermStr s => Capability s scrollReverse :: TermStr s => Capability s moveDown :: TermStr s => Capability (Int -> s) moveLeft :: TermStr s => Capability (Int -> s) moveRight :: TermStr s => Capability (Int -> s) moveUp :: TermStr s => Capability (Int -> s) cursorDown1 :: TermStr s => Capability s cursorLeft1 :: TermStr s => Capability s cursorRight1 :: TermStr s => Capability s cursorUp1 :: TermStr s => Capability s cursorDown :: TermStr s => Capability (Int -> s) cursorLeft :: TermStr s => Capability (Int -> s) cursorRight :: TermStr s => Capability (Int -> s) cursorUp :: TermStr s => Capability (Int -> s) cursorHome :: TermStr s => Capability s cursorToLL :: TermStr s => Capability s cursorAddress :: TermStr s => Capability (Point -> s) data Point Point :: Int -> Point [row, col] :: Point -> Int rowAddress :: TermStr s => Capability (Int -> s) columnAddress :: TermStr s => Capability (Int -> s) module System.Console.Terminfo.Edit -- | Clear the screen, and move the cursor to the upper left. clearScreen :: Capability (LinesAffected -> TermOutput) -- | Clear from beginning of line to cursor. clearBOL :: TermStr s => Capability s -- | Clear from cursor to end of line. clearEOL :: TermStr s => Capability s -- | Clear display after cursor. clearEOS :: Capability (LinesAffected -> TermOutput) module System.Console.Terminfo.Effects -- | Sound the audible bell. bell :: TermStr s => Capability s -- | Present a visual alert using the flash capability. visualBell :: Capability TermOutput data Attributes Attributes :: Bool -> Attributes [standoutAttr, underlineAttr, reverseAttr, blinkAttr, dimAttr, boldAttr, invisibleAttr, protectedAttr] :: Attributes -> Bool -- | These attributes have all properties turned off. defaultAttributes :: Attributes -- | Sets the attributes on or off before outputting the given text, and -- then turns them all off. This capability will always succeed; -- properties which cannot be set in the current terminal will be -- ignored. withAttributes :: TermStr s => Capability (Attributes -> s -> s) -- | Sets the attributes on or off. This capability will always succeed; -- properties which cannot be set in the current terminal will be -- ignored. setAttributes :: TermStr s => Capability (Attributes -> s) -- | Turns off all text attributes. This capability will always succeed, -- but it has no effect in terminals which do not support text -- attributes. allAttributesOff :: TermStr s => Capability s -- | Turns on standout mode before outputting the given text, and then -- turns it off. withStandout :: TermStr s => Capability (s -> s) -- | Turns on underline mode before outputting the given text, and then -- turns it off. withUnderline :: TermStr s => Capability (s -> s) -- | Turns on bold mode before outputting the given text, and then turns -- all attributes off. withBold :: TermStr s => Capability (s -> s) enterStandoutMode :: TermStr s => Capability s exitStandoutMode :: TermStr s => Capability s enterUnderlineMode :: TermStr s => Capability s exitUnderlineMode :: TermStr s => Capability s reverseOn :: TermStr s => Capability s blinkOn :: TermStr s => Capability s boldOn :: TermStr s => Capability s dimOn :: TermStr s => Capability s invisibleOn :: TermStr s => Capability s protectedOn :: TermStr s => Capability s -- | The string capabilities in this module are the character sequences -- corresponding to user input such as arrow keys and function keys. module System.Console.Terminfo.Keys keypadOn :: TermStr s => Capability s keypadOff :: TermStr s => Capability s keyUp :: Capability String keyDown :: Capability String keyLeft :: Capability String keyRight :: Capability String -- | Look up the control sequence for a given function sequence. For -- example, functionKey 12 retrieves the kf12 -- capability. functionKey :: Int -> Capability String keyBackspace :: Capability String keyDeleteChar :: Capability String keyHome :: Capability String keyEnd :: Capability String keyPageUp :: Capability String keyPageDown :: Capability String keyEnter :: Capability String module System.Console.Terminfo