{-# LANGUAGE CPP, ForeignFunctionInterface #-} module Graphics.UI.FLTK.Window (newWindow, Window, shown, run) where import Graphics.UI.FLTK.Group import Graphics.UI.FLTK.Widget import Foreign.Ptr -- | Type for top level windows. newtype Window = Window (Ptr Window) -- | Class for top level windows. class Window_C a where _window :: a -> Ptr Window instance Widget_C Window where _widget (Window p) = castPtr p instance Group_C Window where _group (Window p) = castPtr p instance Window_C Window where _window (Window p) = p foreign import ccall "Fl_Window_new" _new :: Int -> Int -> Int -> Int -> IO Window -- | Create a new top level window. newWindow :: Int->Int->Int->Int->[Prop Window]->IO Window newWindow x y w h l = do w <- _new x y w h set w l return w foreign import ccall "run" _run :: IO () run :: Window_C c => c -> IO () run w = set w [ shown := True ] >> _run foreign import ccall "fl_Window_shown_AG" fl_Window_shown_AG :: Ptr Window -> IO Bool foreign import ccall "fl_Window_shown_AS" fl_Window_shown_AS :: Ptr Window -> Bool -> IO () -- | Toggle a whether a window is shown or hidden. shown :: Window_C c => Attr c Bool shown = Attr (fl_Window_shown_AG._window) (\c v -> fl_Window_shown_AS (_window c) v)