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 (render) 
import           UI.NCurses.Types
newtype Panel = Panel { panelPtr :: Ptr Panel }
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
deletePanel :: Panel -> Curses ()
deletePanel p = Curses (del_panel p >>= checkRC "deletePanel")
refreshPanels :: Curses ()
refreshPanels = Curses update_panels
panelAbove :: Panel -> Curses (Maybe Panel)
panelAbove p = Curses $ do
	ptr <- panel_above p
	return $ if panelPtr ptr == nullPtr
		then Nothing
		else Just ptr
panelBelow :: Panel -> Curses (Maybe Panel)
panelBelow p = Curses $ do
	ptr <- panel_below p
	return $ if panelPtr ptr == nullPtr
		then Nothing
		else Just ptr
panelTop :: Curses (Maybe Panel)
panelTop = Curses $ do
	ptr <- panel_below (Panel nullPtr)
	return $ if panelPtr ptr == nullPtr
		then Nothing
		else Just ptr
panelBottom :: Curses (Maybe Panel)
panelBottom = Curses $ do
	ptr <- panel_above (Panel nullPtr)
	return $ if panelPtr ptr == nullPtr
		then Nothing
		else Just ptr
showPanel :: Panel -> Curses ()
showPanel p = Curses (show_panel p >>= checkRC "showPanel")
hidePanel :: Panel -> Curses ()
hidePanel p = Curses (hide_panel p >>= checkRC "hidePanel")
panelHidden :: Panel -> Curses Bool
panelHidden p = Curses (cToBool `fmap` panel_hidden p)
movePanel :: Panel
          -> Integer 
          -> Integer 
          -> Curses ()
movePanel p row col = Curses $
	checkRC "movePanel" =<< move_panel p
		(fromInteger row)
		(fromInteger col)
raisePanel :: Panel -> Curses ()
raisePanel p = Curses (top_panel p >>= checkRC "raisePanel")
lowerPanel :: Panel -> Curses ()
lowerPanel p = Curses (bottom_panel p >>= checkRC "lowerPanel")
getPanelWindow :: Panel -> Curses Window
getPanelWindow p = Curses (panel_window p)
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)))