[Haskell-cafe] StateT IO Action on `onKeyPress`
Andy Stewart
lazycat.manatee at gmail.com
Sun May 3 11:27:03 EDT 2009
Hi all,
I have a function named `keymapTest` need moand state WindowListT, and
WindowListT is `type WindowListT = StateT WindowList IO`.
when i add "(\event -> keymapTest winList event >> return False)" after
`onKeyPress` for handle key press event, i got GHC error:
Manatee.hs:57:58:
Couldn't match expected type `IO a'
against inferred type `WindowListT Bool'
In the first argument of `(>>)', namely `keymapTest winList event'
In the expression: keymapTest winList event >> return False
In the second argument of `onKeyPress', namely
`(\ event -> keymapTest winList event >> return False)'
So function `onKeyPress` just accept *one* IO-action?
Have a way to fix above problem?
Any help?
Thanks!
-- Andy
Below is source code of Manatee.hs file.
------------------------------> Manatee.hs start <------------------------------
module Main where
import Text.Printf
import Data.Monoid
import Data.List
import Data.Maybe
import Control.Monad
import Control.Monad.State
import Control.Applicative
import Data.IORef
import Graphics.UI.Gtk hiding (Window, windowNew, get)
import Graphics.UI.Gtk.SourceView
import Graphics.UI.Gtk.Abstract.Widget
import Manatee.Event
import Manatee.Buffer
import Manatee.WindowList
import Manatee.Pane
import Manatee.Statusbar
import Manatee.Utils
import Manatee.Window
import qualified Data.Set as Set
import qualified Graphics.UI.Gtk.Windows.Window as W
import qualified Graphics.UI.Gtk.Gdk.Events as E
main :: IO ()
main = do
-- Init.
initGUI
-- Root frame.
rootFrame <- W.windowNew
rootFrame `onDestroy` mainQuit -- quit main loop when root frame close
-- Root frame status.
windowFullscreen rootFrame -- fullscreen
-- Windows list.
let windowsList = WindowList 0 Set.empty
evalStateT (do
-- Window 1
window1 <- windowNewWithBuffer DTop "test"
liftIO $ containerAdd rootFrame $ windowPaned window1
(window2, window3) <- windowSplitVertically window1
(window4, window5) <- windowSplitHorizontally window3
winList <- windowListGetList
liftIO $ rootFrame `onKeyPress` (\event -> keymapTest winList event >> return False)
-- Handle window content synchronous.
windowHandleSynchronous
) windowsList
-- Loop
widgetShowAll rootFrame -- display all widget
mainGUI
keymapTest :: [Window] -> E.Event -> WindowListT Bool
keymapTest winList event = do
window <- liftIO $ windowFindFocus winList
case window of
Just x -> handleKeyPress x event
Nothing -> return False
handleKeyPress :: Window -> E.Event -> WindowListT Bool
handleKeyPress window ev = do
liftIO $
case eventTransform ev of
Nothing -> return False
Just e -> do
let display = statusbarOutputSubitemSetText $ paneStatusbar $ windowPane $ window
eventName = eventGetName e
case eventName of
-- Window commands.
"M-t" -> display "windowSplitVertically"
-- "M-t" -> windowSplitVertically window >> return False
_ -> display $ printf "%s undefined." eventName
------------------------------> Manatee.hs end <------------------------------
More information about the Haskell-Cafe
mailing list