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


{-# LINE 1 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}
{-# LANGUAGE CPP, ExistentialQuantification, TypeSynonymInstances, FlexibleInstances, MultiParamTypeClasses, FlexibleContexts, ScopedTypeVariables #-}
module Graphics.UI.FLTK.LowLevel.FL
    (
     Option(..),
     scrollbarSize,
     setScrollbarSize,
     selectionOwner,
     setSelectionOwner,
     run,
     check,
     ready,
     option,
     setOption,
     addAwakeHandler,
     getAwakeHandler_,
     display,
     ownColormap,
     getSystemColors,
     foreground,
     background,
     background2,
     setScheme,
     isScheme,
     setFirstWindow,
     nextWindow,
     setGrab,
     getMouse,
     eventStates,
     extract,
     extractEventStates,
     handle,
     handle_,
     belowmouse,
     setBelowmouse,
     setPushed,
     setFocus,
     setHandler,
     paste,
     toRectangle,
     fromRectangle,
     screenBounds,
     screenDPI,
     screenWorkArea,
     setColorRgb,
     toAttribute,
     release,
     setVisibleFocus,
     visibleFocus,
     setDndTextOps,
     dndTextOps,
     deleteWidget,
     doWidgetDeletion,
     watchWidgetPointer,
     releaseWidgetPointer,
     clearWidgetPointer,
     version,
     help,
     visual,
     glVisual,
     glVisualWithAlist,
     scheme,
     wait,
     setWait,
     readqueue,
     addTimeout,
     repeatTimeout,
     hasTimeout,
     removeTimeout,
     addCheck,
     hasCheck,
     removeCheck,
     addIdle,
     hasIdle,
     removeIdle,
     damage,
     redraw,
     flush,
     firstWindow,
     modal,
     grab,
     getKey,
     compose,
     composeReset,
     testShortcut,
     enableIm,
     disableIm,
     pushed,
     focus,
     copy,
     copyWithDestination,
     pasteWithSource,
     dnd,
     x,
     y,
     w,
     h,
     screenCount,
     setColor,
     getColor,
     getColorRgb,
     removeFromColormap,
     -- * Box
     BoxtypeSpec,
     getBoxtype,
     setBoxtype,
     boxDx,
     boxDy,
     boxDw,
     boxDh,
     drawBoxActive,
     -- * Fonts
     getFontName,
     getFont,
     getFontSizes,
     setFontByString,
     setFontByFont,
     setFonts,
     setFontsWithString,
     -- * File Descriptor Callbacks
     addFd,
     addFdWhen,
     removeFd,
     removeFdWhen,
     -- * Events
     event,
     eventShift,
     eventCtrl,
     eventCommand,
     eventAlt,
     eventButtons,
     eventButton1,
     eventButton2,
     eventButton3,
     eventX,
     eventY,
     eventXRoot,
     eventYRoot,
     eventDx,
     eventDy,
     eventClicks,
     setEventClicks,
     eventIsClick,
     setEventIsClick,
     eventButton,
     eventState,
     containsEventState,
     eventKey,
     eventOriginalKey,
     eventKeyPressed,
     eventInsideRegion,
     eventInsideWidget,
     eventDispatch,
     setEventDispatch,
     eventText,
     eventLength,
     setBoxColor,
     boxColor,
     abiVersion,
     apiVersion,
     localCtrl,
     localMeta,
     localAlt,
     localShift
    )
where
import qualified Foreign.C.Types as C2HSImp
import qualified Foreign.Ptr as C2HSImp
import qualified System.IO.Unsafe as C2HSImp



import C2HS hiding (cFromEnum, cToBool,cToEnum)
import Data.IORef
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.Hierarchy hiding (
                                                   setVisibleFocus,
                                                   handle,
                                                   redraw,
                                                   flush,
                                                   testShortcut,
                                                   copy,
                                                   setColor,
                                                   getColor,
                                                   focus,
                                                   display,
                                                   setScrollbarSize
                                                  )
import Graphics.UI.FLTK.LowLevel.Dispatch
import qualified Data.Text as T
import qualified Data.Text.Foreign as TF
import qualified System.IO.Unsafe as Unsafe (unsafePerformIO)
data Option = OptionArrowFocus
            | OptionVisibleFocus
            | OptionDndText
            | OptionShowTooltips
            | OptionLast
  deriving (Show)
instance Enum Option where
  succ OptionArrowFocus = OptionVisibleFocus
  succ OptionVisibleFocus = OptionDndText
  succ OptionDndText = OptionShowTooltips
  succ OptionShowTooltips = OptionLast
  succ OptionLast = error "Option.succ: OptionLast has no successor"

  pred OptionVisibleFocus = OptionArrowFocus
  pred OptionDndText = OptionVisibleFocus
  pred OptionShowTooltips = OptionDndText
  pred OptionLast = OptionShowTooltips
  pred OptionArrowFocus = error "Option.pred: OptionArrowFocus 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 OptionLast

  fromEnum OptionArrowFocus = 0
  fromEnum OptionVisibleFocus = 1
  fromEnum OptionDndText = 2
  fromEnum OptionShowTooltips = 3
  fromEnum OptionLast = 4

  toEnum 0 = OptionArrowFocus
  toEnum 1 = OptionVisibleFocus
  toEnum 2 = OptionDndText
  toEnum 3 = OptionShowTooltips
  toEnum 4 = OptionLast
  toEnum unmatched = error ("Option.toEnum: Cannot match " ++ show unmatched)

{-# LINE 203 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}


ptrToGlobalEventHandler :: IORef (FunPtr GlobalEventHandlerPrim)
ptrToGlobalEventHandler = Unsafe.unsafePerformIO $ do
                            initialHandler <- toGlobalEventHandlerPrim (\_ -> return (-1))
                            newIORef initialHandler

type EventDispatchPrim = (CInt ->
                          Ptr () ->
                          IO CInt)
foreign import ccall "wrapper"
        wrapEventDispatchPrim :: EventDispatchPrim ->
                                 IO (FunPtr EventDispatchPrim)
foreign import ccall "dynamic"
        unwrapEventDispatchPrim :: FunPtr EventDispatchPrim -> EventDispatchPrim

run :: IO Int
run = fl_run >>= return . fromIntegral

check :: IO Int
check = fl_check >>= return . fromIntegral

ready :: IO Int
ready = fl_ready >>= return . fromIntegral


option :: Option -> IO Bool
option o = fl_option (cFromEnum o) >>= \(c::CInt) -> return $ cToBool $ ((fromIntegral c) :: Int)

setOption :: Option -> Bool -> IO ()
setOption o t = fl_set_option (cFromEnum o) (Graphics.UI.FLTK.LowLevel.Utils.cFromBool t)

unsafeToCallbackPrim :: GlobalCallback -> FunPtr CallbackPrim
unsafeToCallbackPrim = (Unsafe.unsafePerformIO) . toGlobalCallbackPrim

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

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

addAwakeHandler :: GlobalCallback -> IO Int
addAwakeHandler awakeHandler =
    do
      callbackPtr <-  toGlobalCallbackPrim awakeHandler
      addAwakeHandler' callbackPtr nullPtr

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

{-# LINE 247 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

getAwakeHandler_ :: IO GlobalCallback
getAwakeHandler_ =
    alloca $ \ptrToFunPtr ->
        alloca $ \ptrToUD -> do
          _ <- getAwakeHandler_' ptrToFunPtr ptrToUD
          funPtr <- peek ptrToFunPtr
          return $ unwrapGlobalCallbackPtr $ castFunPtr funPtr

version :: IO ((Double))
version =
  version'_ >>= \res ->
  let {res' = realToFrac res} in
  return (res')

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

help :: IO ((T.Text))
help =
  help'_ >>= \res ->
  let {res' = unsafeFromCString res} in
  return (res')

{-# LINE 259 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}


display :: T.Text -> IO ()
display text = TF.withCStringLen text $ \(str,_) -> fl_display str
visual :: (Mode) -> IO ((Bool))
visual a1 =
  let {a1' = cFromEnum a1} in 
  visual'_ a1' >>= \res ->
  let {res' = cToBool res} in
  return (res')

{-# LINE 265 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

glVisual :: (Mode) -> IO ((Bool))
glVisual a1 =
  let {a1' = cFromEnum a1} in 
  glVisual'_ a1' >>= \res ->
  let {res' = cToBool res} in
  return (res')

{-# LINE 267 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

glVisualWithAlist :: (Mode) -> (Ptr CInt) -> IO ((Bool))
glVisualWithAlist a1 a2 =
  let {a1' = cFromEnum a1} in 
  let {a2' = id a2} in 
  glVisualWithAlist'_ a1' a2' >>= \res ->
  let {res' = cToBool res} in
  return (res')

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


ownColormap :: IO ()
ownColormap = fl_own_colormap
{-# LINE 273 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}


getSystemColors :: IO ()
getSystemColors = fl_get_system_colors
{-# LINE 276 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}


foreground :: RGB -> IO ()
foreground (r,g,b) = fl_foreground
{-# LINE 279 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

                    (fromIntegral r)
                    (fromIntegral g)
                    (fromIntegral b)
background :: RGB -> IO ()
background (r,g,b) = fl_background
{-# LINE 284 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

                    (fromIntegral r)
                    (fromIntegral g)
                    (fromIntegral b)
background2 :: RGB -> IO ()
background2 (r,g,b) = fl_background2
{-# LINE 289 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

                    (fromIntegral r)
                    (fromIntegral g)
                    (fromIntegral b)
scheme :: (T.Text)
scheme =
  C2HSImp.unsafePerformIO $
  scheme'_ >>= \res ->
  let {res' = unsafeFromCString res} in
  return (res')

{-# LINE 294 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

setScheme :: T.Text -> IO Int
setScheme sch = TF.withCStringLen sch $ \(str,_) -> fl_set_scheme str >>= return . fromIntegral
isScheme :: T.Text -> IO Bool
isScheme sch = TF.withCStringLen sch $ \(str,_) -> fl_is_scheme str >>= return . toBool
wait :: IO ((Int))
wait =
  wait'_ >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 300 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

setWait :: (Double) -> IO ((Double))
setWait a1 =
  let {a1' = realToFrac a1} in 
  setWait'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

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


scrollbarSize :: IO ((Int))
scrollbarSize =
  scrollbarSize'_ >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

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

setScrollbarSize :: (Int) -> IO ()
setScrollbarSize a1 =
  let {a1' = fromIntegral a1} in 
  setScrollbarSize'_ a1' >>
  return ()

{-# LINE 307 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}


readqueue :: IO ((Ref Widget))
readqueue =
  readqueue'_ >>= \res ->
  let {res' = unsafeToRef res} in
  return (res')

{-# LINE 310 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

addTimeout :: (Double) -> (GlobalCallback) -> IO ((()))
addTimeout a1 a2 =
  let {a1' = realToFrac a1} in 
  let {a2' = unsafeToCallbackPrim a2} in 
  addTimeout'_ a1' a2' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

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

repeatTimeout :: (Double) -> (GlobalCallback) -> IO ((()))
repeatTimeout a1 a2 =
  let {a1' = realToFrac a1} in 
  let {a2' = unsafeToCallbackPrim a2} in 
  repeatTimeout'_ a1' a2' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 314 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

hasTimeout :: (GlobalCallback) -> IO ((Int))
hasTimeout a1 =
  let {a1' = unsafeToCallbackPrim a1} in 
  hasTimeout'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

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

removeTimeout :: (GlobalCallback) -> IO ((()))
removeTimeout a1 =
  let {a1' = unsafeToCallbackPrim a1} in 
  removeTimeout'_ a1' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 318 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

addCheck :: (GlobalCallback) -> IO ((()))
addCheck a1 =
  let {a1' = unsafeToCallbackPrim a1} in 
  addCheck'_ a1' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

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

hasCheck :: (GlobalCallback) -> IO ((Int))
hasCheck a1 =
  let {a1' = unsafeToCallbackPrim a1} in 
  hasCheck'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

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

removeCheck :: (GlobalCallback) -> IO ((()))
removeCheck a1 =
  let {a1' = unsafeToCallbackPrim a1} in 
  removeCheck'_ a1' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

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

addIdle :: (GlobalCallback) -> IO ((()))
addIdle a1 =
  let {a1' = unsafeToCallbackPrim a1} in 
  addIdle'_ a1' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 326 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

hasIdle :: (GlobalCallback) -> IO ((Int))
hasIdle a1 =
  let {a1' = unsafeToCallbackPrim a1} in 
  hasIdle'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

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

removeIdle :: (GlobalCallback) -> IO ((()))
removeIdle a1 =
  let {a1' = unsafeToCallbackPrim a1} in 
  removeIdle'_ a1' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 330 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

damage :: IO ((Int))
damage =
  damage'_ >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

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

redraw :: IO ((()))
redraw =
  redraw'_ >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

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

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

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

firstWindow :: IO ((Maybe (Ref Window)))
firstWindow =
  firstWindow'_ >>= \res ->
  let {res' = unsafeToMaybeRef res} in
  return (res')

{-# LINE 338 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

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

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

setFirstWindow :: (Parent a Window) => Ref a -> IO ()
setFirstWindow wp =
    withRef wp setFirstWindow'
nextWindow' :: (Ptr ()) -> IO ((Maybe (Ref Window)))
nextWindow' a1 =
  let {a1' = id a1} in 
  nextWindow''_ a1' >>= \res ->
  let {res' = unsafeToMaybeRef res} in
  return (res')

{-# LINE 345 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

nextWindow :: (Parent a Window) => Ref a -> IO (Maybe (Ref Window))
nextWindow currWindow =
    withRef currWindow nextWindow'
modal :: IO ((Maybe (Ref Window)))
modal =
  modal'_ >>= \res ->
  let {res' = unsafeToMaybeRef res} in
  return (res')

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

grab :: IO ((Maybe (Ref Window)))
grab =
  grab'_ >>= \res ->
  let {res' = unsafeToMaybeRef res} in
  return (res')

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

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

{-# LINE 354 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

setGrab :: (Parent a Window) => Ref a -> IO ()
setGrab wp = withRef wp setGrab'
event :: IO ((Event))
event =
  event'_ >>= \res ->
  let {res' = cToEnum res} in
  return (res')

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

eventX :: IO ((Int))
eventX =
  eventX'_ >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 360 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

eventY :: IO ((Int))
eventY =
  eventY'_ >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

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

eventXRoot :: IO ((Int))
eventXRoot =
  eventXRoot'_ >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

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

eventYRoot :: IO ((Int))
eventYRoot =
  eventYRoot'_ >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 366 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

eventDx :: IO ((Int))
eventDx =
  eventDx'_ >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 368 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

eventDy :: IO ((Int))
eventDy =
  eventDy'_ >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

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

getMouse' :: IO ((Int), (Int))
getMouse' =
  alloca $ \a1' -> 
  alloca $ \a2' -> 
  getMouse''_ a1' a2' >>
  peekIntConv  a1'>>= \a1'' -> 
  peekIntConv  a2'>>= \a2'' -> 
  return (a1'', a2'')

{-# LINE 375 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

getMouse :: IO Position
getMouse = do
  (x_pos,y_pos) <- getMouse'
  return $ (Position (X x_pos) (Y y_pos))
eventClicks :: IO ((Int))
eventClicks =
  eventClicks'_ >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 381 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

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

{-# LINE 383 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

eventIsClick :: IO ((Bool))
eventIsClick =
  eventIsClick'_ >>= \res ->
  let {res' = toBool res} in
  return (res')

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

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

{-# LINE 387 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

eventButton :: IO ((MouseButton))
eventButton =
  eventButton'_ >>= \res ->
  let {res' = cToEnum res} in
  return (res')

{-# LINE 389 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

eventStates :: [EventState]
eventStates = [
               Kb_ShiftState,
               Kb_CapsLockState,
               Kb_CtrlState,
               Kb_AltState,
               Kb_NumLockState,
               Kb_MetaState,
               Kb_ScrollLockState,
               Mouse_Button1State,
               Mouse_Button2State,
               Mouse_Button3State
              ]
extractEventStates :: CInt -> [EventState]
extractEventStates = extract eventStates
-- foldModifiers :: [KeyboardCode] -> CInt
-- foldModifiers codes =
--     let validKeysyms = map cFromEnum (filter (\c -> c `elem` validKeyboardStates) codes)
--     in
--       case validKeysyms of
--         [] -> (-1)
--         (k:ks) -> foldl (\accum k' -> accum .&. k') k ks
eventState :: IO (([EventState]))
eventState =
  eventState'_ >>= \res ->
  let {res' = extractEventStates res} in
  return (res')

{-# LINE 413 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

containsEventState :: (EventState) -> IO ((Bool))
containsEventState a1 =
  let {a1' = cFromEnum a1} in 
  containsEventState'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')

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

eventKey :: IO ((KeyType))
eventKey =
  eventKey'_ >>= \res ->
  let {res' = cToKeyType res} in
  return (res')

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

eventOriginalKey :: IO ((KeyType))
eventOriginalKey =
  eventOriginalKey'_ >>= \res ->
  let {res' = cToKeyType res} in
  return (res')

{-# LINE 419 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

eventKeyPressed :: (KeyType) -> IO ((Bool))
eventKeyPressed a1 =
  let {a1' = cFromKeyType a1} in 
  eventKeyPressed'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')

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

getKey :: (KeyType) -> IO ((Bool))
getKey a1 =
  let {a1' = cFromKeyType a1} in 
  getKey'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')

{-# LINE 423 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

eventText :: IO ((T.Text))
eventText =
  eventText'_ >>= \res ->
  let {res' = unsafeFromCString res} in
  return (res')

{-# LINE 425 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

eventLength :: IO ((Int))
eventLength =
  eventLength'_ >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 427 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

compose :: IO ((Bool), (Int))
compose =
  alloca $ \a1' -> 
  compose'_ a1' >>= \res ->
  let {res' = toBool res} in
  peekIntConv  a1'>>= \a1'' -> 
  return (res', a1'')

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

composeReset :: IO ((()))
composeReset =
  composeReset'_ >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 431 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

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

{-# LINE 433 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

eventInsideRegion :: Rectangle -> IO Event
eventInsideRegion (Rectangle
                   (Position
                    (X x_pos)
                    (Y y_pos))
                   (Size
                    (Width width)
                    (Height height))) =
    do
      eventNum <- eventInsideRegion' x_pos y_pos width height
      return $ toEnum eventNum
eventInsideWidget' :: (Ptr ()) -> IO ((Int))
eventInsideWidget' a1 =
  let {a1' = id a1} in 
  eventInsideWidget''_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 446 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

eventInsideWidget :: (Parent a Widget) => Ref a -> IO Event
eventInsideWidget wp =
    withRef wp  (\ptr -> do
                      eventNum <- eventInsideWidget' (castPtr ptr)
                      return $ toEnum eventNum)
testShortcut :: (FlShortcut) -> IO ((Bool))
testShortcut a1 =
  let {a1' = id a1} in 
  testShortcut'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')

{-# LINE 453 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

enableIm :: IO ((()))
enableIm =
  enableIm'_ >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

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

disableIm :: IO ((()))
disableIm =
  disableIm'_ >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 457 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

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

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

handle :: (Parent a Window) =>  Event -> Ref a -> IO Int
handle e wp =
    withRef wp (handle' (cFromEnum e))
handle_' :: (Int) -> (Ptr ()) -> IO ((Int))
handle_' a1 a2 =
  let {a1' = fromIntegral a1} in 
  let {a2' = id a2} in 
  handle_''_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 464 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

handle_ :: (Parent a Window) =>  Event -> Ref a -> IO Int
handle_ e wp =
    withRef wp (handle_' (cFromEnum e))
belowmouse :: IO ((Maybe (Ref Widget)))
belowmouse =
  belowmouse'_ >>= \res ->
  let {res' = unsafeToMaybeRef res} in
  return (res')

{-# LINE 469 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

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

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

setBelowmouse :: (Parent a Widget) => Ref a -> IO ()
setBelowmouse wp = withRef wp setBelowmouse'
pushed' :: IO ((Ptr ()))
pushed' =
  pushed''_ >>= \res ->
  let {res' = id res} in
  return (res')

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

pushed :: IO (Maybe (Ref Widget))
pushed = pushed' >>= toMaybeRef
setPushed' :: (Ptr ()) -> IO ((()))
setPushed' a1 =
  let {a1' = id a1} in 
  setPushed''_ a1' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 479 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

setPushed :: (Parent a Widget) => Ref a -> IO ()
setPushed wp = withRef wp setPushed'
focus :: IO ((Maybe (Ref Widget)))
focus =
  focus'_ >>= \res ->
  let {res' = unsafeToMaybeRef res} in
  return (res')

{-# LINE 483 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

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

{-# LINE 485 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

setFocus :: (Parent a Widget) => Ref a -> IO ()
setFocus wp = withRef wp setFocus'
selectionOwner :: IO ((Maybe (Ref Widget)))
selectionOwner =
  selectionOwner'_ >>= \res ->
  let {res' = unsafeToMaybeRef res} in
  return (res')

{-# LINE 489 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

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

{-# LINE 491 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

setSelectionOwner :: (Parent a Widget) => Ref a -> IO ()
setSelectionOwner wp = withRef wp setSelection_Owner'
addHandler' :: (FunPtr GlobalEventHandlerPrim) -> IO ((()))
addHandler' a1 =
  let {a1' = id a1} in 
  addHandler''_ a1' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 495 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

removeHandler' :: (FunPtr GlobalEventHandlerPrim) -> IO ((()))
removeHandler' a1 =
  let {a1' = id a1} in 
  removeHandler''_ a1' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 497 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

setHandler :: GlobalEventHandlerF -> IO ()
setHandler eh = do
  newGlobalEventHandler <- toGlobalEventHandlerPrim eh
  curr <- do
    old <- readIORef ptrToGlobalEventHandler
    writeIORef ptrToGlobalEventHandler newGlobalEventHandler
    return old
  removeHandler' curr
  addHandler' newGlobalEventHandler

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

{-# LINE 509 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

eventDispatch' :: IO ((FunPtr EventDispatchPrim))
eventDispatch' =
  eventDispatch''_ >>= \res ->
  let {res' = id res} in
  return (res')

{-# LINE 511 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

eventDispatch :: (Parent a Widget) => IO (Event -> Ref a -> IO (Int))
eventDispatch =
    do
      funPtr <- eventDispatch'
      return (\e window ->
                  withRef
                   window
                    (\ptr ->
                         let eventNum = fromIntegral (fromEnum e)
                             fun = unwrapEventDispatchPrim funPtr
                         in fun eventNum (castPtr ptr) >>=
                            return . fromIntegral
                    )
             )

setEventDispatch :: (Parent a Widget) => (Event -> Ref a -> IO Int) -> IO ()
setEventDispatch ed = do
    do
      let toPrim = (\e ptr ->
                      let eventEnum = toEnum $ fromIntegral e
                      in do
                      obj <- toRef ptr
                      result <- ed eventEnum obj
                      return $ fromIntegral result
                    )
      callbackPtr <-  wrapEventDispatchPrim toPrim
      ptrToCallbackPtr <- new callbackPtr
      poke ptrToCallbackPtr callbackPtr
      setEventDispatch' ptrToCallbackPtr
copy :: (T.Text) -> (Int) -> IO ((()))
copy a1 a2 =
  let {a1' = unsafeToCString a1} in 
  let {a2' = fromIntegral a2} in 
  copy'_ a1' a2' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 542 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

copyWithDestination :: (T.Text) -> (Int) -> (Int) -> IO ((()))
copyWithDestination a1 a2 a3 =
  let {a1' = unsafeToCString a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  copyWithDestination'_ a1' a2' a3' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 544 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

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

{-# LINE 546 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

paste :: (Parent a Widget) => Ref a -> Maybe Int -> IO ()
paste widget (Just clipboard) = withRef widget ((flip pasteWithSource) clipboard)
paste widget Nothing          = withRef widget ((flip pasteWithSource) 0)

dnd :: IO ((Int))
dnd =
  dnd'_ >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 552 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

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

{-# LINE 554 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

y :: IO ((Int))
y =
  y'_ >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 556 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

w :: IO ((Int))
w =
  w'_ >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 558 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

h :: IO ((Int))
h =
  h'_ >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 560 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

screenCount :: IO ((Int))
screenCount =
  screenCount'_ >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 562 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}


screenXYWH :: IO ((Int), (Int), (Int), (Int))
screenXYWH =
  alloca $ \a1' -> 
  alloca $ \a2' -> 
  alloca $ \a3' -> 
  alloca $ \a4' -> 
  screenXYWH'_ a1' a2' a3' a4' >>
  peekIntConv  a1'>>= \a1'' -> 
  peekIntConv  a2'>>= \a2'' -> 
  peekIntConv  a3'>>= \a3'' -> 
  peekIntConv  a4'>>= \a4'' -> 
  return (a1'', a2'', a3'', a4'')

{-# LINE 570 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

screenXYWYWithMXMY :: (Int) -> (Int) -> IO ((Int), (Int), (Int), (Int))
screenXYWYWithMXMY a5 a6 =
  alloca $ \a1' -> 
  alloca $ \a2' -> 
  alloca $ \a3' -> 
  alloca $ \a4' -> 
  let {a5' = fromIntegral a5} in 
  let {a6' = fromIntegral a6} in 
  screenXYWYWithMXMY'_ a1' a2' a3' a4' a5' a6' >>
  peekIntConv  a1'>>= \a1'' -> 
  peekIntConv  a2'>>= \a2'' -> 
  peekIntConv  a3'>>= \a3'' -> 
  peekIntConv  a4'>>= \a4'' -> 
  return (a1'', a2'', a3'', a4'')

{-# LINE 579 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

screenXYWNWithN :: (Int) -> IO ((Int), (Int), (Int), (Int))
screenXYWNWithN a5 =
  alloca $ \a1' -> 
  alloca $ \a2' -> 
  alloca $ \a3' -> 
  alloca $ \a4' -> 
  let {a5' = fromIntegral a5} in 
  screenXYWNWithN'_ a1' a2' a3' a4' a5' >>
  peekIntConv  a1'>>= \a1'' -> 
  peekIntConv  a2'>>= \a2'' -> 
  peekIntConv  a3'>>= \a3'' -> 
  peekIntConv  a4'>>= \a4'' -> 
  return (a1'', a2'', a3'', a4'')

{-# LINE 587 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

screenXYWHWithNMXMYMWMH :: (Int) -> (Int) -> (Int) -> (Int) -> IO ((Int), (Int), (Int), (Int))
screenXYWHWithNMXMYMWMH a5 a6 a7 a8 =
  alloca $ \a1' -> 
  alloca $ \a2' -> 
  alloca $ \a3' -> 
  alloca $ \a4' -> 
  let {a5' = fromIntegral a5} in 
  let {a6' = fromIntegral a6} in 
  let {a7' = fromIntegral a7} in 
  let {a8' = fromIntegral a8} in 
  screenXYWHWithNMXMYMWMH'_ a1' a2' a3' a4' a5' a6' a7' a8' >>
  peekIntConv  a1'>>= \a1'' -> 
  peekIntConv  a2'>>= \a2'' -> 
  peekIntConv  a3'>>= \a3'' -> 
  peekIntConv  a4'>>= \a4'' -> 
  return (a1'', a2'', a3'', a4'')

{-# LINE 598 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}


screenBounds :: Maybe ScreenLocation -> IO Rectangle
screenBounds location =
    case location of
      (Just (Intersect (Rectangle (Position (X x_pos) (Y y_pos)) (Size (Width width) (Height height))))) ->
          screenXYWHWithNMXMYMWMH x_pos y_pos width height >>= return . toRectangle
      (Just (ScreenPosition (Position (X x_pos) (Y y_pos)))) ->
          screenXYWYWithMXMY x_pos y_pos >>= return . toRectangle
      (Just (ScreenNumber n)) ->
          screenXYWNWithN n >>= return . toRectangle
      Nothing ->
          screenXYWH >>= return . toRectangle

screenDpi' :: IO ((Float), (Float))
screenDpi' =
  alloca $ \a1' -> 
  alloca $ \a2' -> 
  screenDpi''_ a1' a2' >>
  peekFloatConv  a1'>>= \a1'' -> 
  peekFloatConv  a2'>>= \a2'' -> 
  return (a1'', a2'')

{-# LINE 615 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

screenDpiWithN' :: (Int) -> IO ((Float), (Float))
screenDpiWithN' a3 =
  alloca $ \a1' -> 
  alloca $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  screenDpiWithN''_ a1' a2' a3' >>
  peekFloatConv  a1'>>= \a1'' -> 
  peekFloatConv  a2'>>= \a2'' -> 
  return (a1'', a2'')

{-# LINE 620 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}


screenDPI :: Maybe Int -> IO DPI
screenDPI (Just n) = do
  (dpiX, dpiY) <- screenDpiWithN' n
  return $ DPI dpiX dpiY
screenDPI Nothing = do
  (dpiX, dpiY) <- screenDpi'
  return $ DPI dpiX dpiY

screenWorkAreaWithMXMY' :: (Int) -> (Int) -> IO ((Int), (Int), (Int), (Int))
screenWorkAreaWithMXMY' a5 a6 =
  alloca $ \a1' -> 
  alloca $ \a2' -> 
  alloca $ \a3' -> 
  alloca $ \a4' -> 
  let {a5' = fromIntegral a5} in 
  let {a6' = fromIntegral a6} in 
  screenWorkAreaWithMXMY''_ a1' a2' a3' a4' a5' a6' >>
  peekIntConv  a1'>>= \a1'' -> 
  peekIntConv  a2'>>= \a2'' -> 
  peekIntConv  a3'>>= \a3'' -> 
  peekIntConv  a4'>>= \a4'' -> 
  return (a1'', a2'', a3'', a4'')

{-# LINE 639 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

screenWorkAreaWithN' :: (Int) -> IO ((Int), (Int), (Int), (Int))
screenWorkAreaWithN' a5 =
  alloca $ \a1' -> 
  alloca $ \a2' -> 
  alloca $ \a3' -> 
  alloca $ \a4' -> 
  let {a5' = fromIntegral a5} in 
  screenWorkAreaWithN''_ a1' a2' a3' a4' a5' >>
  peekIntConv  a1'>>= \a1'' -> 
  peekIntConv  a2'>>= \a2'' -> 
  peekIntConv  a3'>>= \a3'' -> 
  peekIntConv  a4'>>= \a4'' -> 
  return (a1'', a2'', a3'', a4'')

{-# LINE 648 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

screenWorkArea' :: IO ((Int), (Int), (Int), (Int))
screenWorkArea' =
  alloca $ \a1' -> 
  alloca $ \a2' -> 
  alloca $ \a3' -> 
  alloca $ \a4' -> 
  screenWorkArea''_ a1' a2' a3' a4' >>= \res ->
  peekIntConv  a1'>>= \a1'' -> 
  peekIntConv  a2'>>= \a2'' -> 
  peekIntConv  a3'>>= \a3'' -> 
  peekIntConv  a4'>>= \a4'' -> 
  return (a1'', a2'', a3'', a4'')

{-# LINE 656 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

screenWorkArea :: Maybe ScreenLocation -> IO Rectangle
screenWorkArea location =
    case location of
      (Just (Intersect (Rectangle (Position (X x_pos) (Y y_pos)) _))) ->
          screenWorkAreaWithMXMY' x_pos y_pos >>= return . toRectangle
      (Just (ScreenPosition (Position (X x_pos) (Y y_pos)))) ->
          screenWorkAreaWithMXMY' x_pos y_pos >>= return . toRectangle
      (Just (ScreenNumber n)) ->
          screenWorkAreaWithN' n >>= return . toRectangle
      Nothing ->
          screenWorkArea' >>= return . toRectangle

setColorRgb :: Color -> Word8 -> Word8 -> Word8 -> IO ()
setColorRgb c r g b = fl_set_color_rgb
{-# LINE 670 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

                        (cFromColor c)
                        (fromIntegral r)
                        (fromIntegral g)
                        (fromIntegral b)
setColor :: (Color) -> (Int) -> IO ((()))
setColor a1 a2 =
  let {a1' = cFromColor a1} in 
  let {a2' = fromIntegral a2} in 
  setColor'_ a1' a2' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 676 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

getColor :: (Color) -> IO ((Int))
getColor a1 =
  let {a1' = cFromColor a1} in 
  getColor'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 678 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

getColorRgb' :: (Color) -> IO ((()), (CUChar), (CUChar), (CUChar))
getColorRgb' a1 =
  let {a1' = cFromColor a1} in 
  alloca $ \a2' -> 
  alloca $ \a3' -> 
  alloca $ \a4' -> 
  getColorRgb''_ a1' a2' a3' a4' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  peekIntConv  a2'>>= \a2'' -> 
  peekIntConv  a3'>>= \a3'' -> 
  peekIntConv  a4'>>= \a4'' -> 
  return (res', a2'', a3'', a4'')

{-# LINE 685 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

getColorRgb :: Color -> IO RGB
getColorRgb c = do
   (_,r,g,b) <- getColorRgb' c
   return (r,g,b)

freeColor' :: (Color) -> IO ((()))
freeColor' a1 =
  let {a1' = cFromColor a1} in 
  freeColor''_ a1' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 693 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

freeColorWithOverlay' :: (Color) -> (Int) -> IO ((()))
freeColorWithOverlay' a1 a2 =
  let {a1' = cFromColor a1} in 
  let {a2' = fromIntegral a2} in 
  freeColorWithOverlay''_ a1' a2' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 695 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

removeFromColormap :: Maybe Int -> Color -> IO ()
removeFromColormap (Just overlay) c = freeColorWithOverlay' c overlay
removeFromColormap Nothing c = freeColor' c
getFont :: (Font) -> IO ((T.Text))
getFont a1 =
  let {a1' = cFromFont a1} in 
  getFont'_ a1' >>= \res ->
  let {res' = unsafeFromCString res} in
  return (res')

{-# LINE 701 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

getFontNameWithAttributes' :: (Font) -> IO ((T.Text), (Maybe FontAttribute))
getFontNameWithAttributes' a1 =
  let {a1' = cFromFont a1} in 
  alloca $ \a2' -> 
  getFontNameWithAttributes''_ a1' a2' >>= \res ->
  let {res' = unsafeFromCString res} in
  toAttribute  a2'>>= \a2'' -> 
  return (res', a2'')

{-# LINE 703 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

toAttribute :: Ptr CInt -> IO (Maybe FontAttribute)
toAttribute ptr =
        do
          attributeCode <- peekIntConv ptr
          return $ cToFontAttribute attributeCode
getFontName :: Font -> IO (T.Text, Maybe FontAttribute)
getFontName f = getFontNameWithAttributes' f
getFontSizes :: (Font) -> IO ((Int), (Int))
getFontSizes a1 =
  let {a1' = cFromFont a1} in 
  alloca $ \a2' -> 
  getFontSizes'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  peekIntConv  a2'>>= \a2'' -> 
  return (res', a2'')

{-# LINE 712 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

setFontByString :: (Font) -> (T.Text) -> IO ((()))
setFontByString a1 a2 =
  let {a1' = cFromFont a1} in 
  let {a2' = unsafeToCString a2} in 
  setFontByString'_ a1' a2' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 714 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

setFontByFont :: (Font) -> (Font) -> IO ((()))
setFontByFont a1 a2 =
  let {a1' = cFromFont a1} in 
  let {a2' = cFromFont a2} in 
  setFontByFont'_ a1' a2' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 716 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

setFonts :: IO ((Font))
setFonts =
  setFonts'_ >>= \res ->
  let {res' = cToFont res} in
  return (res')

{-# LINE 718 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

setFontsWithString :: (T.Text) -> IO ((Font))
setFontsWithString a1 =
  let {a1' = unsafeToCString a1} in 
  setFontsWithString'_ a1' >>= \res ->
  let {res' = cToFont res} in
  return (res')

{-# LINE 720 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}


addFdWhen' :: (CInt) -> (CInt) -> (FunPtr FDHandlerPrim) -> IO ()
addFdWhen' a1 a2 a3 =
  let {a1' = fromIntegral a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = id a3} in 
  addFdWhen''_ a1' a2' a3' >>
  return ()

{-# LINE 727 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}


addFdWhen :: CInt -> [FdWhen] -> FDHandler -> IO ()
addFdWhen fd fdWhens handler = do
  fPtr <- toFDHandlerPrim handler
  addFdWhen' fd (fromIntegral . combine $ fdWhens) fPtr

addFd' :: (CInt) -> (FunPtr FDHandlerPrim) -> IO ()
addFd' a1 a2 =
  let {a1' = fromIntegral a1} in 
  let {a2' = id a2} in 
  addFd''_ a1' a2' >>
  return ()

{-# LINE 738 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}


addFd :: CInt -> FDHandler -> IO ()
addFd fd handler = do
  fPtr <- toFDHandlerPrim handler
  addFd' fd fPtr

removeFdWhen' :: (CInt) -> (CInt) -> IO ()
removeFdWhen' a1 a2 =
  let {a1' = fromIntegral a1} in 
  let {a2' = fromIntegral a2} in 
  removeFdWhen''_ a1' a2' >>
  return ()

{-# LINE 745 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

removeFdWhen :: CInt -> [FdWhen] -> IO ()
removeFdWhen fd fdWhens =
  removeFdWhen' fd (fromIntegral . combine $ fdWhens)

removeFd' :: (CInt) -> IO ()
removeFd' a1 =
  let {a1' = fromIntegral a1} in 
  removeFd''_ a1' >>
  return ()

{-# LINE 750 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

removeFd :: CInt -> IO ()
removeFd fd = removeFd' fd

getBoxtype' :: (Boxtype) -> IO ((FunPtr BoxDrawFPrim))
getBoxtype' a1 =
  let {a1' = cFromEnum a1} in 
  getBoxtype''_ a1' >>= \res ->
  let {res' = id res} in
  return (res')

{-# LINE 755 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

getBoxtype :: Boxtype -> IO BoxDrawF
getBoxtype bt = do
  wrappedFunPtr <- getBoxtype' bt
  let boxDrawPrim = unwrapBoxDrawFPrim wrappedFunPtr
  return $ toBoxDrawF boxDrawPrim

setBoxtype' :: (Boxtype) -> (FunPtr BoxDrawFPrim) -> (Word8) -> (Word8) -> (Word8) -> (Word8) -> IO ((()))
setBoxtype' a1 a2 a3 a4 a5 a6 =
  let {a1' = cFromEnum a1} in 
  let {a2' = id a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  let {a5' = fromIntegral a5} in 
  let {a6' = fromIntegral a6} in 
  setBoxtype''_ a1' a2' a3' a4' a5' a6' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 770 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

setBoxtypeByBoxtype' :: (Boxtype) -> (Boxtype) -> IO ((()))
setBoxtypeByBoxtype' a1 a2 =
  let {a1' = cFromEnum a1} in 
  let {a2' = cFromEnum a2} in 
  setBoxtypeByBoxtype''_ a1' a2' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 775 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}


data BoxtypeSpec = FromSpec BoxDrawF Word8 Word8 Word8 Word8
                 | FromBoxtype Boxtype
setBoxtype :: Boxtype -> BoxtypeSpec -> IO ()
setBoxtype bt (FromSpec f dx dy dw dh) =
    do
      funPtr <- wrapBoxDrawFPrim (toBoxDrawFPrim f)
      setBoxtype' bt funPtr dx dy dw dh
setBoxtype bt (FromBoxtype template) =
    setBoxtypeByBoxtype' bt template

boxDx :: (Boxtype) -> IO ((Int))
boxDx a1 =
  let {a1' = cFromEnum a1} in 
  boxDx'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 788 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

boxDy :: (Boxtype) -> IO ((Int))
boxDy a1 =
  let {a1' = cFromEnum a1} in 
  boxDy'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 790 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

boxDw :: (Boxtype) -> IO ((Int))
boxDw a1 =
  let {a1' = cFromEnum a1} in 
  boxDw'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 792 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

boxDh :: (Boxtype) -> IO ((Int))
boxDh a1 =
  let {a1' = cFromEnum a1} in 
  boxDh'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 794 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

drawBoxActive :: IO ((Bool))
drawBoxActive =
  drawBoxActive'_ >>= \res ->
  let {res' = toBool res} in
  return (res')

{-# LINE 796 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

eventShift :: IO ((Bool))
eventShift =
  eventShift'_ >>= \res ->
  let {res' = toBool res} in
  return (res')

{-# LINE 798 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

eventCtrl :: IO ((Bool))
eventCtrl =
  eventCtrl'_ >>= \res ->
  let {res' = toBool res} in
  return (res')

{-# LINE 800 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

eventCommand :: IO ((Bool))
eventCommand =
  eventCommand'_ >>= \res ->
  let {res' = toBool res} in
  return (res')

{-# LINE 802 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

eventAlt :: IO ((Bool))
eventAlt =
  eventAlt'_ >>= \res ->
  let {res' = toBool res} in
  return (res')

{-# LINE 804 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

eventButtons :: IO ((Bool))
eventButtons =
  eventButtons'_ >>= \res ->
  let {res' = toBool res} in
  return (res')

{-# LINE 806 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

eventButton1 :: IO ((Bool))
eventButton1 =
  eventButton1'_ >>= \res ->
  let {res' = toBool res} in
  return (res')

{-# LINE 808 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

eventButton2 :: IO ((Bool))
eventButton2 =
  eventButton2'_ >>= \res ->
  let {res' = toBool res} in
  return (res')

{-# LINE 810 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

eventButton3 :: IO ((Bool))
eventButton3 =
  eventButton3'_ >>= \res ->
  let {res' = toBool res} in
  return (res')

{-# LINE 812 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

release :: IO ()
release = fl_release
{-# LINE 814 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

setVisibleFocus :: Int -> IO ()
setVisibleFocus = fl_set_visible_focus . fromIntegral
visibleFocus :: IO Int
visibleFocus = fl_visible_focus >>= return . fromIntegral
setDndTextOps :: Bool -> IO ()
setDndTextOps =  fl_set_dnd_text_ops . fromBool
dndTextOps :: IO Option
dndTextOps = fl_dnd_text_ops >>= return . cToEnum
deleteWidget :: (Parent a Widget) => Ref a -> IO ()
deleteWidget wptr =
  swapRef wptr $ \ptr -> do
    fl_delete_widget ptr
    return nullPtr
doWidgetDeletion :: IO ()
doWidgetDeletion = fl_do_widget_deletion
{-# LINE 829 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

watchWidgetPointer :: (Parent a Widget) => Ref a -> IO ()
watchWidgetPointer wp = withRef wp fl_Watch_widget_Pointer
{-# LINE 831 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

releaseWidgetPointer :: (Parent a Widget) => Ref a -> IO ()
releaseWidgetPointer wp = withRef wp fl_release_widget_pointer
{-# LINE 833 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

clearWidgetPointer :: (Parent a Widget) => Ref a -> IO ()
clearWidgetPointer wp = withRef wp fl_Clear_Widget_Pointer
{-# LINE 835 "src/Graphics/UI/FLTK/LowLevel/FL.chs" #-}

setBoxColor :: Color -> IO ()
setBoxColor c = fl_set_box_color (cFromColor c)
boxColor :: Color -> IO Color
boxColor c = fl_box_color (cFromColor c) >>= return . cToColor
abiVersion :: IO Int
abiVersion = fl_abi_version >>= return . fromIntegral
apiVersion :: IO Int
apiVersion = fl_abi_version >>= return . fromIntegral
localCtrl :: IO T.Text
localCtrl = fl_local_ctrl >>= cStringToText
localAlt :: IO T.Text
localAlt = fl_local_alt >>= cStringToText
localMeta :: IO T.Text
localMeta = fl_local_meta >>= cStringToText
localShift :: IO T.Text
localShift = fl_local_shift >>= cStringToText

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_run"
  fl_run :: (IO C2HSImp.CInt)

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_check"
  fl_check :: (IO C2HSImp.CInt)

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_ready"
  fl_ready :: (IO C2HSImp.CInt)

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_option"
  fl_option :: (C2HSImp.CInt -> (IO C2HSImp.CInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_set_option"
  fl_set_option :: (C2HSImp.CInt -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_add_awake_handler_"
  addAwakeHandler''_ :: ((C2HSImp.FunPtr ((C2HSImp.Ptr ()) -> (IO ()))) -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_get_awake_handler_"
  getAwakeHandler_''_ :: ((C2HSImp.Ptr (C2HSImp.FunPtr ((C2HSImp.Ptr ()) -> (IO ())))) -> ((C2HSImp.Ptr (C2HSImp.Ptr ())) -> (IO C2HSImp.CInt)))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_version"
  version'_ :: (IO C2HSImp.CDouble)

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_help"
  help'_ :: (IO (C2HSImp.Ptr C2HSImp.CChar))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_display"
  fl_display :: ((C2HSImp.Ptr C2HSImp.CChar) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_visual"
  visual'_ :: (C2HSImp.CInt -> (IO C2HSImp.CInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_gl_visual"
  glVisual'_ :: (C2HSImp.CInt -> (IO C2HSImp.CInt))

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

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_own_colormap"
  fl_own_colormap :: (IO ())

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_get_system_colors"
  fl_get_system_colors :: (IO ())

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_foreground"
  fl_foreground :: (C2HSImp.CUChar -> (C2HSImp.CUChar -> (C2HSImp.CUChar -> (IO ()))))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_background"
  fl_background :: (C2HSImp.CUChar -> (C2HSImp.CUChar -> (C2HSImp.CUChar -> (IO ()))))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_background2"
  fl_background2 :: (C2HSImp.CUChar -> (C2HSImp.CUChar -> (C2HSImp.CUChar -> (IO ()))))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_scheme"
  scheme'_ :: (IO (C2HSImp.Ptr C2HSImp.CChar))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_set_scheme"
  fl_set_scheme :: ((C2HSImp.Ptr C2HSImp.CChar) -> (IO C2HSImp.CInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_is_scheme"
  fl_is_scheme :: ((C2HSImp.Ptr C2HSImp.CChar) -> (IO C2HSImp.CInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_wait"
  wait'_ :: (IO C2HSImp.CInt)

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_set_wait"
  setWait'_ :: (C2HSImp.CDouble -> (IO C2HSImp.CDouble))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_scrollbar_size"
  scrollbarSize'_ :: (IO C2HSImp.CInt)

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_set_scrollbar_size"
  setScrollbarSize'_ :: (C2HSImp.CInt -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_readqueue"
  readqueue'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_add_timeout"
  addTimeout'_ :: (C2HSImp.CDouble -> ((C2HSImp.FunPtr ((C2HSImp.Ptr ()) -> (IO ()))) -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_repeat_timeout"
  repeatTimeout'_ :: (C2HSImp.CDouble -> ((C2HSImp.FunPtr ((C2HSImp.Ptr ()) -> (IO ()))) -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_has_timeout"
  hasTimeout'_ :: ((C2HSImp.FunPtr ((C2HSImp.Ptr ()) -> (IO ()))) -> (IO C2HSImp.CInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_remove_timeout"
  removeTimeout'_ :: ((C2HSImp.FunPtr ((C2HSImp.Ptr ()) -> (IO ()))) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_add_check"
  addCheck'_ :: ((C2HSImp.FunPtr ((C2HSImp.Ptr ()) -> (IO ()))) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_has_check"
  hasCheck'_ :: ((C2HSImp.FunPtr ((C2HSImp.Ptr ()) -> (IO ()))) -> (IO C2HSImp.CInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_remove_check"
  removeCheck'_ :: ((C2HSImp.FunPtr ((C2HSImp.Ptr ()) -> (IO ()))) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_add_idle"
  addIdle'_ :: ((C2HSImp.FunPtr ((C2HSImp.Ptr ()) -> (IO ()))) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_has_idle"
  hasIdle'_ :: ((C2HSImp.FunPtr ((C2HSImp.Ptr ()) -> (IO ()))) -> (IO C2HSImp.CInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_remove_idle"
  removeIdle'_ :: ((C2HSImp.FunPtr ((C2HSImp.Ptr ()) -> (IO ()))) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_damage"
  damage'_ :: (IO C2HSImp.CInt)

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_redraw"
  redraw'_ :: (IO ())

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_flush"
  flush'_ :: (IO ())

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_first_window"
  firstWindow'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_set_first_window"
  setFirstWindow''_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_next_window"
  nextWindow''_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_modal"
  modal'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_grab"
  grab'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_set_grab"
  setGrab''_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_event"
  event'_ :: (IO C2HSImp.CInt)

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_event_x"
  eventX'_ :: (IO C2HSImp.CInt)

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_event_y"
  eventY'_ :: (IO C2HSImp.CInt)

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_event_x_root"
  eventXRoot'_ :: (IO C2HSImp.CInt)

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_event_y_root"
  eventYRoot'_ :: (IO C2HSImp.CInt)

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_event_dx"
  eventDx'_ :: (IO C2HSImp.CInt)

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_event_dy"
  eventDy'_ :: (IO C2HSImp.CInt)

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

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_event_clicks"
  eventClicks'_ :: (IO C2HSImp.CInt)

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_set_event_clicks"
  setEventClicks'_ :: (C2HSImp.CInt -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_event_is_click"
  eventIsClick'_ :: (IO C2HSImp.CInt)

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_set_event_is_click"
  setEventIsClick'_ :: (C2HSImp.CInt -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_event_button"
  eventButton'_ :: (IO C2HSImp.CInt)

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_event_state"
  eventState'_ :: (IO C2HSImp.CInt)

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_contains_event_state"
  containsEventState'_ :: (C2HSImp.CInt -> (IO C2HSImp.CInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_event_key"
  eventKey'_ :: (IO C2HSImp.CInt)

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_event_original_key"
  eventOriginalKey'_ :: (IO C2HSImp.CInt)

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_event_key_pressed"
  eventKeyPressed'_ :: (C2HSImp.CInt -> (IO C2HSImp.CInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_get_key"
  getKey'_ :: (C2HSImp.CInt -> (IO C2HSImp.CInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_event_text"
  eventText'_ :: (IO (C2HSImp.Ptr C2HSImp.CChar))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_event_length"
  eventLength'_ :: (IO C2HSImp.CInt)

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

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_compose_reset"
  composeReset'_ :: (IO ())

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_event_inside_region"
  eventInsideRegion''_ :: (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))))

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

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_test_shortcut"
  testShortcut'_ :: (C2HSImp.CUInt -> (IO C2HSImp.CInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_enable_im"
  enableIm'_ :: (IO ())

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_disable_im"
  disableIm'_ :: (IO ())

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

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

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_belowmouse"
  belowmouse'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_set_belowmouse"
  setBelowmouse''_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_pushed"
  pushed''_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_set_pushed"
  setPushed''_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_focus"
  focus'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_set_focus"
  setFocus''_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_selection_owner"
  selectionOwner'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_set_selection_owner"
  setSelection_Owner''_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_add_handler"
  addHandler''_ :: ((C2HSImp.FunPtr (C2HSImp.CInt -> (IO C2HSImp.CInt))) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_remove_handler"
  removeHandler''_ :: ((C2HSImp.FunPtr (C2HSImp.CInt -> (IO C2HSImp.CInt))) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_set_event_dispatch"
  setEventDispatch''_ :: ((C2HSImp.Ptr (C2HSImp.FunPtr (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))))) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_event_dispatch"
  eventDispatch''_ :: (IO (C2HSImp.FunPtr (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))))

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

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

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

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_dnd"
  dnd'_ :: (IO C2HSImp.CInt)

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_x"
  x'_ :: (IO C2HSImp.CInt)

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_y"
  y'_ :: (IO C2HSImp.CInt)

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_w"
  w'_ :: (IO C2HSImp.CInt)

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_h"
  h'_ :: (IO C2HSImp.CInt)

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_screen_count"
  screenCount'_ :: (IO C2HSImp.CInt)

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

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

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

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

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_screen_dpi"
  screenDpi''_ :: ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_screen_dpi_with_n"
  screenDpiWithN''_ :: ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (C2HSImp.CInt -> (IO ()))))

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

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

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

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_set_color_rgb"
  fl_set_color_rgb :: (C2HSImp.CUInt -> (C2HSImp.CUChar -> (C2HSImp.CUChar -> (C2HSImp.CUChar -> (IO ())))))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_set_color"
  setColor'_ :: (C2HSImp.CUInt -> (C2HSImp.CUInt -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_get_color"
  getColor'_ :: (C2HSImp.CUInt -> (IO C2HSImp.CUInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_get_color_rgb"
  getColorRgb''_ :: (C2HSImp.CUInt -> ((C2HSImp.Ptr C2HSImp.CUChar) -> ((C2HSImp.Ptr C2HSImp.CUChar) -> ((C2HSImp.Ptr C2HSImp.CUChar) -> (IO ())))))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_free_color"
  freeColor''_ :: (C2HSImp.CUInt -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_free_color_with_overlay"
  freeColorWithOverlay''_ :: (C2HSImp.CUInt -> (C2HSImp.CInt -> (IO ())))

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

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

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

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

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_set_font_by_font"
  setFontByFont'_ :: (C2HSImp.CInt -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_set_fonts"
  setFonts'_ :: (IO C2HSImp.CInt)

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

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_add_fd_with_when"
  addFdWhen''_ :: (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.FunPtr (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (IO ())))) -> (IO ()))))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_add_fd"
  addFd''_ :: (C2HSImp.CInt -> ((C2HSImp.FunPtr (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (IO ())))) -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_remove_fd_with_when"
  removeFdWhen''_ :: (C2HSImp.CInt -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_remove_fd"
  removeFd''_ :: (C2HSImp.CInt -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_get_boxtype"
  getBoxtype''_ :: (C2HSImp.CInt -> (IO (C2HSImp.FunPtr (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CUInt -> (IO ())))))))))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_set_boxtype"
  setBoxtype''_ :: (C2HSImp.CInt -> ((C2HSImp.FunPtr (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CUInt -> (IO ()))))))) -> (C2HSImp.CUChar -> (C2HSImp.CUChar -> (C2HSImp.CUChar -> (C2HSImp.CUChar -> (IO ())))))))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_set_boxtype_by_boxtype"
  setBoxtypeByBoxtype''_ :: (C2HSImp.CInt -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_box_dx"
  boxDx'_ :: (C2HSImp.CInt -> (IO C2HSImp.CInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_box_dy"
  boxDy'_ :: (C2HSImp.CInt -> (IO C2HSImp.CInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_box_dw"
  boxDw'_ :: (C2HSImp.CInt -> (IO C2HSImp.CInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_box_dh"
  boxDh'_ :: (C2HSImp.CInt -> (IO C2HSImp.CInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_draw_box_active"
  drawBoxActive'_ :: (IO C2HSImp.CInt)

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_event_shift"
  eventShift'_ :: (IO C2HSImp.CInt)

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_event_ctrl"
  eventCtrl'_ :: (IO C2HSImp.CInt)

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_event_command"
  eventCommand'_ :: (IO C2HSImp.CInt)

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_event_alt"
  eventAlt'_ :: (IO C2HSImp.CInt)

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_event_buttons"
  eventButtons'_ :: (IO C2HSImp.CInt)

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_event_button1"
  eventButton1'_ :: (IO C2HSImp.CInt)

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_event_button2"
  eventButton2'_ :: (IO C2HSImp.CInt)

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_event_button3"
  eventButton3'_ :: (IO C2HSImp.CInt)

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_release"
  fl_release :: (IO ())

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_set_visible_focus"
  fl_set_visible_focus :: (C2HSImp.CInt -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_visible_focus"
  fl_visible_focus :: (IO C2HSImp.CInt)

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_set_dnd_text_ops"
  fl_set_dnd_text_ops :: (C2HSImp.CInt -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_dnd_text_ops"
  fl_dnd_text_ops :: (IO C2HSImp.CInt)

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_delete_widget"
  fl_delete_widget :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_do_widget_deletion"
  fl_do_widget_deletion :: (IO ())

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_watch_widget_pointer"
  fl_Watch_widget_Pointer :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_release_widget_pointer"
  fl_release_widget_pointer :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_clear_widget_pointer"
  fl_Clear_Widget_Pointer :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_set_box_color"
  fl_set_box_color :: (C2HSImp.CUInt -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_box_color"
  fl_box_color :: (C2HSImp.CUInt -> (IO C2HSImp.CUInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_abi_version"
  fl_abi_version :: (IO C2HSImp.CInt)

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_local_ctrl"
  fl_local_ctrl :: (IO (C2HSImp.Ptr C2HSImp.CChar))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_local_alt"
  fl_local_alt :: (IO (C2HSImp.Ptr C2HSImp.CChar))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_local_meta"
  fl_local_meta :: (IO (C2HSImp.Ptr C2HSImp.CChar))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/FL.chs.h Fl_local_shift"
  fl_local_shift :: (IO (C2HSImp.Ptr C2HSImp.CChar))