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


{-# LINE 1 "src/Graphics/UI/FLTK/LowLevel/Input.chs" #-}
{-# LANGUAGE CPP, ExistentialQuantification, TypeSynonymInstances, FlexibleInstances, MultiParamTypeClasses, FlexibleContexts, ScopedTypeVariables #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Graphics.UI.FLTK.LowLevel.Input
    (
     FlInputType(..),
     -- * Constructor
     inputNew,
     inputCustom
     -- * Hierarchy
     --
     -- $hierarchy

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













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

data FlInputType = FlNormalInput
                 | FlFloatInput
                 | FlIntInput
                 | FlHiddenInput
                 | FlMultilineInput
                 | FlSecretInput
instance Enum FlInputType where
  succ FlNormalInput = FlFloatInput
  succ FlFloatInput = FlIntInput
  succ FlIntInput = FlHiddenInput
  succ FlHiddenInput = FlMultilineInput
  succ FlMultilineInput = FlSecretInput
  succ FlSecretInput = error "FlInputType.succ: FlSecretInput has no successor"

  pred FlFloatInput = FlNormalInput
  pred FlIntInput = FlFloatInput
  pred FlHiddenInput = FlIntInput
  pred FlMultilineInput = FlHiddenInput
  pred FlSecretInput = FlMultilineInput
  pred FlNormalInput = error "FlInputType.pred: FlNormalInput 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 FlSecretInput

  fromEnum FlNormalInput = 0
  fromEnum FlFloatInput = 1
  fromEnum FlIntInput = 2
  fromEnum FlHiddenInput = 3
  fromEnum FlMultilineInput = 4
  fromEnum FlSecretInput = 5

  toEnum 0 = FlNormalInput
  toEnum 1 = FlFloatInput
  toEnum 2 = FlIntInput
  toEnum 3 = FlHiddenInput
  toEnum 4 = FlMultilineInput
  toEnum 5 = FlSecretInput
  toEnum unmatched = error ("FlInputType.toEnum: Cannot match " ++ show unmatched)

{-# LINE 47 "src/Graphics/UI/FLTK/LowLevel/Input.chs" #-}

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

{-# LINE 48 "src/Graphics/UI/FLTK/LowLevel/Input.chs" #-}

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

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

inputCustom ::
       Rectangle                         -- ^ The bounds of this Input
    -> Maybe T.Text                      -- ^ The Input label
    -> Maybe FlInputType                 -- ^ The input type
    -> Maybe (Ref Input -> IO ())        -- ^ Optional custom drawing function
    -> Maybe (CustomWidgetFuncs Input)   -- ^ Optional custom widget functions
    -> IO (Ref Input)
inputCustom rectangle l' itMaybe draw' funcs' = do
  i <- widgetMaker
         rectangle
         l'
         draw'
         funcs'
         overriddenWidgetNew'
         overriddenWidgetNewWithLabel'
  maybe
    (return ())
    (\it -> do
        setInputType i it
        case it of
          FlNormalInput -> return ()
          FlFloatInput -> clearFlag i WidgetFlagMacUseAccentsMenu
          FlIntInput -> clearFlag i WidgetFlagMacUseAccentsMenu
          FlMultilineInput -> return ()
          FlSecretInput -> clearFlag i WidgetFlagMacUseAccentsMenu
          FlHiddenInput -> return ()
        )
    itMaybe
  setFlag i WidgetFlagCopiedLabel
  setFlag i WidgetFlagCopiedTooltip
  return i

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

{-# LINE 82 "src/Graphics/UI/FLTK/LowLevel/Input.chs" #-}

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

{-# LINE 83 "src/Graphics/UI/FLTK/LowLevel/Input.chs" #-}

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

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

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

{-# LINE 85 "src/Graphics/UI/FLTK/LowLevel/Input.chs" #-}

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

{-# LINE 86 "src/Graphics/UI/FLTK/LowLevel/Input.chs" #-}

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

{-# LINE 87 "src/Graphics/UI/FLTK/LowLevel/Input.chs" #-}

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

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

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

{-# LINE 89 "src/Graphics/UI/FLTK/LowLevel/Input.chs" #-}

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

{-# LINE 90 "src/Graphics/UI/FLTK/LowLevel/Input.chs" #-}

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

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

inputNew :: Rectangle -> Maybe T.Text -> Maybe FlInputType -> IO (Ref Input)
inputNew rectangle l' flInputType =
    let (x_pos, y_pos, width, height) = fromRectangle rectangle
        constructor = case flInputType of
                       Just FlNormalInput -> maybe inputNew' (\l -> (\x y w h -> copyTextToCString l >>= \l' -> inputNewWithLabel' x y w h l')) l'
                       Just FlFloatInput -> maybe floatInputNew' (\l -> (\x y w h -> copyTextToCString l >>= \l' -> floatInputNewWithLabel' x y w h l')) l'
                       Just FlIntInput -> maybe intInputNew'  (\l -> (\x y w h -> copyTextToCString l >>= \l' -> intInputNewWithLabel' x y w h l')) l'
                       Just FlMultilineInput -> maybe multilineInputNew'  (\l -> (\x y w h -> copyTextToCString l >>= \l' -> multilineInputNewWithLabel' x y w h l')) l'
                       Just FlSecretInput -> maybe secretInputNew' (\l -> (\x y w h -> copyTextToCString l >>= \l' -> secretInputNewWithLabel' x y w h l')) l'
                       Just FlHiddenInput -> maybe inputNew' (\l -> (\x y w h -> copyTextToCString l >>= \l' -> inputNewWithLabel' x y w h l')) l'
                       Nothing -> inputNew'
    in do
    i <- constructor x_pos y_pos width height >>= toRef
    case flInputType of { Just FlHiddenInput -> setInputType i FlHiddenInput; _ -> return () }
    setFlag i WidgetFlagCopiedLabel
    setFlag i WidgetFlagCopiedTooltip
    return i

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

