Calendario

El widget Calendar es una buena manera de mostrar y recuperar la información cronológica. Es un widget muy sencillo de crear y su funcionamiento es muy simple. Debes usar:

calendarNew: IO Calendar

Por defecto se muestra el mes actual. Para recuperar la información de un calendario emplea:

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

donde la terna contendría la información (año, mes, día). (Enero es el 0). Los atributos relacionados son:

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

El widget Calendar tiene algunas opciones que te permiten cambiar la apariencia y el modo de operación del widget. Para ello debes usar la función calendarSetDisplayOptions. Para recuperar los valores usa: calendarGetDisplayOptions.

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

CalendarDisplayOptions tiene los siguientes constructores:

También puede obtenerse y cambiarse el valor de las opciones usando atributos Booleanos mediante las funciones genéricas get y set.

Nota: No hay atributo para CalendarWeekStartMonday y el uso de la función calendarSetDisplay origina un mensaje en tiempo de ejecución indicando que el primer día de la semana se toma por defecto y se ignora GTK_CALENDAR_WEEK_START_MONDAY.

Por último, destacar que se pueden marcar algunos días del mes. Un día marcado se resalta en el calendario mostrado. Las siguientes funciones (sin atributos) sirven para manipular los días marcados:

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

El valor Booleano no se usa (siempre True). Las marcas se mantienen en los cambios de mes y de año.

El widget Calendar puede generar señales que indican los cambios y la fecha seleccionada. Los nombres de esas señales son:

Nota: lo siguiente está mencionado en la documentación de la API, pero aparece implementado como onDaySelected. Mira el comentario en el código del ejemplo.

El siguiente ejemplo muestra el uso del widget Calendar:

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

{- Comentado para hacer una comprobación específica de la plataforma:
Estas señales parecen implementadas como onDaySelected.
La plataforma es: Gtk2Hs 0.9.12 en 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")
-}