hscurses
Safe HaskellNone
LanguageHaskell2010

UI.HSCurses.Curses

Description

Binding to the [wn]curses library. From the ncurses man page:

     The curses library routines give the user a terminal-inde-
     pendent method of updating character screens with  reason-
     able  optimization.

Sections of the quoted documentation are from the OpenBSD man pages, which are distributed under a BSD license.

A useful reference is: Writing Programs with NCURSES, by Eric S. Raymond and Zeyd M. Ben-Halim, http://dickey.his.com/ncurses/

N.B attrs don't work with Irix curses.h. This should be fixed.

Synopsis

Documentation

stdScr :: Window Source #

The standard screen

initScr :: IO Window Source #

initScr is normally the first curses routine to call when initializing a program. curs_initscr(3):

To initialize the routines, the routine initscr or newterm must be called
before any of the other routines that deal with windows and screens are
used.

The initscr code determines the terminal type and initial- izes all curses
data structures. initscr also causes the first call to refresh to clear the
screen. If errors occur, initscr writes an appropriate error message to
standard error and exits; otherwise, a pointer is returned to stdscr.

initCurses :: IO () Source #

initCurses does all initialization necessary for a Curses application.

endWin :: IO () Source #

 The program must call endwin for each terminal being used before
 exiting from curses.

scrSize :: IO (Int, Int) Source #

Get the dimensions of the screen (lines, cols).

newTerm :: String -> FD -> FD -> IO Screen Source #

A program that outputs to more than one terminal should use the newTerm routine for each terminal instead of initScr. A program that needs to inspect capabilities, so it can continue to run in a line-oriented mode if the terminal cannot support a screen-oriented program, would also use newTerm. curs_initscr(3X):

   The routine newterm should be called once for each terminal. It returns
   a variable of type SCREEN * which should be saved as a reference to that
   terminal. newterm's arguments are

   - the type of the terminal to be used in place of $TERM,

   - an output stream connected to the terminal, and

   - an input stream connected to the terminal

   If the type parameter is NULL, $TERM will be used.

type Screen = Ptr () Source #

type Window = Ptr WindowTag Source #

data Border Source #

Constructors

Border 

Fields

pRefresh :: Window -> Int -> Int -> Int -> Int -> Int -> Int -> IO () Source #

newWin :: Int -> Int -> Int -> Int -> IO Window Source #

wRefresh :: Window -> IO () Source #

Refresh the specified window, copying the data from the virtual screen to the physical screen.

wnoutRefresh :: Window -> IO () Source #

Stage an update to a window, but don't actually do the refresh until update is called. This allows multiple windows to be updated together more smoothly.

wBorder :: Window -> Border -> IO () Source #

Draw a border around the edges of a window. defaultBorder is a record representing all 0 parameters to wrecord.

refresh :: IO () Source #

Refresh curses windows and lines. curs_refresh(3)

update :: IO () Source #

Do an actual update. Used after endWin on linux to restore the terminal.

timeout :: Int -> IO () Source #

Set a delay in milliseconds.

move :: Int -> Int -> IO () Source #

move the cursor associated with the window to line y and column x. This
routine does not move the physical cursor of the terminal until refresh
is called. The position specified is relative to the upper left-hand
corner of the window, which is (0,0).

Note that move_c may be a macro.

getYX :: Window -> IO (Int, Int) Source #

Get the current cursor coordinates.

getCh :: IO Key Source #

Read a single character from the window.

getch :: IO CInt Source #

     The getch, wgetch, mvgetch and mvwgetch, routines read a
     character  from the window.

ungetCh :: Integral a => a -> IO () Source #

Input Options

cBreak :: Bool -> IO () Source #

The cbreak routine disables line buffering and erase/kill
character-processing (interrupt and flow control characters are
unaffected), making characters typed by the user immediately available to
the program. The nocbreak routine returns the terminal to normal (cooked)
mode.

raw :: Bool -> IO () Source #

The raw and noraw routines place the terminal into or out of raw mode.
Raw mode is similar to cbreak mode, in that characters typed are
immediately passed through to the user program. The differences are that
in raw mode, the interrupt, quit, suspend, and flow control characters
are all passed through uninterpreted, instead of generating a signal. The
behavior of the BREAK key depends on other bits in the tty driver that
are not set by curses.

echo :: Bool -> IO () Source #

