module Graphics.UI.Gtk.Misc.Calendar (
Calendar,
CalendarClass,
castToCalendar, gTypeCalendar,
toCalendar,
CalendarDisplayOptions(..),
calendarNew,
calendarSelectMonth,
calendarSelectDay,
calendarMarkDay,
calendarUnmarkDay,
calendarClearMarks,
calendarDisplayOptions,
calendarSetDisplayOptions,
calendarGetDisplayOptions,
calendarGetDate,
calendarFreeze,
calendarYear,
calendarMonth,
calendarDay,
calendarShowHeading,
calendarShowDayNames,
calendarNoMonthChange,
calendarShowWeekNumbers,
onDaySelected,
afterDaySelected,
onDaySelectedDoubleClick,
afterDaySelectedDoubleClick,
onMonthChanged,
afterMonthChanged,
onNextMonth,
afterNextMonth,
onNextYear,
afterNextYear,
onPrevMonth,
afterPrevMonth,
onPrevYear,
afterPrevYear,
) where
import Control.Monad (liftM)
import System.Glib.FFI
import System.Glib.Flags (fromFlags, toFlags)
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.Enums (CalendarDisplayOptions(..))
calendarNew :: IO Calendar
calendarNew =
makeNewObject mkCalendar $
liftM (castPtr :: Ptr Widget -> Ptr Calendar) $
gtk_calendar_new
calendarSelectMonth :: CalendarClass self => self
-> Int
-> Int
-> IO Bool
calendarSelectMonth self month year =
liftM toBool $
(\(Calendar arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gtk_calendar_select_month argPtr1 arg2 arg3)
(toCalendar self)
(fromIntegral month)
(fromIntegral year)
calendarSelectDay :: CalendarClass self => self
-> Int
-> IO ()
calendarSelectDay self day =
(\(Calendar arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_calendar_select_day argPtr1 arg2)
(toCalendar self)
(fromIntegral day)
calendarMarkDay :: CalendarClass self => self
-> Int
-> IO Bool
calendarMarkDay self day =
liftM toBool $
(\(Calendar arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_calendar_mark_day argPtr1 arg2)
(toCalendar self)
(fromIntegral day)
calendarUnmarkDay :: CalendarClass self => self
-> Int
-> IO Bool
calendarUnmarkDay self day =
liftM toBool $
(\(Calendar arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_calendar_unmark_day argPtr1 arg2)
(toCalendar self)
(fromIntegral day)
calendarClearMarks :: CalendarClass self => self -> IO ()
calendarClearMarks self =
(\(Calendar arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_calendar_clear_marks argPtr1)
(toCalendar self)
calendarSetDisplayOptions :: CalendarClass self => self
-> [CalendarDisplayOptions]
-> IO ()
calendarSetDisplayOptions self flags =
(\(Calendar arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_calendar_set_display_options argPtr1 arg2)
(toCalendar self)
((fromIntegral . fromFlags) flags)
calendarGetDisplayOptions :: CalendarClass self => self
-> IO [CalendarDisplayOptions]
calendarGetDisplayOptions self =
liftM (toFlags . fromIntegral) $
(\(Calendar arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_calendar_get_display_options argPtr1)
(toCalendar self)
calendarDisplayOptions :: CalendarClass self => self
-> [CalendarDisplayOptions] -> IO ()
calendarDisplayOptions self flags =
(\(Calendar arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_calendar_display_options argPtr1 arg2)
(toCalendar self)
((fromIntegral . fromFlags) flags)
calendarGetDate :: CalendarClass self => self
-> IO (Int,Int,Int)
calendarGetDate self =
alloca $ \yearPtr ->
alloca $ \monthPtr ->
alloca $ \dayPtr -> do
(\(Calendar arg1) arg2 arg3 arg4 -> withForeignPtr arg1 $ \argPtr1 ->gtk_calendar_get_date argPtr1 arg2 arg3 arg4)
(toCalendar self)
yearPtr
monthPtr
dayPtr
year <- liftM fromIntegral $ peek yearPtr
month <- liftM fromIntegral $ peek monthPtr
day <- liftM fromIntegral $ peek dayPtr
return (year,month,day)
calendarFreeze :: CalendarClass self => self
-> IO a
-> IO a
calendarFreeze self update = do
(\(Calendar arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_calendar_freeze argPtr1) (toCalendar self)
res <- update
(\(Calendar arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_calendar_thaw argPtr1) (toCalendar self)
return res
calendarYear :: CalendarClass self => Attr self Int
calendarYear = newAttrFromIntProperty "year"
calendarMonth :: CalendarClass self => Attr self Int
calendarMonth = newAttrFromIntProperty "month"
calendarDay :: CalendarClass self => Attr self Int
calendarDay = newAttrFromIntProperty "day"
calendarShowHeading :: CalendarClass self => Attr self Bool
calendarShowHeading = newAttrFromBoolProperty "show-heading"
calendarShowDayNames :: CalendarClass self => Attr self Bool
calendarShowDayNames = newAttrFromBoolProperty "show-day-names"
calendarNoMonthChange :: CalendarClass self => Attr self Bool
calendarNoMonthChange = newAttrFromBoolProperty "no-month-change"
calendarShowWeekNumbers :: CalendarClass self => Attr self Bool
calendarShowWeekNumbers = newAttrFromBoolProperty "show-week-numbers"
onDaySelected, afterDaySelected :: CalendarClass self => self
-> IO ()
-> IO (ConnectId self)
onDaySelected = connect_NONE__NONE "day-selected" False
afterDaySelected = connect_NONE__NONE "day-selected" True
onDaySelectedDoubleClick, afterDaySelectedDoubleClick :: CalendarClass self => self
-> IO ()
-> IO (ConnectId self)
onDaySelectedDoubleClick =
connect_NONE__NONE "day-selected-double-click" False
afterDaySelectedDoubleClick =
connect_NONE__NONE "day-selected-double-click" True
onMonthChanged, afterMonthChanged :: CalendarClass self => self
-> IO ()
-> IO (ConnectId self)
onMonthChanged = connect_NONE__NONE "month-changed" False
afterMonthChanged = connect_NONE__NONE "month-changed" True
onNextMonth, afterNextMonth :: CalendarClass self => self
-> IO ()
-> IO (ConnectId self)
onNextMonth = connect_NONE__NONE "next-month" False
afterNextMonth = connect_NONE__NONE "next-month" True
onNextYear, afterNextYear :: CalendarClass self => self
-> IO ()
-> IO (ConnectId self)
onNextYear = connect_NONE__NONE "next-year" False
afterNextYear = connect_NONE__NONE "next-year" True
onPrevMonth, afterPrevMonth :: CalendarClass self => self
-> IO ()
-> IO (ConnectId self)
onPrevMonth = connect_NONE__NONE "prev-month" False
afterPrevMonth = connect_NONE__NONE "prev-month" True
onPrevYear, afterPrevYear :: CalendarClass self => self
-> IO ()
-> IO (ConnectId self)
onPrevYear = connect_NONE__NONE "prev-year" False
afterPrevYear = connect_NONE__NONE "prev-year" True
foreign import ccall unsafe "gtk_calendar_new"
gtk_calendar_new :: (IO (Ptr Widget))
foreign import ccall safe "gtk_calendar_select_month"
gtk_calendar_select_month :: ((Ptr Calendar) -> (CUInt -> (CUInt -> (IO CInt))))
foreign import ccall safe "gtk_calendar_select_day"
gtk_calendar_select_day :: ((Ptr Calendar) -> (CUInt -> (IO ())))
foreign import ccall safe "gtk_calendar_mark_day"
gtk_calendar_mark_day :: ((Ptr Calendar) -> (CUInt -> (IO CInt)))
foreign import ccall safe "gtk_calendar_unmark_day"
gtk_calendar_unmark_day :: ((Ptr Calendar) -> (CUInt -> (IO CInt)))
foreign import ccall safe "gtk_calendar_clear_marks"
gtk_calendar_clear_marks :: ((Ptr Calendar) -> (IO ()))
foreign import ccall safe "gtk_calendar_set_display_options"
gtk_calendar_set_display_options :: ((Ptr Calendar) -> (CInt -> (IO ())))
foreign import ccall safe "gtk_calendar_get_display_options"
gtk_calendar_get_display_options :: ((Ptr Calendar) -> (IO CInt))
foreign import ccall safe "gtk_calendar_display_options"
gtk_calendar_display_options :: ((Ptr Calendar) -> (CInt -> (IO ())))
foreign import ccall unsafe "gtk_calendar_get_date"
gtk_calendar_get_date :: ((Ptr Calendar) -> ((Ptr CUInt) -> ((Ptr CUInt) -> ((Ptr CUInt) -> (IO ())))))
foreign import ccall unsafe "gtk_calendar_freeze"
gtk_calendar_freeze :: ((Ptr Calendar) -> (IO ()))
foreign import ccall safe "gtk_calendar_thaw"
gtk_calendar_thaw :: ((Ptr Calendar) -> (IO ()))