[Haskell-cafe] Re: HSCurses - Hello World? (can't find much
documentation)
Michael Forster
mike at sharedlogic.ca
Thu Nov 4 23:16:25 EDT 2010
On Fri, Oct 22, 2010 at 17:09:52 EDT, Ari Rahikkala wrote:
> On Fri, Oct 22, 2010 at 11:18 PM, Anonymous Void <byteasphyxia at gmail.com> wrote:
> > But since I've never seen how the HSCurses functions really integrate
> > together, or any tutorials/examples (besides hsFishEx),
> > I fear toying with it is going to be annoying until I figure it out on my
> > own, especially since I'm already doing a project for someone...
> > So, I was wondering if anyone would be kind enough to point me to (or write
> > me) a basic example of how HSCurses works,
> > maybe w/ some very simple example of interactivity (e.g. getch processing,
> > screen refresh, ..) support.
> > Also, maybe warn me of some of the common pitfalls and differences in
> > hscurses vs ncurses in other languages.
>
> UI.HSCurses.Curses follows ncurses quite closely so you can get pretty
> far reading the NCurses Programming HOWTO:
> http://tldp.org/HOWTO/NCURSES-Programming-HOWTO/
Also, http://invisible-island.net/ncurses/ncurses-intro.html.
And below is a hscurses version of the first example from that document.
Cheers,
Mike
module Main where
import Control.Exception (bracket_)
import qualified UI.HSCurses.Curses as Curses
import qualified UI.HSCurses.CursesHelper as CursesH
start = do
Curses.initScr
Curses.keypad Curses.stdScr True
Curses.nl False
Curses.cBreak True
Curses.echo True
hasColors <- Curses.hasColors
if hasColors
then do
Curses.startColor
Curses.initPair (Curses.Pair 1) (CursesH.black) (CursesH.black)
Curses.initPair (Curses.Pair 2) (CursesH.green) (CursesH.black)
Curses.initPair (Curses.Pair 3) (CursesH.red) (CursesH.black)
Curses.initPair (Curses.Pair 4) (CursesH.cyan) (CursesH.black)
Curses.initPair (Curses.Pair 5) (CursesH.white) (CursesH.black)
Curses.initPair (Curses.Pair 6) (CursesH.magenta) (CursesH.black)
Curses.initPair (Curses.Pair 7) (CursesH.blue) (CursesH.black)
Curses.initPair (Curses.Pair 8) (CursesH.yellow) (CursesH.black)
return ()
else
return ()
Curses.wclear Curses.stdScr
return ()
loop num = do
c <- Curses.getch
Curses.attrSet Curses.attr0 (Curses.Pair (mod num 8))
Curses.refresh
if Curses.decodeKey c == Curses.KeyChar 'q'
then return()
else loop (num + 1)
end = do
Curses.endWin
return ()
main = do
bracket_ start end (loop 0)
More information about the Haskell-Cafe
mailing list