The echo and noecho routines control whether characters typed by the user
are echoed by getch as they are typed. Echoing by the tty driver is
always disabled, but ini- tially getch is in echo mode, so characters
typed are echoed. Authors of most interactive programs prefer to do their
own echoing in a controlled area of the screen, or not to echo at all, so
they disable echoing by calling noecho. [See curs_getch(3) for a
discussion of how these routines interact with cbreak and nocbreak.]

intrFlush :: Bool -> IO () Source #

If the intrflush option is enabled, (bf is TRUE), when an interrupt key
is pressed on the keyboard (interrupt, break, quit) all output in the tty
driver queue will be flushed, giving the effect of faster response to the
interrupt, but causing curses to have the wrong idea of what is on the
screen. Disabling (bf is FALSE), the option prevents the flush.

keypad :: Window -> Bool -> IO () Source #

Enable the keypad of the user's terminal.

Output

mvWAddStr :: Window -> Int -> Int -> String -> IO () Source #

mvAddCh :: Int -> Int -> ChType -> IO () Source #

wMove :: Window -> Int -> Int -> IO () Source #

   move the cursor associated with the window
   to line y and column x.  This routine does  not  move  the
   physical  cursor  of the terminal until refresh is called.
   The position specified is relative to the upper  left-hand
   corner of the window, which is (0,0).

erase :: IO () Source #

Copy blanks to every position in the screen.

wclear :: Window -> IO () Source #

Copy blanks to a window and set clearOk for that window.

werase :: Window -> IO () Source #

Copy blanks to every position in a window.

beep :: IO () Source #

waddch :: Window -> ChType -> IO CInt Source #

Raw NCurses routine.

winsch :: Window -> ChType -> IO CInt Source #

Raw NCurses routine.

waddchnstr :: Window -> CString -> CInt -> IO CInt Source #

Raw NCurses routine.

Output Options

leaveOk :: Bool -> IO CInt Source #

Normally, the hardware cursor is left at the location of the window cursor being refreshed. The leaveok option allows the cursor to be left wherever the update happens to leave it. It is useful for applications where the cursor is not used, since it reduces the need for cursor motions. If possible, the cursor is made invisible when this option is enabled.

nl :: Bool -> IO () Source #

The nl and nonl routines control whether the underlying display device
translates the return key into newline on input, and whether it
translates newline into return and line-feed on output (in either case,
the call addch('\n') does the equivalent of return and line feed on the
virtual screen). Initially, these translations do occur. If you disable
them using nonl, curses will be able to make bet- ter use of the
line-feed capability, resulting in faster cursor motion. Also, curses
will then be able to detect the return key.

Cursor Routines

cursSet :: CursorVisibility -> IO CursorVisibility Source #

Set the cursor state.

The curs_set routine sets the cursor state is set to invisible, normal, or
very visible for visibility equal to 0, 1, or 2 respectively. If the
terminal supports the visibility requested, the previous cursor state is
returned; otherwise, ERR is returned.

Color Support

startColor :: IO () Source #

Initialise the color settings. Also sets the screen to the default colors (white on black).

newtype Pair Source #

Constructors

Pair Int 

Instances

Instances details
Ix Pair Source # 
Instance details

Defined in UI.HSCurses.Curses

Methods

range :: (Pair, Pair) -> [Pair] #

index :: (Pair, Pair) -> Pair -> Int #

unsafeIndex :: (Pair, Pair) -> Pair -> Int #

inRange :: (Pair, Pair) -> Pair -> Bool #

rangeSize :: (Pair, Pair) -> Int #

unsafeRangeSize :: (Pair, Pair) -> Int #

Show Pair Source # 
Instance details

Defined in UI.HSCurses.Curses

Methods

showsPrec :: Int -> Pair -> ShowS #

show :: Pair -> String #

showList :: [Pair] -> ShowS #

Eq Pair Source # 
Instance details

Defined in UI.HSCurses.Curses

Methods

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

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

Ord Pair Source # 
Instance details

Defined in UI.HSCurses.Curses

Methods

compare :: Pair -> Pair -> Ordering #

(<) :: Pair -> Pair -> Bool #

(<=) :: Pair -> Pair -> Bool #

(>) :: Pair -> Pair -> Bool #

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

max :: Pair -> Pair -> Pair #

