[Haskell-cafe] Re: StateT IO Action on `onKeyPress`
Andy Stewart
lazycat.manatee at gmail.com
Tue May 5 03:03:42 EDT 2009
Ryan Ingram <ryani.spam at gmail.com> writes:
> Something like this:
>
> -- Replaces "runStateT" for callbacks that might affect the state
> invert :: IORef s -> StateT s IO a -> IO a
> invert r m = do
> s <- readIORef r
> (a, s') <- runStateT m s
> writeIORef r s'
> return a
>
> -- Replaces "liftIO" when the action called might use "invert"
> revert :: IORef s -> IO a -> StateT s IO a
> revert r m = do
> s <- get
> writeIORef r s
> a <- liftIO m
> s' <- readIORef r
> put s'
> return a
>
> Then you use ... `onKeyPress` (\event -> invert windowListRef (...))
>
> I'm not sure where in your code revert is required; I don't know when
> WindowListT might call back into IO. If you want to be extra safe,
> make the IORef be a Maybe WindowList and make sure it's "Nothing"
> except between 'revert' and 'invert'.
Result is ReaderT is cleaner and simpler.
Thanks for your help!
-- Andy
>
> -- ryan
>
> On Mon, May 4, 2009 at 1:02 AM, Andy Stewart <lazycat.manatee at gmail.com> wrote:
>> Hi Ryan,
>>
>> Ryan Ingram <ryani.spam at gmail.com> writes:
>>
>>> Hi Andy.
>>>
>>> The GTK bindings use IO for their callbacks, not any custom monad like
>>> your WindowListT.
>>>
>>> I suggest, instead of StateT s IO a, you use ReaderT (IORef s) IO a:
>>>
>>> putR :: s -> ReaderT (IORef s) IO ()
>>> putR s = do
>>> r <- ask
>>> liftIO $ writeIORef r s
>>>
>>> getR :: ReaderT (IORef s) IO s
>>> getR = ask >>= liftIO . readIORef
>>>
>>> Otherwise, there are techniques to use an IORef to hold onto the state
>>> while calling into IO (which might make callbacks), and then read it
>>> back out and put it in the state while running your action. But it's
>>> simpler to just switch to ReaderT
>> I'm curious another techniques that use IORef hold on state.
>>
>> Can you implement a simple example that make my code pass `onKeyPress`?
>>
>> Thanks!
>>
>> -- Andy
>>
>>>
>>> -- ryan
>>>
>>> On Sun, May 3, 2009 at 8:27 AM, Andy Stewart <lazycat.manatee at gmail.com> wrote:
>>>> 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 <------------------------------
>>>>
>>>> _______________________________________________
>>>> Haskell-Cafe mailing list
>>>> Haskell-Cafe at haskell.org
>>>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>>>
>>
>> _______________________________________________
>> Haskell-Cafe mailing list
>> Haskell-Cafe at haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
More information about the Haskell-Cafe
mailing list