[Haskell-cafe] Re: How to use dyre relaunch/restore State of Gtk2hs
Object?
Will Donnelly
will.donnelly at gmail.com
Mon Aug 31 09:40:34 EDT 2009
Hi Andy,
Your program didn't compile as given, so I cut out some of the event
handling fanciness you were doing. Also, my modified version restarts
whenever the 'r' key is pressed. I figure those changes aren't important to
the problem at hand.
Anyway, I don't think it's ever going to be possible to define a Binary
instance for a TextView, since all of the functions which can yield
information about it are impure. I would recommend extracting the relevant
data beforehand, and then persisting it in a tuple. You could use some
'marshal<WIDGET>' and 'recreate<WIDGET>' functions if you need to persist
many different widget types. Saving just the text can be done as follows:
<code>
module DyreExample where
import Graphics.UI.Gtk hiding (get)
import qualified Graphics.UI.Gtk.Gdk.Events as E
import qualified Config.Dyre as Dyre
import Config.Dyre.Relaunch
import System.IO
import Data.Binary
data Config = Config { message :: String, errorMsg :: Maybe String }
defaultConfig :: Config
defaultConfig = Config "Dyre Example v0.1" Nothing
showError :: Config -> String -> Config
showError cfg msg = cfg { errorMsg = Just msg }
realMain Config{message = message, errorMsg = errorMsg } = do
initGUI
textView <- textViewNew
textBuffer <- textViewGetBuffer textView
text <- restoreBinaryState ""
putStrLn $ "Restored state: " ++ text
textBufferSetText textBuffer text
rootWindow <- windowNew
rootWindow `onDestroy` mainQuit
windowFullscreen rootWindow
rootWindow `containerAdd` textView
widgetShowAll rootWindow
rootWindow `onKeyPress` (\event -> dyreKeyTest event textView)
mainGUI
dyreExample = Dyre.wrapMain $ Dyre.defaultParams
{ Dyre.projectName = "Main"
, Dyre.realMain = realMain
, Dyre.showError = showError
}
dyreKeyTest :: E.Event -> TextView -> IO Bool
dyreKeyTest ev textView = do
case E.eventKeyName ev of
"r" -> do textBuffer <- textViewGetBuffer textView
sI <- textBufferGetStartIter textBuffer
eI <- textBufferGetEndIter textBuffer
text <- textBufferGetText textBuffer sI eI True
putStrLn $ "Relaunching with state: " ++ text
relaunchWithBinaryState text Nothing
return True
_ -> return False
</code>
Other comments:
1. It isn't necessary to explicitly tell Dyre to do a custom compile. It
will take care of figuring that out once you restart it.
2. Instead of manually setting paths in the code, you can use the
'--dyre-debug' command-line flag, which will cause Dyre to look for
configurations in the current directory, and store temporary files in a
'cache' subdirectory.
3. Giving a project name of 'Main' causes Dyre to see the file 'Main.hs'
as a custom configuration. I'm not sure if that's what you intended, but it
will make testing custom configurations harder than it needs to be.
4. Good luck with the rest of your project!
- Will Donnelly
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20090831/9ca8678d/attachment.html
More information about the Haskell-Cafe
mailing list