-- 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/Input.chs" #-}
{-# LANGUAGE CPP, ExistentialQuantification, TypeSynonymInstances, FlexibleInstances, MultiParamTypeClasses, FlexibleContexts, ScopedTypeVariables #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Graphics.UI.FLTK.LowLevel.Input
    (
     FlInputType(..),
     -- * Constructor
     inputNew
     -- * 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 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
import Graphics.UI.FLTK.LowLevel.Dispatch
import qualified Data.Text as T
data FlInputType = FlNormalInput
                 | FlFloatInput
                 | FlIntInput
                 | FlMultilineInput
                 | FlSecretInput
instance Enum FlInputType where
  succ FlNormalInput = FlFloatInput
  succ FlFloatInput = FlIntInput
  succ FlIntInput = FlMultilineInput
  succ FlMultilineInput = FlSecretInput
  succ FlSecretInput = error "FlInputType.succ: FlSecretInput has no successor"

  pred FlFloatInput = FlNormalInput
  pred FlIntInput = FlFloatInput
  pred FlMultilineInput = FlIntInput
  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 FlMultilineInput = 4
  fromEnum FlSecretInput = 5

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

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

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 45 "src/Graphics/UI/FLTK/LowLevel/Input.chs" #-}

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

{-# LINE 46 "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 47 "src/Graphics/UI/FLTK/LowLevel/Input.chs" #-}

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

{-# LINE 48 "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 49 "src/Graphics/UI/FLTK/LowLevel/Input.chs" #-}

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

{-# LINE 50 "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 51 "src/Graphics/UI/FLTK/LowLevel/Input.chs" #-}

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

{-# LINE 52 "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 53 "src/Graphics/UI/FLTK/LowLevel/Input.chs" #-}

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

{-# LINE 54 "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 -> inputNewWithLabel' x y w h l)) l'
                       Just FlFloatInput -> maybe floatInputNew' (\l -> (\x y w h -> floatInputNewWithLabel' x y w h l)) l'
                       Just FlIntInput -> maybe intInputNew'  (\l -> (\x y w h -> intInputNewWithLabel' x y w h l)) l'
                       Just FlMultilineInput -> maybe multilineInputNew'  (\l -> (\x y w h -> multilineInputNewWithLabel' x y w h l)) l'
                       Just FlSecretInput -> maybe secretInputNew' (\l -> (\x y w h -> secretInputNewWithLabel' x y w h l)) l'
                       Nothing -> inputNew'
    in
    constructor x_pos y_pos width height >>= toRef

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

{-# LINE 68 "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 74 "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 75 "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 (toEnum (fromIntegral t)) of
           FlSecretInput -> secretInputHandle' p (fromIntegral . fromEnum $ event)
           _             -> inputHandle' p (fromIntegral . fromEnum $ event)
      )
    >>= return . successOrUnknownEvent

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

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

instance (impl ~ (FlInputType ->  IO ())) => Op (SetType ()) Input orig impl where
  runOp _ _ widget t = withRef widget $ \widgetPtr -> setType' widgetPtr (fromInteger $ toInteger $ fromEnum t)

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

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

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

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

instance (impl ~ (T.Text -> Maybe Int -> IO (Int))) => Op (SetValue ()) Input orig impl where
  runOp _ _ input text l' =
    case l' of
     Nothing -> withRef input $ \inputPtr -> setValue' inputPtr text
     Just l -> withRef input $ \inputPtr -> setValueWithLength' inputPtr text l
