5.1 Calendar

The Calendar widget is an effective way to display and retrieve monthly date related information. It is a very simple widget to create and work with. Use:

calendarNew: IO Calendar

By default the current date is shown. To retrieve the date from a calendar use:

calendarGetDate :: CalendarClass self => self -> IO (Int, Int, Int)

where the interpretation is (year, month, day). Note that the months start with a 0, so you'll have to add 1 to get it right. The related attributes are:

calendarYear :: CalendarClass self => Attr self Int
calendarMonth :: CalendarClass self => Attr self Int
calendarDay :: CalendarClass self => Attr self Int

The Calendar widget has a few options that allow you to change the way the widget looks and operates by using the function calendarSetDisplayOptions. To retrieve the settings use: calendarGetDisplayOptions.

calendarSetDisplayOptions :: CalendarClass self => self -> [CalendarDisplayOptions] -> IO ()
calendarGetDisplayOptions :: CalendarClass self => self -> IO [CalendarDisplayOptions]

CalendarDisplayOptionshas the following constructors:

These options can also be set and retrieved through Boolean attributes using the generic getand setfunctions.

Note: there is no attribute for CalendarWeekStartMonday and using the calendarSetDisplayfunction resulted in a run-time message that the first day of the week was taken from the locale and GTK_CALENDAR_WEEK_START_MONDAY is ignored.

Finally, any number of days in the month may be "marked". A marked day is highlighted within the calendar display. The following functions (there are no attributes) are provided to manipulate marked days:

calendarMarkDay :: CalendarClass self => self -> Int -> IO Bool
calendarUnmarkDay :: CalendarClass self => self -> Int -> IO Bool
calendarClearMarks :: CalendarClass self => self -> IO ()

The Boolean value is not used (always True). Note that marks are persistent across month and year changes.

The Calendar widget can generate a number of signals indicating date selection and change. The names of these signals are:

Note: the following are also mentioned in the API documentation, but appear to implemented as onDaySelected. See the comment in the example code.

The following example illustrates the use of the Calendar widget:

GtkChap5-1.png

import Graphics.UI.Gtk

main :: IO ()
main= do
     initGUI
     window <- windowNew
     set window [windowTitle := "Calendar",
                 windowDefaultWidth:= 200,
                 windowDefaultHeight:= 100]
     mainbox <- vBoxNew True 0
     containerAdd window mainbox

     hbox1 <- hBoxNew True 0
     boxPackStart mainbox hbox1 PackGrow 0

     cal <-calendarNew
     boxPackStart hbox1 cal PackGrow 0   

     vbox1 <- vBoxNew True 0
     frame1 <- frameNew
     set frame1 [frameLabel := "Display Options",
                 containerBorderWidth := 10,
                 frameLabelYAlign := 0.5, 
                 frameLabelXAlign := 0.5,
                 containerChild := vbox1 ]
     boxPackStart hbox1 frame1 PackGrow 0
     headingopt <- addDisplayOpt vbox1 "Show Heading"
     daynameopt <- addDisplayOpt vbox1 "Show Day Names"
     monchngopt <- addDisplayOpt vbox1 "No Month Change"
     weeknumopt <- addDisplayOpt vbox1 "Show Week Numbers"

     set headingopt [toggleButtonActive := True]
     set daynameopt [toggleButtonActive := True]

     reslabel <- labelNew Nothing
     showMess cal reslabel "Nothing Done Yet"
     frame2 <- frameNew
     set frame2 [frameLabel := "Last Action:",
                 containerBorderWidth := 10, 
                 containerChild := reslabel]
     boxPackStart mainbox frame2 PackGrow 0     

     mySetOnToggled headingopt cal calendarShowHeading
     mySetOnToggled daynameopt cal calendarShowDayNames
     mySetOnToggled monchngopt cal calendarNoMonthChange
     mySetOnToggled weeknumopt cal calendarShowWeekNumbers

     onDaySelected cal (showMess cal reslabel "Day Selected")
     onDaySelectedDoubleClick cal 
            (showMess cal reslabel "Double Click Day Selected")

     widgetShowAll window
     onDestroy window mainQuit
     mainGUI


addDisplayOpt :: VBox -> String -> IO CheckButton
addDisplayOpt box lbl = do
         cb <- checkButtonNewWithLabel lbl
         boxPackStart box cb PackGrow 5
         return cb

mySetOnToggled :: CheckButton -> Calendar -> 
               Attr Calendar Bool -> 
               IO (ConnectId CheckButton)
mySetOnToggled cb cl att = onToggled cb $ do
         cbstate <- get cb toggleButtonActive
         set cl [att := cbstate]

showMess :: Calendar -> Label -> String -> IO ()
showMess cal lbl str = do  
         (year, month, day) <- calendarGetDate cal
         labelSetText lbl $ str ++ "\n" ++ "Date = " ++
                      (show year) ++ "//" ++ 
                      (myshow (month +1))  -- month is 0 to 11
                       ++ "//" ++ (myshow day) 
                            where myshow n | n <= 9 = '0':(show
n)
                                           | otherwise = show n

{- Commented out for platform specific testing:
These signals all seem to be implemented as onDaySelected.
The platform was: Gtk2Hs 0.9.12 on Fedora Core 6

     onMonthChanged cal (showMess cal reslabel "Month Changed")
     onNextMonth cal (showMess cal reslabel "Next Month Selected")
     onNextYear cal (showMess cal reslabel "Next Year Selected")
     onPrevMonth cal (showMess cal reslabel "Previous Month
Selected")
     onPrevYear cal (showMess cal reslabel "Previous Year
Selected")
-}