-- GENERATED by C->Haskell Compiler, version 0.28.5 Switcheroo, 25 November 2017 (Haskell)
-- Edit the ORIGNAL .chs file instead!


{-# LINE 1 "src/Graphics/UI/FLTK/LowLevel/Base/Window.chs" #-}
{-# LANGUAGE CPP, UndecidableInstances, TypeSynonymInstances, FlexibleInstances, MultiParamTypeClasses, FlexibleContexts, ExistentialQuantification #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Graphics.UI.FLTK.LowLevel.Base.Window
    (
     CustomWindowFuncs(..),
     OptionalSizeRangeArgs(..),
     PositionSpec(..),
     WindowType(..),
     defaultCustomWindowFuncs,
     fillCustomWidgetFunctionStruct,
     defaultOptionalSizeRangeArgs,
     windowCustom,
     windowNew,
     windowMaker,
     currentWindow
   , handleWindowBase
   , resizeWindowBase
   , hideWindowBase
   , showWidgetWindowBase
   , flushWindowBase
     -- * Hierarchy
     --
     -- $hierarchy

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






import Foreign
import Foreign.C
import Graphics.UI.FLTK.LowLevel.Fl_Types
import Graphics.UI.FLTK.LowLevel.Fl_Enumerations
import Graphics.UI.FLTK.LowLevel.Utils
import Graphics.UI.FLTK.LowLevel.Dispatch
import qualified Data.Text as T
import Graphics.UI.FLTK.LowLevel.Hierarchy
import Graphics.UI.FLTK.LowLevel.Base.Widget

data WindowType = SingleWindowType
                | DoubleWindowType
  deriving (Show,Eq)
instance Enum WindowType where
  succ SingleWindowType = DoubleWindowType
  succ DoubleWindowType = error "WindowType.succ: DoubleWindowType has no successor"

  pred DoubleWindowType = SingleWindowType
  pred SingleWindowType = error "WindowType.pred: SingleWindowType has no predecessor"

  enumFromTo from to = go from
    where
      end = fromEnum to
      go v = case compare (fromEnum v) end of
                 LT -> v : go (succ v)
                 EQ -> [v]
                 GT -> []

  enumFrom from = enumFromTo from DoubleWindowType

  fromEnum SingleWindowType = 240
  fromEnum DoubleWindowType = 241

  toEnum 240 = SingleWindowType
  toEnum 241 = DoubleWindowType
  toEnum unmatched = error ("WindowType.toEnum: Cannot match " ++ show unmatched)

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


data PositionSpec = ByPosition Position
                  | forall a. (Parent a WidgetBase) => ByWidget (Ref a)

data CustomWindowFuncs a =
    CustomWindowFuncs {
      flushCustom :: Maybe (Ref a -> IO ())
    }

data OptionalSizeRangeArgs = OptionalSizeRangeArgs {
      maxw :: Maybe Int,
      maxh :: Maybe Int,
      dw :: Maybe Int,
      dh :: Maybe Int,
      aspect :: Maybe Bool
    }

optionalSizeRangeArgsToStruct :: OptionalSizeRangeArgs -> IO (Ptr ())
optionalSizeRangeArgsToStruct args = do
  p <- mallocBytes 20
{-# LINE 70 "src/Graphics/UI/FLTK/LowLevel/Base/Window.chs" #-}

  (\ptr val -> do {C2HSImp.pokeByteOff ptr 0 (val :: C2HSImp.CInt)}) p $ maybe 0 fromIntegral (maxw args)
  (\ptr val -> do {C2HSImp.pokeByteOff ptr 4 (val :: C2HSImp.CInt)}) p $ maybe 0 fromIntegral (maxh args)
  (\ptr val -> do {C2HSImp.pokeByteOff ptr 8 (val :: C2HSImp.CInt)}) p $ maybe 0 fromIntegral (dw args)
  (\ptr val -> do {C2HSImp.pokeByteOff ptr 12 (val :: C2HSImp.CInt)}) p $ maybe 0 fromIntegral (dh args)
  (\ptr val -> do {C2HSImp.pokeByteOff ptr 16 (val :: C2HSImp.CInt)}) p $ maybe 0 fromBool (aspect args)
  return p

defaultOptionalSizeRangeArgs :: OptionalSizeRangeArgs
defaultOptionalSizeRangeArgs = OptionalSizeRangeArgs Nothing Nothing Nothing Nothing Nothing

fillCustomWindowFunctionStruct :: forall a. (Parent a WindowBase) =>
                                  Ptr () ->
                                  CustomWindowFuncs a ->
                                  IO ()
fillCustomWindowFunctionStruct structPtr (CustomWindowFuncs _flush') =
  toCallbackPrim  `orNullFunPtr` _flush' >>= (\ptr val -> do {C2HSImp.pokeByteOff ptr 64 (val :: (C2HSImp.FunPtr ((C2HSImp.Ptr ()) -> (IO ()))))}) structPtr

defaultCustomWindowFuncs :: forall a. (Parent a WindowBase) => CustomWindowFuncs a
defaultCustomWindowFuncs = CustomWindowFuncs Nothing

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

{-# LINE 91 "src/Graphics/UI/FLTK/LowLevel/Base/Window.chs" #-}

windowMaker :: forall a b. (Parent a WindowBase, Parent b WidgetBase) =>
               Size ->
               Maybe Position ->
               Maybe T.Text ->
               Maybe (Ref b -> IO ()) ->
               CustomWidgetFuncs b ->
               CustomWindowFuncs a ->
               (Int -> Int -> Ptr () -> IO (Ptr ())) ->
               (Int -> Int -> CString -> Ptr () -> IO (Ptr ())) ->
               (Int -> Int -> Int -> Int -> Ptr () -> IO (Ptr ())) ->
               (Int -> Int -> Int -> Int -> CString -> Ptr () -> IO (Ptr ())) ->
               IO (Ref a)
windowMaker (Size (Width w) (Height h))
            position
            title
            draw'
            customWidgetFuncs'
            customWindowFuncs'
            custom'
            customWithLabel'
            customXY'
            customXYWithLabel' =
     do
       p <- virtualFuncs'
       fillCustomWidgetFunctionStruct p draw' customWidgetFuncs'
       fillCustomWindowFunctionStruct p customWindowFuncs'
       ref <- case (position, title) of
                (Nothing, Nothing) -> custom' w h p >>= toRef
                (Just (Position (X x) (Y y)), Nothing) -> customXY' x y w h p >>= toRef
                (Just (Position (X x) (Y y)), (Just l')) -> copyTextToCString l' >>= \l'' -> customXYWithLabel' x y w h l'' p >>= toRef
                (Nothing, (Just l')) -> copyTextToCString l' >>= \l'' -> customWithLabel' w h l'' p >>= toRef
       setFlag (safeCast ref :: Ref WindowBase) WidgetFlagCopiedLabel
       setFlag (safeCast ref :: Ref WindowBase) WidgetFlagCopiedTooltip
       return ref

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

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

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

{-# LINE 128 "src/Graphics/UI/FLTK/LowLevel/Base/Window.chs" #-}

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

{-# LINE 129 "src/Graphics/UI/FLTK/LowLevel/Base/Window.chs" #-}

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

{-# LINE 130 "src/Graphics/UI/FLTK/LowLevel/Base/Window.chs" #-}

windowCustom :: Size                        -- ^ Size of this window
             -> Maybe Position              -- ^ Optional position of this window
             -> Maybe T.Text                -- ^ Optional label
             -> Maybe (Ref Window -> IO ()) -- ^ Optional table drawing routine
             -> CustomWidgetFuncs Window    -- ^ Custom widget overrides
             -> CustomWindowFuncs Window    -- ^ Custom window overrides
             -> IO (Ref Window)
windowCustom size position title draw' customWidgetFuncs' customWindowFuncs' =
  windowMaker
    size
    position
    title
    draw'
    customWidgetFuncs'
    customWindowFuncs'
    overriddenWindowNew'
    overriddenWindowNewWithLabel'
    overriddenWindowNewXY'
    overriddenWindowNewXYWithLabel'

windowNew :: Size -> Maybe Position -> Maybe T.Text -> IO (Ref Window)
windowNew size position title =
  windowMaker
    size
    position
    title
    Nothing
    (defaultCustomWidgetFuncs :: CustomWidgetFuncs Window)
    (defaultCustomWindowFuncs :: CustomWindowFuncs Window)
    overriddenWindowNew'
    overriddenWindowNewWithLabel'
    overriddenWindowNewXY'
    overriddenWindowNewXYWithLabel'

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

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

instance (impl ~ (IO ())) => Op (Destroy ()) WindowBase orig impl where
  runOp _ _ win = withRef win $ \winPtr -> windowDestroy' winPtr

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

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

instance (impl ~ ((Ref orig -> IO ()) -> IO ())) => Op (SetCallback ()) WindowBase orig impl where
  runOp _ _ window callback =
   withRef window $ (\p -> do
     callbackPtr <- toCallbackPrimWithUserData callback
     oldCb <- windowSetCallback' (castPtr p) callbackPtr
     if (oldCb == nullFunPtr)
     then return ()
     else freeHaskellFunPtr oldCb)

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

{-# LINE 179 "src/Graphics/UI/FLTK/LowLevel/Base/Window.chs" #-}

instance (impl ~ ( IO (Bool))) => Op (Changed ()) WindowBase orig impl where
  runOp _ _ win = withRef win $ \winPtr -> changed' winPtr

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

{-# LINE 183 "src/Graphics/UI/FLTK/LowLevel/Base/Window.chs" #-}

instance (impl ~ ( IO ())) => Op (MakeFullscreen ()) WindowBase orig impl where
  runOp _ _ win = withRef win $ \winPtr -> fullscreen' winPtr

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

{-# LINE 187 "src/Graphics/UI/FLTK/LowLevel/Base/Window.chs" #-}

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

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

instance (impl ~ (Maybe Rectangle ->  IO ())) => Op (FullscreenOff ()) WindowBase orig impl where
  runOp _ _ win (Just rectangle) =
    withRef win $ \winPtr ->
        let (x_pos, y_pos, width, height) = fromRectangle rectangle
        in fullscreenOffWithResize' winPtr x_pos y_pos width height
  runOp _ _ win Nothing =
    withRef win $ \winPtr -> fullscreenOff' winPtr

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

{-# LINE 197 "src/Graphics/UI/FLTK/LowLevel/Base/Window.chs" #-}

instance (impl ~ (Bool ->  IO ())) => Op (SetBorder ()) WindowBase orig impl where
  runOp _ _ win b = withRef win $ \winPtr -> setBorder' winPtr b

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

{-# LINE 201 "src/Graphics/UI/FLTK/LowLevel/Base/Window.chs" #-}

instance (impl ~ ( IO ())) => Op (ClearBorder ()) WindowBase orig impl where
  runOp _ _ win = withRef win $ \winPtr -> clearBorder' winPtr

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

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

instance (impl ~ ( IO (Bool))) => Op (GetBorder ()) WindowBase orig impl where
  runOp _ _ win = withRef win $ \winPtr -> border' winPtr

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

{-# LINE 209 "src/Graphics/UI/FLTK/LowLevel/Base/Window.chs" #-}

instance (impl ~ ( IO ())) => Op (SetOverride ()) WindowBase orig impl where
  runOp _ _ win = withRef win $ \winPtr -> setOverride' winPtr

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

{-# LINE 213 "src/Graphics/UI/FLTK/LowLevel/Base/Window.chs" #-}

instance (impl ~ ( IO (Bool))) => Op (GetOverride ()) WindowBase orig impl where
  runOp _ _ win = withRef win $ \winPtr -> override' winPtr

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

{-# LINE 217 "src/Graphics/UI/FLTK/LowLevel/Base/Window.chs" #-}

instance (impl ~ ( IO ())) => Op (SetModal ()) WindowBase orig impl where
  runOp _ _ win = withRef win $ \winPtr -> setModal' winPtr

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

{-# LINE 221 "src/Graphics/UI/FLTK/LowLevel/Base/Window.chs" #-}

instance (impl ~ ( IO (Bool))) => Op (GetModal ()) WindowBase orig impl where
  runOp _ _ win = withRef win $ \winPtr -> modal' winPtr

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

{-# LINE 225 "src/Graphics/UI/FLTK/LowLevel/Base/Window.chs" #-}

instance (impl ~ ( IO ())) => Op (SetNonModal ()) WindowBase orig impl where
  runOp _ _ win = withRef win $ \winPtr -> setNonModal' winPtr

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

{-# LINE 229 "src/Graphics/UI/FLTK/LowLevel/Base/Window.chs" #-}

instance (impl ~ ( IO (Bool))) => Op (NonModal ()) WindowBase orig impl where
  runOp _ _ win = withRef win $ \winPtr -> nonModal' winPtr

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

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

instance (impl ~ ( IO ())) => Op (SetMenuWindow ()) WindowBase orig impl where
  runOp _ _ win = withRef win $ \winPtr -> setMenuWindow' winPtr

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

{-# LINE 237 "src/Graphics/UI/FLTK/LowLevel/Base/Window.chs" #-}

instance (impl ~ ( IO (Bool))) => Op (GetMenuWindow ()) WindowBase orig impl where
  runOp _ _ win = withRef win $ \winPtr -> menuWindow' winPtr

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

{-# LINE 241 "src/Graphics/UI/FLTK/LowLevel/Base/Window.chs" #-}

instance (impl ~ ( IO ())) => Op (SetTooltipWindow ()) WindowBase orig impl where
  runOp _ _ win = withRef win $ \winPtr -> setTooltipWindow' winPtr

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

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

instance (impl ~ ( IO (Bool))) => Op (GetTooltipWindow ()) WindowBase orig impl where
  runOp _ _ win = withRef win $ \winPtr -> tooltipWindow' winPtr

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

{-# LINE 249 "src/Graphics/UI/FLTK/LowLevel/Base/Window.chs" #-}

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

{-# LINE 250 "src/Graphics/UI/FLTK/LowLevel/Base/Window.chs" #-}

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

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

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

{-# LINE 252 "src/Graphics/UI/FLTK/LowLevel/Base/Window.chs" #-}

instance (impl ~ (PositionSpec -> Maybe Bool -> IO ())) => Op (HotSpot ()) WindowBase orig impl where
  runOp _ _ win positionSpec offscreen =
    withRef win $ \winPtr ->
            case (positionSpec, offscreen) of
              ((ByPosition (Position (X x) (Y y))), (Just offscreen')) ->
                  hotspotWithXYWithOffscreen' winPtr x y offscreen'
              ((ByPosition (Position (X x) (Y y))), Nothing) -> hotspotWithXY' winPtr x y
              ((ByWidget templateWidget), (Just offscreen')) ->
                  withRef templateWidget $ \templatePtr ->
                      hotspotWithWidgetWithOffscreen' winPtr templatePtr offscreen'
              ((ByWidget templateWidget), Nothing) ->
                  withRef templateWidget $ \templatePtr ->
                      hotspotWithWidget' winPtr templatePtr
freePosition' :: (Ptr ()) -> IO ((()))
freePosition' a1 =
  let {a1' = id a1} in
  freePosition''_ a1' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

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

instance (impl ~ ( IO ())) => Op (FreePosition ()) WindowBase orig impl where
  runOp _ _ win = withRef win $ \winPtr -> freePosition' winPtr

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

{-# LINE 270 "src/Graphics/UI/FLTK/LowLevel/Base/Window.chs" #-}

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

{-# LINE 271 "src/Graphics/UI/FLTK/LowLevel/Base/Window.chs" #-}

instance (impl ~ (Size -> IO ())) => Op (SizeRange ()) WindowBase orig impl where
  runOp _ _ win (Size (Width minw') (Height minh')) =
    withRef win $ \winPtr -> sizeRange' winPtr minw' minh'
instance (impl ~ (Size -> OptionalSizeRangeArgs ->  IO ())) => Op (SizeRangeWithArgs ()) WindowBase orig impl where
  runOp _ _ win (Size (Width minw') (Height minh')) args =
    withRef win $ \winPtr -> do
      structPtr <- optionalSizeRangeArgsToStruct args
      sizeRangeWithArgs' winPtr minw' minh' structPtr

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

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

instance (impl ~ ( IO T.Text)) => Op (GetLabel ()) WindowBase orig impl where
  runOp _ _ win = withRef win $ \winPtr -> label' winPtr >>= cStringToText

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

{-# LINE 285 "src/Graphics/UI/FLTK/LowLevel/Base/Window.chs" #-}

instance (impl ~ ( IO T.Text)) => Op (GetIconlabel ()) WindowBase orig impl where
  runOp _ _ win = withRef win $ \winPtr -> iconlabel' winPtr >>= cStringToText

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

{-# LINE 289 "src/Graphics/UI/FLTK/LowLevel/Base/Window.chs" #-}

instance (impl ~ (T.Text ->  IO ())) => Op (SetLabel ()) WindowBase orig impl where
  runOp _ _ win l' = withRef win $ \winPtr -> copyTextToCString l' >>= setLabel' winPtr

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

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

instance (impl ~ (T.Text ->  IO ())) => Op (SetIconlabel ()) WindowBase orig impl where
  runOp _ _ win l' = withRef win $ \winPtr -> copyTextToCString l' >>= setIconlabel' winPtr

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

{-# LINE 297 "src/Graphics/UI/FLTK/LowLevel/Base/Window.chs" #-}

instance (impl ~ (T.Text -> T.Text ->  IO ())) => Op (SetLabelWithIconlabel ()) WindowBase orig impl where
  runOp _ _ win label iconlabel = withRef win $ \winPtr -> do
    l' <- copyTextToCString label
    il' <- copyTextToCString iconlabel
    setLabelWithIconlabel' winPtr l' il'

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

{-# LINE 304 "src/Graphics/UI/FLTK/LowLevel/Base/Window.chs" #-}

instance (impl ~ (T.Text ->  IO ())) => Op (CopyLabel ()) WindowBase orig impl where
  runOp _ _ win a = withRef win $ \winPtr -> withText a (copyLabel' winPtr)

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

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

instance (impl ~ ( IO T.Text)) => Op (GetXclass ()) WindowBase orig impl where
  runOp _ _ win = withRef win $ \winPtr -> xclass' winPtr >>= cStringToText

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

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

instance (impl ~ (T.Text ->  IO ())) => Op (SetXclass ()) WindowBase orig impl where
  runOp _ _ win c = withRef win $ \winPtr -> copyTextToCString c >>= setXclass' winPtr

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

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

instance (impl ~ ( IO (Maybe (Ref Image)))) => Op (GetIcon ()) WindowBase orig impl where
  runOp _ _ win = withRef win $ \winPtr -> icon' winPtr >>= toMaybeRef

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

{-# LINE 320 "src/Graphics/UI/FLTK/LowLevel/Base/Window.chs" #-}

instance (Parent a Image, impl ~ (Maybe( Ref a ) ->  IO ())) => Op (SetIcon ()) WindowBase orig impl where
  runOp _ _ win bitmap = withRef win $ \winPtr -> withMaybeRef bitmap $ \bitmapPtr -> setIcon' winPtr bitmapPtr

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

{-# LINE 324 "src/Graphics/UI/FLTK/LowLevel/Base/Window.chs" #-}

instance (impl ~ ( IO (Bool))) => Op (Shown ()) WindowBase orig impl where
  runOp _ _ win = withRef win $ \winPtr -> shown' winPtr

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

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

instance (impl ~ ( IO ())) => Op (Iconize ()) WindowBase orig impl where
  runOp _ _ win = withRef win $ \winPtr -> iconize' winPtr

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

{-# LINE 332 "src/Graphics/UI/FLTK/LowLevel/Base/Window.chs" #-}

instance (impl ~ ( IO (X))) => Op (GetXRoot ()) WindowBase orig impl where
  runOp _ _ win = withRef win $ \winPtr -> xRoot' winPtr >>= return . X

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

{-# LINE 336 "src/Graphics/UI/FLTK/LowLevel/Base/Window.chs" #-}

instance (impl ~ ( IO (Y))) => Op (GetYRoot ()) WindowBase orig impl where
  runOp _ _ win = withRef win $ \winPtr -> yRoot' winPtr >>= return . Y

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

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

currentWindow ::  (Parent a WindowBase) => IO (Ref a)
currentWindow = current' >>= toRef

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

{-# LINE 344 "src/Graphics/UI/FLTK/LowLevel/Base/Window.chs" #-}

instance (impl ~ ( IO ())) => Op (MakeCurrent ()) WindowBase orig impl where
  runOp _ _ win = withRef win $ \winPtr -> makeCurrent' winPtr

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

{-# LINE 348 "src/Graphics/UI/FLTK/LowLevel/Base/Window.chs" #-}

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

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

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

{-# LINE 350 "src/Graphics/UI/FLTK/LowLevel/Base/Window.chs" #-}

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

{-# LINE 351 "src/Graphics/UI/FLTK/LowLevel/Base/Window.chs" #-}

instance (impl ~ (Cursor -> IO ())) => Op (SetCursor ()) WindowBase orig impl where
  runOp _ _ win cursor =  withRef win $ \winPtr -> setCursor' winPtr cursor
instance (impl ~ (Cursor -> (Maybe Color, Maybe Color) ->  IO ())) => Op (SetCursorWithFgBg ()) WindowBase orig impl where
  runOp _ _ win cursor fgbg =
    case fgbg of
      ((Just fg), (Just bg)) -> withRef win $ \winPtr -> setCursorWithFgBg' winPtr cursor fg bg
      (Nothing , (Just bg)) -> withRef win $ \winPtr -> setCursorWithBg' winPtr cursor bg
      ((Just fg), Nothing)  -> withRef win $ \winPtr -> setCursorWithFg' winPtr cursor fg
      (Nothing, Nothing)    -> withRef win $ \winPtr -> setCursor' winPtr cursor

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

{-# LINE 362 "src/Graphics/UI/FLTK/LowLevel/Base/Window.chs" #-}

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

{-# LINE 363 "src/Graphics/UI/FLTK/LowLevel/Base/Window.chs" #-}

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

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

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

{-# LINE 365 "src/Graphics/UI/FLTK/LowLevel/Base/Window.chs" #-}

instance (impl ~ (CursorType -> IO ())) => Op (SetDefaultCursor ()) WindowBase orig impl where
  runOp _ _ win cursor = withRef win $ \winPtr -> setDefaultCursor' winPtr cursor
instance (impl ~ (CursorType -> (Maybe Color, Maybe Color) -> IO ())) => Op (SetDefaultCursorWithFgBg ()) WindowBase orig impl where
  runOp _ _ win cursor fgbg =
    case fgbg of
      ((Just fg), (Just bg)) -> withRef win $ \winPtr -> setDefaultCursorWithFgBg' winPtr cursor fg bg
      (Nothing , (Just bg)) -> withRef win $ \winPtr -> setDefaultCursorWithBg' winPtr cursor bg
      ((Just fg), Nothing)  -> withRef win $ \winPtr -> setDefaultCursorWithFg' winPtr cursor fg
      (Nothing, Nothing)    -> withRef win $ \winPtr -> setDefaultCursor' winPtr cursor

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

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

instance (impl ~ ( IO (Int))) => Op (GetDecoratedW ()) WindowBase orig impl where
  runOp _ _ win = withRef win $ \winPtr -> decoratedW' winPtr

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

{-# LINE 380 "src/Graphics/UI/FLTK/LowLevel/Base/Window.chs" #-}

instance (impl ~ ( IO (Int))) => Op (GetDecoratedH ()) WindowBase orig impl where
  runOp _ _ win = withRef win $ \winPtr -> decoratedH' winPtr

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

{-# LINE 384 "src/Graphics/UI/FLTK/LowLevel/Base/Window.chs" #-}

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

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

windowDrawBoxWithTXywhC' :: (Ptr ()) -> (Boxtype) -> (Int) -> (Int) -> (Int) -> (Int) -> (Color) -> IO ((()))
windowDrawBoxWithTXywhC' 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
  windowDrawBoxWithTXywhC''_ a1' a2' a3' a4' a5' a6' a7' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 386 "src/Graphics/UI/FLTK/LowLevel/Base/Window.chs" #-}

instance (impl ~ (IO ())) => Op (DrawBox ()) WindowBase orig impl where
  runOp _ _ window = withRef window $ \windowPtr -> windowDrawBox' windowPtr
instance (impl ~ (Boxtype -> Color -> Maybe Rectangle -> IO ())) => Op (DrawBoxWithBoxtype ()) WindowBase orig impl where
  runOp _ _ window bx c Nothing =
              withRef window $ \windowPtr -> windowDrawBoxWithTC' windowPtr bx c
  runOp _ _ window bx c (Just r) =
              withRef window $ \windowPtr -> do
                let (x_pos,y_pos,w_pos,h_pos) = fromRectangle r
                windowDrawBoxWithTXywhC' windowPtr bx x_pos y_pos w_pos h_pos c
windowDrawBackdrop' :: (Ptr ()) -> IO ((()))
windowDrawBackdrop' a1 =
  let {a1' = id a1} in
  windowDrawBackdrop''_ a1' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 396 "src/Graphics/UI/FLTK/LowLevel/Base/Window.chs" #-}

instance (impl ~ (IO ())) => Op (DrawBackdrop ()) WindowBase orig impl where
  runOp _ _ window = withRef window $ \windowPtr -> windowDrawBackdrop' windowPtr

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

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

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

{-# LINE 401 "src/Graphics/UI/FLTK/LowLevel/Base/Window.chs" #-}

instance (impl ~ (Maybe (Boxtype, Rectangle) -> IO ())) => Op (DrawFocus ()) WindowBase orig impl where
  runOp _ _ window Nothing =
                withRef window $ \ windowPtr -> windowDrawFocus' windowPtr
  runOp _ _ window (Just (bx, r)) =
                withRef window $ \windowPtr -> do
                  let (x_pos,y_pos,w_pos,h_pos) = fromRectangle r
                  windowDrawFocusWithTXywh' windowPtr bx x_pos y_pos w_pos h_pos

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

{-# LINE 410 "src/Graphics/UI/FLTK/LowLevel/Base/Window.chs" #-}

instance (impl ~ ( IO ())) => Op (WaitForExpose ()) WindowBase orig impl where
  runOp _ _ win = withRef win $ \winPtr -> waitForExpose' winPtr

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 414 "src/Graphics/UI/FLTK/LowLevel/Base/Window.chs" #-}

instance (impl ~ (WindowType ->  IO ())) => Op (SetType ()) WindowBase orig impl where
  runOp _ _ widget t = withRef widget $ \widgetPtr -> setType' widgetPtr (fromInteger $ toInteger $ fromEnum t)
type' :: (Ptr ()) -> IO ((Word8))
type' a1 =
  let {a1' = id a1} in
  type''_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 417 "src/Graphics/UI/FLTK/LowLevel/Base/Window.chs" #-}

instance (impl ~ IO (WindowType)) => Op (GetType_ ()) WindowBase orig impl where
  runOp _ _ widget = withRef widget $ \widgetPtr -> type' widgetPtr >>= return . toEnum . fromInteger . toInteger

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

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

handleWindowBase :: Ref WindowBase -> Event ->  IO (Either UnknownEvent ())
handleWindowBase adjuster event = withRef adjuster $ \adjusterPtr -> handleSuper' adjusterPtr (fromIntegral (fromEnum event)) >>= return . successOrUnknownEvent
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 424 "src/Graphics/UI/FLTK/LowLevel/Base/Window.chs" #-}

resizeWindowBase :: Ref WindowBase -> Rectangle -> IO ()
resizeWindowBase adjuster rectangle =
    let (x_pos, y_pos, width, height) = fromRectangle rectangle
    in withRef adjuster $ \adjusterPtr -> resizeSuper' adjusterPtr x_pos y_pos width height
hideSuper' :: (Ptr ()) -> IO ((()))
hideSuper' a1 =
  let {a1' = id a1} in
  hideSuper''_ a1' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

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

hideWindowBase ::  Ref WindowBase -> IO ()
hideWindowBase adjuster = withRef adjuster $ \adjusterPtr -> hideSuper' adjusterPtr
showSuper' :: (Ptr ()) -> IO ((()))
showSuper' a1 =
  let {a1' = id a1} in
  showSuper''_ a1' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

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

showWidgetWindowBase ::  Ref WindowBase -> IO ()
showWidgetWindowBase adjuster = withRef adjuster $ \adjusterPtr -> showSuper' adjusterPtr
flushSuper' :: (Ptr ()) -> IO ()
flushSuper' a1 =
  let {a1' = id a1} in
  flushSuper''_ a1' >>
  return ()

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

flushWindowBase :: Ref WindowBase -> IO ()
flushWindowBase window = withRef window $ \windowPtr -> flush' windowPtr

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

{-# LINE 439 "src/Graphics/UI/FLTK/LowLevel/Base/Window.chs" #-}

instance (impl ~ (Event -> IO (Either UnknownEvent ()))) => Op (Handle ()) WindowBase orig impl where
  runOp _ _ window event = withRef window (\p -> windowHandle' p (fromIntegral . fromEnum $ event)) >>= return  . successOrUnknownEvent
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 442 "src/Graphics/UI/FLTK/LowLevel/Base/Window.chs" #-}

instance (impl ~ (Rectangle -> IO ())) => Op (Resize ()) WindowBase orig impl where
  runOp _ _ window rectangle = withRef window $ \windowPtr -> do
                                 let (x_pos,y_pos,w_pos,h_pos) = fromRectangle rectangle
                                 resize' windowPtr x_pos y_pos w_pos h_pos
windowShow' :: (Ptr ()) -> IO ((()))
windowShow' a1 =
  let {a1' = id a1} in
  windowShow''_ a1' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 447 "src/Graphics/UI/FLTK/LowLevel/Base/Window.chs" #-}

instance (impl ~ (IO ())) => Op (ShowWidget ()) WindowBase orig impl where
  runOp _ _ window = withRef window (\p -> windowShow' p)

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

{-# LINE 451 "src/Graphics/UI/FLTK/LowLevel/Base/Window.chs" #-}

instance (impl ~ ( IO ())) => Op (Hide ()) WindowBase orig impl where
  runOp _ _ window = withRef window $ \windowPtr -> hide' windowPtr

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

{-# LINE 455 "src/Graphics/UI/FLTK/LowLevel/Base/Window.chs" #-}

instance (impl ~ ( IO ())) => Op (Flush ()) WindowBase orig impl where
  runOp _ _ window = withRef window $ \windowPtr -> flush' windowPtr


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

-- $functions
-- @
-- changed :: 'Ref' 'WindowBase' -> 'IO' ('Bool')
--
-- clearBorder :: 'Ref' 'WindowBase' -> 'IO' ()
--
-- copyLabel :: 'Ref' 'WindowBase' -> 'T.Text' -> 'IO' ()
--
-- destroy :: 'Ref' 'WindowBase' -> 'IO' ()
--
-- drawBackdrop :: 'Ref' 'WindowBase' -> 'IO' ()
--
-- drawBox :: 'Ref' 'WindowBase' -> 'IO' ()
--
-- drawBoxWithBoxtype :: 'Ref' 'WindowBase' -> 'Boxtype' -> 'Color' -> 'Maybe' 'Rectangle' -> 'IO' ()
--
-- drawFocus :: 'Ref' 'WindowBase' -> 'Maybe' ('Boxtype', 'Rectangle') -> 'IO' ()
--
-- flush :: 'Ref' 'WindowBase' -> 'IO' ()
--
-- freePosition :: 'Ref' 'WindowBase' -> 'IO' ()
--
-- fullscreenOff :: 'Ref' 'WindowBase' -> 'Maybe' 'Rectangle' -> 'IO' ()
--
-- getBorder :: 'Ref' 'WindowBase' -> 'IO' ('Bool')
--
-- getDecoratedH :: 'Ref' 'WindowBase' -> 'IO' ('Int')
--
-- getDecoratedW :: 'Ref' 'WindowBase' -> 'IO' ('Int')
--
-- getIcon :: 'Ref' 'WindowBase' -> 'IO' ('Maybe' ('Ref' 'Image'))
--
-- getIconlabel :: 'Ref' 'WindowBase' -> 'IO' 'T.Text'
--
-- getLabel :: 'Ref' 'WindowBase' -> 'IO' 'T.Text'
--
-- getMenuWindow :: 'Ref' 'WindowBase' -> 'IO' ('Bool')
--
-- getModal :: 'Ref' 'WindowBase' -> 'IO' ('Bool')
--
-- getOverride :: 'Ref' 'WindowBase' -> 'IO' ('Bool')
--
-- getTooltipWindow :: 'Ref' 'WindowBase' -> 'IO' ('Bool')
--
-- getType_ :: 'Ref' 'WindowBase' -> 'IO' ('WindowType')
--
-- getXRoot :: 'Ref' 'WindowBase' -> 'IO' ('X')
--
-- getXclass :: 'Ref' 'WindowBase' -> 'IO' 'T.Text'
--
-- getYRoot :: 'Ref' 'WindowBase' -> 'IO' ('Y')
--
-- handle :: 'Ref' 'WindowBase' -> 'Event' -> 'IO' ('Either' 'UnknownEvent' ())
--
-- hide :: 'Ref' 'WindowBase' -> 'IO' ()
--
-- hotSpot :: 'Ref' 'WindowBase' -> 'PositionSpec' -> 'Maybe' 'Bool' -> 'IO' ()
--
-- iconize :: 'Ref' 'WindowBase' -> 'IO' ()
--
-- makeCurrent :: 'Ref' 'WindowBase' -> 'IO' ()
--
-- makeFullscreen :: 'Ref' 'WindowBase' -> 'IO' ()
--
-- nonModal :: 'Ref' 'WindowBase' -> 'IO' ('Bool')
--
-- resize :: 'Ref' 'WindowBase' -> 'Rectangle' -> 'IO' ()
--
-- setBorder :: 'Ref' 'WindowBase' -> 'Bool' -> 'IO' ()
--
-- setCallback :: 'Ref' 'WindowBase' -> ('Ref' orig -> 'IO' ()) -> 'IO' ()
--
-- setCursor :: 'Ref' 'WindowBase' -> 'Cursor' -> 'IO' ()
--
-- setCursorWithFgBg :: 'Ref' 'WindowBase' -> 'Cursor' -> ('Maybe' 'Color', 'Maybe' 'Color') -> 'IO' ()
--
-- setDefaultCursor :: 'Ref' 'WindowBase' -> 'CursorType' -> 'IO' ()
--
-- setDefaultCursorWithFgBg :: 'Ref' 'WindowBase' -> 'CursorType' -> ('Maybe' 'Color', 'Maybe' 'Color') -> 'IO' ()
--
-- setIcon:: ('Parent' a 'Image') => 'Ref' 'WindowBase' -> 'Maybe'( 'Ref' a ) -> 'IO' ()
--
-- setIconlabel :: 'Ref' 'WindowBase' -> 'T.Text' -> 'IO' ()
--
-- setLabel :: 'Ref' 'WindowBase' -> 'T.Text' -> 'IO' ()
--
-- setLabelWithIconlabel :: 'Ref' 'WindowBase' -> 'T.Text' -> 'T.Text' -> 'IO' ()
--
-- setMenuWindow :: 'Ref' 'WindowBase' -> 'IO' ()
--
-- setModal :: 'Ref' 'WindowBase' -> 'IO' ()
--
-- setNonModal :: 'Ref' 'WindowBase' -> 'IO' ()
--
-- setOverride :: 'Ref' 'WindowBase' -> 'IO' ()
--
-- setTooltipWindow :: 'Ref' 'WindowBase' -> 'IO' ()
--
-- setType :: 'Ref' 'WindowBase' -> 'WindowType' -> 'IO' ()
--
-- setXclass :: 'Ref' 'WindowBase' -> 'T.Text' -> 'IO' ()
--
-- showWidget :: 'Ref' 'WindowBase' -> 'IO' ()
--
-- shown :: 'Ref' 'WindowBase' -> 'IO' ('Bool')
--
-- sizeRange :: 'Ref' 'WindowBase' -> 'Size' -> 'IO' ()
--
-- sizeRangeWithArgs :: 'Ref' 'WindowBase' -> 'Size' -> 'OptionalSizeRangeArgs' -> 'IO' ()
--
-- waitForExpose :: 'Ref' 'WindowBase' -> 'IO' ()
-- @

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_default_virtual_funcs"
  virtualFuncs''_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_OverriddenWindow_New"
  overriddenWindowNew''_ :: (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_OverriddenWindow_NewXY"
  overriddenWindowNewXY''_ :: (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))))))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_OverriddenWindow_NewXY_WithLabel"
  overriddenWindowNewXYWithLabel''_ :: (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/Base/Window.chs.h Fl_OverriddenWindow_New_WithLabel"
  overriddenWindowNewWithLabel''_ :: (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CChar) -> ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ()))))))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_Destroy"
  windowDestroy''_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_set_callback"
  windowSetCallback''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.FunPtr ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))) -> (IO (C2HSImp.FunPtr ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))))))

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

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_fullscreen"
  fullscreen''_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_fullscreen_off"
  fullscreenOff''_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_fullscreen_off_with_resize"
  fullscreenOffWithResize''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO ()))))))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_set_border"
  setBorder''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_clear_border"
  clearBorder''_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_border"
  border''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CUInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_set_override"
  setOverride''_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_override"
  override''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CUInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_set_modal"
  setModal''_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_modal"
  modal''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CUInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_set_non_modal"
  setNonModal''_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_non_modal"
  nonModal''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CUInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_set_menu_window"
  setMenuWindow''_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_menu_window"
  menuWindow''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CUInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_set_tooltip_window"
  setTooltipWindow''_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_tooltip_window"
  tooltipWindow''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CUInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_hotspot_with_x_y"
  hotspotWithXY''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO ()))))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_hotspot_with_x_y_with_offscreen"
  hotspotWithXYWithOffscreen''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO ())))))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_hotspot_with_widget"
  hotspotWithWidget''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_hotspot_with_widget_with_offscreen"
  hotspotWithWidgetWithOffscreen''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ()))))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_free_position"
  freePosition''_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_size_range"
  sizeRange''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO ()))))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_size_range_with_args"
  sizeRangeWithArgs''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (IO ())))))

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

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_iconlabel"
  iconlabel''_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr C2HSImp.CChar)))

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

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_set_iconlabel"
  setIconlabel''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_set_label_with_iconlabel"
  setLabelWithIconlabel''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CChar) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (IO ()))))

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

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_xclass"
  xclass''_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr C2HSImp.CChar)))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_set_xclass"
  setXclass''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_icon"
  icon''_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_set_icon"
  setIcon''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_shown"
  shown''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_iconize"
  iconize''_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_x_root"
  xRoot''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_y_root"
  yRoot''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_current"
  current''_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_make_current"
  makeCurrent''_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_set_cursor_with_bg"
  setCursorWithBg''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CUInt -> (IO ()))))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_set_cursor_with_fg"
  setCursorWithFg''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CUInt -> (IO ()))))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_set_cursor_with_fg_bg"
  setCursorWithFgBg''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CUInt -> (C2HSImp.CUInt -> (IO ())))))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_set_cursor"
  setCursor''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_set_default_cursor_with_bg"
  setDefaultCursorWithBg''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CUInt -> (IO ()))))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_set_default_cursor_with_fg"
  setDefaultCursorWithFg''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CUInt -> (IO ()))))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_set_default_cursor_with_fg_bg"
  setDefaultCursorWithFgBg''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CUInt -> (C2HSImp.CUInt -> (IO ())))))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_set_default_cursor"
  setDefaultCursor''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_decorated_w"
  decoratedW''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_decorated_h"
  decoratedH''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_draw_box"
  windowDrawBox''_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_draw_box_with_tc"
  windowDrawBoxWithTC''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CUInt -> (IO ()))))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_draw_box_with_txywhc"
  windowDrawBoxWithTXywhC''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CUInt -> (IO ()))))))))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_draw_backdrop"
  windowDrawBackdrop''_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_draw_focus"
  windowDrawFocus''_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_draw_focus_with_txywh"
  windowDrawFocusWithTXywh''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO ())))))))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_wait_for_expose"
  waitForExpose''_ :: ((C2HSImp.Ptr ()) -> (IO ()))

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

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

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_handle_super"
  handleSuper''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))

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

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_hide_super"
  hideSuper''_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_show_super"
  showSuper''_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_flush_super"
  flushSuper''_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_DerivedWindow_handle"
  windowHandle''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))

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

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_DerivedWindow_show"
  windowShow''_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_DerivedWindow_hide"
  hide''_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Base/Window.chs.h Fl_Window_flush"
  flush''_ :: ((C2HSImp.Ptr ()) -> (IO ()))