staticValue' :: (Ptr ()) -> (T.Text) -> IO ((Int))
staticValue' a1 a2 =
  let {a1' = id a1} in 
  let {a2' = unsafeToCString a2} in 
  staticValue''_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

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

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

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

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

{-# LINE 107 "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
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 110 "src/Graphics/UI/FLTK/LowLevel/Input.chs" #-}

instance (impl ~ (Int ->  IO (Char))) => Op (Index ()) Input orig impl where
  runOp _ _ input 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 113 "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 116 "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 119 "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 122 "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 125 "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 128 "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 131 "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 132 "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 139 "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) -> (T.Text) -> IO ((Int))
replace' a1 a2 a3 a4 =
  let {a1' = id a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = unsafeToCString a4} in 
  replace''_ a1' a2' a3' a4' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

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

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

{-# LINE 145 "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 148 "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 151 "src/Graphics/UI/FLTK/LowLevel/Input.chs" #-}

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

{-# LINE 154 "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 -> insert' inputPtr t >>= return . successOrNoChange
insertWithLength' :: (Ptr ()) -> (T.Text) -> (Int) -> IO ((Int))
insertWithLength' a1 a2 a3 =
  let {a1' = id a1} in 
  let {a2' = unsafeToCString a2} in 
  let {a3' = fromIntegral a3} in 
  insertWithLength''_ a1' a2' a3' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 157 "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 -> 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 160 "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 167 "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 170 "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 173 "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 176 "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 180 "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 183 "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 186 "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 189 "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 192 "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 195 "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 198 "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 201 "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 204 "src/Graphics/UI/FLTK/LowLevel/Input.chs" #-}

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

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

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

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

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

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

instance (impl ~ (Int ->  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 216 "src/Graphics/UI/FLTK/LowLevel/Input.chs" #-}

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

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

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

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

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

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

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

-- $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' -> 'Int' -> 'Int' -> 'IO' ('Either' 'NoChange' ())
--
-- destroy :: 'Ref' 'Input' -> 'IO' ()
--
-- getCursorColor :: 'Ref' 'Input' -> 'IO' ('Color')
--
-- getInputType :: 'Ref' 'Input' -> 'IO' ('Int')
--
-- getMark :: 'Ref' 'Input' -> 'IO' ('Int')
--
-- getMaximumSize :: 'Ref' 'Input' -> 'IO' ('Int')
--
-- getPosition :: 'Ref' 'Input' -> 'IO' ('Int')
--
-- getReadonly :: 'Ref' 'Input' -> 'IO' ('Int')
--
-- getShortcut :: 'Ref' 'Input' -> 'IO' ('Maybe' 'ShortcutKeySequence')
--
-- getSize :: 'Ref' 'Input' -> 'IO' ('Int')
--
-- getTabNav :: 'Ref' 'Input' -> 'Int' -> 'IO' ()
--
-- 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' ('Int')
--
-- handle :: 'Ref' 'Input' -> ('Event' -> 'IO' ('Either' 'UnknownEvent' ()))
--
-- index :: 'Ref' 'Input' -> 'Int' -> 'IO' ('Char')
--
-- insert :: 'Ref' 'Input' -> 'T.Text' -> 'IO' ('Either' 'NoChange' ())
--
-- insertWithLength :: 'Ref' 'Input' -> 'T.Text' -> 'Int' -> 'IO' ('Either' 'NoChange' ())
--
-- replace :: 'Ref' 'Input' -> 'Int' -> 'Int' -> 'T.Text' -> 'IO' ('Either' 'NoChange' ())
--
-- setCursorColor :: 'Ref' 'Input' -> 'Color' -> 'IO' ()
--
-- setInputType :: 'Ref' 'Input' -> 'Int' -> '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' -> 'Int' -> 'IO' ()
--
-- setShortcut :: 'Ref' 'Input' -> 'ShortcutKeySequence' -> 'IO' ()
--
-- setSize :: 'Ref' 'Input' -> 'Size' -> 'IO' ()
--
-- setTabNav :: 'Ref' 'Input' -> 'IO' ('Int')
--
-- setTextcolor :: 'Ref' 'Input' -> 'Color' -> 'IO' ()
--
-- setTextfont :: 'Ref' 'Input' -> 'Font' -> 'IO' ()
--
-- setTextsize :: 'Ref' 'Input' -> 'FontSize' -> 'IO' ()
--
-- setType :: 'Ref' 'Input' -> 'FlInputType' -> 'IO' ()
--
-- setValue :: 'Ref' 'Input' -> 'T.Text' -> 'Maybe' 'Int' -> 'IO' ('Int')
--
-- setWrap :: 'Ref' 'Input' -> 'Int' -> 'IO' ()
--
-- staticValue :: 'Ref' 'Input' -> 'T.Text' -> 'Maybe' 'Int' -> '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_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_Widget_set_type"
  setType''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CUChar -> (IO ())))

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_set_value_with_length"
  setValueWithLength''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CInt -> (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_static_value_with_length"
  staticValueWithLength''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CInt -> (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_tab_nav"
  tabNav''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

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