min :: Pair -> Pair -> Pair #

colorPairs :: IO Int Source #

Defines the maximum number of color-pairs the terminal can support).

newtype Color Source #

Constructors

Color Int 

Instances

Instances details
Ix Color Source # 
Instance details

Defined in UI.HSCurses.Curses

Eq Color Source # 
Instance details

Defined in UI.HSCurses.Curses

Methods

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

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

Ord Color Source # 
Instance details

Defined in UI.HSCurses.Curses

Methods

compare :: Color -> Color -> Ordering #

(<) :: Color -> Color -> Bool #

(<=) :: Color -> Color -> Bool #

(>) :: Color -> Color -> Bool #

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

max :: Color -> Color -> Color #

min :: Color -> Color -> Color #

initPair :: Pair -> Color -> Color -> IO () Source #

curses support color attributes on terminals with that capability. To use these routines start_color must be called, usually right after initscr. Colors are always used in pairs (referred to as color-pairs). A color-pair consists of a foreground color (for characters) and a background color (for the blank field on which the charac- ters are displayed). A programmer initializes a color- pair with the routine init_pair. After it has been ini- tialized, COLOR_PAIR(n), a macro defined in curses.h, can be used as a new video attribute.

If a terminal is capable of redefining colors, the pro- grammer can use the routine init_color to change the defi- nition of a color.

The init_pair routine changes the definition of a color- pair. It takes three arguments: the number of the color- pair to be changed, the foreground color number, and the background color number. For portable applications:

  • The value of the first argument must be between 1 and COLOR_PAIRS-1.
  • The value of the second and third arguments must be between 0 and COLORS (the 0 color pair is wired to white on black and cannot be changed).

initColor :: Color -> (Int, Int, Int) -> IO () Source #

Attributes

data Attr Source #

Instances

Instances details
Bits Attr Source # 
Instance details

Defined in UI.HSCurses.Curses

Storable Attr Source # 
Instance details

Defined in UI.HSCurses.Curses

Methods

sizeOf :: Attr -> Int #

alignment :: Attr -> Int #

peekElemOff :: Ptr Attr -> Int -> IO Attr #

pokeElemOff :: Ptr Attr -> Int -> Attr -> IO () #

peekByteOff :: Ptr b -> Int -> IO Attr #

pokeByteOff :: Ptr b -> Int -> Attr -> IO () #

peek :: Ptr Attr -> IO Attr #

poke :: Ptr Attr -> Attr -> IO () #

Num Attr Source # 
Instance details

Defined in UI.HSCurses.Curses

Methods

(+) :: Attr -> Attr -> Attr #

(-) :: Attr -> Attr -> Attr #

(*) :: Attr -> Attr -> Attr #

negate :: Attr -> Attr #

abs :: Attr -> Attr #

signum :: Attr -> Attr #

fromInteger :: Integer -> Attr #

Show Attr Source # 
Instance details

Defined in UI.HSCurses.Curses

Methods

showsPrec :: Int -> Attr -> ShowS #

show :: Attr -> String #

showList :: [Attr] -> ShowS #

Eq Attr Source # 
Instance details

Defined in UI.HSCurses.Curses

Methods

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

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

attr0 :: Attr Source #

Normal display (no highlight)

attrSet :: Attr -> Pair -> IO () Source #

attrOn :: Attr -> IO () Source #

wAttrOn :: Window -> Int -> IO () Source #

wAttrSet :: Window -> (Attr, Pair) -> IO () Source #

wAttrGet :: Window -> IO (Attr, Pair) Source #

Manipulate the current attributes of the named window. see curs_attr(3)

Mouse Routines

withAllMouseEvents :: MonadIO m => m a -> m a Source #

Keys

Lines

vline :: Char -> Int -> IO () Source #

Signals

cursesSigWinch :: Maybe Signal Source #

The SIGWINCH signal is sent whenever the terminal size changes. This signal is not available on all platforms, so it is a |Maybe| value.

Misc

cursesTest :: IO () Source #

A test case printing out some common attributes.

throwIfErr :: (Eq a, Show a, Num a) => String -> IO a -> IO a Source #

throwIfErr_ :: (Eq a, Show a, Num a) => String -> IO a -> IO () Source #

errI :: IO CInt -> IO () Source #

recognize :: Char -> IO a -> (ChType -> IO a) -> IO a Source #