Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
- stdScr :: Window
- initScr :: IO Window
- initCurses :: IO ()
- resetParams :: IO ()
- endWin :: IO ()
- scrSize :: IO (Int, Int)
- newTerm :: String -> FD -> FD -> IO Screen
- delScreen :: Screen -> IO ()
- type Screen = Ptr ()
- type Window = Ptr WindowTag
- data Border = Border {}
- touchWin :: Window -> IO ()
- newPad :: Int -> Int -> IO Window
- pRefresh :: Window -> Int -> Int -> Int -> Int -> Int -> Int -> IO ()
- delWin :: Window -> IO ()
- newWin :: Int -> Int -> Int -> Int -> IO Window
- wRefresh :: Window -> IO ()
- wnoutRefresh :: Window -> IO ()
- wBorder :: Window -> Border -> IO ()
- defaultBorder :: Border
- refresh :: IO ()
- update :: IO ()
- resizeTerminal :: Int -> Int -> IO ()
- timeout :: Int -> IO ()
- noqiflush :: IO ()
- move :: Int -> Int -> IO ()
- getYX :: Window -> IO (Int, Int)
- getCh :: IO Key
- getch :: IO CInt
- decodeKey :: CInt -> Key
- ungetCh :: Integral a => a -> IO ()
- keyResizeCode :: Maybe CInt
- cBreak :: Bool -> IO ()
- raw :: Bool -> IO ()
- echo :: Bool -> IO ()
- intrFlush :: Bool -> IO ()
- keypad :: Window -> Bool -> IO ()
- noDelay :: Window -> Bool -> IO ()
- wAddStr :: Window -> String -> IO ()
- addLn :: IO ()
- mvWAddStr :: Window -> Int -> Int -> String -> IO ()
- mvAddCh :: Int -> Int -> ChType -> IO ()
- wMove :: Window -> Int -> Int -> IO ()
- bkgrndSet :: Attr -> Pair -> IO ()
- erase :: IO ()
- wclear :: Window -> IO ()
- werase :: Window -> IO ()
- clrToEol :: IO ()
- wClrToEol :: Window -> IO ()
- beep :: IO ()
- waddch :: Window -> ChType -> IO CInt
- winsch :: Window -> ChType -> IO CInt
- waddchnstr :: Window -> CString -> CInt -> IO CInt
- clearOk :: Bool -> IO CInt
- leaveOk :: Bool -> IO CInt
- nl :: Bool -> IO ()
- data CursorVisibility
- cursSet :: CursorVisibility -> IO CursorVisibility
- hasColors :: IO Bool
- startColor :: IO ()
- useDefaultColors :: IO ()
- newtype Pair = Pair Int
- colorPairs :: IO Int
- newtype Color = Color Int
- colors :: IO Int
- color :: String -> Maybe Color
- initPair :: Pair -> Color -> Color -> IO ()
- pairContent :: Pair -> IO (Color, Color)
- canChangeColor :: IO Bool
- initColor :: Color -> (Int, Int, Int) -> IO ()
- colorContent :: Color -> IO (Int, Int, Int)
- defaultBackground :: Color
- defaultForeground :: Color
- attrPlus :: Attr -> Attr -> Attr
- data Attr
- attr0 :: Attr
- isAltCharset :: Attr -> Bool
- isBlink :: Attr -> Bool
- isBold :: Attr -> Bool
- isDim :: Attr -> Bool
- isHorizontal :: Attr -> Bool
- isInvis :: Attr -> Bool
- isLeft :: Attr -> Bool
- isLow :: Attr -> Bool
- isProtect :: Attr -> Bool
- isReverse :: Attr -> Bool
- isRight :: Attr -> Bool
- isStandout :: Attr -> Bool
- isTop :: Attr -> Bool
- isUnderline :: Attr -> Bool
- isVertical :: Attr -> Bool
- setAltCharset :: Attr -> Bool -> Attr
- setBlink :: Attr -> Bool -> Attr
- setBold :: Attr -> Bool -> Attr
- setDim :: Attr -> Bool -> Attr
- setHorizontal :: Attr -> Bool -> Attr
- setInvis :: Attr -> Bool -> Attr
- setLeft :: Attr -> Bool -> Attr
- setLow :: Attr -> Bool -> Attr
- setProtect :: Attr -> Bool -> Attr
- setReverse :: Attr -> Bool -> Attr
- setRight :: Attr -> Bool -> Attr
- setStandout :: Attr -> Bool -> Attr
- setTop :: Attr -> Bool -> Attr
- setUnderline :: Attr -> Bool -> Attr
- setVertical :: Attr -> Bool -> Attr
- attrSet :: Attr -> Pair -> IO ()
- attrOn :: Attr -> IO ()
- attrOff :: Attr -> IO ()
- standout :: IO Int
- standend :: IO Int
- attrDim :: Int
- attrBold :: Int
- attrDimOn :: IO ()
- attrDimOff :: IO ()
- attrBoldOn :: IO ()
- attrBoldOff :: IO ()
- wAttrOn :: Window -> Int -> IO ()
- wAttrOff :: Window -> Int -> IO ()
- wAttrSet :: Window -> (Attr, Pair) -> IO ()
- wAttrGet :: Window -> IO (Attr, Pair)
- getMouse :: MonadIO m => m (Maybe MouseEvent)
- withMouseEventMask :: MonadIO m => [ButtonEvent] -> m a -> m a
- withAllMouseEvents :: MonadIO m => m a -> m a
- data ButtonEvent
- data MouseEvent = MouseEvent {
- mouseEventId :: CInt
- mouseEventX :: CInt
- mouseEventY :: CInt
- mouseEventZ :: CInt
- mouseEventButton :: [ButtonEvent]
- data Key
- = KeyChar Char
- | KeyBreak
- | KeyDown
- | KeyUp
- | KeyLeft
- | KeyRight
- | KeyHome
- | KeyBackspace
- | KeyF Int
- | KeyDL
- | KeyIL
- | KeyDC
- | KeyIC
- | KeyEIC
- | KeyClear
- | KeyEOS
- | KeyEOL
- | KeySF
- | KeySR
- | KeyNPage
- | KeyPPage
- | KeySTab
- | KeyCTab
- | KeyCATab
- | KeyEnter
- | KeySReset
- | KeyReset
- | KeyPrint
- | KeyLL
- | KeyA1
- | KeyA3
- | KeyB2
- | KeyC1
- | KeyC3
- | KeyBTab
- | KeyBeg
- | KeyCancel
- | KeyClose
- | KeyCommand
- | KeyCopy
- | KeyCreate
- | KeyEnd
- | KeyExit
- | KeyFind
- | KeyHelp
- | KeyMark
- | KeyMessage
- | KeyMove
- | KeyNext
- | KeyOpen
- | KeyOptions
- | KeyPrevious
- | KeyRedo
- | KeyReference
- | KeyRefresh
- | KeyReplace
- | KeyRestart
- | KeyResume
- | KeySave
- | KeySBeg
- | KeySCancel
- | KeySCommand
- | KeySCopy
- | KeySCreate
- | KeySDC
- | KeySDL
- | KeySelect
- | KeySEnd
- | KeySEOL
- | KeySExit
- | KeySFind
- | KeySHelp
- | KeySHome
- | KeySIC
- | KeySLeft
- | KeySMessage
- | KeySMove
- | KeySNext
- | KeySOptions
- | KeySPrevious
- | KeySPrint
- | KeySRedo
- | KeySReplace
- | KeySRight
- | KeySRsume
- | KeySSave
- | KeySSuspend
- | KeySUndo
- | KeySuspend
- | KeyUndo
- | KeyResize
- | KeyMouse
- | KeyUnknown Int
- cERR :: CInt
- cKEY_UP :: ChType
- cKEY_DOWN :: ChType
- cKEY_LEFT :: ChType
- cKEY_RIGHT :: ChType
- cTRUE :: NBool
- vline :: Char -> Int -> IO ()
- ulCorner :: Char
- llCorner :: Char
- urCorner :: Char
- lrCorner :: Char
- rTee :: Char
- lTee :: Char
- bTee :: Char
- tTee :: Char
- hLine :: Char
- vLine :: Char
- plus :: Char
- s1 :: Char
- s9 :: Char
- diamond :: Char
- ckBoard :: Char
- degree :: Char
- plMinus :: Char
- bullet :: Char
- lArrow :: Char
- rArrow :: Char
- dArrow :: Char
- uArrow :: Char
- board :: Char
- lantern :: Char
- block :: Char
- s3 :: Char
- s7 :: Char
- lEqual :: Char
- gEqual :: Char
- pi :: Char
- nEqual :: Char
- sterling :: Char
- cursesSigWinch :: Maybe Signal
- cursesTest :: IO ()
- throwIfErr :: (Eq a, Show a, Num a) => String -> IO a -> IO a
- throwIfErr_ :: (Eq a, Show a, Num a) => String -> IO a -> IO ()
- errI :: IO CInt -> IO ()
- flushinp :: IO CInt
- recognize :: Char -> IO a -> (ChType -> IO a) -> IO a
- type ChType = Word32
- type NBool = Word8
Documentation
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.
resetParams :: IO () Source #
The program must call endwin for each terminal being used before exiting from curses.
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.
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.
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.
The getch, wgetch, mvgetch and mvwgetch, routines read a character from the window.
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.
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.
Output
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).
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.
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
data CursorVisibility Source #
Constructors
CursorInvisible | |
CursorVisible | |
CursorVeryVisible |
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).
useDefaultColors :: IO () Source #
colorPairs :: IO Int Source #
Defines the maximum number of color-pairs the terminal can support).
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).
canChangeColor :: IO Bool Source #
Attributes
Instances
Bits Attr Source # | |
Defined in UI.HSCurses.Curses Methods (.&.) :: Attr -> Attr -> Attr # (.|.) :: Attr -> Attr -> Attr # complement :: Attr -> Attr # shift :: Attr -> Int -> Attr # rotate :: Attr -> Int -> Attr # setBit :: Attr -> Int -> Attr # clearBit :: Attr -> Int -> Attr # complementBit :: Attr -> Int -> Attr # testBit :: Attr -> Int -> Bool # bitSizeMaybe :: Attr -> Maybe Int # shiftL :: Attr -> Int -> Attr # unsafeShiftL :: Attr -> Int -> Attr # shiftR :: Attr -> Int -> Attr # unsafeShiftR :: Attr -> Int -> Attr # rotateL :: Attr -> Int -> Attr # | |
Storable Attr Source # | |
Defined in UI.HSCurses.Curses | |
Num Attr Source # | |
Show Attr Source # | |
Eq Attr Source # | |
isAltCharset :: Attr -> Bool Source #
isHorizontal :: Attr -> Bool Source #
isStandout :: Attr -> Bool Source #
isUnderline :: Attr -> Bool Source #
isVertical :: Attr -> Bool Source #
attrDimOff :: IO () Source #
attrBoldOn :: IO () Source #
attrBoldOff :: IO () Source #
wAttrGet :: Window -> IO (Attr, Pair) Source #
Manipulate the current attributes of the named window. see curs_attr(3)
Mouse Routines
withMouseEventMask :: MonadIO m => [ButtonEvent] -> m a -> m a Source #
withAllMouseEvents :: MonadIO m => m a -> m a Source #
data ButtonEvent Source #
Constructors
ButtonPressed Int | |
ButtonReleased Int | |
ButtonClicked Int | |
ButtonDoubleClicked Int | |
ButtonTripleClicked Int | |
ButtonShift | |
ButtonControl | |
ButtonAlt |
Instances
Show ButtonEvent Source # | |
Defined in UI.HSCurses.Curses Methods showsPrec :: Int -> ButtonEvent -> ShowS # show :: ButtonEvent -> String # showList :: [ButtonEvent] -> ShowS # | |
Eq ButtonEvent Source # | |
Defined in UI.HSCurses.Curses |
data MouseEvent Source #
Constructors
MouseEvent | |
Fields
|
Instances
Storable MouseEvent Source # | |
Defined in UI.HSCurses.Curses Methods sizeOf :: MouseEvent -> Int # alignment :: MouseEvent -> Int # peekElemOff :: Ptr MouseEvent -> Int -> IO MouseEvent # pokeElemOff :: Ptr MouseEvent -> Int -> MouseEvent -> IO () # peekByteOff :: Ptr b -> Int -> IO MouseEvent # pokeByteOff :: Ptr b -> Int -> MouseEvent -> IO () # peek :: Ptr MouseEvent -> IO MouseEvent # poke :: Ptr MouseEvent -> MouseEvent -> IO () # | |
Show MouseEvent Source # | |
Defined in UI.HSCurses.Curses Methods showsPrec :: Int -> MouseEvent -> ShowS # show :: MouseEvent -> String # showList :: [MouseEvent] -> ShowS # |
Keys
A mapping of curses keys to Haskell values.
Constructors
cKEY_RIGHT :: ChType Source #
Lines
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.