module Graphics.UI.Gtk.Entry.SpinButton (
SpinButton,
SpinButtonClass,
castToSpinButton, gTypeSpinButton,
toSpinButton,
spinButtonNew,
spinButtonNewWithRange,
spinButtonConfigure,
spinButtonSetAdjustment,
spinButtonGetAdjustment,
spinButtonSetDigits,
spinButtonGetDigits,
spinButtonSetIncrements,
spinButtonGetIncrements,
spinButtonSetRange,
spinButtonGetRange,
spinButtonGetValue,
spinButtonGetValueAsInt,
spinButtonSetValue,
SpinButtonUpdatePolicy(..),
spinButtonSetUpdatePolicy,
spinButtonGetUpdatePolicy,
spinButtonSetNumeric,
spinButtonGetNumeric,
SpinType(..),
spinButtonSpin,
spinButtonSetWrap,
spinButtonGetWrap,
spinButtonSetSnapToTicks,
spinButtonGetSnapToTicks,
spinButtonUpdate,
spinButtonAdjustment,
spinButtonClimbRate,
spinButtonDigits,
spinButtonSnapToTicks,
spinButtonNumeric,
spinButtonWrap,
spinButtonUpdatePolicy,
spinButtonValue,
onInput,
afterInput,
onOutput,
afterOutput,
onValueSpinned,
afterValueSpinned
) where
import Control.Monad (liftM)
import System.Glib.FFI
import System.Glib.Attributes
import System.Glib.Properties
import Graphics.UI.Gtk.Abstract.Object (makeNewObject)
import Graphics.UI.Gtk.Types
import Graphics.UI.Gtk.Signals
import Graphics.UI.Gtk.General.Structs (inputError)
import Graphics.UI.Gtk.General.Enums (SpinButtonUpdatePolicy(..), SpinType(..))
instance EditableClass SpinButton
spinButtonNew ::
Adjustment
-> Double
-> Int
-> IO SpinButton
spinButtonNew adjustment climbRate digits =
makeNewObject mkSpinButton $
liftM (castPtr :: Ptr Widget -> Ptr SpinButton) $
(\(Adjustment arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gtk_spin_button_new argPtr1 arg2 arg3)
adjustment
(realToFrac climbRate)
(fromIntegral digits)
spinButtonNewWithRange ::
Double
-> Double
-> Double
-> IO SpinButton
spinButtonNewWithRange min max step =
makeNewObject mkSpinButton $
liftM (castPtr :: Ptr Widget -> Ptr SpinButton) $
gtk_spin_button_new_with_range
(realToFrac min)
(realToFrac max)
(realToFrac step)
spinButtonConfigure :: SpinButtonClass self => self
-> Adjustment
-> Double
-> Int
-> IO ()
spinButtonConfigure self adjustment climbRate digits =
(\(SpinButton arg1) (Adjustment arg2) arg3 arg4 -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_spin_button_configure argPtr1 argPtr2 arg3 arg4)
(toSpinButton self)
adjustment
(realToFrac climbRate)
(fromIntegral digits)
spinButtonSetAdjustment :: SpinButtonClass self => self
-> Adjustment
-> IO ()
spinButtonSetAdjustment self adjustment =
(\(SpinButton arg1) (Adjustment arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_spin_button_set_adjustment argPtr1 argPtr2)
(toSpinButton self)
adjustment
spinButtonGetAdjustment :: SpinButtonClass self => self
-> IO Adjustment
spinButtonGetAdjustment self =
makeNewObject mkAdjustment $
(\(SpinButton arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_spin_button_get_adjustment argPtr1)
(toSpinButton self)
spinButtonSetDigits :: SpinButtonClass self => self
-> Int
-> IO ()
spinButtonSetDigits self digits =
(\(SpinButton arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_spin_button_set_digits argPtr1 arg2)
(toSpinButton self)
(fromIntegral digits)
spinButtonGetDigits :: SpinButtonClass self => self
-> IO Int
spinButtonGetDigits self =
liftM fromIntegral $
(\(SpinButton arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_spin_button_get_digits argPtr1)
(toSpinButton self)
spinButtonSetIncrements :: SpinButtonClass self => self
-> Double
-> Double
-> IO ()
spinButtonSetIncrements self step page =
(\(SpinButton arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gtk_spin_button_set_increments argPtr1 arg2 arg3)
(toSpinButton self)
(realToFrac step)
(realToFrac page)
spinButtonGetIncrements :: SpinButtonClass self => self
-> IO (Double, Double)
spinButtonGetIncrements self =
alloca $ \stepPtr ->
alloca $ \pagePtr -> do
(\(SpinButton arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gtk_spin_button_get_increments argPtr1 arg2 arg3)
(toSpinButton self)
stepPtr
pagePtr
step <- peek stepPtr
page <- peek pagePtr
return (realToFrac step, realToFrac page)
spinButtonSetRange :: SpinButtonClass self => self
-> Double
-> Double
-> IO ()
spinButtonSetRange self min max =
(\(SpinButton arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gtk_spin_button_set_range argPtr1 arg2 arg3)
(toSpinButton self)
(realToFrac min)
(realToFrac max)
spinButtonGetRange :: SpinButtonClass self => self
-> IO (Double, Double)
spinButtonGetRange self =
alloca $ \minPtr ->
alloca $ \maxPtr -> do
(\(SpinButton arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gtk_spin_button_get_range argPtr1 arg2 arg3)
(toSpinButton self)
minPtr
maxPtr
min <- peek minPtr
max <- peek maxPtr
return (realToFrac min, realToFrac max)
spinButtonGetValue :: SpinButtonClass self => self -> IO Double
spinButtonGetValue self =
liftM realToFrac $
(\(SpinButton arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_spin_button_get_value argPtr1)
(toSpinButton self)
spinButtonGetValueAsInt :: SpinButtonClass self => self -> IO Int
spinButtonGetValueAsInt self =
liftM fromIntegral $
(\(SpinButton arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_spin_button_get_value_as_int argPtr1)
(toSpinButton self)
spinButtonSetValue :: SpinButtonClass self => self -> Double -> IO ()
spinButtonSetValue self value =
(\(SpinButton arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_spin_button_set_value argPtr1 arg2)
(toSpinButton self)
(realToFrac value)
spinButtonSetUpdatePolicy :: SpinButtonClass self => self
-> SpinButtonUpdatePolicy
-> IO ()
spinButtonSetUpdatePolicy self policy =
(\(SpinButton arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_spin_button_set_update_policy argPtr1 arg2)
(toSpinButton self)
((fromIntegral . fromEnum) policy)
spinButtonGetUpdatePolicy :: SpinButtonClass self => self
-> IO SpinButtonUpdatePolicy
spinButtonGetUpdatePolicy self =
liftM (toEnum . fromIntegral) $
(\(SpinButton arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_spin_button_get_update_policy argPtr1)
(toSpinButton self)
spinButtonSetNumeric :: SpinButtonClass self => self
-> Bool
-> IO ()
spinButtonSetNumeric self numeric =
(\(SpinButton arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_spin_button_set_numeric argPtr1 arg2)
(toSpinButton self)
(fromBool numeric)
spinButtonGetNumeric :: SpinButtonClass self => self
-> IO Bool
spinButtonGetNumeric self =
liftM toBool $
(\(SpinButton arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_spin_button_get_numeric argPtr1)
(toSpinButton self)
spinButtonSpin :: SpinButtonClass self => self
-> SpinType
-> Double
-> IO ()
spinButtonSpin self direction increment =
(\(SpinButton arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gtk_spin_button_spin argPtr1 arg2 arg3)
(toSpinButton self)
((fromIntegral . fromEnum) direction)
(realToFrac increment)
spinButtonSetWrap :: SpinButtonClass self => self
-> Bool
-> IO ()
spinButtonSetWrap self wrap =
(\(SpinButton arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_spin_button_set_wrap argPtr1 arg2)
(toSpinButton self)
(fromBool wrap)
spinButtonGetWrap :: SpinButtonClass self => self
-> IO Bool
spinButtonGetWrap self =
liftM toBool $
(\(SpinButton arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_spin_button_get_wrap argPtr1)
(toSpinButton self)
spinButtonSetSnapToTicks :: SpinButtonClass self => self
-> Bool
-> IO ()
spinButtonSetSnapToTicks self snapToTicks =
(\(SpinButton arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_spin_button_set_snap_to_ticks argPtr1 arg2)
(toSpinButton self)
(fromBool snapToTicks)
spinButtonGetSnapToTicks :: SpinButtonClass self => self
-> IO Bool
spinButtonGetSnapToTicks self =
liftM toBool $
(\(SpinButton arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_spin_button_get_snap_to_ticks argPtr1)
(toSpinButton self)
spinButtonUpdate :: SpinButtonClass self => self -> IO ()
spinButtonUpdate self =
(\(SpinButton arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_spin_button_update argPtr1)
(toSpinButton self)
spinButtonAdjustment :: SpinButtonClass self => Attr self Adjustment
spinButtonAdjustment = newAttr
spinButtonGetAdjustment
spinButtonSetAdjustment
spinButtonClimbRate :: SpinButtonClass self => Attr self Double
spinButtonClimbRate = newAttrFromDoubleProperty "climb-rate"
spinButtonDigits :: SpinButtonClass self => Attr self Int
spinButtonDigits = newAttr
spinButtonGetDigits
spinButtonSetDigits
spinButtonSnapToTicks :: SpinButtonClass self => Attr self Bool
spinButtonSnapToTicks = newAttr
spinButtonGetSnapToTicks
spinButtonSetSnapToTicks
spinButtonNumeric :: SpinButtonClass self => Attr self Bool
spinButtonNumeric = newAttr
spinButtonGetNumeric
spinButtonSetNumeric
spinButtonWrap :: SpinButtonClass self => Attr self Bool
spinButtonWrap = newAttr
spinButtonGetWrap
spinButtonSetWrap
spinButtonUpdatePolicy :: SpinButtonClass self => Attr self SpinButtonUpdatePolicy
spinButtonUpdatePolicy = newAttr
spinButtonGetUpdatePolicy
spinButtonSetUpdatePolicy
spinButtonValue :: SpinButtonClass self => Attr self Double
spinButtonValue = newAttr
spinButtonGetValue
spinButtonSetValue
onInput, afterInput :: SpinButtonClass sb => sb -> (IO (Maybe Double)) ->
IO (ConnectId sb)
onInput sb user = connect_PTR__INT "input" False sb $ \dPtr -> do
mVal <- user
case mVal of
(Just val) -> do
poke dPtr ((realToFrac val)::(CDouble))
return 0
Nothing -> return (fromIntegral inputError)
afterInput sb user = connect_PTR__INT "input" True sb $ \dPtr -> do
mVal <- user
case mVal of
(Just val) -> do
poke dPtr ((realToFrac val)::(CDouble))
return 0
Nothing -> return (fromIntegral inputError)
onOutput, afterOutput :: SpinButtonClass sb => sb -> IO Bool ->
IO (ConnectId sb)
onOutput = connect_NONE__BOOL "output" False
afterOutput = connect_NONE__BOOL "output" True
onValueSpinned, afterValueSpinned :: SpinButtonClass sb => sb -> IO () ->
IO (ConnectId sb)
onValueSpinned = connect_NONE__NONE "value-changed" False
afterValueSpinned = connect_NONE__NONE "value-changed" True
foreign import ccall safe "gtk_spin_button_new"
gtk_spin_button_new :: ((Ptr Adjustment) -> (CDouble -> (CUInt -> (IO (Ptr Widget)))))
foreign import ccall unsafe "gtk_spin_button_new_with_range"
gtk_spin_button_new_with_range :: (CDouble -> (CDouble -> (CDouble -> (IO (Ptr Widget)))))
foreign import ccall safe "gtk_spin_button_configure"
gtk_spin_button_configure :: ((Ptr SpinButton) -> ((Ptr Adjustment) -> (CDouble -> (CUInt -> (IO ())))))
foreign import ccall safe "gtk_spin_button_set_adjustment"
gtk_spin_button_set_adjustment :: ((Ptr SpinButton) -> ((Ptr Adjustment) -> (IO ())))
foreign import ccall unsafe "gtk_spin_button_get_adjustment"
gtk_spin_button_get_adjustment :: ((Ptr SpinButton) -> (IO (Ptr Adjustment)))
foreign import ccall safe "gtk_spin_button_set_digits"
gtk_spin_button_set_digits :: ((Ptr SpinButton) -> (CUInt -> (IO ())))
foreign import ccall safe "gtk_spin_button_get_digits"
gtk_spin_button_get_digits :: ((Ptr SpinButton) -> (IO CUInt))
foreign import ccall safe "gtk_spin_button_set_increments"
gtk_spin_button_set_increments :: ((Ptr SpinButton) -> (CDouble -> (CDouble -> (IO ()))))
foreign import ccall unsafe "gtk_spin_button_get_increments"
gtk_spin_button_get_increments :: ((Ptr SpinButton) -> ((Ptr CDouble) -> ((Ptr CDouble) -> (IO ()))))
foreign import ccall safe "gtk_spin_button_set_range"
gtk_spin_button_set_range :: ((Ptr SpinButton) -> (CDouble -> (CDouble -> (IO ()))))
foreign import ccall unsafe "gtk_spin_button_get_range"
gtk_spin_button_get_range :: ((Ptr SpinButton) -> ((Ptr CDouble) -> ((Ptr CDouble) -> (IO ()))))
foreign import ccall unsafe "gtk_spin_button_get_value"
gtk_spin_button_get_value :: ((Ptr SpinButton) -> (IO CDouble))
foreign import ccall unsafe "gtk_spin_button_get_value_as_int"
gtk_spin_button_get_value_as_int :: ((Ptr SpinButton) -> (IO CInt))
foreign import ccall safe "gtk_spin_button_set_value"
gtk_spin_button_set_value :: ((Ptr SpinButton) -> (CDouble -> (IO ())))
foreign import ccall safe "gtk_spin_button_set_update_policy"
gtk_spin_button_set_update_policy :: ((Ptr SpinButton) -> (CInt -> (IO ())))
foreign import ccall unsafe "gtk_spin_button_get_update_policy"
gtk_spin_button_get_update_policy :: ((Ptr SpinButton) -> (IO CInt))
foreign import ccall safe "gtk_spin_button_set_numeric"
gtk_spin_button_set_numeric :: ((Ptr SpinButton) -> (CInt -> (IO ())))
foreign import ccall unsafe "gtk_spin_button_get_numeric"
gtk_spin_button_get_numeric :: ((Ptr SpinButton) -> (IO CInt))
foreign import ccall safe "gtk_spin_button_spin"
gtk_spin_button_spin :: ((Ptr SpinButton) -> (CInt -> (CDouble -> (IO ()))))
foreign import ccall safe "gtk_spin_button_set_wrap"
gtk_spin_button_set_wrap :: ((Ptr SpinButton) -> (CInt -> (IO ())))
foreign import ccall safe "gtk_spin_button_get_wrap"
gtk_spin_button_get_wrap :: ((Ptr SpinButton) -> (IO CInt))
foreign import ccall safe "gtk_spin_button_set_snap_to_ticks"
gtk_spin_button_set_snap_to_ticks :: ((Ptr SpinButton) -> (CInt -> (IO ())))
foreign import ccall unsafe "gtk_spin_button_get_snap_to_ticks"
gtk_spin_button_get_snap_to_ticks :: ((Ptr SpinButton) -> (IO CInt))
foreign import ccall safe "gtk_spin_button_update"
gtk_spin_button_update :: ((Ptr SpinButton) -> (IO ()))