Scrolled windows are used to create a scrollable area with another widget inside it. You may insert any type of widget into a scrolled window, and it will be accessible regardless of the size by using the scrollbars.
The following function is used to create a new scrolled window.
scrolledWindowNew :: Maybe Adjustment -> Maybe Adjustment -> IO ScrolledWindow
The first argument is the adjustment for the horizontal
direction, and the second is for the vertical direction. They
are almost always set to
Nothing .
scrolledWindowSetPolicy :: ScrolledWindowClass self => self -> PolicyType -> PolicyType -> IO ()
This sets the policy to be used with respect to the
horizontal and vertical scrollbars. The constructor
PolicyAlways always shows the scrollbar,
PolicyNever never shows it and
PolicyAutomatic shows it only if the page size is
larger than the window. The default is
PolicyAlways .
You can then place your object into the scrolled window
using
containerAdd if that object has a window associated
with it. If not, then you'll need a
Viewport , but you can add one automatically
with:
scrolledWindowAddWithViewport :: (ScrolledWindowClass self, WidgetClass child) => self -> child -> IO ()
Should you forget about the viewport, GHCi produces a
helpful error message if you use
containerAdd when you should not have done so!
Here is an example that packs a table with 100 toggle
buttons into a scrolled window. It implements a program from
'Yet Another Haskell Tutorial' by Hal Daumé III. This
tutorial is freely available from the Haskell website. On page
43 there is a small program that lets a user repeatedly guess a
number between 1 and 100 and tells whether the guess is too
high, too low or correct. The random number is generated with
function
randomRIO from module System.Random.
The example implements this with a graphical user interface.

In the main window we use a vertical box to pack a label
(for user information), a horizontal separator, a scrolled
window, a horizontal separator and a horizontal box for two
buttons from stock. The scrolled window is packed with
PackGrow , to let it resize with the window, and
the play and quit buttons are packed at the opposite ends of
the horizontal box.
The 100 buttons are created with:
buttonlist <- sequence (map numButton [1..100])
where the function
numButton is defined as:
numButton :: Int -> IO Button
numButton n = do
button <- buttonNewWithLabel (show n)
return button
So, each button automatically gets the appropriate number as its label.
Inside the scrolled window we create a 10 by 10 table for
the 100 buttons. To position the buttons we use the function
cross , which is based on the
List monad . This function, a very simple way to
get a Cartesian product from two or more lists, is also
discussed in YAHT (another program).
cross :: [Int] -> [Int] -> [(Int,Int)]
cross row col = do
x <- row
y <- col
return (x,y)
The function
attachButton takes a table, a button and a tuple of
coordinates to place a button in the table. (See Chapter 3.3
for more on packing tables.)
attachButton :: Table -> Button -> (Int,Int) -> IO () attachButton ta bu (x,y) = tableAttachDefaults ta bu y (y+1) x (x+1)
Now the following code segment packs all the buttons in the
table, with
buttonlist as described above.
let places = cross [0..9] [0..9]
sequence_ (zipWith (attachButton table) buttonlist places)
Every time the user presses the play button, a random number
must be generated, which can subsequently be compared to the
user choice. But the Gtk2Hs signal handler
onClicked takes a button, and a function which
takes no parameters and has a value of type
IO () . We need something like a global variable,
and this is provided with the module Data.IORef. We can now use
the following snippets, in different functions, to initialize,
write and read the random number.
snippet 1 -- randstore <- newIORef 50 snippet 2 -- writeIORef rst rand snippet 3 -- rand <- readIORef rst
The first gets a variable of type
IORef Int and initializes it with 50. The second is
implemented in the function
randomButton :
randomButton :: ButtonClass b => Label -> IORef Int -> b -> IO (ConnectId b)
randomButton inf rst b =
onClicked b $ do rand <- randomRIO (1::Int, 100)
writeIORef rst rand
set inf [labelLabel := "Ready"]
widgetModifyFg inf StateNormal (Color 0 0 65535)
and then used in the following snippet, where
info is the label for the user information.
(See Chapter 5.3 for colors and how they can be changed.)
Similar to the writing of the random number, the function
actionButton implements the reading of
randstore. It then compares the number obtained
from the label of the button which has been clicked, and
displays the relevant information on the
info label.
Finally we have to monitor all 100 buttons to find out which one was pressed, if any.
sequence_ (map (actionButton info randstore) buttonlist)
The above is analogous to all the other
sequence _ and
map combinations we've used, but in this case
exactly one of the 100 signal handlers will be triggered, any
time the user presses that particular button.
The following is the complete code for the example.
import Graphics.UI.Gtk
import Data.IORef
import System.Random (randomRIO)
main:: IO ()
main= do
initGUI
window <- windowNew
set window [ windowTitle := "Guess a Number",
windowDefaultWidth := 300, windowDefaultHeight := 250]
mb <- vBoxNew False 0
containerAdd window mb
info <- labelNew (Just "Press \"New\" for a random number")
boxPackStart mb info PackNatural 7
sep1 <- hSeparatorNew
boxPackStart mb sep1 PackNatural 7
scrwin <- scrolledWindowNew Nothing Nothing
boxPackStart mb scrwin PackGrow 0
table <- tableNew 10 10 True
scrolledWindowAddWithViewport scrwin table
buttonlist <- sequence (map numButton [1..100])
let places = cross [0..9] [0..9]
sequence_ (zipWith (attachButton table) buttonlist places)
sep2 <- hSeparatorNew
boxPackStart mb sep2 PackNatural 7
hb <- hBoxNew False 0
boxPackStart mb hb PackNatural 0
play <- buttonNewFromStock stockNew
quit <- buttonNewFromStock stockQuit
boxPackStart hb play PackNatural 0
boxPackEnd hb quit PackNatural 0
randstore <- newIORef 50
randomButton info randstore play
sequence_ (map (actionButton info randstore) buttonlist)
widgetShowAll window
onClicked quit (widgetDestroy window)
onDestroy window mainQuit
mainGUI
numButton :: Int -> IO Button
numButton n = do
button <- buttonNewWithLabel (show n)
return button
cross :: [Int] -> [Int] -> [(Int,Int)]
cross row col = do
x <- row
y <- col
return (x,y)
attachButton :: Table -> Button -> (Int,Int) -> IO ()
attachButton ta bu (x,y) =
tableAttachDefaults ta bu y (y+1) x (x+1)
actionButton :: ButtonClass b => Label -> IORef Int -> b -> IO (ConnectId b)
actionButton inf rst b =
onClicked b $ do label <- get b buttonLabel
let num = (read label):: Int
rand <- readIORef rst
case compare num rand of
GT -> do set inf [labelLabel := "Too High"]
widgetModifyFg inf StateNormal (Color 65535 0 0)
LT -> do set inf [labelLabel := "Too Low"]
widgetModifyFg inf StateNormal (Color 65535 0 0)
EQ -> do set inf [labelLabel := "Correct"]
widgetModifyFg inf StateNormal (Color 0 35000 0)
randomButton :: ButtonClass b => Label -> IORef Int -> b -> IO (ConnectId b)
randomButton inf rst b =
onClicked b $ do rand <- randomRIO (1::Int, 100)
writeIORef rst rand
set inf [labelLabel := "Ready"]
widgetModifyFg inf StateNormal (Color 0 0 65535)