-- 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/Group.chs" #-}
{-# LANGUAGE CPP,EmptyDataDecls, TypeSynonymInstances, FlexibleInstances, MultiParamTypeClasses, FlexibleContexts, UndecidableInstances #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Graphics.UI.FLTK.LowLevel.Group
    (
    -- * Constructor
     groupNew,
     groupCustom,
     groupSetCurrent,
     groupCurrent,
     -- * Hierarchy
     --
     -- $hierarchy

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






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

groupSetCurrent' :: (Ptr ()) -> IO ()
groupSetCurrent' a1 =
  let {a1' = id a1} in 
  groupSetCurrent''_ a1' >>
  return ()

{-# LINE 31 "src/Graphics/UI/FLTK/LowLevel/Group.chs" #-}

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

{-# LINE 32 "src/Graphics/UI/FLTK/LowLevel/Group.chs" #-}


groupSetCurrent :: (Parent a Group) => Maybe (Ref a) -> IO ()
groupSetCurrent group = withMaybeRef group $ \groupPtr -> groupSetCurrent' groupPtr

groupCurrent :: IO (Maybe (Ref Group))
groupCurrent = groupCurrent' >>= toMaybeRef

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

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

groupNewWithLabel' :: (Int) -> (Int) -> (Int) -> (Int) -> (T.Text) -> IO ((Ptr ()))
groupNewWithLabel' 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 
  groupNewWithLabel''_ a1' a2' a3' a4' a5' >>= \res ->
  let {res' = id res} in
  return (res')

{-# LINE 41 "src/Graphics/UI/FLTK/LowLevel/Group.chs" #-}

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

overriddenGroupNewWithLabel' :: (Int) -> (Int) -> (Int) -> (Int) -> (T.Text) -> (Ptr ()) -> IO ((Ptr ()))
overriddenGroupNewWithLabel' a1 a2 a3 a4 a5 a6 =
  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 
  let {a6' = id a6} in 
  overriddenGroupNewWithLabel''_ a1' a2' a3' a4' a5' a6' >>= \res ->
  let {res' = id res} in
  return (res')

{-# LINE 49 "src/Graphics/UI/FLTK/LowLevel/Group.chs" #-}

overriddenGroupNew' :: (Int) -> (Int) -> (Int) -> (Int) -> (Ptr ()) -> IO ((Ptr ()))
overriddenGroupNew' 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' = id a5} in 
  overriddenGroupNew''_ a1' a2' a3' a4' a5' >>= \res ->
  let {res' = id res} in
  return (res')

{-# LINE 50 "src/Graphics/UI/FLTK/LowLevel/Group.chs" #-}

groupCustom :: Rectangle -> Maybe T.Text -> Maybe (Ref Group -> IO ()) -> CustomWidgetFuncs Group -> IO (Ref Group)
groupCustom rectangle l' draw' funcs' =
  widgetMaker rectangle l' draw' (Just funcs') overriddenGroupNew' overriddenGroupNewWithLabel'

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

{-# LINE 55 "src/Graphics/UI/FLTK/LowLevel/Group.chs" #-}

instance (impl ~ ( IO ())) => Op (Destroy ()) Group orig impl where
  runOp _ _ group = withRef group $ \groupPtr -> groupDestroy' groupPtr


drawChild' :: (Ptr ()) -> (Ptr ()) -> IO ()
drawChild' a1 a2 =
  let {a1' = id a1} in 
  let {a2' = id a2} in 
  drawChild''_ a1' a2' >>
  return ()

{-# LINE 60 "src/Graphics/UI/FLTK/LowLevel/Group.chs" #-}

instance (Parent a Widget, impl ~ (Ref a -> IO ())) => Op (DrawChild ()) Group orig impl where
  runOp _ _ group widget = withRef group $ \groupPtr -> withRef widget $ \widgetPtr -> drawChild' groupPtr widgetPtr

drawChildren' :: (Ptr ()) -> IO ()
drawChildren' a1 =
  let {a1' = id a1} in 
  drawChildren''_ a1' >>
  return ()

{-# LINE 64 "src/Graphics/UI/FLTK/LowLevel/Group.chs" #-}

instance (impl ~ (IO ())) => Op (DrawChildren ()) Group orig impl where
  runOp _ _ group = withRef group $ \groupPtr -> drawChildren' groupPtr

drawOutsideLabel' :: (Ptr ()) -> (Ptr ()) -> IO ()
drawOutsideLabel' a1 a2 =
  let {a1' = id a1} in 
  let {a2' = id a2} in 
  drawOutsideLabel''_ a1' a2' >>
  return ()

{-# LINE 68 "src/Graphics/UI/FLTK/LowLevel/Group.chs" #-}

instance (Parent a Widget, impl ~ (Ref a -> IO ())) => Op (DrawOutsideLabel ()) Group orig impl where
  runOp _ _ group widget = withRef group $ \groupPtr -> withRef widget $ \widgetPtr -> drawOutsideLabel' groupPtr widgetPtr

updateChild' :: (Ptr ()) -> (Ptr ()) -> IO ()
updateChild' a1 a2 =
  let {a1' = id a1} in 
  let {a2' = id a2} in 
  updateChild''_ a1' a2' >>
  return ()

{-# LINE 72 "src/Graphics/UI/FLTK/LowLevel/Group.chs" #-}

instance (Parent a Widget, impl ~ (Ref a -> IO ())) => Op (UpdateChild ()) Group orig impl where
  runOp _ _ group widget = withRef group $ \groupPtr -> withRef widget $ \widgetPtr -> updateChild' groupPtr widgetPtr

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

{-# LINE 76 "src/Graphics/UI/FLTK/LowLevel/Group.chs" #-}

instance (impl ~ ( IO ())) => Op (Begin ()) Group orig impl where
  runOp _ _ group = withRef group $ \groupPtr -> begin' groupPtr

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

{-# LINE 80 "src/Graphics/UI/FLTK/LowLevel/Group.chs" #-}

instance (impl ~ (IO ())) => Op (End ()) Group orig impl where
  runOp _ _ group = withRef group $ \groupPtr -> end' groupPtr

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

{-# LINE 84 "src/Graphics/UI/FLTK/LowLevel/Group.chs" #-}

instance (Parent a Widget, impl ~ (Ref a ->  IO (Int))) => Op (Find ()) Group orig impl where
  runOp _ _ group w = withRef group $ \groupPtr -> withRef w $ \wPtr -> find' groupPtr wPtr

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

{-# LINE 88 "src/Graphics/UI/FLTK/LowLevel/Group.chs" #-}

instance (Parent a Widget, impl ~ (Ref a->  IO ())) => Op (Add ()) Group orig impl where
  runOp _ _ group w = withRef group $ \groupPtr -> withRef w $ \wPtr -> add' groupPtr wPtr

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

{-# LINE 92 "src/Graphics/UI/FLTK/LowLevel/Group.chs" #-}

instance (Parent a Widget, impl ~ (Ref a-> Int ->  IO ())) => Op (Insert ()) Group orig impl where
  runOp _ _ group w i = withRef group $ \groupPtr -> withRef w $ \wPtr -> insert' groupPtr wPtr i

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

{-# LINE 96 "src/Graphics/UI/FLTK/LowLevel/Group.chs" #-}

instance (impl ~ ( Int ->  IO ())) => Op (RemoveIndex ()) Group orig impl where
  runOp _ _ group index' = withRef group $ \groupPtr -> removeIndex' groupPtr index'

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

{-# LINE 100 "src/Graphics/UI/FLTK/LowLevel/Group.chs" #-}

instance (Parent a Widget, impl ~ (Ref a ->  IO ())) => Op (RemoveWidget ()) Group orig impl where
  runOp _ _ group w = withRef group $ \groupPtr -> withRef w $ \wPtr -> removeWidget' groupPtr wPtr

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

{-# LINE 104 "src/Graphics/UI/FLTK/LowLevel/Group.chs" #-}

instance (impl ~ (IO ())) => Op (Clear ()) Group orig impl where
  runOp _ _ group = withRef group $ \groupPtr -> clear' groupPtr

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

{-# LINE 108 "src/Graphics/UI/FLTK/LowLevel/Group.chs" #-}

instance (Parent a Widget, impl ~ (Maybe ( Ref a ) -> IO ())) => Op (SetResizable ()) Group orig impl where
  runOp _ _ group o = withRef group $ \groupPtr -> withMaybeRef o $ \oPtr -> setResizable' groupPtr oPtr

instance (impl ~ IO ()) => Op (SetNotResizable ()) Group orig impl where
  runOp _ _ group = withRef group $ \groupPtr -> setResizable' groupPtr nullPtr

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

{-# LINE 115 "src/Graphics/UI/FLTK/LowLevel/Group.chs" #-}

instance (impl ~ ( IO (Maybe (Ref Widget)))) => Op (GetResizable ()) Group orig impl where
  runOp _ _ group = withRef group $ \groupPtr -> resizable' groupPtr >>= toMaybeRef

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

{-# LINE 119 "src/Graphics/UI/FLTK/LowLevel/Group.chs" #-}

instance (Parent a Widget, impl ~ (Ref a ->  IO ())) => Op (AddResizable ()) Group orig impl where
  runOp _ _ group o = withRef group $ \groupPtr -> withRef o $ \oPtr -> addResizable' groupPtr oPtr

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

{-# LINE 123 "src/Graphics/UI/FLTK/LowLevel/Group.chs" #-}

instance (impl ~ ( IO ())) => Op (InitSizes ()) Group orig impl where
  runOp _ _ group = withRef group $ \groupPtr -> initSizes' groupPtr

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

{-# LINE 127 "src/Graphics/UI/FLTK/LowLevel/Group.chs" #-}

instance (impl ~ ( IO (Int))) => Op (Children ()) Group orig impl where
  runOp _ _ group = withRef group $ \groupPtr -> children' groupPtr

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

{-# LINE 131 "src/Graphics/UI/FLTK/LowLevel/Group.chs" #-}

instance (impl ~ (Bool ->  IO ())) => Op (SetClipChildren ()) Group orig impl where
  runOp _ _ group c = withRef group $ \groupPtr -> setClipChildren' groupPtr c

clipChildren' :: (Ptr ()) -> IO ((Bool))
clipChildren' a1 =
  let {a1' = id a1} in 
  clipChildren''_ a1' >>= \res ->
  let {res' = cToBool res} in
  return (res')

{-# LINE 135 "src/Graphics/UI/FLTK/LowLevel/Group.chs" #-}

instance (impl ~ ( IO (Bool))) => Op (ClipChildren ()) Group orig impl where
  runOp _ _ group = withRef group $ \groupPtr -> clipChildren' groupPtr

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

{-# LINE 139 "src/Graphics/UI/FLTK/LowLevel/Group.chs" #-}

instance (Parent a Widget, impl ~ (Ref a ->  IO ())) => Op (Focus ()) Group orig impl where
  runOp _ _ group w = withRef group $ \groupPtr -> withRef w $ \wPtr -> focus' groupPtr wPtr

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

{-# LINE 143 "src/Graphics/UI/FLTK/LowLevel/Group.chs" #-}

instance (impl ~ (IO (Maybe (Ref Widget)))) => Op (DdfdesignKludge ()) Group orig impl where
  runOp _ _ group = withRef group $ \groupPtr -> ddfdesignKludge' groupPtr >>= toMaybeRef

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

{-# LINE 147 "src/Graphics/UI/FLTK/LowLevel/Group.chs" #-}

instance (Parent a Widget, impl ~ (Ref a -> Ref b ->  IO ())) => Op (InsertWithBefore ()) Group orig impl where
  runOp _ _ self w before = withRef self $ \selfPtr -> withRef w $ \wPtr -> withRef before $ \beforePtr -> insertWithBefore' selfPtr wPtr beforePtr

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

{-# LINE 151 "src/Graphics/UI/FLTK/LowLevel/Group.chs" #-}

instance (impl ~ (IO [Ref Widget])) => Op (GetArray ()) Group orig impl where
  runOp _ _ group = withRef group $ \groupPtr -> do
                    childArrayPtr <- array' groupPtr
                    numChildren <- children group
                    arrayToRefs childArrayPtr numChildren

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

{-# LINE 158 "src/Graphics/UI/FLTK/LowLevel/Group.chs" #-}

instance (impl ~ (Int ->  IO (Maybe (Ref Widget)))) => Op (GetChild ()) Group orig impl where
  runOp _ _ self n = withRef self $ \selfPtr -> child' selfPtr n >>= toMaybeRef

-- $groupfunctions
-- @
-- add:: ('Parent' a 'Widget') => 'Ref' 'Group' -> 'Ref' a-> 'IO' ()
--
-- addResizable:: ('Parent' a 'Widget') => 'Ref' 'Group' -> 'Ref' a -> 'IO' ()
--
-- begin :: 'Ref' 'Group' -> 'IO' ()
--
-- children :: 'Ref' 'Group' -> 'IO' ('Int')
--
-- clear :: 'Ref' 'Group' -> 'IO' ()
--
-- clipChildren :: 'Ref' 'Group' -> 'IO' ('Bool')
--
-- ddfdesignKludge :: 'Ref' 'Group' -> 'IO' ('Maybe' ('Ref' 'Widget'))
--
-- destroy :: 'Ref' 'Group' -> 'IO' ()
--
-- drawChild:: ('Parent' a 'Widget') => 'Ref' 'Group' -> 'Ref' a -> 'IO' ()
--
-- drawChildren :: 'Ref' 'Group' -> 'IO' ()
--
-- drawOutsideLabel:: ('Parent' a 'Widget') => 'Ref' 'Group' -> 'Ref' a -> 'IO' ()
--
-- end :: 'Ref' 'Group' -> 'IO' ()
--
-- find:: ('Parent' a 'Widget') => 'Ref' 'Group' -> 'Ref' a -> 'IO' ('Int')
--
-- focus:: ('Parent' a 'Widget') => 'Ref' 'Group' -> 'Ref' a -> 'IO' ()
--
-- getArray :: 'Ref' 'Group' -> 'IO' ['Ref' 'Widget']
--
-- getChild :: 'Ref' 'Group' -> 'Int' -> 'IO' ('Maybe' ('Ref' 'Widget'))
--
-- getResizable :: 'Ref' 'Group' -> 'IO' ('Maybe' ('Ref' 'Widget'))
--
-- initSizes :: 'Ref' 'Group' -> 'IO' ()
--
-- insert:: ('Parent' a 'Widget') => 'Ref' 'Group' -> 'Ref' a-> 'Int' -> 'IO' ()
--
-- insertWithBefore:: ('Parent' a 'Widget') => 'Ref' 'Group' -> 'Ref' a -> 'Ref' b -> 'IO' ()
--
-- removeIndex :: 'Ref' 'Group' -> 'Int' -> 'IO' ()
--
-- removeWidget:: ('Parent' a 'Widget') => 'Ref' 'Group' -> 'Ref' a -> 'IO' ()
--
-- setClipChildren :: 'Ref' 'Group' -> 'Bool' -> 'IO' ()
--
-- setNotResizable :: 'Ref' 'Group' -> 'IO' ()
--
-- setResizable:: ('Parent' a 'Widget') => 'Ref' 'Group' -> 'Maybe' ( 'Ref' a ) -> 'IO' ()
--
-- updateChild:: ('Parent' a 'Widget') => 'Ref' 'Group' -> 'Ref' a -> 'IO' ()
-- @

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

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Group.chs.h Fl_Group_set_current"
  groupSetCurrent''_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Group.chs.h Fl_Group_current"
  groupCurrent''_ :: (IO (C2HSImp.Ptr ()))

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

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

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

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

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Group.chs.h Fl_Group_Destroy"
  groupDestroy''_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Group.chs.h Fl_Group_draw_child"
  drawChild''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Group.chs.h Fl_Group_draw_children"
  drawChildren''_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Group.chs.h Fl_Group_draw_outside_label"
  drawOutsideLabel''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Group.chs.h Fl_Group_update_child"
  updateChild''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Group.chs.h Fl_Group_begin"
  begin''_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Group.chs.h Fl_Group_end"
  end''_ :: ((C2HSImp.Ptr ()) -> (IO ()))

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

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Group.chs.h Fl_Group_add"
  add''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

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

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

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Group.chs.h Fl_Group_remove_widget"
  removeWidget''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Group.chs.h Fl_Group_clear"
  clear''_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Group.chs.h Fl_Group_set_resizable"
  setResizable''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Group.chs.h Fl_Group_resizable"
  resizable''_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Group.chs.h Fl_Group_add_resizable"
  addResizable''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Group.chs.h Fl_Group_init_sizes"
  initSizes''_ :: ((C2HSImp.Ptr ()) -> (IO ()))

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

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

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Group.chs.h Fl_Group_clip_children"
  clipChildren''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CUInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Group.chs.h Fl_Group_focus"
  focus''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Group.chs.h Fl_Group__ddfdesign_kludge"
  ddfdesignKludge''_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Group.chs.h Fl_Group_insert_with_before"
  insertWithBefore''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ()))))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Group.chs.h Fl_Group_array"
  array''_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr (C2HSImp.Ptr ()))))

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