-- GENERATED by C->Haskell Compiler, version 0.16.0 Crystal Seed, 24 Jan 2009 (Haskell)
-- Edit the ORIGNAL .chs file instead!


{-# LINE 1 "./UI/NCurses/Panel.chs" #-}{-# LANGUAGE ForeignFunctionInterface #-}
-----------------------------------------------------------------------------
-- Copyright (C) 2010 John Millikin <jmillikin@gmail.com>
--
-- This program is free software: you can redistribute it and/or modify
-- it under the terms of the GNU General Public License as published by
-- the Free Software Foundation, either version 3 of the License, or
-- any later version.
--
-- This program 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 General Public License for more details.
--
-- You should have received a copy of the GNU General Public License
-- along with this program.  If not, see <http://www.gnu.org/licenses/>.
-----------------------------------------------------------------------------
-- |
-- Module: UI.NCurses.Panel
-- Copyright: 2010 John Millikin
-- License: GPL-3
--
-- Maintainer: jmillikin@gmail.com
-- Portability: portable (requires FFI)
--
-----------------------------------------------------------------------------
module UI.NCurses.Panel
	( Panel
	, newPanel
	, deletePanel
	, refreshPanels
	, panelAbove
	, panelBelow
	, panelTop
	, panelBottom
	, showPanel
	, hidePanel
	, panelHidden
	, movePanel
	, raisePanel
	, lowerPanel
	, getPanelWindow
	, replacePanelWindow
	) where
import Foreign
import Foreign.C
import UI.NCurses.Types

-- for haddock
import UI.NCurses (render)



{-# LINE 54 "./UI/NCurses/Panel.chs" #-}

{-# LINE 55 "./UI/NCurses/Panel.chs" #-}
newtype Panel = Panel { panelPtr :: Ptr Panel }

-- | Creates a new 'Panel', on top of the panel stack.
newPanel :: Window -> Curses Panel
newPanel win = Curses $ do
	p <- new_panel win
	if panelPtr p == nullPtr
		then error "newPanel: new_panel() returned NULL"
		else return p

-- | Permanently removes the given panel from the panel stack.
deletePanel :: Panel -> Curses ()
deletePanel p = Curses (del_panel p >>= checkRC "deletePanel")

-- | Updates windows to account for the current panel stack order. The user
-- must call 'render' before changes are drawn to the screen.
refreshPanels :: Curses ()
refreshPanels = Curses update_panels
{-# LINE 73 "./UI/NCurses/Panel.chs" #-}

-- | @panelAbove p@ retrieve the panel above /p/.
panelAbove :: Panel -> Curses (Maybe Panel)
panelAbove p = Curses $ do
	ptr <- panel_above p
	return $ if panelPtr ptr == nullPtr
		then Nothing
		else Just ptr

-- | @panelAbove p@ retrieve the panel below /p/.
panelBelow :: Panel -> Curses (Maybe Panel)
panelBelow p = Curses $ do
	ptr <- panel_below p
	return $ if panelPtr ptr == nullPtr
		then Nothing
		else Just ptr

-- | Retrieve the top&#x2013;most panel in the stack.
panelTop :: Curses (Maybe Panel)
panelTop = Curses $ do
	ptr <- panel_below (Panel nullPtr)
	return $ if panelPtr ptr == nullPtr
		then Nothing
		else Just ptr

-- | Retrieve the bottom&#x2013;most panel in the stack.
panelBottom :: Curses (Maybe Panel)
panelBottom = Curses $ do
	ptr <- panel_above (Panel nullPtr)
	return $ if panelPtr ptr == nullPtr
		then Nothing
		else Just ptr

-- | Makes a hidden panel visible, and places it on the top of the stack.
showPanel :: Panel -> Curses ()
showPanel p = Curses (show_panel p >>= checkRC "showPanel")

-- | Temporarily removes the given panel from the panel stack. Use
-- 'showPanel' to restore it.
hidePanel :: Panel -> Curses ()
hidePanel p = Curses (hide_panel p >>= checkRC "hidePanel")

-- | Checks if the given panel is currently visible.
panelHidden :: Panel -> Curses Bool
panelHidden p = Curses (cToBool `fmap` panel_hidden p)

-- | Move the panel so its upper&#x2013;left corner is at the new
-- coordinates.
movePanel :: Panel
          -> Integer -- ^ New upper&#x2013;left row
          -> Integer -- ^ New upper&#x2013;left column
          -> Curses ()
movePanel p row col = Curses $
	checkRC "movePanel" =<< move_panel p
		(fromInteger row)
		(fromInteger col)

-- | Raise a bottom to the top of the stack.
raisePanel :: Panel -> Curses ()
raisePanel p = Curses (top_panel p >>= checkRC "raisePanel")

-- | Lower a panel to the bottom of the stack.
lowerPanel :: Panel -> Curses ()
lowerPanel p = Curses (bottom_panel p >>= checkRC "lowerPanel")

-- | Retrieves which window a panel is drawn to.
getPanelWindow :: Panel -> Curses Window
getPanelWindow p = Curses (panel_window p)

-- | Replaces which window a panel is drawn to.
replacePanelWindow :: Panel -> Window -> Curses ()
replacePanelWindow p win = Curses $
	replace_panel p win >>= checkRC "replacePanelWindow"

foreign import ccall safe "UI/NCurses/Panel.chs.h new_panel"
  new_panel :: ((Window) -> (IO (Panel)))

foreign import ccall safe "UI/NCurses/Panel.chs.h del_panel"
  del_panel :: ((Panel) -> (IO CInt))

foreign import ccall safe "UI/NCurses/Panel.chs.h update_panels"
  update_panels :: (IO ())

foreign import ccall safe "UI/NCurses/Panel.chs.h panel_above"
  panel_above :: ((Panel) -> (IO (Panel)))

foreign import ccall safe "UI/NCurses/Panel.chs.h panel_below"
  panel_below :: ((Panel) -> (IO (Panel)))

foreign import ccall safe "UI/NCurses/Panel.chs.h show_panel"
  show_panel :: ((Panel) -> (IO CInt))

foreign import ccall safe "UI/NCurses/Panel.chs.h hide_panel"
  hide_panel :: ((Panel) -> (IO CInt))

foreign import ccall safe "UI/NCurses/Panel.chs.h panel_hidden"
  panel_hidden :: ((Panel) -> (IO CInt))

foreign import ccall safe "UI/NCurses/Panel.chs.h move_panel"
  move_panel :: ((Panel) -> (CInt -> (CInt -> (IO CInt))))

foreign import ccall safe "UI/NCurses/Panel.chs.h top_panel"
  top_panel :: ((Panel) -> (IO CInt))

foreign import ccall safe "UI/NCurses/Panel.chs.h bottom_panel"
  bottom_panel :: ((Panel) -> (IO CInt))

foreign import ccall safe "UI/NCurses/Panel.chs.h panel_window"
  panel_window :: ((Panel) -> (IO (Window)))

foreign import ccall safe "UI/NCurses/Panel.chs.h replace_panel"
  replace_panel :: ((Panel) -> ((Window) -> (IO CInt)))