-- 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/FileInput.chs" #-}
{-# LANGUAGE CPP, TypeSynonymInstances, FlexibleInstances, MultiParamTypeClasses, FlexibleContexts #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Graphics.UI.FLTK.LowLevel.FileInput
    (
     fileInputNew
     -- * Hierarchy
     --
     -- $hierarchy

     -- * Functions
     --
     -- $functions
    )
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_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.Fl_Enumerations

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

{-# LINE 27 "src/Graphics/UI/FLTK/LowLevel/FileInput.chs" #-}

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

{-# LINE 28 "src/Graphics/UI/FLTK/LowLevel/FileInput.chs" #-}

fileInputNew :: Rectangle -> Maybe T.Text -> IO (Ref FileInput)
fileInputNew rectangle l' =
    let (x_pos, y_pos, width, height) = fromRectangle rectangle
    in case l' of
        Nothing -> fileInputNew' x_pos y_pos width height >>=
                             toRef
        Just l -> fileInputNewWithLabel' x_pos y_pos width height l >>=
                             toRef

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

{-# LINE 38 "src/Graphics/UI/FLTK/LowLevel/FileInput.chs" #-}

instance (impl ~ ( IO (Boxtype))) => Op (GetDownBox ()) FileInput orig impl where
  runOp _ _ fileInput = withRef fileInput $ \fileInputPtr -> downBox' fileInputPtr
setDownBox' :: (Ptr ()) -> (Boxtype) -> IO ()
setDownBox' a1 a2 =
  let {a1' = id a1} in 
  let {a2' = cFromEnum a2} in 
  setDownBox''_ a1' a2' >>
  return ()

{-# LINE 41 "src/Graphics/UI/FLTK/LowLevel/FileInput.chs" #-}

instance (impl ~ (Boxtype ->  IO ())) => Op (SetDownBox ()) FileInput orig impl where
  runOp _ _ fileInput b = withRef fileInput $ \fileInputPtr -> setDownBox' fileInputPtr b
errorColor' :: (Ptr ()) -> IO ((Color))
errorColor' a1 =
  let {a1' = id a1} in 
  errorColor''_ a1' >>= \res ->
  let {res' = cToColor res} in
  return (res')

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

instance (impl ~ ( IO (Color))) => Op (GetErrorColor ()) FileInput orig impl where
  runOp _ _ fileInput = withRef fileInput $ \fileInputPtr -> errorColor' fileInputPtr
setErrorColor' :: (Ptr ()) -> (Color) -> IO ()
setErrorColor' a1 a2 =
  let {a1' = id a1} in 
  let {a2' = cFromColor a2} in 
  setErrorColor''_ a1' a2' >>
  return ()

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

instance (impl ~ (Color ->  IO ())) => Op (SetErrorColor ()) FileInput orig impl where
  runOp _ _ fileInput b = withRef fileInput $ \fileInputPtr -> setErrorColor' fileInputPtr b
setValue' :: (Ptr ()) -> (T.Text) -> IO ()
setValue' a1 a2 =
  let {a1' = id a1} in 
  let {a2' = unsafeToCString a2} in 
  setValue''_ a1' a2' >>
  return ()

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

instance (impl ~ (T.Text -> IO ())) => Op (SetValue ()) FileInput orig impl where
  runOp _ _ fileInput s = withRef fileInput $ \fileInputPtr -> setValue' fileInputPtr s
getValue' :: (Ptr ()) -> IO ((T.Text))
getValue' a1 =
  let {a1' = id a1} in 
  getValue''_ a1' >>= \res ->
  let {res' = unsafeFromCString res} in
  return (res')

{-# LINE 53 "src/Graphics/UI/FLTK/LowLevel/FileInput.chs" #-}

instance (impl ~ (IO T.Text)) => Op (GetValue ()) FileInput orig impl where
  runOp _ _ fileInput = withRef fileInput $ \fileInputPtr -> getValue' fileInputPtr

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

-- $functions
-- @
-- getDownBox :: 'Ref' 'FileInput' -> 'IO' ('Boxtype')
--
-- getErrorColor :: 'Ref' 'FileInput' -> 'IO' ('Color')
--
-- getValue :: 'Ref' 'FileInput' -> 'IO' 'T.Text'
  --
-- setDownBox :: 'Ref' 'FileInput' -> 'Boxtype' -> 'IO' ()
--
-- setErrorColor :: 'Ref' 'FileInput' -> 'Color' -> 'IO' ()
--
-- setValue :: 'Ref' 'FileInput' -> 'T.Text' -> 'IO' ()
-- @

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

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

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

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

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

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

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

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