How to use dyre relaunch/restore State of Gtk2hs Object?

Hi all. I try to use dyre (http://hackage.haskell.org/packages/archive/dyre/0.7.2/doc/html/Config-Dyre....) to relaunch/restore State of TextView to make TextView's content can't lost when main program reboot. Below is source code for example: ------------------------------> source code start <------------------------------ module DyreExample where import Graphics.UI.Gtk hiding (get) import qualified Config.Dyre as Dyre import Config.Dyre.Relaunch import Config.Dyre.Compile import System.IO import Event import Test import Data.Binary import qualified Graphics.UI.Gtk.Gdk.Events as E 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 tn <- restoreTextState testName tv <- restoreBinaryState textView putStrLn tn rootWindow <- windowNew rootWindow `onDestroy` mainQuit windowFullscreen rootWindow -- rootWindow `containerAdd` textView rootWindow `containerAdd` tv widgetShowAll rootWindow rootWindow `onKeyPress` (\event -> dyreKeyTest event textView) mainGUI dyreExample = Dyre.wrapMain $ Dyre.defaultParams { Dyre.projectName = "Main" , Dyre.configDir = Just (return "/home/andy/Projects/Haskell/dyre/") , Dyre.cacheDir = Just (return "/test/Download/cache/") , Dyre.realMain = realMain , Dyre.showError = showError } dyreMainParams = Dyre.defaultParams { Dyre.projectName = "Main" , Dyre.configDir = Just (return "/home/andy/Projects/Haskell/dyre/") , Dyre.cacheDir = Just (return "/test/Download/cache/") , Dyre.realMain = realMain , Dyre.showError = showError } dyreTestParams = Dyre.defaultParams {Dyre.projectName = "Test" ,Dyre.configDir = Just (return "/home/andy/Projects/Haskell/dyre/")} dyreKeyTest :: E.Event -> TextView -> IO Bool dyreKeyTest ev textView = do case eventTransform ev of Nothing -> return False Just e -> do let eventName = eventGetName e case eventName of "M-m" -> do out2 <- customCompile dyreMainParams putStrLn $ show out2 relaunchWithTextState testName Nothing relaunchWithBinaryState textView Nothing return True _ -> return False -- instance Binary TextView where -- put a = put a -- get = get ------------------------------> source code end <------------------------------ On the surface, just add TextView's Binary instance can fix problem. But TextView is Haskell binding (by gtk2hs) for C struct in GTK+ library, i wonder how to write Binary instance for TextView. My aim is write GUI program (through gtk2hs) will keep GUI State when main program recompile/reboot (like XMonad). Example, above code, i add TextView widget in Window, and type "I love Haskell" in it, when this program recompile/reboot itself, the content "I love Haskell" still display in TextView widget, and not empty. So any ideas or suggestions? Thanks! -- Andy
participants (1)
-
Andy Stewart