{-# LINE 1 "UI/HSCurses/Curses.hsc" #-}
{-# LANGUAGE ForeignFunctionInterface, GeneralizedNewtypeDeriving #-}
{-# LINE 2 "UI/HSCurses/Curses.hsc" #-}
-- glaexts needed for newtype deriving

-- Copyright (c) 2002-2004 John Meacham (john at repetae dot net)
-- Copyright (c) 2004 Don Stewart - http://www.cse.unsw.edu.au/~dons
-- Copyright (c) 2005-2011 Stefan Wehr - http://www.stefanwehr.de
--
-- This library is free software; you can redistribute it and/or
-- modify it under the terms of the GNU Lesser General Public
-- License as published by the Free Software Foundation; either
-- version 2.1 of the License, or (at your option) any later version.
--
-- This library is distributed in the hope that it will be useful,
-- but WITHOUT ANY WARRANTY; without even the implied warranty of
-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
-- Lesser General Public License for more details.
--
-- You should have received a copy of the GNU Lesser General Public
-- License along with this library; if not, write to the Free Software
-- Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, MA  02110-1301  USA



--
-- | 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.
--

module UI.HSCurses.Curses (

    -- * Basic Functions
    stdScr,             -- :: Window
    initScr,            -- :: IO Window
    initCurses,         -- :: IO ()
    resetParams,
    endWin,             -- :: IO ()
    scrSize,            -- :: IO (Int, Int)

    -- * Windows and Pads
    Window,             -- data Window deriving Eq
    Border(..),         -- data Border
    touchWin,
    newPad, pRefresh, delWin, newWin, wRefresh, wBorder, defaultBorder,


    -- * Refresh Routines
    refresh,            -- :: IO ()
    update,
    resizeTerminal,
    timeout,            -- :: Int -> IO ()
    noqiflush,           -- :: IO ()

    -- * Navigation
    move,               -- :: Int -> Int -> IO ()
    getYX,

    -- * Input
    getCh, getch, decodeKey, ungetCh, keyResizeCode,

    -- * Input Options
    cBreak,             -- :: Bool -> IO ()
    raw,                -- :: Bool -> IO ()
    echo,               -- :: Bool -> IO ()
    intrFlush,          -- :: Bool -> IO ()
    keypad,             -- :: Window -> Bool -> IO ()
    noDelay,            -- :: Window -> Bool -> IO ()

    -- * Output
    wAddStr,       -- :: Window -> String -> IO ()
    addLn,         -- :: IO ()
    mvWAddStr,
    mvAddCh,       -- :: Int -> Int -> ChType -> IO ()
    wMove,
    bkgrndSet,     -- :: Attr -> Pair -> IO ()
    erase,         -- :: IO ()
    wclear,        -- :: Window -> IO ()
    clrToEol,      -- :: IO ()
    wClrToEol,
    beep,
    waddch,
    waddchnstr,    -- :: Window -> CString -> CInt -> IO CInt

    -- * Output Options
    clearOk,
    leaveOk,
    nl,                 -- :: Bool -> IO ()

    -- * Cursor Routines
    CursorVisibility(..), cursSet,

    -- * Color Support
    hasColors,      -- :: IO Bool
    startColor,     -- :: IO ()
    useDefaultColors,   -- :: IO ()
    Pair(..),       -- newtype Pair = Pair Int deriving (Eq, Ord, Ix)
    colorPairs,     -- :: IO Int
    Color(..),      -- newtype Color = Color Int deriving (Eq, Ord, Ix)
    colors,         -- :: IO Int
    color,          -- :: String -> Maybe Color
--    black, red, green, yellow, blue, magenta, cyan, white, -- :: 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, defaultForeground,

    -- * Attributes
    attrPlus,
    Attr,
    attr0, -- :: Attr

    isAltCharset, isBlink, isBold, isDim, isHorizontal, isInvis,
    isLeft, isLow, isProtect, isReverse, isRight, isStandout, isTop,
    isUnderline, isVertical,
        -- :: Attr -> Bool

    setAltCharset, setBlink, setBold, setDim, setHorizontal, setInvis,
    setLeft, setLow, setProtect, setReverse, setRight, setStandout,
    setTop, setUnderline, setVertical,
        -- :: Attr -> Bool -> Attr

    attrSet, -- :: Attr -> Pair -> IO ()
    attrOn, attrOff,

    standout,standend,
    attrDim, attrBold,
    attrDimOn, attrDimOff,
    attrBoldOn, attrBoldOff,
    wAttrOn,
    wAttrOff,
    wAttrSet, wAttrGet,

    -- * Mouse Routines
    withMouseEventMask,
    ButtonEvent(..),
    MouseEvent(..),

    -- * Keys
    Key(..),
    cERR,
    cKEY_UP,
    cKEY_DOWN,
    cKEY_LEFT,
    cKEY_RIGHT,
    cTRUE,
--    cACS_BLOCK,

    -- * Lines
    vline,
    ulCorner, llCorner, urCorner, lrCorner, rTee, lTee, bTee, tTee, hLine,
    vLine, plus, s1, s9, diamond, ckBoard, degree, plMinus, bullet,
    lArrow, rArrow, dArrow, uArrow, board, lantern, block,
    s3, s7, lEqual, gEqual, pi, nEqual, sterling,

    -- * Signals
    cursesSigWinch,

    -- * Misc
    cursesTest,
    throwIfErr, throwIfErr_,
    errI,       -- :: IO CInt -> IO ()
    flushinp,
    recognize,
    ChType,
    NBool

  ) where


{-# LINE 183 "UI/HSCurses/Curses.hsc" #-}


{-# LINE 185 "UI/HSCurses/Curses.hsc" #-}

{-# LINE 186 "UI/HSCurses/Curses.hsc" #-}

{-# LINE 187 "UI/HSCurses/Curses.hsc" #-}

import UI.HSCurses.CWString       ( withLCStringLen )
import UI.HSCurses.Logging

import Prelude hiding           ( pi )
import Data.Char
import Data.List
import Data.Ix                  ( Ix )

import System.IO.Unsafe ( unsafePerformIO )

import Control.Monad ( when, liftM, void )
import Control.Monad.Trans
import Control.Concurrent

import Foreign hiding ( unsafePerformIO, void )
import Foreign.C.String
import Foreign.C.Types
import Foreign.C.Error


{-# LINE 208 "UI/HSCurses/Curses.hsc" #-}
import System.Posix.Signals

{-# LINE 210 "UI/HSCurses/Curses.hsc" #-}


{-# LINE 214 "UI/HSCurses/Curses.hsc" #-}


------------------------------------------------------------------------
--
-- | @initCurses fn@ does all initialization necessary for a Curses
--   application.
--
initCurses :: IO ()
initCurses = do
    initScr
    b <- hasColors
    when b $ startColor >> useDefaultColors

resetParams :: IO ()
resetParams = do
    raw True    -- raw mode please
    echo False
    nl False
    intrFlush True
    leaveOk False
    keypad stdScr True

{-# LINE 236 "UI/HSCurses/Curses.hsc" #-}
    defineKey (259) "\x1b[1;2A"
{-# LINE 237 "UI/HSCurses/Curses.hsc" #-}
    defineKey (258) "\x1b[1;2B"
{-# LINE 238 "UI/HSCurses/Curses.hsc" #-}
    defineKey (393) "\x1b[1;2D"
{-# LINE 239 "UI/HSCurses/Curses.hsc" #-}
    defineKey (402) "\x1b[1;2C"
{-# LINE 240 "UI/HSCurses/Curses.hsc" #-}
    defineKey (350) "\x1b[E"  -- xterm seems to emit B2, not BEG
{-# LINE 241 "UI/HSCurses/Curses.hsc" #-}
    defineKey (360) "\x1b[F"
{-# LINE 242 "UI/HSCurses/Curses.hsc" #-}
    defineKey (360) "\x1b[4~"
{-# LINE 243 "UI/HSCurses/Curses.hsc" #-}
    defineKey (262) "\x1b[H"
{-# LINE 244 "UI/HSCurses/Curses.hsc" #-}
    defineKey (262) "\x1b[1~"
{-# LINE 245 "UI/HSCurses/Curses.hsc" #-}

{-# LINE 246 "UI/HSCurses/Curses.hsc" #-}

------------------------------------------------------------------------

fi :: (Integral a, Num b) => a -> b
fi = fromIntegral

throwIfErr :: (Eq a, Show a, Num a) => String -> IO a -> IO a
--throwIfErr name act = do
--    res <- act
--    if res == (cERR)
--        then ioError (userError ("Curses: "++name++" failed"))
--        else return res
throwIfErr s = throwIf (== (-1)) (\a -> "Curses[" ++ show a ++ "]:"  ++ s)
{-# LINE 259 "UI/HSCurses/Curses.hsc" #-}

throwIfErr_ :: (Eq a, Show a, Num a) => String -> IO a -> IO ()
throwIfErr_ name act = void $ throwIfErr name act

errI :: IO CInt -> IO ()
errI f = do r <- f
            if r == cERR then do _ <- endwin
                                 error "curses returned an error"
             else return ()

------------------------------------------------------------------------

type WindowTag = ()
type Window = Ptr WindowTag
type ChType = Word32
{-# LINE 274 "UI/HSCurses/Curses.hsc" #-}
type NBool = Word8
{-# LINE 275 "UI/HSCurses/Curses.hsc" #-}


--
-- | The standard screen
--
stdScr :: Window
stdScr = unsafePerformIO (peek stdscr)
foreign import ccall "static HSCurses.h &stdscr"
    stdscr :: Ptr Window

--
-- | 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.
--
initScr :: IO Window
initScr = throwIfNull "initscr" initscr
foreign import ccall unsafe "HSCurses.h initscr" initscr :: IO Window

--
-- | > The cbreak routine
--   > disables line buffering and erase/kill  character-process-
--   > ing  (interrupt  and  flow  control  characters  are unaf-
--   > fected), making characters typed by the  user  immediately
--   > available  to  the  program.  The nocbreak routine returns
--   > the terminal to normal (cooked) mode.
--
cBreak :: Bool -> IO ()
cBreak True  = throwIfErr_ "cbreak"   cbreak
cBreak False = throwIfErr_ "nocbreak" nocbreak

foreign import ccall unsafe "HSCurses.h cbreak"     cbreak :: IO CInt
foreign import ccall unsafe "HSCurses.h nocbreak" nocbreak :: IO CInt

--
-- |>    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.
--
raw :: Bool -> IO ()
raw False = throwIfErr_ "noraw" noraw
raw True  = throwIfErr_ "raw"   raw_c

foreign import ccall unsafe "HSCurses.h noraw" noraw :: IO CInt
foreign import ccall unsafe "HSCurses.h raw"   raw_c :: IO CInt

--
-- |>      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.]
-- >
--
echo :: Bool -> IO ()
echo False = throwIfErr_ "noecho" noecho
echo True  = throwIfErr_ "echo"   echo_c

foreign import ccall unsafe "HSCurses.h noecho" noecho :: IO CInt
foreign import ccall unsafe "HSCurses.h echo" echo_c :: IO CInt

--
-- |>       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.
-- >
nl :: Bool -> IO ()
nl True  = throwIfErr_ "nl"   nl_c
nl False = throwIfErr_ "nonl" nonl

foreign import ccall unsafe "HSCurses.h nl" nl_c :: IO CInt
foreign import ccall unsafe "HSCurses.h nonl" nonl :: IO CInt

-- |>       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.
-- >
intrFlush :: Bool -> IO ()
intrFlush bf =
    throwIfErr_ "intrflush" $ intrflush stdScr (if bf then 1 else 0)
foreign import ccall unsafe "HSCurses.h intrflush" intrflush :: Window -> (Word8) -> IO CInt
{-# LINE 386 "UI/HSCurses/Curses.hsc" #-}

--
-- | Enable the keypad of the user's terminal.
--
keypad :: Window -> Bool -> IO ()
keypad win bf = throwIfErr_ "keypad" $ keypad_c win (if bf then 1 else 0)
foreign import ccall unsafe "HSCurses.h keypad"
    keypad_c :: Window -> (Word8) -> IO CInt
{-# LINE 394 "UI/HSCurses/Curses.hsc" #-}

noDelay :: Window -> Bool -> IO ()
noDelay win bf =
    throwIfErr_ "nodelay" $ nodelay win (if bf then 1 else 0)

foreign import ccall unsafe "HSCurses.h nodelay"
    nodelay :: Window -> (Word8) -> IO CInt
{-# LINE 401 "UI/HSCurses/Curses.hsc" #-}

--
-- |   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 cur-
--     sor is not used, since it  reduces  the  need  for  cursor
--     motions.   If  possible, the cursor is made invisible when
--     this option is enabled.
--
leaveOk  :: Bool -> IO CInt
leaveOk True  = leaveok_c stdScr 1
leaveOk False = leaveok_c stdScr 0

foreign import ccall unsafe "HSCurses.h leaveok"
    leaveok_c :: Window -> (Word8) -> IO CInt
{-# LINE 417 "UI/HSCurses/Curses.hsc" #-}

clearOk :: Bool -> IO CInt
clearOk True  = clearok_c stdScr 1
clearOk False = clearok_c stdScr 0

foreign import ccall unsafe "HSCurses.h clearok"
    clearok_c :: Window -> (Word8) -> IO CInt
{-# LINE 424 "UI/HSCurses/Curses.hsc" #-}

------------------------------------------------------------------------

foreign import ccall unsafe "HSCurses.h use_default_colors"
    useDefaultColors :: IO ()

defaultBackground, defaultForeground :: Color
defaultBackground = Color (-1)
defaultForeground = Color (-1)

------------------------------------------------------------------------


{-# LINE 437 "UI/HSCurses/Curses.hsc" #-}
defineKey :: CInt -> String -> IO ()
defineKey k s =  withCString s (\s' -> define_key s' k) >> return ()

foreign import ccall unsafe "HSCurses.h define_key"
    define_key :: Ptr CChar -> CInt -> IO ()

{-# LINE 443 "UI/HSCurses/Curses.hsc" #-}

--
-- | >  The program must call endwin for each terminal being used before
--   >  exiting from curses.
--
endWin :: IO ()
endWin = throwIfErr_ "endwin" endwin
foreign import ccall unsafe "HSCurses.h endwin" endwin :: IO CInt

------------------------------------------------------------------------

--
-- | get the dimensions of the screen
--
scrSize :: IO (Int, Int)
scrSize = do
    lnes <- peek linesPtr
    cols <- peek colsPtr
    return (fromIntegral lnes, fromIntegral cols)

foreign import ccall "HSCurses.h &LINES" linesPtr :: Ptr CInt
foreign import ccall "HSCurses.h &COLS"  colsPtr  :: Ptr CInt

--
-- | refresh curses windows and lines. curs_refresh(3)
--
refresh :: IO ()
refresh = throwIfErr_ "refresh" refresh_c

foreign import ccall unsafe "HSCurses.h refresh"
    refresh_c :: IO CInt

--
-- | wRefresh refreshes the specified window, copying the data
-- | from the virtual screen to the physical screen.
--
wRefresh :: Window -> IO ()
wRefresh w = throwIfErr_ "wrefresh" $ wrefresh_c w

foreign import ccall unsafe "HSCurses.h wrefresh"
    wrefresh_c :: Window -> IO CInt

--
-- | Do an actual update. Used after endWin on linux to restore the terminal
--
update :: IO ()
update = throwIfErr_ "update" update_c

foreign import ccall unsafe "HSCurses.h doupdate" update_c :: IO CInt

foreign import ccall unsafe "static curses.h timeout" timeout_c :: CInt -> IO ()

-- | Set a delay in milliseconds.
timeout :: Int -> IO ()
timeout = timeout_c . fromIntegral

------------------------------------------------------------------------

hasColors :: IO Bool
hasColors = liftM (/= 0) has_colors
foreign import ccall unsafe "HSCurses.h has_colors" has_colors :: IO (Word8)
{-# LINE 504 "UI/HSCurses/Curses.hsc" #-}

--
-- | Initialise the color settings, also sets the screen to the
-- default colors (white on black)
--
startColor :: IO ()
startColor = throwIfErr_ "start_color" start_color
foreign import ccall unsafe start_color :: IO CInt

newtype Pair = Pair Int deriving (Eq, Ord, Ix, Show)

--
-- | colorPairs defines the maximum number of color-pairs the terminal
-- can support).
--
colorPairs :: IO Int
colorPairs = fmap fromIntegral $ peek colorPairsPtr

foreign import ccall "HSCurses.h &COLOR_PAIRS"
        colorPairsPtr :: Ptr CInt

newtype Color = Color Int deriving (Eq, Ord, Ix)

colors :: IO Int
colors = liftM fromIntegral $ peek colorsPtr

foreign import ccall "HSCurses.h &COLORS" colorsPtr :: Ptr CInt

--black, red, green, yellow, blue, magenta, cyan, white :: Color

color :: String -> Maybe Color
color "default"  = Just $ Color (-1)
color "black"    = Just $ Color (0)
{-# LINE 537 "UI/HSCurses/Curses.hsc" #-}
color "red"      = Just $ Color (1)
{-# LINE 538 "UI/HSCurses/Curses.hsc" #-}
color "green"    = Just $ Color (2)
{-# LINE 539 "UI/HSCurses/Curses.hsc" #-}
color "yellow"   = Just $ Color (3)
{-# LINE 540 "UI/HSCurses/Curses.hsc" #-}
color "blue"     = Just $ Color (4)
{-# LINE 541 "UI/HSCurses/Curses.hsc" #-}
color "magenta"  = Just $ Color (5)
{-# LINE 542 "UI/HSCurses/Curses.hsc" #-}
color "cyan"     = Just $ Color (6)
{-# LINE 543 "UI/HSCurses/Curses.hsc" #-}
color "white"    = Just $ Color (7)
{-# LINE 544 "UI/HSCurses/Curses.hsc" #-}
color _ =  Nothing


--
-- |   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).
--
--
initPair :: Pair -> Color -> Color -> IO ()
initPair (Pair p) (Color f) (Color b) =
    throwIfErr_ "init_pair" $
        init_pair (fromIntegral p) (fromIntegral f) (fromIntegral b)

foreign import ccall unsafe
    init_pair :: CShort -> CShort -> CShort -> IO CInt


pairContent :: Pair -> IO (Color, Color)
pairContent (Pair p) =
    alloca $ \fPtr ->
    alloca $ \bPtr -> do
        throwIfErr "pair_content" $ pair_content (fromIntegral p) fPtr bPtr
        f <- peek fPtr
        b <- peek bPtr
        return (Color (fromIntegral f), Color (fromIntegral b))

foreign import ccall unsafe pair_content :: CShort -> Ptr CShort -> Ptr CShort -> IO CInt

canChangeColor :: IO Bool
canChangeColor = liftM (/= 0) can_change_color

foreign import ccall unsafe can_change_color :: IO (Word8)
{-# LINE 600 "UI/HSCurses/Curses.hsc" #-}

initColor :: Color -> (Int, Int, Int) -> IO ()
initColor (Color c) (r, g, b) =
    throwIfErr_ "init_color" $
        init_color (fromIntegral c) (fromIntegral r) (fromIntegral g) (fromIntegral b)
foreign import ccall unsafe init_color :: CShort -> CShort -> CShort -> CShort -> IO CInt

colorContent :: Color -> IO (Int, Int, Int)
colorContent (Color c) =
    alloca $ \rPtr ->
    alloca $ \gPtr ->
    alloca $ \bPtr -> do
        throwIfErr "color_content" $ color_content (fromIntegral c) rPtr gPtr bPtr
        r <- peek rPtr
        g <- peek gPtr
        b <- peek bPtr
        return (fromIntegral r, fromIntegral g, fromIntegral b)

foreign import ccall unsafe
    color_content :: CShort -> Ptr CShort -> Ptr CShort -> Ptr CShort -> IO CInt

foreign import ccall unsafe "HSCurses.h hs_curses_color_pair" colorPair :: Pair -> ChType

-------------
-- Attributes
-------------

foreign import ccall unsafe "HSCurses.h attr_set"
    attr_set :: Attr -> CShort -> Ptr a -> IO Int

-- foreign import ccall unsafe "HSCurses.h attr_get" :: Attr -> CShort -> Ptr a -> IO Int

foreign import ccall unsafe "HSCurses.h wattr_set"
    wattr_set :: Window -> Attr -> CInt -> Ptr a -> IO CInt

foreign import ccall unsafe "HSCurses.h wattr_get"
    wattr_get :: Window -> Ptr Attr -> Ptr CShort -> Ptr a -> IO CInt

foreign import ccall "HSCurses.h attr_on" attr_on :: (Word32) -> Ptr a -> IO Int
{-# LINE 639 "UI/HSCurses/Curses.hsc" #-}
foreign import ccall "HSCurses.h attr_off" attr_off :: (Word32) -> Ptr a -> IO Int
{-# LINE 640 "UI/HSCurses/Curses.hsc" #-}
foreign import ccall "HSCurses.h attron" attron :: Int -> IO Int
foreign import ccall "HSCurses.h attroff" attroff :: Int -> IO Int
foreign import ccall unsafe "HSCurses.h wattron" wattron :: Window -> CInt -> IO CInt
foreign import ccall unsafe "HSCurses.h wattroff" wattroff :: Window -> CInt -> IO CInt
foreign import ccall standout :: IO Int
foreign import ccall standend :: IO Int

--
-- |
--
wAttrSet :: Window -> (Attr,Pair) -> IO ()
wAttrSet w (a,(Pair p)) = throwIfErr_ "wattr_set" $
    wattr_set w a (fromIntegral p) nullPtr

--
-- | manipulate the current attributes of the named window. see curs_attr(3)
--
wAttrGet :: Window -> IO (Attr,Pair)
wAttrGet w =
    alloca $ \pa ->
        alloca $ \pp -> do
            throwIfErr_ "wattr_get" $ wattr_get w pa pp nullPtr
            a <- peek pa
            p <- peek pp
            return (a,Pair $ fromIntegral p)


newtype Attr = Attr (Word32) deriving (Eq,Storable,Bits, Num, Show)
{-# LINE 668 "UI/HSCurses/Curses.hsc" #-}

--
-- | Normal display (no highlight)
--
attr0 :: Attr

{-# LINE 674 "UI/HSCurses/Curses.hsc" #-}
attr0 = Attr (0)
{-# LINE 675 "UI/HSCurses/Curses.hsc" #-}

{-# LINE 678 "UI/HSCurses/Curses.hsc" #-}

isAltCharset, isBlink, isBold, isDim, isHorizontal, isInvis, isLeft,
    isLow, isProtect, isReverse, isRight, isStandout, isTop,
    isUnderline, isVertical :: Attr -> Bool

isAltCharset = isAttr (4194304)
{-# LINE 684 "UI/HSCurses/Curses.hsc" #-}
isBlink      = isAttr (524288)
{-# LINE 685 "UI/HSCurses/Curses.hsc" #-}
isBold       = isAttr (2097152)
{-# LINE 686 "UI/HSCurses/Curses.hsc" #-}
isDim        = isAttr (1048576)
{-# LINE 687 "UI/HSCurses/Curses.hsc" #-}
isHorizontal = isAttr (33554432)
{-# LINE 688 "UI/HSCurses/Curses.hsc" #-}
isInvis      = isAttr (8388608)
{-# LINE 689 "UI/HSCurses/Curses.hsc" #-}
isLeft       = isAttr (67108864)
{-# LINE 690 "UI/HSCurses/Curses.hsc" #-}
isLow        = isAttr (134217728)
{-# LINE 691 "UI/HSCurses/Curses.hsc" #-}
isProtect    = isAttr (16777216)
{-# LINE 692 "UI/HSCurses/Curses.hsc" #-}
isReverse    = isAttr (262144)
{-# LINE 693 "UI/HSCurses/Curses.hsc" #-}
isRight      = isAttr (268435456)
{-# LINE 694 "UI/HSCurses/Curses.hsc" #-}
isStandout   = isAttr (65536)
{-# LINE 695 "UI/HSCurses/Curses.hsc" #-}
isTop        = isAttr (536870912)
{-# LINE 696 "UI/HSCurses/Curses.hsc" #-}
isUnderline  = isAttr (131072)
{-# LINE 697 "UI/HSCurses/Curses.hsc" #-}
isVertical   = isAttr (1073741824)
{-# LINE 698 "UI/HSCurses/Curses.hsc" #-}

isAttr :: (Word32) -> Attr -> Bool
{-# LINE 700 "UI/HSCurses/Curses.hsc" #-}
isAttr b (Attr a) = a .&. b /= 0

--
-- | Setting attributes
--
setAltCharset, setBlink, setBold, setDim, setHorizontal, setInvis,
    setLeft, setLow, setProtect, setReverse, setRight, setStandout,
    setTop, setUnderline, setVertical :: Attr -> Bool -> Attr

setAltCharset = setAttr (4194304)
{-# LINE 710 "UI/HSCurses/Curses.hsc" #-}
setBlink      = setAttr (524288)
{-# LINE 711 "UI/HSCurses/Curses.hsc" #-}
setBold       = setAttr (2097152)
{-# LINE 712 "UI/HSCurses/Curses.hsc" #-}
setDim        = setAttr (1048576)
{-# LINE 713 "UI/HSCurses/Curses.hsc" #-}
setHorizontal = setAttr (33554432)
{-# LINE 714 "UI/HSCurses/Curses.hsc" #-}
setInvis      = setAttr (8388608)
{-# LINE 715 "UI/HSCurses/Curses.hsc" #-}
setLeft       = setAttr (67108864)
{-# LINE 716 "UI/HSCurses/Curses.hsc" #-}
setLow        = setAttr (134217728)
{-# LINE 717 "UI/HSCurses/Curses.hsc" #-}
setProtect    = setAttr (16777216)
{-# LINE 718 "UI/HSCurses/Curses.hsc" #-}
setReverse    = setAttr (262144)
{-# LINE 719 "UI/HSCurses/Curses.hsc" #-}
setRight      = setAttr (268435456)
{-# LINE 720 "UI/HSCurses/Curses.hsc" #-}
setStandout   = setAttr (65536)
{-# LINE 721 "UI/HSCurses/Curses.hsc" #-}
setTop        = setAttr (536870912)
{-# LINE 722 "UI/HSCurses/Curses.hsc" #-}
setUnderline  = setAttr (131072)
{-# LINE 723 "UI/HSCurses/Curses.hsc" #-}
setVertical   = setAttr (1073741824)
{-# LINE 724 "UI/HSCurses/Curses.hsc" #-}

setAttr :: (Word32) -> Attr -> Bool -> Attr
{-# LINE 726 "UI/HSCurses/Curses.hsc" #-}
setAttr b (Attr a) False = Attr (a .&. complement b)
setAttr b (Attr a) True  = Attr (a .|.            b)

attrPlus :: Attr -> Attr -> Attr
attrPlus (Attr a) (Attr b) = Attr (a .|. b)

attrSet :: Attr -> Pair -> IO ()
attrSet attr (Pair p) = throwIfErr_ "attrset" $
    attr_set attr (fromIntegral p) nullPtr

attrOn :: Attr -> IO ()
attrOn (Attr attr) = throwIfErr_ "attr_on" $
    attr_on attr nullPtr


attrOff :: Attr -> IO ()
attrOff (Attr attr) = throwIfErr_ "attr_off" $
    attr_off attr nullPtr



wAttrOn :: Window -> Int -> IO ()
wAttrOn w x = throwIfErr_ "wattron" $ wattron w (fi x)

wAttrOff :: Window -> Int -> IO ()
wAttrOff w x = throwIfErr_ "wattroff" $ wattroff w (fi x)

attrDimOn :: IO ()
attrDimOn  = throwIfErr_ "attron A_DIM" $
    attron (1048576)
{-# LINE 756 "UI/HSCurses/Curses.hsc" #-}

attrDimOff :: IO ()
attrDimOff = throwIfErr_ "attroff A_DIM" $
    attroff (1048576)
{-# LINE 760 "UI/HSCurses/Curses.hsc" #-}

attrBoldOn :: IO ()
attrBoldOn  = throwIfErr_ "attron A_BOLD" $
    attron (2097152)
{-# LINE 764 "UI/HSCurses/Curses.hsc" #-}

attrBoldOff :: IO ()
attrBoldOff = throwIfErr_ "attroff A_BOLD" $
    attroff (2097152)
{-# LINE 768 "UI/HSCurses/Curses.hsc" #-}


attrDim :: Int
attrDim = (1048576)
{-# LINE 772 "UI/HSCurses/Curses.hsc" #-}
attrBold :: Int
attrBold = (2097152)
{-# LINE 774 "UI/HSCurses/Curses.hsc" #-}

------------------------------------------------------------------------

foreign import ccall safe
    waddch :: Window -> ChType -> IO CInt

foreign import ccall safe
    waddchnstr :: Window -> CString -> CInt -> IO CInt

foreign import ccall safe "static curses.h mvaddch" mvaddch_c :: CInt -> CInt -> ChType -> IO ()

mvWAddStr :: Window -> Int -> Int -> String -> IO ()
mvWAddStr w y x str = wMove w y x >> wAddStr w str

mvAddCh :: Int -> Int -> ChType -> IO ()
mvAddCh l m n = mvaddch_c (fromIntegral l) (fromIntegral m) (fromIntegral n)

addLn :: IO ()
addLn = wAddStr stdScr "\n"

--
-- | normalise the string, stripping \\r and making control chars
-- printable. Called over all output(?)

{-
normalise :: String -> String
normalise []        = []
normalise ('\r':cs) = normalise cs
normalise (c:cs) | isControl c   = '@' : normalise cs
                 | otherwise     = c   : normalise cs
{-# INLINE normalise #-}
-}

{-
normalise s = map f . filter (/= '\r') s
    where
        f c | isPrint c  = c
        f c = '@'
-}

------------------------------------------------------------------------


{-# LINE 817 "UI/HSCurses/Curses.hsc" #-}

--wAddStr :: Window -> String -> IO ()
--wAddStr w str = throwIfErr_ ("waddnwstr: " ++ show str) $ withCWStringLen (normalise str) (\(ws,len) -> waddnwstr w ws (fi len))

foreign import ccall unsafe
    waddnwstr :: Window -> CWString -> CInt -> IO CInt

wAddStr :: Window -> String -> IO ()
wAddStr win str = do
    let
        convStr f = case f [] of
            [] -> return ()
            s  -> throwIfErr_ "waddnstr" $
                withCWStringLen  (s) (\(ws,len) ->  (waddnwstr win ws (fi len)))
        loop []        acc = convStr acc
        loop (ch:str') acc = recognize
            ch
            (loop str' (acc . (ch:)))
            (\ch' -> do
                convStr acc
                throwIfErr "waddch" $ waddch win ch'
                loop str' id)
    loop str id


{-# LINE 864 "UI/HSCurses/Curses.hsc" #-}

foreign import ccall safe
    vline  :: Char -> Int -> IO ()

------------------------------------------------------------------------

--
-- what ?
--


{-# LINE 877 "UI/HSCurses/Curses.hsc" #-}

bkgrndSet :: Attr -> Pair -> IO ()
bkgrndSet (Attr a) p = bkgdset $
    fromIntegral (ord ' ') .|.
    (if a .&. 4194304 /= 0 then 4194304 else 0) .|.
{-# LINE 882 "UI/HSCurses/Curses.hsc" #-}
    (if a .&. 524288 /= 0 then 524288 else 0) .|.
{-# LINE 883 "UI/HSCurses/Curses.hsc" #-}
    (if a .&. 2097152 /= 0 then 2097152 else 0) .|.
{-# LINE 884 "UI/HSCurses/Curses.hsc" #-}
    (if a .&. 1048576 /= 0 then 1048576 else 0) .|.
{-# LINE 885 "UI/HSCurses/Curses.hsc" #-}
    (if a .&. 8388608 /= 0 then 8388608 else 0) .|.
{-# LINE 886 "UI/HSCurses/Curses.hsc" #-}
    (if a .&. 16777216 /= 0 then 16777216 else 0) .|.
{-# LINE 887 "UI/HSCurses/Curses.hsc" #-}
    (if a .&. 262144 /= 0 then 262144 else 0) .|.
{-# LINE 888 "UI/HSCurses/Curses.hsc" #-}
    (if a .&. 65536 /= 0 then 65536 else 0) .|.
{-# LINE 889 "UI/HSCurses/Curses.hsc" #-}
    (if a .&. 131072 /= 0 then 131072 else 0) .|.
{-# LINE 890 "UI/HSCurses/Curses.hsc" #-}
    colorPair p

foreign import ccall unsafe bkgdset :: ChType -> IO ()

erase :: IO ()
erase = throwIfErr_ "erase" $ werase_c  stdScr
foreign import ccall unsafe "werase" werase_c :: Window -> IO CInt

wclear :: Window -> IO ()
wclear w = throwIfErr_ "wclear" $ wclear_c  w
foreign import ccall unsafe "wclear" wclear_c :: Window -> IO CInt

clrToEol :: IO ()
clrToEol = throwIfErr_ "clrtoeol" clrtoeol
foreign import ccall unsafe clrtoeol :: IO CInt

--
-- | >    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.
--
move :: Int -> Int -> IO ()
move y x = throwIfErr_ "move" $ move_c (fromIntegral y) (fromIntegral x)

foreign import ccall unsafe "move"
    move_c :: CInt -> CInt -> IO CInt

--
-- | >    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).
--
wMove :: Window -> Int -> Int -> IO ()
wMove w y x = throwIfErr_ "wmove" $ wmove w (fi y) (fi x)

foreign import ccall unsafe
    wmove :: Window -> CInt -> CInt -> IO CInt

------------------
-- Cursor routines
------------------

data CursorVisibility = CursorInvisible | CursorVisible | CursorVeryVisible

vis_c :: CursorVisibility -> CInt
vis_c vis = case vis of
    CursorInvisible   -> 0
    CursorVisible     -> 1
    CursorVeryVisible -> 2

c_vis :: CInt -> CursorVisibility
c_vis 0 = CursorInvisible
c_vis 1 = CursorVisible
c_vis 2 = CursorVeryVisible
c_vis n = error ("Illegal C value for cursor visibility: " ++ show n)

--
-- | 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.
--
cursSet :: CursorVisibility -> IO CursorVisibility
cursSet CursorInvisible =
    do leaveOk True
       old <- curs_set 0
       return $ c_vis old
cursSet v =
    do leaveOk False
       old <- curs_set (vis_c v)
       return $ c_vis old

foreign import ccall unsafe "HSCurses.h curs_set"
    curs_set :: CInt -> IO CInt

--
-- | Get the current cursor coordinates
--
getYX :: Window -> IO (Int, Int)
getYX w =
    alloca $ \py ->                 -- allocate two ints on the stack
        alloca $ \px -> do
            nomacro_getyx w py px   -- writes current cursor coords
            y <- peek py
            x <- peek px
            return (fromIntegral y, fromIntegral x)

--
-- | Get the current cursor coords, written into the two argument ints.
--
-- >    The getyx macro places the current cursor position of the given
-- >    window in the two integer variables y and x.
--
--      void getyx(WINDOW *win, int y, int x);
--
foreign import ccall unsafe "HSCursesUtils.h hscurses_nomacro_getyx"
        nomacro_getyx :: Window -> Ptr CInt -> Ptr CInt -> IO ()

------------------------------------------------------------------------


touchWin :: Window -> IO ()
touchWin w = throwIfErr_ "touchwin" $ touchwin w
foreign import ccall touchwin :: Window -> IO CInt

newPad :: Int -> Int -> IO Window
newPad nlines ncols = throwIfNull "newpad" $
    newpad (fromIntegral nlines) (fromIntegral ncols)

pRefresh :: Window -> Int -> Int -> Int -> Int -> Int -> Int -> IO ()
pRefresh pad pminrow pmincol sminrow smincol smaxrow smaxcol =
    throwIfErr_ "prefresh" $
        prefresh pad (fromIntegral pminrow)
                     (fromIntegral pmincol)
                     (fromIntegral sminrow)
                     (fromIntegral smincol)
                     (fromIntegral smaxrow)
                     (fromIntegral smaxcol)

delWin :: Window -> IO ()
delWin w = throwIfErr_ "delwin" $ delwin w

data Border = Border {
      ls :: Char
    , rs :: Char
    , ts :: Char
    , bs :: Char
    , tl :: Char
    , tr :: Char
    , bl :: Char
    , br :: Char
}

defaultBorder :: Border
defaultBorder = Border '\0' '\0' '\0' '\0' '\0' '\0' '\0' '\0'

--
-- | >    Draw a border around the edges of a window. defaultBorder is
--   >    a record  representing all 0 parameters to wrecord.
--
wBorder :: Window -> Border -> IO ()
wBorder w (Border ls rs ts bs tl tr bl br) = throwIfErr_ "wborder" $
                                             wborder w ls' rs' ts' bs' tl' tr' bl' br'
    where ls' = castCharToCChar ls
          rs' = castCharToCChar rs
          ts' = castCharToCChar ts
          bs' = castCharToCChar bs
          tl' = castCharToCChar tl
          tr' = castCharToCChar tr
          bl' = castCharToCChar bl
          br' = castCharToCChar br
foreign import ccall unsafe
    prefresh :: Window -> CInt -> CInt -> CInt -> CInt -> CInt -> CInt -> IO CInt

foreign import ccall unsafe
    newpad :: CInt -> CInt -> IO Window

foreign import ccall unsafe
    delwin :: Window -> IO CInt

foreign import ccall unsafe
    wborder :: Window -> CChar -> CChar -> CChar -> CChar -> CChar -> CChar -> CChar -> CChar -> IO CInt

newWin :: Int -> Int -> Int -> Int -> IO Window
newWin nlines ncolumn begin_y begin_x = throwIfNull "newwin" $
    newwin (fi nlines) (fi ncolumn) (fi begin_y) (fi begin_x)

foreign import ccall unsafe
    newwin :: CInt -> CInt -> CInt -> CInt -> IO Window

wClrToEol :: Window -> IO ()
wClrToEol w = throwIfErr_ "wclrtoeol" $ wclrtoeol w

foreign import ccall unsafe wclrtoeol :: Window -> IO CInt

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


{-# LINE 1082 "UI/HSCurses/Curses.hsc" #-}
foreign import ccall unsafe "HSCurses.h getch" getch :: IO CInt

{-# LINE 1084 "UI/HSCurses/Curses.hsc" #-}

--foreign import ccall unsafe def_prog_mode :: IO CInt
--foreign import ccall unsafe reset_prog_mode :: IO CInt
foreign import ccall unsafe flushinp :: IO CInt

foreign import ccall unsafe "HSCurses.h noqiflush" noqiflush :: IO ()

foreign import ccall unsafe "HSCurses.h beep" c_beep :: IO CInt
foreign import ccall unsafe "HSCurses.h flash" c_flash :: IO CInt

beep :: IO ()
beep = do
    br <- c_beep
    when (br /= (0)) (c_flash >> return ())
{-# LINE 1098 "UI/HSCurses/Curses.hsc" #-}

------------------------------------------------------------------------
--
-- | Map curses keys to key abstraction
--

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
    deriving (Eq,Show)

decodeKey :: CInt -> Key
decodeKey key = case key of
    _ | key >= 0 && key <= 255 -> KeyChar (chr (fromIntegral key))
    (257)         -> KeyBreak
{-# LINE 1127 "UI/HSCurses/Curses.hsc" #-}
    (258)          -> KeyDown
{-# LINE 1128 "UI/HSCurses/Curses.hsc" #-}
    (259)            -> KeyUp
{-# LINE 1129 "UI/HSCurses/Curses.hsc" #-}
    (260)          -> KeyLeft
{-# LINE 1130 "UI/HSCurses/Curses.hsc" #-}
    (261)         -> KeyRight
{-# LINE 1131 "UI/HSCurses/Curses.hsc" #-}
    (262)          -> KeyHome
{-# LINE 1132 "UI/HSCurses/Curses.hsc" #-}
    (263)     -> KeyBackspace
{-# LINE 1133 "UI/HSCurses/Curses.hsc" #-}
    _ | key >= (264) && key <= (327)
{-# LINE 1134 "UI/HSCurses/Curses.hsc" #-}
                               -> KeyF (fromIntegral (key - 264))
{-# LINE 1135 "UI/HSCurses/Curses.hsc" #-}
    (328)            -> KeyDL
{-# LINE 1136 "UI/HSCurses/Curses.hsc" #-}
    (329)            -> KeyIL
{-# LINE 1137 "UI/HSCurses/Curses.hsc" #-}
    (330)            -> KeyDC
{-# LINE 1138 "UI/HSCurses/Curses.hsc" #-}
    (331)            -> KeyIC
{-# LINE 1139 "UI/HSCurses/Curses.hsc" #-}
    (332)           -> KeyEIC
{-# LINE 1140 "UI/HSCurses/Curses.hsc" #-}
    (333)         -> KeyClear
{-# LINE 1141 "UI/HSCurses/Curses.hsc" #-}
    (334)           -> KeyEOS
{-# LINE 1142 "UI/HSCurses/Curses.hsc" #-}
    (335)           -> KeyEOL
{-# LINE 1143 "UI/HSCurses/Curses.hsc" #-}
    (336)            -> KeySF
{-# LINE 1144 "UI/HSCurses/Curses.hsc" #-}
    (337)            -> KeySR
{-# LINE 1145 "UI/HSCurses/Curses.hsc" #-}
    (338)         -> KeyNPage
{-# LINE 1146 "UI/HSCurses/Curses.hsc" #-}
    (339)         -> KeyPPage
{-# LINE 1147 "UI/HSCurses/Curses.hsc" #-}
    (340)          -> KeySTab
{-# LINE 1148 "UI/HSCurses/Curses.hsc" #-}
    (341)          -> KeyCTab
{-# LINE 1149 "UI/HSCurses/Curses.hsc" #-}
    (342)         -> KeyCATab
{-# LINE 1150 "UI/HSCurses/Curses.hsc" #-}
    (343)         -> KeyEnter
{-# LINE 1151 "UI/HSCurses/Curses.hsc" #-}
    (344)        -> KeySReset
{-# LINE 1152 "UI/HSCurses/Curses.hsc" #-}
    (345)         -> KeyReset
{-# LINE 1153 "UI/HSCurses/Curses.hsc" #-}
    (346)         -> KeyPrint
{-# LINE 1154 "UI/HSCurses/Curses.hsc" #-}
    (347)            -> KeyLL
{-# LINE 1155 "UI/HSCurses/Curses.hsc" #-}
    (348)            -> KeyA1
{-# LINE 1156 "UI/HSCurses/Curses.hsc" #-}
    (349)            -> KeyA3
{-# LINE 1157 "UI/HSCurses/Curses.hsc" #-}
    (350)            -> KeyB2
{-# LINE 1158 "UI/HSCurses/Curses.hsc" #-}
    (351)            -> KeyC1
{-# LINE 1159 "UI/HSCurses/Curses.hsc" #-}
    (352)            -> KeyC3
{-# LINE 1160 "UI/HSCurses/Curses.hsc" #-}
    (353)          -> KeyBTab
{-# LINE 1161 "UI/HSCurses/Curses.hsc" #-}
    (354)           -> KeyBeg
{-# LINE 1162 "UI/HSCurses/Curses.hsc" #-}
    (355)        -> KeyCancel
{-# LINE 1163 "UI/HSCurses/Curses.hsc" #-}
    (356)         -> KeyClose
{-# LINE 1164 "UI/HSCurses/Curses.hsc" #-}
    (357)       -> KeyCommand
{-# LINE 1165 "UI/HSCurses/Curses.hsc" #-}
    (358)          -> KeyCopy
{-# LINE 1166 "UI/HSCurses/Curses.hsc" #-}
    (359)        -> KeyCreate
{-# LINE 1167 "UI/HSCurses/Curses.hsc" #-}
    (360)           -> KeyEnd
{-# LINE 1168 "UI/HSCurses/Curses.hsc" #-}
    (361)          -> KeyExit
{-# LINE 1169 "UI/HSCurses/Curses.hsc" #-}
    (362)          -> KeyFind
{-# LINE 1170 "UI/HSCurses/Curses.hsc" #-}
    (363)          -> KeyHelp
{-# LINE 1171 "UI/HSCurses/Curses.hsc" #-}
    (364)          -> KeyMark
{-# LINE 1172 "UI/HSCurses/Curses.hsc" #-}
    (365)       -> KeyMessage
{-# LINE 1173 "UI/HSCurses/Curses.hsc" #-}
    (366)          -> KeyMove
{-# LINE 1174 "UI/HSCurses/Curses.hsc" #-}
    (367)          -> KeyNext
{-# LINE 1175 "UI/HSCurses/Curses.hsc" #-}
    (368)          -> KeyOpen
{-# LINE 1176 "UI/HSCurses/Curses.hsc" #-}
    (369)       -> KeyOptions
{-# LINE 1177 "UI/HSCurses/Curses.hsc" #-}
    (370)      -> KeyPrevious
{-# LINE 1178 "UI/HSCurses/Curses.hsc" #-}
    (371)          -> KeyRedo
{-# LINE 1179 "UI/HSCurses/Curses.hsc" #-}
    (372)     -> KeyReference
{-# LINE 1180 "UI/HSCurses/Curses.hsc" #-}
    (373)       -> KeyRefresh
{-# LINE 1181 "UI/HSCurses/Curses.hsc" #-}
    (374)       -> KeyReplace
{-# LINE 1182 "UI/HSCurses/Curses.hsc" #-}
    (375)       -> KeyRestart
{-# LINE 1183 "UI/HSCurses/Curses.hsc" #-}
    (376)        -> KeyResume
{-# LINE 1184 "UI/HSCurses/Curses.hsc" #-}
    (377)          -> KeySave
{-# LINE 1185 "UI/HSCurses/Curses.hsc" #-}
    (378)          -> KeySBeg
{-# LINE 1186 "UI/HSCurses/Curses.hsc" #-}
    (379)       -> KeySCancel
{-# LINE 1187 "UI/HSCurses/Curses.hsc" #-}
    (380)      -> KeySCommand
{-# LINE 1188 "UI/HSCurses/Curses.hsc" #-}
    (381)         -> KeySCopy
{-# LINE 1189 "UI/HSCurses/Curses.hsc" #-}
    (382)       -> KeySCreate
{-# LINE 1190 "UI/HSCurses/Curses.hsc" #-}
    (383)           -> KeySDC
{-# LINE 1191 "UI/HSCurses/Curses.hsc" #-}
    (384)           -> KeySDL
{-# LINE 1192 "UI/HSCurses/Curses.hsc" #-}
    (385)        -> KeySelect
{-# LINE 1193 "UI/HSCurses/Curses.hsc" #-}
    (386)          -> KeySEnd
{-# LINE 1194 "UI/HSCurses/Curses.hsc" #-}
    (387)          -> KeySEOL
{-# LINE 1195 "UI/HSCurses/Curses.hsc" #-}
    (388)         -> KeySExit
{-# LINE 1196 "UI/HSCurses/Curses.hsc" #-}
    (389)         -> KeySFind
{-# LINE 1197 "UI/HSCurses/Curses.hsc" #-}
    (390)         -> KeySHelp
{-# LINE 1198 "UI/HSCurses/Curses.hsc" #-}
    (391)         -> KeySHome
{-# LINE 1199 "UI/HSCurses/Curses.hsc" #-}
    (392)           -> KeySIC
{-# LINE 1200 "UI/HSCurses/Curses.hsc" #-}
    (393)         -> KeySLeft
{-# LINE 1201 "UI/HSCurses/Curses.hsc" #-}
    (394)      -> KeySMessage
{-# LINE 1202 "UI/HSCurses/Curses.hsc" #-}
    (395)         -> KeySMove
{-# LINE 1203 "UI/HSCurses/Curses.hsc" #-}
    (396)         -> KeySNext
{-# LINE 1204 "UI/HSCurses/Curses.hsc" #-}
    (397)      -> KeySOptions
{-# LINE 1205 "UI/HSCurses/Curses.hsc" #-}
    (398)     -> KeySPrevious
{-# LINE 1206 "UI/HSCurses/Curses.hsc" #-}
    (399)        -> KeySPrint
{-# LINE 1207 "UI/HSCurses/Curses.hsc" #-}
    (400)         -> KeySRedo
{-# LINE 1208 "UI/HSCurses/Curses.hsc" #-}
    (401)      -> KeySReplace
{-# LINE 1209 "UI/HSCurses/Curses.hsc" #-}
    (402)        -> KeySRight
{-# LINE 1210 "UI/HSCurses/Curses.hsc" #-}
    (403)        -> KeySRsume
{-# LINE 1211 "UI/HSCurses/Curses.hsc" #-}
    (404)         -> KeySSave
{-# LINE 1212 "UI/HSCurses/Curses.hsc" #-}
    (405)      -> KeySSuspend
{-# LINE 1213 "UI/HSCurses/Curses.hsc" #-}
    (406)         -> KeySUndo
{-# LINE 1214 "UI/HSCurses/Curses.hsc" #-}
    (407)       -> KeySuspend
{-# LINE 1215 "UI/HSCurses/Curses.hsc" #-}
    (408)          -> KeyUndo
{-# LINE 1216 "UI/HSCurses/Curses.hsc" #-}

{-# LINE 1217 "UI/HSCurses/Curses.hsc" #-}
    (410)        -> KeyResize
{-# LINE 1218 "UI/HSCurses/Curses.hsc" #-}

{-# LINE 1219 "UI/HSCurses/Curses.hsc" #-}

{-# LINE 1220 "UI/HSCurses/Curses.hsc" #-}
    (409)         -> KeyMouse
{-# LINE 1221 "UI/HSCurses/Curses.hsc" #-}

{-# LINE 1222 "UI/HSCurses/Curses.hsc" #-}
    _                          -> KeyUnknown (fromIntegral key)

keyResizeCode :: Maybe CInt

{-# LINE 1226 "UI/HSCurses/Curses.hsc" #-}
keyResizeCode = Just (410)
{-# LINE 1227 "UI/HSCurses/Curses.hsc" #-}

{-# LINE 1230 "UI/HSCurses/Curses.hsc" #-}

cERR :: CInt
cERR = -1
{-# LINE 1233 "UI/HSCurses/Curses.hsc" #-}

cKEY_UP, cKEY_DOWN, cKEY_LEFT, cKEY_RIGHT :: ChType
cKEY_UP = 259
{-# LINE 1236 "UI/HSCurses/Curses.hsc" #-}
cKEY_DOWN = 258
{-# LINE 1237 "UI/HSCurses/Curses.hsc" #-}
cKEY_LEFT = 260
{-# LINE 1238 "UI/HSCurses/Curses.hsc" #-}
cKEY_RIGHT = 261
{-# LINE 1239 "UI/HSCurses/Curses.hsc" #-}

-- cACS_BLOCK :: ChType
-- cACS_BLOCK = #const ACS_BLOCK

cTRUE :: NBool
cTRUE = 1
{-# LINE 1245 "UI/HSCurses/Curses.hsc" #-}


-- ---------------------------------------------------------------------
-- get char
--

-- ncurses ungetch and Haskell's threadWaitRead do not work together well.
-- So I decided to implement my own input queue.
ungetCh :: (Integral a) => a -> IO ()
ungetCh i =
    do debug "ungetCh called"
       writeChan inputBuf (BufDirect (fi i))

data BufData = BufDirect CInt  -- data directly available
             | DataViaGetch    -- data can be obtained by calling getch

inputBuf :: Chan BufData
inputBuf = unsafePerformIO newChan
{-# NOINLINE inputBuf #-}

getchToInputBuf :: IO ()
getchToInputBuf =
    do threadWaitRead (fi (0::Int))
       {- From the (n)curses manpage:
       Programmers  concerned  about portability should be prepared for either
       of two cases: (a) signal receipt does not interrupt getch;  (b)  signal
       receipt  interrupts getch and causes it to return ERR with errno set to
       EINTR.  Under the ncurses implementation, handled signals never  inter$B!>(B
       rupt getch.
       -}
       -- we only signalize that getch can now called without getting blocked.
       -- directly calling `getch' might result in losing the character just
       -- read (race condition).
       debug "now input available on stdin"
       writeChan inputBuf DataViaGetch
--
-- | read a character from the window
--
getCh :: IO Key
getCh =
    do debug "getCh called"
       tid <- forkIO getchToInputBuf
       d <- readChan inputBuf
       killThread tid  -- we can kill the thread savely, because the thread does
                       -- not read any data via getch
       v <- case d of
              BufDirect x ->
                do debug "getCh: getting data directly from buffer"
                   return x
              DataViaGetch ->
                do debug "getCh: getting data via getch"
                   getch -- won't block!
       case v of
         (-1) -> -- NO CODE IN THIS LINE
{-# LINE 1299 "UI/HSCurses/Curses.hsc" #-}
             do e <- getErrno
                if e `elem` [eAGAIN, eINTR]
                   then do debug "Curses.getCh returned eAGAIN or eINTR"
                           getCh
                   else throwErrno "HSCurses.Curses.getch"
         k -> let k' = decodeKey k
                  in do debug ("getCh: result = " ++ show k')
                        return k'


resizeTerminal :: Int -> Int -> IO ()


{-# LINE 1317 "UI/HSCurses/Curses.hsc" #-}
resizeTerminal _ _ = return ()

{-# LINE 1319 "UI/HSCurses/Curses.hsc" #-}

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


{-# LINE 1328 "UI/HSCurses/Curses.hsc" #-}

cursesSigWinch :: Maybe Signal

{-# LINE 1331 "UI/HSCurses/Curses.hsc" #-}
cursesSigWinch = Just (28)
{-# LINE 1332 "UI/HSCurses/Curses.hsc" #-}

{-# LINE 1335 "UI/HSCurses/Curses.hsc" #-}

------------
-- Test case
------------

cursesTest :: IO ()
cursesTest = do
    initScr
    hc <- hasColors
    when hc startColor
    ccc <- canChangeColor
    (ys,xs) <- scrSize
    cp <- colorPairs
    cs <- colors
    endWin
    putStrLn $ "ScreenSize: " ++ show (xs,ys)
    putStrLn $ "hasColors: " ++ show hc
    putStrLn $ "canChangeColor: " ++ show ccc
    putStrLn $ "colorPairs: " ++ show cp
    putStrLn $ "colors: " ++ show cs




-----------------
-- Mouse Routines
-----------------

data MouseEvent = MouseEvent {
    mouseEventId :: Int,
    mouseEventX :: Int,
    mouseEventY :: Int,
    mouseEventZ :: Int,
    mouseEventButton :: [ButtonEvent]
   } deriving(Show)

data ButtonEvent = ButtonPressed Int | ButtonReleased Int | ButtonClicked Int |
    ButtonDoubleClicked Int | ButtonTripleClicked Int | ButtonShift | ButtonControl | ButtonAlt
                deriving(Eq,Show)

withMouseEventMask :: MonadIO m => [ButtonEvent] -> m a -> m a


{-# LINE 1378 "UI/HSCurses/Curses.hsc" #-}

foreign import ccall unsafe "HSCurses.h mousemask"
    mousemask :: (Word32) -> Ptr (Word32) -> IO (Word32)
{-# LINE 1381 "UI/HSCurses/Curses.hsc" #-}

withMouseEventMask bes action = do
    ov <- liftIO $ alloca (\a ->  mousemask (besToMouseMask bes) a >> peek a)
    r <- action
    liftIO $ mousemask ov nullPtr
    return r

besToMouseMask :: [ButtonEvent] -> (Word32)
{-# LINE 1389 "UI/HSCurses/Curses.hsc" #-}
besToMouseMask bes = foldl' (.|.) 0 (map cb bes) where
    cb (ButtonPressed 1) = (2)
{-# LINE 1391 "UI/HSCurses/Curses.hsc" #-}
    cb (ButtonPressed 2) = (128)
{-# LINE 1392 "UI/HSCurses/Curses.hsc" #-}
    cb (ButtonPressed 3) = (8192)
{-# LINE 1393 "UI/HSCurses/Curses.hsc" #-}
    cb (ButtonPressed 4) = (524288)
{-# LINE 1394 "UI/HSCurses/Curses.hsc" #-}
    cb (ButtonReleased 1) = (1)
{-# LINE 1395 "UI/HSCurses/Curses.hsc" #-}
    cb (ButtonReleased 2) = (64)
{-# LINE 1396 "UI/HSCurses/Curses.hsc" #-}
    cb (ButtonReleased 3) = (4096)
{-# LINE 1397 "UI/HSCurses/Curses.hsc" #-}
    cb (ButtonReleased 4) = (262144)
{-# LINE 1398 "UI/HSCurses/Curses.hsc" #-}
    cb (ButtonClicked 1) = (4)
{-# LINE 1399 "UI/HSCurses/Curses.hsc" #-}
    cb (ButtonClicked 2) = (256)
{-# LINE 1400 "UI/HSCurses/Curses.hsc" #-}
    cb (ButtonClicked 3) = (16384)
{-# LINE 1401 "UI/HSCurses/Curses.hsc" #-}
    cb (ButtonClicked 4) = (1048576)
{-# LINE 1402 "UI/HSCurses/Curses.hsc" #-}
    cb ButtonShift = (33554432)
{-# LINE 1403 "UI/HSCurses/Curses.hsc" #-}
    cb ButtonAlt = (67108864)
{-# LINE 1404 "UI/HSCurses/Curses.hsc" #-}

{-# LINE 1405 "UI/HSCurses/Curses.hsc" #-}
    cb ButtonControl = (16777216)
{-# LINE 1406 "UI/HSCurses/Curses.hsc" #-}

{-# LINE 1409 "UI/HSCurses/Curses.hsc" #-}
    cb _ = 0



{-# LINE 1416 "UI/HSCurses/Curses.hsc" #-}




ulCorner, llCorner, urCorner, lrCorner, rTee, lTee, bTee, tTee, hLine,
    vLine, plus, s1, s9, diamond, ckBoard, degree, plMinus, bullet,
    lArrow, rArrow, dArrow, uArrow, board, lantern, block,
    s3, s7, lEqual, gEqual, pi, nEqual, sterling
    :: Char

ulCorner = chr 0x250C
llCorner = chr 0x2514
urCorner = chr 0x2510
lrCorner = chr 0x2518
rTee     = chr 0x2524
lTee     = chr 0x251C
bTee     = chr 0x2534
tTee     = chr 0x252C
hLine    = chr 0x2500
vLine    = chr 0x2502
plus     = chr 0x253C
s1       = chr 0x23BA -- was: 0xF800
s9       = chr 0x23BD -- was: 0xF804
diamond  = chr 0x25C6
ckBoard  = chr 0x2592
degree   = chr 0x00B0
plMinus  = chr 0x00B1
bullet   = chr 0x00B7
lArrow   = chr 0x2190
rArrow   = chr 0x2192
dArrow   = chr 0x2193
uArrow   = chr 0x2191
board    = chr 0x2591
lantern  = chr 0x256C
block    = chr 0x2588
s3       = chr 0x23BB -- was: 0xF801
s7       = chr 0x23BC -- was: 0xF803
lEqual   = chr 0x2264
gEqual   = chr 0x2265
pi       = chr 0x03C0
nEqual   = chr 0x2260
sterling = chr 0x00A3

{-
-- haddock doesn't like these commented out with --
   #if defined(__STDC_ISO_10646__)  && defined(HAVE_WADDNWSTR)
   #else
-}

recognize :: Char -> IO a -> (ChType -> IO a) -> IO a
recognize _ch noConvert _convert = noConvert -- Handle the most common case first.




-- ---------------------------------------------------------------------
-- code graveyard
--

{-

addStr :: String -> IO ()
addStr str =
    throwIfErr_ "addstr" $
    withCStringConv (readIORef cursesOutConv) str addstr
foreign import ccall unsafe addstr :: Ptr CChar -> IO CInt

addStrLn :: String -> IO ()
addStrLn str = addStr str >> addLn

--
-- | add a string of characters to a curses window and advance cursor
-- curs_addstr(3)
--
wAddStr :: Window -> String -> IO ()
wAddStr w str = throwIfErr_ "waddstr" $
    withCStringConv (readIORef cursesOutConv) str (waddstr w)

foreign import ccall unsafe waddstr :: Window -> Ptr CChar -> IO CInt


addGraphStr :: String -> IO ()
addGraphStr str = do
    conv <- readIORef cursesOutConv
    let
        convStr f = case f [] of
            [] -> return ()
            s  -> throwIfErr_ "addstr" $
                withCStringConv (return conv) s addstr
        loop []        acc = convStr acc
        loop (ch:str') acc = recognize
            ch
            (loop str' (acc . (ch:)))
            (\ch' -> do
                convStr acc
                throwIfErr "addch" $ addch ch'
                loop str' id)
    loop str id

addGraphStrLn :: String -> IO ()
addGraphStrLn str = do addGraphStr str; addLn

-}

-- vim: sw=4 ts=4