-- GENERATED by C->Haskell Compiler, version 0.28.1 Switcheroo, 1 April 2016 (Haskell)
-- Edit the ORIGNAL .chs file instead!


{-# LINE 1 "src/Graphics/UI/FLTK/LowLevel/Wizard.chs" #-}
{-# LANGUAGE CPP, ExistentialQuantification, TypeSynonymInstances, FlexibleInstances, MultiParamTypeClasses, FlexibleContexts, ScopedTypeVariables, UndecidableInstances #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Graphics.UI.FLTK.LowLevel.Wizard
    (
     wizardNew
     -- * Hierarchy
     --
     -- $hierarchy

     -- * Functions
     --
     -- $functions
    )
where
import qualified Foreign.C.Types as C2HSImp
import qualified Foreign.Ptr as C2HSImp





import C2HS hiding (cFromEnum, cFromBool, cToBool,cToEnum)
import Foreign.C.Types
import Graphics.UI.FLTK.LowLevel.Fl_Types
import Graphics.UI.FLTK.LowLevel.Utils
import Graphics.UI.FLTK.LowLevel.Hierarchy
import Graphics.UI.FLTK.LowLevel.Dispatch
import qualified Data.Text as T

wizardNew' :: (Int) -> (Int) -> (Int) -> (Int) -> IO ((Ptr ()))
wizardNew' a1 a2 a3 a4 =
  let {a1' = fromIntegral a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  wizardNew''_ a1' a2' a3' a4' >>= \res ->
  let {res' = id res} in
  return (res')

{-# LINE 26 "src/Graphics/UI/FLTK/LowLevel/Wizard.chs" #-}

wizardNewWithLabel' :: (Int) -> (Int) -> (Int) -> (Int) -> (T.Text) -> IO ((Ptr ()))
wizardNewWithLabel' a1 a2 a3 a4 a5 =
  let {a1' = fromIntegral a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  let {a5' = unsafeToCString a5} in 
  wizardNewWithLabel''_ a1' a2' a3' a4' a5' >>= \res ->
  let {res' = id res} in
  return (res')

{-# LINE 27 "src/Graphics/UI/FLTK/LowLevel/Wizard.chs" #-}

wizardNew :: Rectangle -> Maybe T.Text -> IO (Ref Wizard)
wizardNew rectangle label' =
    let (x_pos, y_pos, width, height) = fromRectangle rectangle
    in case label' of
        (Just l') -> wizardNewWithLabel' x_pos y_pos width height l' >>= toRef
        Nothing -> wizardNew' x_pos y_pos width height >>= toRef

wizardDestroy' :: (Ptr ()) -> IO ((()))
wizardDestroy' a1 =
  let {a1' = id a1} in 
  wizardDestroy''_ a1' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 35 "src/Graphics/UI/FLTK/LowLevel/Wizard.chs" #-}

instance (impl ~ (IO ())) => Op (Destroy ()) Wizard orig impl where
  runOp _ _ wizard = swapRef wizard $ \wizardPtr -> do
    wizardDestroy' wizardPtr
    return nullPtr
wizardNext' :: (Ptr ()) -> IO ()
wizardNext' a1 =
  let {a1' = id a1} in 
  wizardNext''_ a1' >>
  return ()

{-# LINE 40 "src/Graphics/UI/FLTK/LowLevel/Wizard.chs" #-}

instance (impl ~ (IO ())) => Op (Next ()) Wizard orig impl where
  runOp _ _ wizard = withRef wizard $ \wizardPtr -> wizardNext' wizardPtr
wizardPrev' :: (Ptr ()) -> IO ()
wizardPrev' a1 =
  let {a1' = id a1} in 
  wizardPrev''_ a1' >>
  return ()

{-# LINE 43 "src/Graphics/UI/FLTK/LowLevel/Wizard.chs" #-}

instance (impl ~ (IO ())) => Op (Prev ()) Wizard orig impl where
  runOp _ _ wizard = withRef wizard $ \wizardPtr -> wizardPrev' wizardPtr
wizardSetValue' :: (Ptr ()) -> (Ptr ()) -> IO ()
wizardSetValue' a1 a2 =
  let {a1' = id a1} in 
  let {a2' = id a2} in 
  wizardSetValue''_ a1' a2' >>
  return ()

{-# LINE 46 "src/Graphics/UI/FLTK/LowLevel/Wizard.chs" #-}

instance (Parent a Widget, impl ~ ( Maybe ( Ref a ) -> IO ())) => Op (SetValue ()) Wizard orig impl where
  runOp _ _ wizard widget =
    withRef wizard $ \wizardPtr ->
      withMaybeRef widget $ \widgetPtr ->
        wizardSetValue' wizardPtr widgetPtr
wizardValue' :: (Ptr ()) -> IO ((Ptr ()))
wizardValue' a1 =
  let {a1' = id a1} in 
  wizardValue''_ a1' >>= \res ->
  let {res' = id res} in
  return (res')

{-# LINE 52 "src/Graphics/UI/FLTK/LowLevel/Wizard.chs" #-}

instance (impl ~ (IO (Maybe (Ref Widget)))) => Op (GetValue ()) Wizard orig impl where
  runOp _ _ wizard =
    withRef wizard $ \wizardPtr -> wizardValue' wizardPtr >>= toMaybeRef

-- $functions
-- @
--
-- destroy :: 'Ref' 'Wizard' -> 'IO' ()
--
-- getValue :: 'Ref' 'Wizard' -> 'IO' ('Maybe' ('Ref' 'Widget'))
--
-- next :: 'Ref' 'Wizard' -> 'IO' ()
--
-- prev :: 'Ref' 'Wizard' -> 'IO' ()
--
-- setValue:: ('Parent' a 'Widget') => 'Ref' 'Wizard' -> 'Maybe' ( 'Ref' a ) -> 'IO' ()
-- @

-- $hierarchy
-- @
-- "Graphics.UI.FLTK.LowLevel.Widget"
--  |
--  v
-- "Graphics.UI.FLTK.LowLevel.Group"
--  |
--  v
-- "Graphics.UI.FLTK.LowLevel.Wizard"
-- @

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Wizard.chs.h Fl_Wizard_New"
  wizardNew''_ :: (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO (C2HSImp.Ptr ()))))))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Wizard.chs.h Fl_Wizard_New_WithLabel"
  wizardNewWithLabel''_ :: (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CChar) -> (IO (C2HSImp.Ptr ())))))))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Wizard.chs.h Fl_Wizard_Destroy"
  wizardDestroy''_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Wizard.chs.h Fl_Wizard_next"
  wizardNext''_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Wizard.chs.h Fl_Wizard_prev"
  wizardPrev''_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Wizard.chs.h Fl_Wizard_set_value"
  wizardSetValue''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Wizard.chs.h Fl_Wizard_value"
  wizardValue''_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))