{-# LINE 110 "src/Graphics/UI/FLTK/LowLevel/Input.chs" #-}

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

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

{-# LINE 116 "src/Graphics/UI/FLTK/LowLevel/Input.chs" #-}

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

{-# LINE 117 "src/Graphics/UI/FLTK/LowLevel/Input.chs" #-}

instance (impl ~ (Event -> IO (Either UnknownEvent ()))) => Op (Handle ()) Input orig impl where
  runOp _ _ input event =
    withRef
      input
      (\p -> do
          t <- getInputType input
          case t of
           FlSecretInput -> secretInputHandle' p (fromIntegral . fromEnum $ event)
           _             -> inputHandle' p (fromIntegral . fromEnum $ event)
      )
    >>= return . successOrUnknownEvent

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

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

instance (impl ~ (T.Text -> IO (Either NoChange ()))) => Op (SetValue ()) Input orig impl where
  runOp _ _ input text = withRef input $ \inputPtr -> copyTextToCString text >>= \t -> setValue' inputPtr t >>= return . successOrNoChange

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

{-# LINE 134 "src/Graphics/UI/FLTK/LowLevel/Input.chs" #-}

instance (impl ~ (T.Text -> IO (Either NoChange ()))) => Op (StaticValue ()) Input orig impl where
  runOp _ _ input text = do
    status' <- withRef input $ \inputPtr -> copyTextToCString text >>= staticValue' inputPtr
    return $ successOrNoChange status'
value' :: (Ptr ()) -> IO ((CString))
value' a1 =
  let {a1' = id a1} in
  value''_ a1' >>= \res ->
  return res >>= \res' ->
  return (res')

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

instance (impl ~ ( IO T.Text)) => Op (GetValue ()) Input orig impl where
  runOp _ _ input = withRef input $ \inputPtr -> value' inputPtr >>= cStringToText
index' :: (Ptr ()) -> (Int) -> IO ((Int))
index' a1 a2 =
  let {a1' = id a1} in
  let {a2' = fromIntegral a2} in
  index''_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

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

instance (impl ~ (AtIndex ->  IO (Char))) => Op (Index ()) Input orig impl where
  runOp _ _ input (AtIndex i) = withRef input $ \inputPtr -> index' inputPtr i >>= return . toEnum
setSize' :: (Ptr ()) -> (Int) -> (Int) -> IO ()
setSize' a1 a2 a3 =
  let {a1' = id a1} in
  let {a2' = fromIntegral a2} in
  let {a3' = fromIntegral a3} in
  setSize''_ a1' a2' a3' >>
  return ()

{-# LINE 145 "src/Graphics/UI/FLTK/LowLevel/Input.chs" #-}

instance (impl ~ (Size ->  IO ())) => Op (SetSize ()) Input orig impl where
  runOp _ _ input (Size (Width w') (Height h')) = withRef input $ \inputPtr -> setSize' inputPtr w' h'
maximumSize' :: (Ptr ()) -> IO ((Int))
maximumSize' a1 =
  let {a1' = id a1} in
  maximumSize''_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 148 "src/Graphics/UI/FLTK/LowLevel/Input.chs" #-}

instance (impl ~ ( IO (Int))) => Op (GetMaximumSize ()) Input orig impl where
  runOp _ _ input = withRef input $ \inputPtr -> maximumSize' inputPtr
size' :: (Ptr ()) -> IO ((Int))
size' a1 =
  let {a1' = id a1} in
  size''_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

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

instance (impl ~ ( IO (Int))) => Op (GetSize ()) Input orig impl where
  runOp _ _ input = withRef input $ \inputPtr -> size' inputPtr
setMaximumSize' :: (Ptr ()) -> (Int) -> IO ()
setMaximumSize' a1 a2 =
  let {a1' = id a1} in
  let {a2' = fromIntegral a2} in
  setMaximumSize''_ a1' a2' >>
  return ()

{-# LINE 154 "src/Graphics/UI/FLTK/LowLevel/Input.chs" #-}

instance (impl ~ (Int ->  IO ())) => Op (SetMaximumSize ()) Input orig impl where
  runOp _ _ input m = withRef input $ \inputPtr -> setMaximumSize' inputPtr m
position' :: (Ptr ()) -> IO ((Int))
position' a1 =
  let {a1' = id a1} in
  position''_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 157 "src/Graphics/UI/FLTK/LowLevel/Input.chs" #-}

instance (impl ~ ( IO (Int))) => Op (GetPosition ()) Input orig impl where
  runOp _ _ input = withRef input $ \inputPtr -> position' inputPtr
mark' :: (Ptr ()) -> IO ((Int))
mark' a1 =
  let {a1' = id a1} in
  mark''_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 160 "src/Graphics/UI/FLTK/LowLevel/Input.chs" #-}

instance (impl ~ ( IO (Int))) => Op (GetMark ()) Input orig impl where
  runOp _ _ input = withRef input $ \inputPtr -> mark' inputPtr
setPositionWithCursorMark' :: (Ptr ()) -> (Int) -> (Int) -> IO ((Int))
setPositionWithCursorMark' a1 a2 a3 =
  let {a1' = id a1} in
  let {a2' = fromIntegral a2} in
  let {a3' = fromIntegral a3} in
  setPositionWithCursorMark''_ a1' a2' a3' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 163 "src/Graphics/UI/FLTK/LowLevel/Input.chs" #-}

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

{-# LINE 164 "src/Graphics/UI/FLTK/LowLevel/Input.chs" #-}

instance (impl ~ (Int -> Maybe Int -> IO (Either NoChange ()))) => Op (SetPosition ()) Input orig impl where
  runOp _ _ input point mark = do
   status' <- case mark of
      Just m ->  withRef input $ \inputPtr -> setPositionWithCursorMark' inputPtr point m
      Nothing -> withRef input $ \inputPtr -> setPositionNN' inputPtr point
   return $ successOrNoChange status'
setMark' :: (Ptr ()) -> (Int) -> IO ((Int))
setMark' a1 a2 =
  let {a1' = id a1} in
  let {a2' = fromIntegral a2} in
  setMark''_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 171 "src/Graphics/UI/FLTK/LowLevel/Input.chs" #-}

instance (impl ~ (Int ->  IO (Either NoChange ()))) => Op (SetMark ()) Input orig impl where
  runOp _ _ input m = withRef input $ \inputPtr -> setMark' inputPtr m >>= return . successOrNoChange
replace' :: (Ptr ()) -> (Int) -> (Int) -> (CString) -> IO ((Int))
replace' a1 a2 a3 a4 =
  let {a1' = id a1} in
  let {a2' = fromIntegral a2} in
  let {a3' = fromIntegral a3} in
  (flip ($)) a4 $ \a4' ->
  replace''_ a1' a2' a3' a4' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 174 "src/Graphics/UI/FLTK/LowLevel/Input.chs" #-}

instance (impl ~ (IndexRange -> T.Text ->  IO (Either NoChange ()))) => Op (Replace ()) Input orig impl where
  runOp _ _ input (IndexRange (AtIndex b) (AtIndex e)) text = withRef input $ \inputPtr -> copyTextToCString text >>= \t -> replace' inputPtr b e t >>= return . successOrNoChange
cut' :: (Ptr ()) -> IO ((Int))
cut' a1 =
  let {a1' = id a1} in
  cut''_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 177 "src/Graphics/UI/FLTK/LowLevel/Input.chs" #-}

instance (impl ~ ( IO (Either NoChange ()))) => Op (Cut ()) Input orig impl where
  runOp _ _ input = withRef input $ \inputPtr -> cut' inputPtr >>= return . successOrNoChange
cutBytes' :: (Ptr ()) -> (Int) -> IO ((Int))
cutBytes' a1 a2 =
  let {a1' = id a1} in
  let {a2' = fromIntegral a2} in
  cutBytes''_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 180 "src/Graphics/UI/FLTK/LowLevel/Input.chs" #-}

instance (impl ~ (Int ->  IO (Either NoChange ()))) => Op (CutFromCursor ()) Input orig impl where
  runOp _ _ input n = withRef input $ \inputPtr -> cutBytes' inputPtr n >>= return . successOrNoChange
cutRange' :: (Ptr ()) -> (Int) -> (Int) -> IO ((Int))
cutRange' a1 a2 a3 =
  let {a1' = id a1} in
  let {a2' = fromIntegral a2} in
  let {a3' = fromIntegral a3} in
  cutRange''_ a1' a2' a3' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

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

instance (impl ~ (IndexRange ->  IO (Either NoChange ()))) => Op (CutRange ()) Input orig impl where
  runOp _ _ input (IndexRange (AtIndex a) (AtIndex b)) = withRef input $ \inputPtr -> cutRange' inputPtr a b >>= return . successOrNoChange
insert' :: (Ptr ()) -> (CString) -> IO ((Int))
insert' a1 a2 =
  let {a1' = id a1} in
  (flip ($)) a2 $ \a2' ->
  insert''_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 186 "src/Graphics/UI/FLTK/LowLevel/Input.chs" #-}

instance (impl ~ (T.Text ->  IO (Either NoChange ()))) => Op (Insert ()) Input orig impl where
  runOp _ _ input t = withRef input $ \inputPtr -> copyTextToCString t >>= \t' -> insert' inputPtr t' >>= return . successOrNoChange
insertWithLength' :: (Ptr ()) -> (CString) -> (Int) -> IO ((Int))
insertWithLength' a1 a2 a3 =
  let {a1' = id a1} in
  (flip ($)) a2 $ \a2' ->
  let {a3' = fromIntegral a3} in
  insertWithLength''_ a1' a2' a3' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

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

instance (impl ~ (T.Text -> Int ->  IO (Either NoChange ()))) => Op (InsertWithLength ()) Input orig impl where
  runOp _ _ input t l = withRef input $ \inputPtr -> copyTextToCString t >>= \t' -> insertWithLength' inputPtr t' l >>= return . successOrNoChange
copy' :: (Ptr ()) -> (Int) -> IO ((Int))
copy' a1 a2 =
  let {a1' = id a1} in
  let {a2' = fromIntegral a2} in
  copy''_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 192 "src/Graphics/UI/FLTK/LowLevel/Input.chs" #-}

instance (impl ~ (Clipboard ->  IO (Either NoChange ()))) => Op (Copy ()) Input orig impl where
  runOp _ _ input clipboard = do
    status' <- case clipboard of
      InternalClipboard -> withRef input $ \inputPtr -> copy' inputPtr 1
      SharedClipboard -> withRef input $ \inputPtr -> copy' inputPtr 0
    return $ successOrNoChange status'
undo' :: (Ptr ()) -> IO ((Int))
undo' a1 =
  let {a1' = id a1} in
  undo''_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

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

instance (impl ~ ( IO (Either NoChange ()))) => Op (Undo ()) Input orig impl where
  runOp _ _ input = withRef input $ \inputPtr -> undo' inputPtr >>= return . successOrNoChange
copyCuts' :: (Ptr ()) -> IO ((Int))
copyCuts' a1 =
  let {a1' = id a1} in
  copyCuts''_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

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

instance (impl ~ ( IO (Either NoChange ()))) => Op (CopyCuts ()) Input orig impl where
  runOp _ _ input = withRef input $ \inputPtr -> copyCuts' inputPtr >>= return . successOrNoChange
shortcut' :: (Ptr ()) -> IO ((CInt))
shortcut' a1 =
  let {a1' = id a1} in
  shortcut''_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

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

instance (impl ~ ( IO (Maybe ShortcutKeySequence))) => Op (GetShortcut ()) Input orig impl where
  runOp _ _ input = withRef input $ \inputPtr -> shortcut' inputPtr >>= return . cIntToKeySequence
setShortcut' :: (Ptr ()) -> (CInt) -> IO ()
setShortcut' a1 a2 =
  let {a1' = id a1} in
  let {a2' = id a2} in
  setShortcut''_ a1' a2' >>
  return ()

{-# LINE 208 "src/Graphics/UI/FLTK/LowLevel/Input.chs" #-}

instance (impl ~ (ShortcutKeySequence ->  IO ())) => Op (SetShortcut ()) Input orig impl where
  runOp _ _ input (ShortcutKeySequence modifiers char) =
    withRef input $ \inputPtr -> setShortcut' inputPtr (keySequenceToCInt modifiers char)
textfont' :: (Ptr ()) -> IO ((Font))
textfont' a1 =
  let {a1' = id a1} in
  textfont''_ a1' >>= \res ->
  let {res' = cToFont res} in
  return (res')

{-# LINE 212 "src/Graphics/UI/FLTK/LowLevel/Input.chs" #-}

instance (impl ~ ( IO (Font))) => Op (GetTextfont ()) Input orig impl where
  runOp _ _ input = withRef input $ \inputPtr -> textfont' inputPtr
setTextfont' :: (Ptr ()) -> (Font) -> IO ()
setTextfont' a1 a2 =
  let {a1' = id a1} in
  let {a2' = cFromFont a2} in
  setTextfont''_ a1' a2' >>
  return ()

{-# LINE 215 "src/Graphics/UI/FLTK/LowLevel/Input.chs" #-}

instance (impl ~ (Font ->  IO ())) => Op (SetTextfont ()) Input orig impl where
  runOp _ _ input s = withRef input $ \inputPtr -> setTextfont' inputPtr s
textsize' :: (Ptr ()) -> IO ((CInt))
textsize' a1 =
  let {a1' = id a1} in
  textsize''_ a1' >>= \res ->
  let {res' = id res} in
  return (res')

{-# LINE 218 "src/Graphics/UI/FLTK/LowLevel/Input.chs" #-}

instance (impl ~ ( IO (FontSize))) => Op (GetTextsize ()) Input orig impl where
  runOp _ _ input = withRef input $ \inputPtr -> textsize' inputPtr >>= return . FontSize
setTextsize' :: (Ptr ()) -> (CInt) -> IO ()
setTextsize' a1 a2 =
  let {a1' = id a1} in
  let {a2' = id a2} in
  setTextsize''_ a1' a2' >>
  return ()

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

instance (impl ~ (FontSize ->  IO ())) => Op (SetTextsize ()) Input orig impl where
  runOp _ _ input (FontSize s) = withRef input $ \inputPtr -> setTextsize' inputPtr s
textcolor' :: (Ptr ()) -> IO ((Color))
textcolor' a1 =
  let {a1' = id a1} in
  textcolor''_ a1' >>= \res ->
  let {res' = cToColor res} in
  return (res')

{-# LINE 224 "src/Graphics/UI/FLTK/LowLevel/Input.chs" #-}

instance (impl ~ ( IO (Color))) => Op (GetTextcolor ()) Input orig impl where
  runOp _ _ input = withRef input $ \inputPtr -> textcolor' inputPtr
setTextcolor' :: (Ptr ()) -> (Color) -> IO ()
setTextcolor' a1 a2 =
  let {a1' = id a1} in
  let {a2' = cFromColor a2} in
  setTextcolor''_ a1' a2' >>
  return ()

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

instance (impl ~ (Color ->  IO ())) => Op (SetTextcolor ()) Input orig impl where
  runOp _ _ input n = withRef input $ \inputPtr -> setTextcolor' inputPtr n
cursorColor' :: (Ptr ()) -> IO ((Color))
cursorColor' a1 =
  let {a1' = id a1} in
  cursorColor''_ a1' >>= \res ->
  let {res' = cToColor res} in
  return (res')

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

instance (impl ~ ( IO (Color))) => Op (GetCursorColor ()) Input orig impl where
  runOp _ _ input = withRef input $ \inputPtr -> cursorColor' inputPtr
setCursorColor' :: (Ptr ()) -> (Color) -> IO ()
setCursorColor' a1 a2 =
  let {a1' = id a1} in
  let {a2' = cFromColor a2} in
  setCursorColor''_ a1' a2' >>
  return ()

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

instance (impl ~ (Color ->  IO ())) => Op (SetCursorColor ()) Input orig impl where
  runOp _ _ input n = withRef input $ \inputPtr -> setCursorColor' inputPtr n
inputType' :: (Ptr ()) -> IO ((Int))
inputType' a1 =
  let {a1' = id a1} in
  inputType''_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

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

instance (impl ~ ( IO (FlInputType))) => Op (GetInputType ()) Input orig impl where
  runOp _ _ input = withRef input $ \inputPtr -> inputType' inputPtr >>= return . toEnum . fromIntegral
setInputType' :: (Ptr ()) -> (Int) -> IO ()
setInputType' a1 a2 =
  let {a1' = id a1} in
  let {a2' = fromIntegral a2} in
  setInputType''_ a1' a2' >>
  return ()

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

instance (impl ~ (FlInputType ->  IO ())) => Op (SetInputType ()) Input orig impl where
  runOp _ _ input t = withRef input $ \inputPtr -> setInputType' inputPtr (fromIntegral (fromEnum t))
readonly' :: (Ptr ()) -> IO ((Bool))
readonly' a1 =
  let {a1' = id a1} in
  readonly''_ a1' >>= \res ->
  let {res' = cToBool res} in
  return (res')

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

instance (impl ~ ( IO (Bool))) => Op (GetReadonly ()) Input orig impl where
  runOp _ _ input = withRef input $ \inputPtr -> readonly' inputPtr
setReadonly' :: (Ptr ()) -> (Bool) -> IO ()
setReadonly' a1 a2 =
  let {a1' = id a1} in
  let {a2' = cFromBool a2} in
  setReadonly''_ a1' a2' >>
  return ()

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

instance (impl ~ (Bool ->  IO ())) => Op (SetReadonly ()) Input orig impl where
  runOp _ _ input b = withRef input $ \inputPtr -> setReadonly' inputPtr b
wrap' :: (Ptr ()) -> IO ((Int))
wrap' a1 =
  let {a1' = id a1} in
  wrap''_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

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

instance (impl ~ ( IO (Bool))) => Op (GetWrap ()) Input orig impl where
  runOp _ _ input = withRef input $ \inputPtr -> wrap' inputPtr >>= return . cToBool
setWrap' :: (Ptr ()) -> (Int) -> IO ()
setWrap' a1 a2 =
  let {a1' = id a1} in
  let {a2' = fromIntegral a2} in
  setWrap''_ a1' a2' >>
  return ()

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

instance (impl ~ (Bool ->  IO ())) => Op (SetWrap ()) Input orig impl where
  runOp _ _ input b = withRef input $ \inputPtr -> setWrap' inputPtr (cFromBool b)
setTabNav' :: (Ptr ()) -> (Int) -> IO ()
setTabNav' a1 a2 =
  let {a1' = id a1} in
  let {a2' = fromIntegral a2} in
  setTabNav''_ a1' a2' >>
  return ()

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

instance (impl ~ (Bool ->  IO ())) => Op (SetTabNav ()) Input orig impl where
  runOp _ _ input val = withRef input $ \inputPtr -> setTabNav' inputPtr (cFromBool val)
tabNav' :: (Ptr ()) -> IO ((Int))
tabNav' a1 =
  let {a1' = id a1} in
  tabNav''_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

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

instance (impl ~ ( IO (Bool))) => Op (GetTabNav ()) Input orig impl where
  runOp _ _ input = withRef input $ \inputPtr -> tabNav' inputPtr >>= return . cToBool
draw'' :: (Ptr ()) -> IO ()
draw'' a1 =
  let {a1' = id a1} in
  draw'''_ a1' >>
  return ()

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

instance (impl ~ (  IO ())) => Op (Draw ()) Input orig impl where
  runOp _ _ input = withRef input $ \inputPtr -> draw'' inputPtr
drawSuper' :: (Ptr ()) -> IO ((()))
drawSuper' a1 =
  let {a1' = id a1} in
  drawSuper''_ a1' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

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

instance (impl ~ ( IO ())) => Op (DrawSuper ()) Input orig impl where
  runOp _ _ input = withRef input $ \inputPtr -> drawSuper' inputPtr
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 266 "src/Graphics/UI/FLTK/LowLevel/Input.chs" #-}

instance (impl ~ (Event ->  IO (Either UnknownEvent ()))) => Op (HandleSuper ()) Input orig impl where
  runOp _ _ input event = withRef input $ \inputPtr -> handleSuper' inputPtr (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 269 "src/Graphics/UI/FLTK/LowLevel/Input.chs" #-}

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

{-# LINE 274 "src/Graphics/UI/FLTK/LowLevel/Input.chs" #-}

instance (impl ~ (Rectangle -> IO ())) => Op (ResizeSuper ()) Input orig impl where
  runOp _ _ input rectangle =
    let (x_pos, y_pos, width, height) = fromRectangle rectangle
    in withRef input $ \inputPtr -> resizeSuper' inputPtr x_pos y_pos width height
hide' :: (Ptr ()) -> IO ()
hide' a1 =
  let {a1' = id a1} in
  hide''_ a1' >>
  return ()

{-# LINE 279 "src/Graphics/UI/FLTK/LowLevel/Input.chs" #-}

instance (impl ~ (  IO ())) => Op (Hide ()) Input orig impl where
  runOp _ _ input = withRef input $ \inputPtr -> hide' inputPtr
hideSuper' :: (Ptr ()) -> IO ((()))
hideSuper' a1 =
  let {a1' = id a1} in
  hideSuper''_ a1' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 282 "src/Graphics/UI/FLTK/LowLevel/Input.chs" #-}

instance (impl ~ ( IO ())) => Op (HideSuper ()) Input orig impl where
  runOp _ _ input = withRef input $ \inputPtr -> hideSuper' inputPtr
show' :: (Ptr ()) -> IO ()
show' a1 =
  let {a1' = id a1} in
  show''_ a1' >>
  return ()

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

instance (impl ~ (  IO ())) => Op (ShowWidget ()) Input orig impl where
  runOp _ _ input = withRef input $ \inputPtr -> show' inputPtr
showSuper' :: (Ptr ()) -> IO ((()))
showSuper' a1 =
  let {a1' = id a1} in
  showSuper''_ a1' >>= \res ->
  let {res' = supressWarningAboutRes res} in
  return (res')

{-# LINE 288 "src/Graphics/UI/FLTK/LowLevel/Input.chs" #-}

instance (impl ~ ( IO ())) => Op (ShowWidgetSuper ()) Input orig impl where
  runOp _ _ input = withRef input $ \inputPtr -> showSuper' inputPtr

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

{-# LINE 292 "src/Graphics/UI/FLTK/LowLevel/Input.chs" #-}

instance (impl ~ (Rectangle -> IO ())) => Op (DrawText ()) Input orig impl where
  runOp _ _ input rectangle = withRef input (\inputPtr -> do
                                 let (x_pos,y_pos,w_pos,h_pos) = fromRectangle rectangle
                                 drawtext' inputPtr x_pos y_pos w_pos h_pos)

-- $Input
-- @
-- copy :: 'Ref' 'Input' -> 'Clipboard' -> 'IO' ('Either' 'NoChange' ())
--
-- copyCuts :: 'Ref' 'Input' -> 'IO' ('Either' 'NoChange' ())
--
-- cut :: 'Ref' 'Input' -> 'IO' ('Either' 'NoChange' ())
--
-- cutFromCursor :: 'Ref' 'Input' -> 'Int' -> 'IO' ('Either' 'NoChange' ())
--
-- cutRange :: 'Ref' 'Input' -> 'IndexRange' -> 'IO' ('Either' 'NoChange' ())
--
-- destroy :: 'Ref' 'Input' -> 'IO' ()
--
-- draw :: 'Ref' 'Input' -> 'IO' ()
--
-- drawSuper :: 'Ref' 'Input' -> 'IO' ()
--
-- drawText :: 'Ref' 'Input' -> 'Rectangle' -> 'IO' ()
--
-- getCursorColor :: 'Ref' 'Input' -> 'IO' ('Color')
--
-- getInputType :: 'Ref' 'Input' -> 'IO' ('FlInputType')
--
-- getMark :: 'Ref' 'Input' -> 'IO' ('Int')
--
-- getMaximumSize :: 'Ref' 'Input' -> 'IO' ('Int')
--
-- getPosition :: 'Ref' 'Input' -> 'IO' ('Int')
--
-- getReadonly :: 'Ref' 'Input' -> 'IO' ('Bool')
--
-- getShortcut :: 'Ref' 'Input' -> 'IO' ('Maybe' 'ShortcutKeySequence')
--
-- getSize :: 'Ref' 'Input' -> 'IO' ('Int')
--
-- getTabNav :: 'Ref' 'Input' -> 'IO' ('Bool')
--
-- getTextcolor :: 'Ref' 'Input' -> 'IO' ('Color')
--
-- getTextfont :: 'Ref' 'Input' -> 'IO' ('Font')
--
-- getTextsize :: 'Ref' 'Input' -> 'IO' ('FontSize')
--
-- getValue :: 'Ref' 'Input' -> 'IO' 'T.Text'
--
-- getWrap :: 'Ref' 'Input' -> 'IO' ('Bool')
--
-- handle :: 'Ref' 'Input' -> 'Event' -> 'IO' ('Either' 'UnknownEvent' ())
--
-- handleSuper :: 'Ref' 'Input' -> 'Event' -> 'IO' ('Either' 'UnknownEvent' ())
--
-- hide :: 'Ref' 'Input' -> 'IO' ()
--
-- hideSuper :: 'Ref' 'Input' -> 'IO' ()
--
-- index :: 'Ref' 'Input' -> 'AtIndex' -> 'IO' ('Char')
--
-- insert :: 'Ref' 'Input' -> 'T.Text' -> 'IO' ('Either' 'NoChange' ())
--
-- insertWithLength :: 'Ref' 'Input' -> 'T.Text' -> 'Int' -> 'IO' ('Either' 'NoChange' ())
--
-- replace :: 'Ref' 'Input' -> 'IndexRange' -> 'T.Text' -> 'IO' ('Either' 'NoChange' ())
--
-- resize :: 'Ref' 'Input' -> 'Rectangle' -> 'IO' ()
--
-- resizeSuper :: 'Ref' 'Input' -> 'Rectangle' -> 'IO' ()
--
-- setCursorColor :: 'Ref' 'Input' -> 'Color' -> 'IO' ()
--
-- setInputType :: 'Ref' 'Input' -> 'FlInputType' -> 'IO' ()
--
-- setMark :: 'Ref' 'Input' -> 'Int' -> 'IO' ('Either' 'NoChange' ())
--
-- setMaximumSize :: 'Ref' 'Input' -> 'Int' -> 'IO' ()
--
-- setPosition :: 'Ref' 'Input' -> 'Int' -> 'Maybe' 'Int' -> 'IO' ('Either' 'NoChange' ())
--
-- setReadonly :: 'Ref' 'Input' -> 'Bool' -> 'IO' ()
--
-- setShortcut :: 'Ref' 'Input' -> 'ShortcutKeySequence' -> 'IO' ()
--
-- setSize :: 'Ref' 'Input' -> 'Size' -> 'IO' ()
--
-- setTabNav :: 'Ref' 'Input' -> 'Bool' -> 'IO' ()
--
-- setTextcolor :: 'Ref' 'Input' -> 'Color' -> 'IO' ()
--
-- setTextfont :: 'Ref' 'Input' -> 'Font' -> 'IO' ()
--
-- setTextsize :: 'Ref' 'Input' -> 'FontSize' -> 'IO' ()
--
-- setValue :: 'Ref' 'Input' -> 'T.Text' -> 'IO' ('Either' 'NoChange' ())
--
-- setWrap :: 'Ref' 'Input' -> 'Bool' -> 'IO' ()
--
-- showWidget :: 'Ref' 'Input' -> 'IO' ()
--
-- showWidgetSuper :: 'Ref' 'Input' -> 'IO' ()
--
-- staticValue :: 'Ref' 'Input' -> 'T.Text' -> 'IO' ('Either' 'NoChange' ())
--
-- undo :: 'Ref' 'Input' -> 'IO' ('Either' 'NoChange' ())
-- @


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

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Input.chs.h Fl_OverriddenInput_New_WithLabel"
  overriddenWidgetNewWithLabel''_ :: (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/Input.chs.h Fl_OverriddenInput_New"
  overriddenWidgetNew''_ :: (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))))))

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

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

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

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

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

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

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

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

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

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

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Input.chs.h Fl_Input_Destroy"
  inputDestroy''_ :: ((C2HSImp.Ptr ()) -> (IO ()))

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

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

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

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

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Input.chs.h Fl_Input_value"
  value''_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr C2HSImp.CChar)))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Input.chs.h Fl_Input_index"
  index''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO C2HSImp.CUInt)))

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Input.chs.h Fl_Input_draw"
  draw'''_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Input.chs.h Fl_Input_draw_super"
  drawSuper''_ :: ((C2HSImp.Ptr ()) -> (IO ()))

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

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

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

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

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

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

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

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