{-# LANGUAGE ForeignFunctionInterface, TypeSynonymInstances #-} module Graphics.UI.FLTK.Input (newInput, newFileInput, newFloatInput, newIntInput, newMultiInput, newSecretInput, newOutput, newMultiOutput, Input) where import Foreign.Ptr import Foreign.C.String import Graphics.UI.FLTK.Widget -- Type for the input widgets newtype Input = Input (Ptr Input) instance Widget_C Input where _widget (Input p) = castPtr p foreign import ccall "fl_Input_value_AG" fl_Input_value_AG :: Ptr Input -> IO CString foreign import ccall "fl_Input_value_AS" fl_Input_value_AS :: Ptr Input -> CString -> IO () -- | Value of the input widget. instance Value_FC Input String where value = Attr (\(Input i) -> fl_Input_value_AG i >>= peekCString) (\(Input i) v -> withCString v (fl_Input_value_AS i)) foreign import ccall "newFlInput" _newInput :: Int->Int->Int->Int->IO (Ptr Input) foreign import ccall "newFlFileInput" _newFileInput::Int->Int->Int->Int->IO (Ptr Input) foreign import ccall "newFlFloatInput" _newFloatInput :: Int->Int->Int->Int->IO (Ptr Input) foreign import ccall "newFlIntInput" _newIntInput:: Int->Int->Int->Int->IO (Ptr Input) foreign import ccall "newFlMultilineInput" _newMultiInput :: Int->Int->Int->Int->IO (Ptr Input) foreign import ccall "newFlOutput" _newOutput :: Int->Int->Int->Int->IO (Ptr Input) foreign import ccall "newFlSecretInput" _newSecretInput :: Int->Int->Int->Int->IO (Ptr Input) foreign import ccall "newFlMultilineOutput" _newMultiOutput :: Int->Int->Int->Int->IO (Ptr Input) -- | New text input field. newInput :: Int->Int->Int->Int->[Prop Input]->IO Input newInput x y w h l = _newInput x y w h >>= b2 l -- | New file input field. Graphics.UI.FLTK.ASK's file_chooser is better... newFileInput :: Int->Int->Int->Int->[Prop Input]->IO Input newFileInput x y w h l = _newFileInput x y w h >>= b2 l -- | New float input field. newFloatInput :: Int->Int->Int->Int->[Prop Input]->IO Input newFloatInput x y w h l = _newFloatInput x y w h >>= b2 l -- | New int input field. newIntInput :: Int->Int->Int->Int->[Prop Input]->IO Input newIntInput x y w h l = _newIntInput x y w h >>= b2 l -- | New multiline input field. newMultiInput :: Int->Int->Int->Int->[Prop Input]->IO Input newMultiInput x y w h l = _newMultiInput x y w h >>= b2 l -- | New password input field. newSecretInput:: Int->Int->Int->Int->[Prop Input]->IO Input newSecretInput x y w h l = _newSecretInput x y w h >>= b2 l -- | New simple output field. newOutput :: Int->Int->Int->Int->[Prop Input]->IO Input newOutput x y w h l = _newOutput x y w h >>= b2 l -- | New multiline output field. newMultiOutput :: Int->Int->Int->Int->[Prop Input]->IO Input newMultiOutput x y w h l = _newMultiOutput x y w h >>= b2 l b2 l p = do let b = Input p set b l return b