-- GENERATED by C->Haskell Compiler, version 0.25.2 Snowboundest, 31 Oct 2014 (Haskell)
-- Edit the ORIGNAL .chs file instead!


{-# LINE 1 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}
{-# LANGUAGE CPP, RankNTypes, UndecidableInstances, GADTs, TypeSynonymInstances, FlexibleInstances, MultiParamTypeClasses, FlexibleContexts, ScopedTypeVariables #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Graphics.UI.FLTK.LowLevel.Widget
    (
     -- * Constructor
     widgetCustom,
     widgetMaker,
     -- * Custom
     CustomWidgetFuncs(..),
     defaultCustomWidgetFuncs,
     fillCustomWidgetFunctionStruct,
     customWidgetFunctionStruct,
     -- * Hierarchy
     --
     -- $hierarchy

     -- * Widget Functions
     --
     -- $widgetfunctions
    )
where



import C2HS hiding (cFromEnum, cFromBool, cToBool,cToEnum)
import Foreign.C.Types
import Graphics.UI.FLTK.LowLevel.Fl_Enumerations
import Graphics.UI.FLTK.LowLevel.Fl_Types
import Graphics.UI.FLTK.LowLevel.Utils
import Graphics.UI.FLTK.LowLevel.Dispatch
import Graphics.UI.FLTK.LowLevel.Hierarchy

type RectangleFPrim              = Ptr () -> CInt -> CInt -> CInt -> CInt -> IO ()

foreign import ccall "wrapper"
        mkWidgetEventHandler :: (Ptr () -> CInt -> IO CInt) -> IO (FunPtr (Ptr () -> CInt -> IO CInt))
foreign import ccall "wrapper"
        mkRectanglePtr :: RectangleFPrim -> IO (FunPtr RectangleFPrim)

toRectangleFPrim ::  (Ref a -> Rectangle -> IO ()) ->
                     IO (FunPtr (Ptr () -> CInt -> CInt -> CInt -> CInt -> IO ()))
toRectangleFPrim f = mkRectanglePtr $ \wPtr x_pos y_pos width height ->
  let rectangle = toRectangle (fromIntegral x_pos,
                               fromIntegral y_pos,
                               fromIntegral width,
                               fromIntegral height)
  in do
  fptr <- wrapNonNull wPtr "Null Pointer. toRectangleFPrim"
  f (wrapInRef fptr) rectangle

toEventHandlerPrim :: (Ref a -> Event -> IO Int) ->
                      IO (FunPtr (Ptr () -> CInt -> IO CInt))
toEventHandlerPrim f = mkWidgetEventHandler $
                       \wPtr eventNumber ->
                            let event = cToEnum (eventNumber :: CInt)
                            in do
                            fptr <- wrapNonNull wPtr "Null Pointer: toEventHandlerPrim"
                            result <- f (wrapInRef fptr) event
                            return $ fromIntegral result

-- | Overrideable 'Widget' functions
data CustomWidgetFuncs a =
    CustomWidgetFuncs
    {
     -- | See <http://www.fltk.org/doc-1.3/classFl__Widget.html#a1acb38c6b3cb40452ad02ccfeedbac8a Fl_Widget::draw>
     drawCustom   :: Maybe (Ref a -> IO ())
     -- | See <http://www.fltk.org/doc-1.3/classFl__Widget.html#a9cb17cc092697dfd05a3fab55856d218 Fl_Widget::handle>
    ,handleCustom :: Maybe (Ref a -> Event -> IO Int)
     -- | See <http://www.fltk.org/doc-1.3/classFl__Widget.html#aca98267e7a9b94f699ebd27d9f59e8bb Fl_Widget::resize>
    ,resizeCustom :: Maybe (Ref a -> Rectangle -> IO ())
     -- | See <http://www.fltk.org/doc-1.3/classFl__Widget.html#ab572c6fbc922bf3268b72cf9e2939606 Fl_Widget::show>
    ,showCustom   :: Maybe (Ref a -> IO ())
     -- | See <http://www.fltk.org/doc-1.3/classFl__Widget.html#a1fe8405b86da29d147dc3b5841cf181c Fl_Widget::hide>
    ,hideCustom   :: Maybe (Ref a -> IO ())
    }


-- | Fill up a struct with pointers to functions on the Haskell side that will get called instead of the default ones.
--
-- Fill up the 'Widget' part the function pointer struct.
--
-- Only of interest to 'Widget' contributors
fillCustomWidgetFunctionStruct :: forall a. (Parent a Widget) =>
                                  Ptr () ->
                                  CustomWidgetFuncs a ->
                                  IO ()
fillCustomWidgetFunctionStruct structPtr (CustomWidgetFuncs _draw' _handle' _resize' _show' _hide') = do
      toCallbackPrim `orNullFunPtr` _draw'       >>= (\ptr val -> do {pokeByteOff ptr 0 (val :: (FunPtr ((Ptr ()) -> (IO ()))))}) structPtr
      toEventHandlerPrim `orNullFunPtr` _handle' >>= (\ptr val -> do {pokeByteOff ptr 8 (val :: (FunPtr ((Ptr ()) -> (CInt -> (IO CInt)))))}) structPtr
      toRectangleFPrim `orNullFunPtr` _resize'   >>= (\ptr val -> do {pokeByteOff ptr 16 (val :: (FunPtr ((Ptr ()) -> (CInt -> (CInt -> (CInt -> (CInt -> (IO ()))))))))}) structPtr
      toCallbackPrim `orNullFunPtr` _show'       >>= (\ptr val -> do {pokeByteOff ptr 24 (val :: (FunPtr ((Ptr ()) -> (IO ()))))}) structPtr
      toCallbackPrim `orNullFunPtr` _hide'       >>= (\ptr val -> do {pokeByteOff ptr 32 (val :: (FunPtr ((Ptr ()) -> (IO ()))))}) structPtr

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

{-# LINE 94 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

-- | Given a record of functions, return a pointer to a struct with function pointers back
-- to those functions.
--
-- Only of interest to 'Widget' contributors.
customWidgetFunctionStruct :: forall a. (Parent a Widget) =>
                              CustomWidgetFuncs a ->
                              IO (Ptr ())
customWidgetFunctionStruct customWidgetFuncs' = do
  p <- virtualFuncs'
  fillCustomWidgetFunctionStruct p customWidgetFuncs'
  return p

-- | An empty set of functions to pass to 'widgetCustom'.
defaultCustomWidgetFuncs :: forall a. (Parent a Widget) => CustomWidgetFuncs a
defaultCustomWidgetFuncs = CustomWidgetFuncs
                            Nothing
                            Nothing
                            Nothing
                            Nothing
                            Nothing

-- | Lots of 'Widget' subclasses have the same constructor parameters. This function consolidates them.
--
-- Only of interest to 'Widget' contributors.
widgetMaker :: forall a. (Parent a Widget) =>
               Rectangle                                                          -- ^ Position and size
               -> Maybe String                                                    -- ^ Title
               -> Maybe (CustomWidgetFuncs a)                                     -- ^ Custom functions
               -> (Int -> Int -> Int -> Int -> IO ( Ptr ()))                      -- ^ Foreign constructor to call if neither title nor custom functions are given
               -> (Int -> Int -> Int -> Int -> String -> IO ( Ptr () ))           -- ^ Foreign constructor to call if only title is given
               -> (Int -> Int -> Int -> Int -> Ptr () -> IO ( Ptr () ))           -- ^ Foreign constructor to call if only custom functions are given
               -> (Int -> Int -> Int -> Int -> String -> Ptr () -> IO ( Ptr () )) -- ^ Foreign constructor to call if both title and custom functions are given
               -> IO (Ref a)                                                      -- ^ Reference to the widget
widgetMaker rectangle _label' customFuncs' new' newWithLabel' newWithCustomFuncs' newWithCustomFuncsLabel' =
    let (x_pos, y_pos, width, height) = fromRectangle rectangle
    in case (_label', customFuncs') of
        (Nothing,Nothing) -> new' x_pos y_pos width height >>= toRef
        ((Just l), Nothing) -> newWithLabel' x_pos y_pos width height l >>= toRef
        ((Just l), (Just fs)) -> do
          ptr <- customWidgetFunctionStruct fs
          newWithCustomFuncsLabel' x_pos y_pos width height l (castPtr ptr) >>= toRef
        (Nothing, (Just fs)) -> do
          ptr <- customWidgetFunctionStruct fs
          newWithCustomFuncs' x_pos y_pos width height (castPtr ptr) >>= toRef

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

{-# LINE 140 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

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

{-# LINE 141 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

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

{-# LINE 142 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

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

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

-- | Widget constructor.
widgetCustom :: Rectangle
                -> Maybe String
                -> CustomWidgetFuncs Widget
                -> IO (Ref Widget)
widgetCustom rectangle l' funcs' =
  widgetMaker
    rectangle
    l'
    (Just  funcs')
    widgetNew'
    widgetNewWithLabel'
    overriddenWidgetNew'
    overriddenWidgetNewWithLabel'

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

{-# LINE 159 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~  IO ()) => Op (Destroy ()) Widget orig impl where
  runOp _ _ win = swapRef win $ \winPtr -> do
    widgetDestroy' winPtr
    return nullPtr

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

{-# LINE 165 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ (Event -> IO Int)) => Op (Handle ()) Widget orig impl where
  runOp _ _ widget event = withRef widget (\p -> widgetHandle' p (fromIntegral . fromEnum $ event))

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

{-# LINE 169 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~  IO (Maybe (Ref Group))) => Op (GetParent ()) Widget orig impl where
  runOp _ _ widget = withRef widget widgetParent' >>= toMaybeRef

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

{-# LINE 173 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (Parent a Group, impl ~ (Maybe (Ref a) -> IO ())) => Op (SetParent ()) Widget orig impl where
  runOp _ _ widget group =
      withRef widget
      (\widgetPtr ->
        withMaybeRef group (\groupPtr ->
                        widgetSetParent' widgetPtr groupPtr
                      )
      )
type' :: (Ptr ()) -> IO ((Word8))
type' a1 =
  let {a1' = id a1} in 
  type''_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 182 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ IO (Word8)) => Op (GetType_ ()) Widget orig impl where
  runOp _ _ widget = withRef widget $ \widgetPtr -> type' widgetPtr
setType' :: (Ptr ()) -> (Word8) -> IO ((()))
setType' a1 a2 =
  let {a1' = id a1} in 
  let {a2' = fromIntegral a2} in 
  setType''_ a1' a2' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 185 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ (Word8 ->  IO ())) => Op (SetType ()) Widget orig impl where
  runOp _ _ widget t = withRef widget $ \widgetPtr -> setType' widgetPtr t
drawLabel' :: (Ptr ()) -> IO ((()))
drawLabel' a1 =
  let {a1' = id a1} in 
  drawLabel''_ a1' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 188 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

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

{-# LINE 189 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ (Maybe (Rectangle,Alignments) ->  IO ())) => Op (DrawLabel ()) Widget orig impl where
  runOp _ _ widget Nothing = withRef widget $ \widgetPtr -> drawLabel' widgetPtr
  runOp _ _ widget (Just (rectangle,align_)) = withRef widget $ \widgetPtr -> do
    let (x_pos,y_pos,w_pos,h_pos) = fromRectangle rectangle
    drawLabelWithXywhAlignment' widgetPtr x_pos y_pos w_pos h_pos (alignmentsToInt align_)

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

{-# LINE 196 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ IO (Int)) => Op (GetX ()) Widget orig impl where
  runOp _ _ widget = withRef widget $ \widgetPtr -> x' widgetPtr
y' :: (Ptr ()) -> IO ((Int))
y' a1 =
  let {a1' = id a1} in 
  y''_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 199 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ IO (Int)) => Op (GetY ()) Widget orig impl where
  runOp _ _ widget = withRef widget $ \widgetPtr -> y' widgetPtr
w' :: (Ptr ()) -> IO ((Int))
w' a1 =
  let {a1' = id a1} in 
  w''_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 202 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ IO (Int)) => Op (GetW ()) Widget orig impl where
  runOp _ _ widget = withRef widget $ \widgetPtr -> w' widgetPtr
h' :: (Ptr ()) -> IO ((Int))
h' a1 =
  let {a1' = id a1} in 
  h''_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 205 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ IO (Int)) => Op (GetH ()) Widget orig impl where
  runOp _ _ widget = withRef widget $ \widgetPtr -> h' widgetPtr
instance (
         FindOp orig (GetX ()) (Match obj),
         FindOp orig (GetY ()) (Match obj),
         FindOp orig (GetW ()) (Match obj),
         FindOp orig (GetH ()) (Match obj),
         Op (GetX ()) obj orig (IO Int),
         Op (GetY ()) obj orig (IO Int),
         Op (GetW ()) obj orig (IO Int),
         Op (GetH ()) obj orig (IO Int),
         impl ~ IO Rectangle
         )
         =>
         Op (GetRectangle ()) Widget orig impl where
   runOp _ _ widget = do
     _x <- getX (castTo widget :: Ref orig)
     _y <- getY (castTo widget :: Ref orig)
     _w <- getW (castTo widget :: Ref orig)
     _h <- getH (castTo widget :: Ref orig)
     return (toRectangle (_x,_y,_w,_h))
setAlign' :: (Ptr ()) -> (Int) -> IO ((()))
setAlign' a1 a2 =
  let {a1' = id a1} in 
  let {a2' = fromIntegral a2} in 
  setAlign''_ a1' a2' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 227 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ (Alignments ->  IO ())) => Op (SetAlign ()) Widget orig impl where
  runOp _ _ widget _align = withRef widget $ \widgetPtr -> setAlign' widgetPtr (alignmentsToInt _align)
align' :: (Ptr ()) -> IO ((CUInt))
align' a1 =
  let {a1' = id a1} in 
  align''_ a1' >>= \res ->
  let {res' = id res} in
  return (res')

{-# LINE 230 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ IO Alignments) => Op (GetAlign ()) Widget orig impl where
  runOp _ _ widget = withRef widget $ \widgetPtr -> align' widgetPtr >>= return . intToAlignments . fromIntegral
box' :: (Ptr ()) -> IO ((Boxtype))
box' a1 =
  let {a1' = id a1} in 
  box''_ a1' >>= \res ->
  let {res' = cToEnum res} in
  return (res')

{-# LINE 233 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ IO (Boxtype)) => Op (GetBox ()) Widget orig impl where
  runOp _ _ widget = withRef widget $ \widgetPtr -> box' widgetPtr
setBox' :: (Ptr ()) -> (Boxtype) -> IO ((()))
setBox' a1 a2 =
  let {a1' = id a1} in 
  let {a2' = cFromEnum a2} in 
  setBox''_ a1' a2' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 236 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ (Boxtype ->  IO ())) => Op (SetBox ()) Widget orig impl where
  runOp _ _ widget new_box = withRef widget $ \widgetPtr -> setBox' widgetPtr new_box
color' :: (Ptr ()) -> IO ((Color))
color' a1 =
  let {a1' = id a1} in 
  color''_ a1' >>= \res ->
  let {res' = cToColor res} in
  return (res')

{-# LINE 239 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ IO (Color)) => Op (GetColor ()) Widget orig impl where
  runOp _ _ widget = withRef widget $ \widgetPtr -> color' widgetPtr
setColor' :: (Ptr ()) -> (Color) -> IO ((()))
setColor' a1 a2 =
  let {a1' = id a1} in 
  let {a2' = cFromColor a2} in 
  setColor''_ a1' a2' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 242 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ (Color ->  IO ())) => Op (SetColor ()) Widget orig impl where
  runOp _ _ widget bg = withRef widget $ \widgetPtr -> setColor' widgetPtr bg
setColorWithBgSel' :: (Ptr ()) -> (Color) -> (Color) -> IO ((()))
setColorWithBgSel' a1 a2 a3 =
  let {a1' = id a1} in 
  let {a2' = cFromColor a2} in 
  let {a3' = cFromColor a3} in 
  setColorWithBgSel''_ a1' a2' a3' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 245 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ (Color -> Color ->  IO ())) => Op (SetColorWithBgSel ()) Widget orig impl where
  runOp _ _ widget bg a = withRef widget $ \widgetPtr -> setColorWithBgSel' widgetPtr bg a
selectionColor' :: (Ptr ()) -> IO ((Color))
selectionColor' a1 =
  let {a1' = id a1} in 
  selectionColor''_ a1' >>= \res ->
  let {res' = cToColor res} in
  return (res')

{-# LINE 248 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ IO (Color)) => Op (GetSelectionColor ()) Widget orig impl where
  runOp _ _ widget = withRef widget $ \widgetPtr -> selectionColor' widgetPtr
setSelectionColor' :: (Ptr ()) -> (Color) -> IO ((()))
setSelectionColor' a1 a2 =
  let {a1' = id a1} in 
  let {a2' = cFromColor a2} in 
  setSelectionColor''_ a1' a2' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 251 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ (Color ->  IO ())) => Op (SetSelectionColor ()) Widget orig impl where
  runOp _ _ widget a = withRef widget $ \widgetPtr -> setSelectionColor' widgetPtr a
label' :: (Ptr ()) -> IO ((String))
label' a1 =
  let {a1' = id a1} in 
  label''_ a1' >>= \res ->
  let {res' = unsafeFromCString res} in
  return (res')

{-# LINE 254 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ IO (String)) => Op (GetLabel ()) Widget orig impl where
  runOp _ _ widget = withRef widget $ \widgetPtr -> label' widgetPtr
copyLabel' :: (Ptr ()) -> (String) -> IO ((()))
copyLabel' a1 a2 =
  let {a1' = id a1} in 
  let {a2' = unsafeToCString a2} in 
  copyLabel''_ a1' a2' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 257 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ (String ->  IO ())) => Op (CopyLabel ()) Widget orig impl where
  runOp _ _ widget new_label = withRef widget $ \widgetPtr -> copyLabel' widgetPtr new_label
setLabel' :: (Ptr ()) -> (String) -> IO ((()))
setLabel' a1 a2 =
  let {a1' = id a1} in 
  let {a2' = unsafeToCString a2} in 
  setLabel''_ a1' a2' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 260 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ ( String -> IO ())) => Op (SetLabel ()) Widget orig impl where
  runOp _ _ widget text = withRef widget $ \widgetPtr -> setLabel' widgetPtr text
labeltype' :: (Ptr ()) -> IO ((Labeltype))
labeltype' a1 =
  let {a1' = id a1} in 
  labeltype''_ a1' >>= \res ->
  let {res' = cToEnum res} in
  return (res')

{-# LINE 263 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ (IO (Labeltype))) => Op (GetLabeltype ()) Widget orig impl where
  runOp _ _ widget = withRef widget $ \widgetPtr -> labeltype' widgetPtr
setLabeltype' :: (Ptr ()) -> (Labeltype) -> IO ((()))
setLabeltype' a1 a2 =
  let {a1' = id a1} in 
  let {a2' = cFromEnum a2} in 
  setLabeltype''_ a1' a2' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 266 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ ( Labeltype ->  IO ())) => Op (SetLabeltype ()) Widget orig impl where
  runOp _ _ widget a = withRef widget $ \widgetPtr -> setLabeltype' widgetPtr a
labelcolor' :: (Ptr ()) -> IO ((Color))
labelcolor' a1 =
  let {a1' = id a1} in 
  labelcolor''_ a1' >>= \res ->
  let {res' = cToColor res} in
  return (res')

{-# LINE 269 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ (IO (Color))) => Op (GetLabelcolor ()) Widget orig impl where
  runOp _ _ widget = withRef widget $ \widgetPtr -> labelcolor' widgetPtr
setLabelcolor' :: (Ptr ()) -> (Color) -> IO ((()))
setLabelcolor' a1 a2 =
  let {a1' = id a1} in 
  let {a2' = cFromColor a2} in 
  setLabelcolor''_ a1' a2' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 272 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ ( Color ->  IO ())) => Op (SetLabelcolor ()) Widget orig impl where
  runOp _ _ widget c = withRef widget $ \widgetPtr -> setLabelcolor' widgetPtr c
labelfont' :: (Ptr ()) -> IO ((Font))
labelfont' a1 =
  let {a1' = id a1} in 
  labelfont''_ a1' >>= \res ->
  let {res' = cToFont res} in
  return (res')

{-# LINE 275 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ (IO (Font))) => Op (GetLabelfont ()) Widget orig impl where
  runOp _ _ widget = withRef widget $ \widgetPtr -> labelfont' widgetPtr
setLabelfont' :: (Ptr ()) -> (Font) -> IO ((()))
setLabelfont' a1 a2 =
  let {a1' = id a1} in 
  let {a2' = cFromFont a2} in 
  setLabelfont''_ a1' a2' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 278 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ ( Font ->  IO ())) => Op (SetLabelfont ()) Widget orig impl where
  runOp _ _ widget c = withRef widget $ \widgetPtr -> setLabelfont' widgetPtr c
labelsize' :: (Ptr ()) -> IO ((CInt))
labelsize' a1 =
  let {a1' = id a1} in 
  labelsize''_ a1' >>= \res ->
  let {res' = id res} in
  return (res')

{-# LINE 281 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ (IO (FontSize))) => Op (GetLabelsize ()) Widget orig impl where
  runOp _ _ widget = withRef widget $ \widgetPtr -> labelsize' widgetPtr >>= return . FontSize
setLabelsize' :: (Ptr ()) -> (CInt) -> IO ((()))
setLabelsize' a1 a2 =
  let {a1' = id a1} in 
  let {a2' = id a2} in 
  setLabelsize''_ a1' a2' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 284 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ ( FontSize ->  IO ())) => Op (SetLabelsize ()) Widget orig impl where
  runOp _ _ widget (FontSize pix) = withRef widget $ \widgetPtr -> setLabelsize' widgetPtr pix
image' :: (Ptr ()) -> IO (((Ref Image)))
image' a1 =
  let {a1' = id a1} in 
  image''_ a1' >>= \res ->
  let {res' = unsafeToRef res} in
  return (res')

{-# LINE 287 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ (IO (Ref Image))) => Op (GetImage ()) Widget orig impl where
  runOp _ _ widget = withRef widget $ \widgetPtr -> image' widgetPtr
setImage' :: (Ptr ()) -> (Ptr ()) -> IO ((()))
setImage' a1 a2 =
  let {a1' = id a1} in 
  let {a2' = id a2} in 
  setImage''_ a1' a2' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 290 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (Parent a Image, impl ~ (Maybe( Ref a ) ->  IO ())) => Op (SetImage ()) Widget orig impl where
  runOp _ _ widget pix = withRef widget $ \widgetPtr -> withMaybeRef pix $ \pixPtr -> setImage' widgetPtr pixPtr
deimage' :: (Ptr ()) -> IO (((Ref Image)))
deimage' a1 =
  let {a1' = id a1} in 
  deimage''_ a1' >>= \res ->
  let {res' = unsafeToRef res} in
  return (res')

{-# LINE 293 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ (IO (Ref Image))) => Op (GetDeimage ()) Widget orig impl where
  runOp _ _ widget = withRef widget $ \widgetPtr -> deimage' widgetPtr
setDeimage' :: (Ptr ()) -> (Ptr ()) -> IO ((()))
setDeimage' a1 a2 =
  let {a1' = id a1} in 
  let {a2' = id a2} in 
  setDeimage''_ a1' a2' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 296 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (Parent a Image, impl ~ (Maybe( Ref a ) ->  IO ())) => Op (SetDeimage ()) Widget orig impl where
  runOp _ _ widget pix = withRef widget $ \widgetPtr -> withMaybeRef pix $ \pixPtr -> setDeimage' widgetPtr pixPtr
tooltip' :: (Ptr ()) -> IO ((String))
tooltip' a1 =
  let {a1' = id a1} in 
  tooltip''_ a1' >>= \res ->
  let {res' = unsafeFromCString res} in
  return (res')

{-# LINE 299 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ (IO (String))) => Op (GetTooltip ()) Widget orig impl where
  runOp _ _ widget = withRef widget $ \widgetPtr -> tooltip' widgetPtr
copyTooltip' :: (Ptr ()) -> (String) -> IO ((()))
copyTooltip' a1 a2 =
  let {a1' = id a1} in 
  let {a2' = unsafeToCString a2} in 
  copyTooltip''_ a1' a2' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 302 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ ( String ->  IO ())) => Op (CopyTooltip ()) Widget orig impl where
  runOp _ _ widget text = withRef widget $ \widgetPtr -> copyTooltip' widgetPtr text
setTooltip' :: (Ptr ()) -> (String) -> IO ((()))
setTooltip' a1 a2 =
  let {a1' = id a1} in 
  let {a2' = unsafeToCString a2} in 
  setTooltip''_ a1' a2' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 305 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ ( String ->  IO ())) => Op (SetTooltip ()) Widget orig impl where
  runOp _ _ widget text = withRef widget $ \widgetPtr -> setTooltip' widgetPtr text
when' :: (Ptr ()) -> IO ((CInt))
when' a1 =
  let {a1' = id a1} in 
  when''_ a1' >>= \res ->
  let {res' = id res} in
  return (res')

{-# LINE 308 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ IO [When]) => Op (GetWhen ()) Widget orig impl where
  runOp _ _ widget = withRef widget $ \widgetPtr ->
      when' widgetPtr >>= return . extract allWhen
setWhen' :: (Ptr ()) -> (Word8) -> IO ((()))
setWhen' a1 a2 =
  let {a1' = id a1} in 
  let {a2' = fromIntegral a2} in 
  setWhen''_ a1' a2' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 312 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ ( [When] ->  IO ())) => Op (SetWhen ()) Widget orig impl where
  runOp _ _ widget i = withRef widget $ \widgetPtr ->
    setWhen' widgetPtr (fromIntegral . combine $ i)
do_callback' :: (Ptr ()) -> IO ((()))
do_callback' a1 =
  let {a1' = id a1} in 
  do_callback''_ a1' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 316 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ (IO ())) => Op (DoCallback ()) Widget orig impl where
  runOp _ _ widget = withRef widget $ \widgetPtr -> do_callback' widgetPtr
visible' :: (Ptr ()) -> IO ((Bool))
visible' a1 =
  let {a1' = id a1} in 
  visible''_ a1' >>= \res ->
  let {res' = cToBool res} in
  return (res')

{-# LINE 319 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ (IO Bool)) => Op (GetVisible ()) Widget orig impl where
  runOp _ _ widget = withRef widget $ \widgetPtr -> visible' widgetPtr
visibleR' :: (Ptr ()) -> IO ((Bool))
visibleR' a1 =
  let {a1' = id a1} in 
  visibleR''_ a1' >>= \res ->
  let {res' = cToBool res} in
  return (res')

{-# LINE 322 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ (IO Bool)) => Op (GetVisibleR ()) Widget orig impl where
  runOp _ _ widget = withRef widget $ \widgetPtr -> visibleR' widgetPtr
showSuper' :: (Ptr ()) -> IO ((()))
showSuper' a1 =
  let {a1' = id a1} in 
  showSuper''_ a1' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 325 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ (IO ())) => Op (ShowWidgetSuper ()) Widget orig impl where
  runOp _ _ widget = withRef widget $ \widgetPtr -> showSuper' widgetPtr
show' :: (Ptr ()) -> IO ((()))
show' a1 =
  let {a1' = id a1} in 
  show''_ a1' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 328 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ (IO ())) => Op (ShowWidget ()) Widget orig impl where
  runOp _ _ widget = withRef widget $ \widgetPtr -> show' widgetPtr
hideSuper' :: (Ptr ()) -> IO ((()))
hideSuper' a1 =
  let {a1' = id a1} in 
  hideSuper''_ a1' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 331 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ (IO ())) => Op (HideSuper ()) Widget orig impl where
  runOp _ _ widget = withRef widget $ \widgetPtr -> hideSuper' widgetPtr
hide' :: (Ptr ()) -> IO ((()))
hide' a1 =
  let {a1' = id a1} in 
  hide''_ a1' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 334 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ (IO ())) => Op (Hide ()) Widget orig impl where
  runOp _ _ widget = withRef widget $ \widgetPtr -> hide' widgetPtr
setVisible' :: (Ptr ()) -> IO ((()))
setVisible' a1 =
  let {a1' = id a1} in 
  setVisible''_ a1' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 337 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ (IO ())) => Op (SetVisible ()) Widget orig impl where
  runOp _ _ widget = withRef widget $ \widgetPtr -> setVisible' widgetPtr
clearVisible' :: (Ptr ()) -> IO ((()))
clearVisible' a1 =
  let {a1' = id a1} in 
  clearVisible''_ a1' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 340 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ (IO ())) => Op (ClearVisible ()) Widget orig impl where
  runOp _ _ widget = withRef widget $ \widgetPtr -> clearVisible' widgetPtr
active' :: (Ptr ()) -> IO ((Bool))
active' a1 =
  let {a1' = id a1} in 
  active''_ a1' >>= \res ->
  let {res' = cToBool res} in
  return (res')

{-# LINE 343 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ (IO (Bool))) => Op (Active ()) Widget orig impl where
  runOp _ _ widget = withRef widget $ \widgetPtr -> active' widgetPtr
activeR' :: (Ptr ()) -> IO ((Bool))
activeR' a1 =
  let {a1' = id a1} in 
  activeR''_ a1' >>= \res ->
  let {res' = cToBool res} in
  return (res')

{-# LINE 346 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ (IO (Bool))) => Op (ActiveR ()) Widget orig impl where
  runOp _ _ widget = withRef widget $ \widgetPtr -> activeR' widgetPtr
activate' :: (Ptr ()) -> IO ((()))
activate' a1 =
  let {a1' = id a1} in 
  activate''_ a1' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 349 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ (IO ())) => Op (Activate ()) Widget orig impl where
  runOp _ _ widget = withRef widget $ \widgetPtr -> activate' widgetPtr
deactivate' :: (Ptr ()) -> IO ((()))
deactivate' a1 =
  let {a1' = id a1} in 
  deactivate''_ a1' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 352 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ (IO ())) => Op (Deactivate ()) Widget orig impl where
  runOp _ _ widget = withRef widget $ \widgetPtr -> deactivate' widgetPtr
output' :: (Ptr ()) -> IO ((Int))
output' a1 =
  let {a1' = id a1} in 
  output''_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 355 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ (IO (Int))) => Op (GetOutput ()) Widget orig impl where
  runOp _ _ widget = withRef widget $ \widgetPtr -> output' widgetPtr
setOutput' :: (Ptr ()) -> IO ((()))
setOutput' a1 =
  let {a1' = id a1} in 
  setOutput''_ a1' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 358 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ (IO ())) => Op (SetOutput ()) Widget orig impl where
  runOp _ _ widget = withRef widget $ \widgetPtr -> setOutput' widgetPtr
clearOutput' :: (Ptr ()) -> IO ((()))
clearOutput' a1 =
  let {a1' = id a1} in 
  clearOutput''_ a1' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 361 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ (IO ())) => Op (ClearOutput ()) Widget orig impl where
  runOp _ _ widget = withRef widget $ \widgetPtr -> clearOutput' widgetPtr
takesevents' :: (Ptr ()) -> IO ((Bool))
takesevents' a1 =
  let {a1' = id a1} in 
  takesevents''_ a1' >>= \res ->
  let {res' = cToBool res} in
  return (res')

{-# LINE 364 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ (IO (Bool))) => Op (Takesevents ()) Widget orig impl where
  runOp _ _ widget = withRef widget $ \widgetPtr -> takesevents' widgetPtr
setActive' :: (Ptr ()) -> IO ((()))
setActive' a1 =
  let {a1' = id a1} in 
  setActive''_ a1' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 367 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ (IO ())) => Op (SetActive ()) Widget orig impl where
  runOp _ _ widget = withRef widget $ \widgetPtr -> setActive' widgetPtr
clearActive' :: (Ptr ()) -> IO ((()))
clearActive' a1 =
  let {a1' = id a1} in 
  clearActive''_ a1' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 370 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ (IO ())) => Op (ClearActive ()) Widget orig impl where
  runOp _ _ widget = withRef widget $ \widgetPtr -> clearActive' widgetPtr
setChanged' :: (Ptr ()) -> IO ((()))
setChanged' a1 =
  let {a1' = id a1} in 
  setChanged''_ a1' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 373 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ (IO ())) => Op (SetChanged ()) Widget orig impl where
  runOp _ _ widget = withRef widget $ \widgetPtr -> setChanged' widgetPtr
clearChanged' :: (Ptr ()) -> IO ((()))
clearChanged' a1 =
  let {a1' = id a1} in 
  clearChanged''_ a1' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 376 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ (IO ())) => Op (ClearChanged ()) Widget orig impl where
  runOp _ _ widget = withRef widget $ \widgetPtr -> clearChanged' widgetPtr
changed' :: (Ptr ()) -> IO ((Bool))
changed' a1 =
  let {a1' = id a1} in 
  changed''_ a1' >>= \res ->
  let {res' = cToBool res} in
  return (res')

{-# LINE 379 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ (IO (Bool))) => Op (Changed ()) Widget orig impl where
  runOp _ _ widget = withRef widget $ \widgetPtr -> changed' widgetPtr
takeFocus' :: (Ptr ()) -> IO ((Int))
takeFocus' a1 =
  let {a1' = id a1} in 
  takeFocus''_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 382 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ (IO (Either NoChange ()))) => Op (TakeFocus ()) Widget orig impl where
  runOp _ _ widget = withRef widget $ \widgetPtr -> takeFocus' widgetPtr >>= return . successOrNoChange
setVisibleFocus' :: (Ptr ()) -> IO ((()))
setVisibleFocus' a1 =
  let {a1' = id a1} in 
  setVisibleFocus''_ a1' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 385 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ (IO ())) => Op (SetVisibleFocus ()) Widget orig impl where
  runOp _ _ widget = withRef widget $ \widgetPtr -> setVisibleFocus' widgetPtr
clearVisibleFocus' :: (Ptr ()) -> IO ((()))
clearVisibleFocus' a1 =
  let {a1' = id a1} in 
  clearVisibleFocus''_ a1' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 388 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ (IO ())) => Op (ClearVisibleFocus ()) Widget orig impl where
  runOp _ _ widget = withRef widget $ \widgetPtr -> clearVisibleFocus' widgetPtr
modifyVisibleFocus' :: (Ptr ()) -> (Int) -> IO ((()))
modifyVisibleFocus' a1 a2 =
  let {a1' = id a1} in 
  let {a2' = fromIntegral a2} in 
  modifyVisibleFocus''_ a1' a2' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 391 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ ( Int ->  IO ())) => Op (ModifyVisibleFocus ()) Widget orig impl where
  runOp _ _ widget v = withRef widget $ \widgetPtr -> modifyVisibleFocus' widgetPtr v
visibleFocus' :: (Ptr ()) -> IO ((Bool))
visibleFocus' a1 =
  let {a1' = id a1} in 
  visibleFocus''_ a1' >>= \res ->
  let {res' = cToBool res} in
  return (res')

{-# LINE 394 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ (IO (Bool))) => Op (GetVisibleFocus ()) Widget orig impl where
  runOp _ _ widget = withRef widget $ \widgetPtr -> visibleFocus' widgetPtr
contains' :: (Ptr ()) -> (Ptr ()) -> IO ((Int))
contains' a1 a2 =
  let {a1' = id a1} in 
  let {a2' = id a2} in 
  contains''_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 397 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (Parent a Widget, impl ~  (Ref a ->  IO Int)) => Op (Contains ()) Widget orig impl where
  runOp _ _ widget otherWidget = withRef widget $ \widgetPtr -> withRef otherWidget $ \otherWidgetPtr -> contains' widgetPtr otherWidgetPtr
inside' :: (Ptr ()) -> (Ptr ()) -> IO ((Int))
inside' a1 a2 =
  let {a1' = id a1} in 
  let {a2' = id a2} in 
  inside''_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 400 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (Parent a Widget, impl ~ (Ref a -> IO (Int))) => Op (Inside ()) Widget orig impl where
  runOp _ _ widget otherWidget = withRef widget $ \widgetPtr -> withRef otherWidget $ \otherWidgetPtr -> inside' widgetPtr otherWidgetPtr
redraw' :: (Ptr ()) -> IO ((()))
redraw' a1 =
  let {a1' = id a1} in 
  redraw''_ a1' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 403 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ (IO ())) => Op (Redraw ()) Widget orig impl where
  runOp _ _ widget = withRef widget $ \widgetPtr -> redraw' widgetPtr
redrawLabel' :: (Ptr ()) -> IO ((()))
redrawLabel' a1 =
  let {a1' = id a1} in 
  redrawLabel''_ a1' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 406 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ (IO ())) => Op (RedrawLabel ()) Widget orig impl where
  runOp _ _ widget = withRef widget $ \widgetPtr -> redrawLabel' widgetPtr
damage' :: (Ptr ()) -> IO ((Word8))
damage' a1 =
  let {a1' = id a1} in 
  damage''_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 409 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ (IO (Word8))) => Op (GetDamage ()) Widget orig impl where
  runOp _ _ widget = withRef widget $ \widgetPtr -> damage' widgetPtr
clearDamageWithBitmask' :: (Ptr ()) -> (Word8) -> IO ((()))
clearDamageWithBitmask' a1 a2 =
  let {a1' = id a1} in 
  let {a2' = fromIntegral a2} in 
  clearDamageWithBitmask''_ a1' a2' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 412 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ ( Word8 ->  IO ())) => Op (ClearDamageWithBitmask ()) Widget orig impl where
  runOp _ _ widget c = withRef widget $ \widgetPtr -> clearDamageWithBitmask' widgetPtr c
clearDamage' :: (Ptr ()) -> IO ((()))
clearDamage' a1 =
  let {a1' = id a1} in 
  clearDamage''_ a1' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 415 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ (IO ())) => Op (ClearDamage ()) Widget orig impl where
  runOp _ _ widget = withRef widget $ \widgetPtr -> clearDamage' widgetPtr
damageWithText' :: (Ptr ()) -> (Word8) -> IO ((()))
damageWithText' a1 a2 =
  let {a1' = id a1} in 
  let {a2' = fromIntegral a2} in 
  damageWithText''_ a1' a2' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 418 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ ( Word8 ->  IO ())) => Op (GetDamageWithText ()) Widget orig impl where
  runOp _ _ widget c = withRef widget $ \widgetPtr -> damageWithText' widgetPtr c
damageInsideWidget' :: (Ptr ()) -> (Word8) -> (Int) -> (Int) -> (Int) -> (Int) -> IO ((()))
damageInsideWidget' a1 a2 a3 a4 a5 a6 =
  let {a1' = id a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  let {a5' = fromIntegral a5} in 
  let {a6' = fromIntegral a6} in 
  damageInsideWidget''_ a1' a2' a3' a4' a5' a6' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 421 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ ( Word8 -> Rectangle ->  IO ())) => Op (GetDamageInsideWidget ()) Widget orig impl where
  runOp _ _ widget c rectangle = withRef widget $ \widgetPtr -> do
    let (x_pos,y_pos,w_pos,h_pos) = fromRectangle rectangle
    damageInsideWidget' widgetPtr c x_pos y_pos w_pos h_pos
measureLabel' :: (Ptr ()) -> IO ((Int), (Int))
measureLabel' a1 =
  let {a1' = id a1} in 
  alloca $ \a2' -> 
  alloca $ \a3' -> 
  measureLabel''_ a1' a2' a3' >>
  peekIntConv  a2'>>= \a2'' -> 
  peekIntConv  a3'>>= \a3'' -> 
  return (a2'', a3'')

{-# LINE 426 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ ( IO (Size))) => Op (MeasureLabel ()) Widget orig impl where
  runOp _ _ widget = withRef widget $ \widgetPtr -> measureLabel' widgetPtr >>= \(width, height) -> return $ Size (Width width) (Height height)
window' :: (Ptr ()) -> IO ((Ptr ()))
window' a1 =
  let {a1' = id a1} in 
  window''_ a1' >>= \res ->
  let {res' = id res} in
  return (res')

{-# LINE 429 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ (IO (Maybe (Ref Window)))) => Op (GetWindow ()) Widget orig impl where
  runOp _ _ widget = withRef widget $ \widgetPtr -> window' widgetPtr >>= toMaybeRef
topWindow' :: (Ptr ()) -> IO ((Ptr ()))
topWindow' a1 =
  let {a1' = id a1} in 
  topWindow''_ a1' >>= \res ->
  let {res' = id res} in
  return (res')

{-# LINE 432 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ (IO (Maybe (Ref Window)))) => Op (GetTopWindow ()) Widget orig impl where
  runOp _ _ widget = withRef widget $ \widgetPtr -> (topWindow' widgetPtr) >>= toMaybeRef
topWindowOffset' :: (Ptr ()) -> IO ((Int), (Int))
topWindowOffset' a1 =
  let {a1' = id a1} in 
  alloca $ \a2' -> 
  alloca $ \a3' -> 
  topWindowOffset''_ a1' a2' a3' >>
  peekIntConv  a2'>>= \a2'' -> 
  peekIntConv  a3'>>= \a3'' -> 
  return (a2'', a3'')

{-# LINE 435 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ ( IO (Position))) => Op (GetTopWindowOffset ()) Widget orig impl where
  runOp _ _ widget = withRef widget $ \widgetPtr -> topWindowOffset' widgetPtr >>= \(x_pos,y_pos) -> return $ Position (X x_pos) (Y y_pos)
resizeSuper' :: (Ptr ()) -> (Int) -> (Int) -> (Int) -> (Int) -> IO ((()))
resizeSuper' a1 a2 a3 a4 a5 =
  let {a1' = id a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  let {a5' = fromIntegral a5} in 
  resizeSuper''_ a1' a2' a3' a4' a5' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 438 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ ( Rectangle ->  IO ())) => Op (ResizeSuper ()) Widget orig impl where
  runOp _ _ widget rectangle = withRef widget $ \widgetPtr -> do
    let (x_pos,y_pos,w_pos,h_pos) = fromRectangle rectangle
    resizeSuper' widgetPtr x_pos y_pos w_pos h_pos
resize' :: (Ptr ()) -> (Int) -> (Int) -> (Int) -> (Int) -> IO ((()))
resize' a1 a2 a3 a4 a5 =
  let {a1' = id a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  let {a5' = fromIntegral a5} in 
  resize''_ a1' a2' a3' a4' a5' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 443 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ ( Rectangle -> IO ())) => Op (Resize ()) Widget orig impl where
  runOp _ _ widget rectangle = withRef widget $ \widgetPtr -> do
    let (x_pos,y_pos,w_pos,h_pos) = fromRectangle rectangle
    resize' widgetPtr x_pos y_pos w_pos h_pos
setCallback' :: (Ptr ()) -> (FunPtr CallbackWithUserDataPrim) -> IO ((()))
setCallback' a1 a2 =
  let {a1' = id a1} in 
  let {a2' = id a2} in 
  setCallback''_ a1' a2' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 448 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ ((Ref orig -> IO ()) -> IO ())) => Op (SetCallback ()) Widget orig impl where
  runOp _ _ widget callback = withRef widget $ \widgetPtr -> do
    ptr <- toCallbackPrimWithUserData callback
    setCallback' widgetPtr (castFunPtr ptr)

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

{-# LINE 454 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ (IO (Bool))) => Op (HasCallback ()) Widget orig impl where
  runOp _ _ widget = withRef widget $ \widgetPtr -> do
    res <- hasCallback' widgetPtr
    return $ if (res == 0) then False else True
widgetDrawBox' :: (Ptr ()) -> IO ((()))
widgetDrawBox' a1 =
  let {a1' = id a1} in 
  widgetDrawBox''_ a1' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 459 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

widgetDrawBoxWithTC' :: (Ptr ()) -> (Boxtype) -> (Color) -> IO ((()))
widgetDrawBoxWithTC' a1 a2 a3 =
  let {a1' = id a1} in 
  let {a2' = cFromEnum a2} in 
  let {a3' = cFromColor a3} in 
  widgetDrawBoxWithTC''_ a1' a2' a3' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 460 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

widgetDrawBoxWithTXywhC' :: (Ptr ()) -> (Boxtype) -> (Int) -> (Int) -> (Int) -> (Int) -> (Color) -> IO ((()))
widgetDrawBoxWithTXywhC' a1 a2 a3 a4 a5 a6 a7 =
  let {a1' = id a1} in 
  let {a2' = cFromEnum a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  let {a5' = fromIntegral a5} in 
  let {a6' = fromIntegral a6} in 
  let {a7' = cFromColor a7} in 
  widgetDrawBoxWithTXywhC''_ a1' a2' a3' a4' a5' a6' a7' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 461 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ ( IO ())) => Op (DrawBox ()) Widget orig impl where
  runOp _ _ widget = withRef widget $ \widgetPtr -> widgetDrawBox' widgetPtr
instance (impl ~ ( Boxtype -> Color -> Maybe Rectangle -> IO ())) => Op (DrawBoxWithBoxtype ()) Widget orig impl where
  runOp _ _ widget bx c Nothing =
    withRef widget $ \widgetPtr -> widgetDrawBoxWithTC' widgetPtr bx c
  runOp _ _ widget bx c (Just r) =
              withRef widget $ \widgetPtr -> do
                let (x_pos,y_pos,w_pos,h_pos) = fromRectangle r
                widgetDrawBoxWithTXywhC' widgetPtr bx x_pos y_pos w_pos h_pos c
widgetDrawBackdrop' :: (Ptr ()) -> IO ((()))
widgetDrawBackdrop' a1 =
  let {a1' = id a1} in 
  widgetDrawBackdrop''_ a1' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 471 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ ( IO ())) => Op (DrawBackdrop ()) Widget orig impl where
  runOp _ _ widget = withRef widget $ \widgetPtr -> widgetDrawBackdrop' widgetPtr

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

{-# LINE 475 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

widgetDrawFocusWithTXywh' :: (Ptr ()) -> (Boxtype) -> (Int) -> (Int) -> (Int) -> (Int) -> IO ((()))
widgetDrawFocusWithTXywh' a1 a2 a3 a4 a5 a6 =
  let {a1' = id a1} in 
  let {a2' = cFromEnum a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  let {a5' = fromIntegral a5} in 
  let {a6' = fromIntegral a6} in 
  widgetDrawFocusWithTXywh''_ a1' a2' a3' a4' a5' a6' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 476 "src/Graphics/UI/FLTK/LowLevel/Widget.chs" #-}

instance (impl ~ ( Maybe (Boxtype, Rectangle) -> IO ())) => Op (DrawFocus ()) Widget orig impl where
  runOp _ _ widget Nothing =
                withRef widget $ \ widgetPtr -> widgetDrawFocus' widgetPtr
  runOp _ _ widget (Just (bx, r)) =
                withRef widget $ \widgetPtr -> do
                  let (x_pos,y_pos,w_pos,h_pos) = fromRectangle r
                  widgetDrawFocusWithTXywh' widgetPtr bx x_pos y_pos w_pos h_pos

-- $widgetfunctions
-- @
--
-- activate :: 'Ref' 'Widget' -> 'IO' ()
--
-- active :: 'Ref' 'Widget' -> 'IO' ('Bool')
--
-- activeR :: 'Ref' 'Widget' -> 'IO' ('Bool')
--
-- changed :: 'Ref' 'Widget' -> 'IO' ('Bool')
--
-- clearActive :: 'Ref' 'Widget' -> 'IO' ()
--
-- clearChanged :: 'Ref' 'Widget' -> 'IO' ()
--
-- clearDamage :: 'Ref' 'Widget' -> 'IO' ()
--
-- clearDamageWithBitmask :: 'Ref' 'Widget' -> 'Word8' -> 'IO' ()
--
-- clearOutput :: 'Ref' 'Widget' -> 'IO' ()
--
-- clearVisible :: 'Ref' 'Widget' -> 'IO' ()
--
-- clearVisibleFocus :: 'Ref' 'Widget' -> 'IO' ()
--
-- contains:: ('Parent' a 'Widget') => 'Ref' 'Widget' -> 'Ref' a -> 'IO' 'Int'
--
-- copyLabel :: 'Ref' 'Widget' -> 'String' -> 'IO' ()
--
-- copyTooltip :: 'Ref' 'Widget' -> 'String' -> 'IO' ()
--
-- deactivate :: 'Ref' 'Widget' -> 'IO' ()
--
-- destroy :: 'Ref' 'Widget' -> 'IO' ()
--
-- drawBackdrop :: 'Ref' 'Widget' -> 'IO' ()
--
-- drawBox :: 'Ref' 'Widget' -> 'IO' ()
--
-- drawBoxWithBoxtype :: 'Ref' 'Widget' -> 'Boxtype' -> 'Color' -> 'Maybe' 'Rectangle' -> 'IO' ()
--
-- drawFocus :: 'Ref' 'Widget' -> 'Maybe' ('Boxtype', 'Rectangle') -> 'IO' ()
--
-- drawLabel :: 'Ref' 'Widget' -> 'Maybe' ('Rectangle,Alignments') -> 'IO' ()
--
-- getAlign :: 'Ref' 'Widget' -> 'IO' 'Alignments'
--
-- getBox :: 'Ref' 'Widget' -> 'IO' ('Boxtype')
--
-- getColor :: 'Ref' 'Widget' -> 'IO' ('Color')
--
-- getDamage :: 'Ref' 'Widget' -> 'IO' ('Word8')
--
-- getDamageInsideWidget :: 'Ref' 'Widget' -> 'Word8' -> 'Rectangle' -> 'IO' ()
--
-- getDamageWithText :: 'Ref' 'Widget' -> 'Word8' -> 'IO' ()
--
-- getDeimage :: 'Ref' 'Widget' -> 'IO' ('Ref' 'Image')
--
-- getH :: 'Ref' 'Widget' -> 'IO' ('Int')
--
-- getImage :: 'Ref' 'Widget' -> 'IO' ('Ref' 'Image')
--
-- getLabel :: 'Ref' 'Widget' -> 'IO' ('String')
--
-- getLabelcolor :: 'Ref' 'Widget' -> 'IO' ('Color')
--
-- getLabelfont :: 'Ref' 'Widget' -> 'IO' ('Font')
--
-- getLabelsize :: 'Ref' 'Widget' -> 'IO' ('FontSize')
--
-- getLabeltype :: 'Ref' 'Widget' -> 'IO' ('Labeltype')
--
-- getOutput :: 'Ref' 'Widget' -> 'IO' ('Int')
--
-- getParent :: 'Ref' 'Widget' -> 'IO' ('Maybe' ('Ref' 'Group'))
--
-- getRectangle:: ('FindOp' orig ('GetX' ()) ('Match' obj), 'FindOp' orig ('GetY' ()) ('Match' obj), 'FindOp' orig ('GetW' ()) ('Match' obj), 'FindOp' orig ('GetH' ()) ('Match' obj), 'Op' ('GetX' ()) obj orig ('IO' 'Int',) 'Op' ('GetY' ()) obj orig ('IO' 'Int',) 'Op' ('GetW' ()) obj orig ('IO' 'Int',) 'Op' ('GetH' ()) obj orig ('IO' 'Int',)) => 'Ref' 'Widget' -> 'IO' 'Rectangle'
--
-- getSelectionColor :: 'Ref' 'Widget' -> 'IO' ('Color')
--
-- getTooltip :: 'Ref' 'Widget' -> 'IO' ('String')
--
-- getTopWindow :: 'Ref' 'Widget' -> 'IO' ('Maybe' ('Ref' 'Window'))
--
-- getTopWindowOffset :: 'Ref' 'Widget' -> 'IO' ('Position')
--
-- getType_ :: 'Ref' 'Widget' -> 'IO' ('Word8')
--
-- getVisible :: 'Ref' 'Widget' -> 'IO' 'Bool'
--
-- getVisibleFocus :: 'Ref' 'Widget' -> 'IO' ('Bool')
--
-- getVisibleR :: 'Ref' 'Widget' -> 'IO' 'Bool'
--
-- getW :: 'Ref' 'Widget' -> 'IO' ('Int')
--
-- getWhen :: 'Ref' 'Widget' -> 'IO' ['When']
--
-- getWindow :: 'Ref' 'Widget' -> 'IO' ('Maybe' ('Ref' 'Window'))
--
-- getX :: 'Ref' 'Widget' -> 'IO' ('Int')
--
-- getY :: 'Ref' 'Widget' -> 'IO' ('Int')
--
-- handle :: 'Ref' 'Widget' -> 'Event' -> 'IO' 'Int'
--
-- hasCallback :: 'Ref' 'Widget' -> 'IO' ('Bool')
--
-- hide :: 'Ref' 'Widget' -> 'IO' ()
--
-- hideSuper :: 'Ref' 'Widget' -> 'IO' ()
--
-- inside:: ('Parent' a 'Widget') => 'Ref' 'Widget' -> 'Ref' a -> 'IO' ('Int')
--
-- measureLabel :: 'Ref' 'Widget' -> 'IO' ('Size')
--
-- modifyVisibleFocus :: 'Ref' 'Widget' -> 'Int' -> 'IO' ()
--
-- redraw :: 'Ref' 'Widget' -> 'IO' ()
--
-- redrawLabel :: 'Ref' 'Widget' -> 'IO' ()
--
-- resize :: 'Ref' 'Widget' -> 'Rectangle' -> 'IO' ()
--
-- resizeSuper :: 'Ref' 'Widget' -> 'Rectangle' -> 'IO' ()
--
-- setActive :: 'Ref' 'Widget' -> 'IO' ()
--
-- setAlign :: 'Ref' 'Widget' -> 'Alignments' -> 'IO' ()
--
-- setBox :: 'Ref' 'Widget' -> 'Boxtype' -> 'IO' ()
--
-- setCallback :: 'Ref' 'Widget' -> ('Ref' orig -> 'IO' ()) -> 'IO' ()
--
-- setChanged :: 'Ref' 'Widget' -> 'IO' ()
--
-- setColor :: 'Ref' 'Widget' -> 'Color' -> 'IO' ()
--
-- setColorWithBgSel :: 'Ref' 'Widget' -> 'Color' -> 'Color' -> 'IO' ()
--
-- setDeimage:: ('Parent' a 'Image') => 'Ref' 'Widget' -> 'Maybe'( 'Ref' a ) -> 'IO' ()
--
-- setImage:: ('Parent' a 'Image') => 'Ref' 'Widget' -> 'Maybe'( 'Ref' a ) -> 'IO' ()
--
-- setLabel :: 'Ref' 'Widget' -> 'String' -> 'IO' ()
--
-- setLabelcolor :: 'Ref' 'Widget' -> 'Color' -> 'IO' ()
--
-- setLabelfont :: 'Ref' 'Widget' -> 'Font' -> 'IO' ()
--
-- setLabelsize :: 'Ref' 'Widget' -> 'FontSize' -> 'IO' ()
--
-- setLabeltype :: 'Ref' 'Widget' -> 'Labeltype' -> 'IO' ()
--
-- setOutput :: 'Ref' 'Widget' -> 'IO' ()
--
-- setParent:: ('Parent' a 'Group') => 'Ref' 'Widget' -> 'Maybe' ('Ref' a) -> 'IO' ()
--
-- setSelectionColor :: 'Ref' 'Widget' -> 'Color' -> 'IO' ()
--
-- setTooltip :: 'Ref' 'Widget' -> 'String' -> 'IO' ()
--
-- setType :: 'Ref' 'Widget' -> 'Word8' -> 'IO' ()
--
-- setVisible :: 'Ref' 'Widget' -> 'IO' ()
--
-- setVisibleFocus :: 'Ref' 'Widget' -> 'IO' ()
--
-- setWhen :: 'Ref' 'Widget' -> ['When'] -> 'IO' ()
--
-- showWidget :: 'Ref' 'Widget' -> 'IO' ()
--
-- showWidgetSuper :: 'Ref' 'Widget' -> 'IO' ()
--
-- takeFocus :: 'Ref' 'Widget' -> 'IO' ('Either' 'NoChange' ())
--
-- takesevents :: 'Ref' 'Widget' -> 'IO' ('Bool')
-- @


-- $hierarchy
-- @
-- "Graphics.UI.FLTK.LowLevel.Widget"
-- @

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_default_virtual_funcs"
  virtualFuncs''_ :: (IO (Ptr ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_New"
  widgetNew''_ :: (CInt -> (CInt -> (CInt -> (CInt -> (IO (Ptr ()))))))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_New_WithLabel"
  widgetNewWithLabel''_ :: (CInt -> (CInt -> (CInt -> (CInt -> ((Ptr CChar) -> (IO (Ptr ())))))))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_OverriddenWidget_New_WithLabel"
  overriddenWidgetNewWithLabel''_ :: (CInt -> (CInt -> (CInt -> (CInt -> ((Ptr CChar) -> ((Ptr ()) -> (IO (Ptr ()))))))))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_OverriddenWidget_New"
  overriddenWidgetNew''_ :: (CInt -> (CInt -> (CInt -> (CInt -> ((Ptr ()) -> (IO (Ptr ())))))))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_Destroy"
  widgetDestroy''_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_handle"
  widgetHandle''_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_parent"
  widgetParent''_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_set_parent"
  widgetSetParent''_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_type"
  type''_ :: ((Ptr ()) -> (IO CUChar))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_set_type"
  setType''_ :: ((Ptr ()) -> (CUChar -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_draw_label"
  drawLabel''_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_draw_label_with_xywh_alignment"
  drawLabelWithXywhAlignment''_ :: ((Ptr ()) -> (CInt -> (CInt -> (CInt -> (CInt -> (CUInt -> (IO ())))))))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_x"
  x''_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_y"
  y''_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_w"
  w''_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_h"
  h''_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_set_align"
  setAlign''_ :: ((Ptr ()) -> (CUInt -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_align"
  align''_ :: ((Ptr ()) -> (IO CUInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_box"
  box''_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_set_box"
  setBox''_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_color"
  color''_ :: ((Ptr ()) -> (IO CUInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_set_color"
  setColor''_ :: ((Ptr ()) -> (CUInt -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_set_color_with_bg_sel"
  setColorWithBgSel''_ :: ((Ptr ()) -> (CUInt -> (CUInt -> (IO ()))))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_selection_color"
  selectionColor''_ :: ((Ptr ()) -> (IO CUInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_set_selection_color"
  setSelectionColor''_ :: ((Ptr ()) -> (CUInt -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_label"
  label''_ :: ((Ptr ()) -> (IO (Ptr CChar)))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_copy_label"
  copyLabel''_ :: ((Ptr ()) -> ((Ptr CChar) -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_set_label"
  setLabel''_ :: ((Ptr ()) -> ((Ptr CChar) -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_labeltype"
  labeltype''_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_set_labeltype"
  setLabeltype''_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_labelcolor"
  labelcolor''_ :: ((Ptr ()) -> (IO CUInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_set_labelcolor"
  setLabelcolor''_ :: ((Ptr ()) -> (CUInt -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_labelfont"
  labelfont''_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_set_labelfont"
  setLabelfont''_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_labelsize"
  labelsize''_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_set_labelsize"
  setLabelsize''_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_image"
  image''_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_set_image"
  setImage''_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_deimage"
  deimage''_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_set_deimage"
  setDeimage''_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_tooltip"
  tooltip''_ :: ((Ptr ()) -> (IO (Ptr CChar)))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_copy_tooltip"
  copyTooltip''_ :: ((Ptr ()) -> ((Ptr CChar) -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_set_tooltip"
  setTooltip''_ :: ((Ptr ()) -> ((Ptr CChar) -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_when"
  when''_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_set_when"
  setWhen''_ :: ((Ptr ()) -> (CUChar -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_do_callback"
  do_callback''_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_visible"
  visible''_ :: ((Ptr ()) -> (IO CUInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_visible_r"
  visibleR''_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_show_super"
  showSuper''_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_show"
  show''_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_hide_super"
  hideSuper''_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_hide"
  hide''_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_set_visible"
  setVisible''_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_clear_visible"
  clearVisible''_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_active"
  active''_ :: ((Ptr ()) -> (IO CUInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_active_r"
  activeR''_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_activate"
  activate''_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_deactivate"
  deactivate''_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_output"
  output''_ :: ((Ptr ()) -> (IO CUInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_set_output"
  setOutput''_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_clear_output"
  clearOutput''_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_takesevents"
  takesevents''_ :: ((Ptr ()) -> (IO CUInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_set_active"
  setActive''_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_clear_active"
  clearActive''_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_set_changed"
  setChanged''_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_clear_changed"
  clearChanged''_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_changed"
  changed''_ :: ((Ptr ()) -> (IO CUInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_take_focus"
  takeFocus''_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_set_visible_focus"
  setVisibleFocus''_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_clear_visible_focus"
  clearVisibleFocus''_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_modify_visible_focus"
  modifyVisibleFocus''_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_visible_focus"
  visibleFocus''_ :: ((Ptr ()) -> (IO CUInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_contains"
  contains''_ :: ((Ptr ()) -> ((Ptr ()) -> (IO CInt)))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_inside"
  inside''_ :: ((Ptr ()) -> ((Ptr ()) -> (IO CInt)))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_redraw"
  redraw''_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_redraw_label"
  redrawLabel''_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_damage"
  damage''_ :: ((Ptr ()) -> (IO CUChar))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_clear_damage_with_bitmask"
  clearDamageWithBitmask''_ :: ((Ptr ()) -> (CUChar -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_clear_damage"
  clearDamage''_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_damage_with_text"
  damageWithText''_ :: ((Ptr ()) -> (CUChar -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_damage_inside_widget"
  damageInsideWidget''_ :: ((Ptr ()) -> (CUChar -> (CInt -> (CInt -> (CInt -> (CInt -> (IO ())))))))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_measure_label"
  measureLabel''_ :: ((Ptr ()) -> ((Ptr CInt) -> ((Ptr CInt) -> (IO ()))))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_window"
  window''_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_top_window"
  topWindow''_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_top_window_offset"
  topWindowOffset''_ :: ((Ptr ()) -> ((Ptr CInt) -> ((Ptr CInt) -> (IO (Ptr ())))))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_resize_super"
  resizeSuper''_ :: ((Ptr ()) -> (CInt -> (CInt -> (CInt -> (CInt -> (IO ()))))))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_resize"
  resize''_ :: ((Ptr ()) -> (CInt -> (CInt -> (CInt -> (CInt -> (IO ()))))))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_set_callback"
  setCallback''_ :: ((Ptr ()) -> ((FunPtr ((Ptr ()) -> ((Ptr ()) -> (IO ())))) -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_has_callback"
  hasCallback''_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_draw_box"
  widgetDrawBox''_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_draw_box_with_tc"
  widgetDrawBoxWithTC''_ :: ((Ptr ()) -> (CInt -> (CUInt -> (IO ()))))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_draw_box_with_txywhc"
  widgetDrawBoxWithTXywhC''_ :: ((Ptr ()) -> (CInt -> (CInt -> (CInt -> (CInt -> (CInt -> (CUInt -> (IO ()))))))))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_draw_backdrop"
  widgetDrawBackdrop''_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_draw_focus"
  widgetDrawFocus''_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Widget.chs.h Fl_Widget_draw_focus_with_txywh"
  widgetDrawFocusWithTXywh''_ :: ((Ptr ()) -> (CInt -> (CInt -> (CInt -> (CInt -> (CInt -> (IO ())))))))