Thu Aug  6 12:45:21 CDT 2009  Jeff Wheeler <jeffwhee...@gmail.com>
  * Replace HConf with Dyre

--~--~---------~--~----~------------~-------~--~----~
Yi development mailing list
yi-devel@googlegroups.com
http://groups.google.com/group/yi-devel
-~----------~----~----~----~------~----~------~--~---

New patches:

[Replace HConf with Dyre
Jeff Wheeler <jeffwhee...@gmail.com>**20090806174521
 Ignore-this: c57bb9b497091674df0513ab24532a57
] hunk ./src/HConf/Paths.hs 1
-module HConf.Paths where
-
-import Control.Applicative ((<$>))
-import Control.Monad.Trans (MonadIO)
-import System.Directory (getAppUserDataDirectory)
-import System.FilePath ((</>))
-import System.Info (arch, os)
-import HConf.Utils (io)
-
--- | Return the path to @~\/.proj...@.
-getProjectDir :: MonadIO m => String -> m FilePath
-getProjectDir projectName = io $ getAppUserDataDirectory projectName
-
--- | Return the full path to the config file
-getConfigFile :: (MonadIO m, Functor m) => String -> m FilePath
-getConfigFile projectName = (</> projectName ++ ".hs") <$> getProjectDir projectName
-
--- | Return the full path to the compiled config file (executable)
-getCustomExecutable :: (MonadIO m, Functor m) => String -> m FilePath
-getCustomExecutable projectName = (</> projectName ++ "-" ++ arch ++ "-" ++ os) <$> 
-                                  getProjectDir projectName
-
--- | Return the full path to the status file
-getStateFile :: (MonadIO m, Functor m) => String -> m FilePath
-getStateFile projectName = (</> "status") <$> getProjectDir projectName
-
--- | Return the full path to the errors file
-getErrorsFile :: (MonadIO m, Functor m) => String -> m FilePath
-getErrorsFile projectName = (</> projectName ++ ".errors") <$> getProjectDir projectName
-
rmfile ./src/HConf/Paths.hs
hunk ./src/HConf/Utils.hs 1
--- | Utility functions/instances for HConf for which a better place has not
--- been found yet.
-module HConf.Utils (shellWords, (+++), io) where
-
-import Control.Monad.Trans (MonadIO, liftIO)
-import Data.List (unfoldr)
-import System.Console.GetOpt (ArgDescr(..), OptDescr(..))
-
-(+++) :: Maybe [a] -> Maybe [a] -> Maybe [a]
-Nothing +++ x = x
-x +++ Nothing = x
-(Just x) +++ (Just y) = Just (x ++ y)
-
--- | Lift an IO action
-io :: MonadIO m => IO a -> m a
-io = liftIO
-
--- | Break up a string the way a shell breaks up a command into arguments.
--- Similar to 'words', but respects quotes and escaped spaces.  TODO: Verify
--- this function.
-
-shellWords :: String -> [String]
-shellWords = filter (not.null) . unfoldr maybeLex
-
--- Helper functions for shellWords
-
-maybeLex :: String -> Maybe (String,String)
-maybeLex "" = Nothing
-maybeLex s  = Just (shellLex s)
-
-shellLex :: String -> (String,String)
-shellLex ""          = ("","")
-shellLex (' ':s)     = ("",s)
-shellLex (c:s) | c `elem` ['\'','"']
-                     = quotes c s
-shellLex ('\\':x:s)  = (x:lexed,rest)       where (lexed,rest) = shellLex s
-shellLex (x:s)       = (x:lexed,rest)       where (lexed,rest) = shellLex s
-
-quotes :: Char -> String -> (String,String)
-quotes _ ""             = ("","")  -- Unterminated quote (an error really)
-quotes c (x:s) | x == c = ("",s)
-quotes c ('\\':s)       = backslash c s
-quotes c (x:s)          = (x:lexed,rest) where (lexed,rest) = quotes c s
-
-backslash :: Char -> String -> (String,String)
-backslash _ ""                = ("\\","") -- Trailing backslash?
-backslash c (x:s) | c == x    = (x:lexed, rest)
-                  | otherwise = ('\\' : x : lexed, rest)
-                    where (lexed,rest) = quotes c s
-
--- Functor instances for data types from System.Console.GetOpt
-
-instance Functor ArgDescr where
-    fmap f (NoArg x)    = NoArg (f x)
-    fmap f (ReqArg x s) = ReqArg (f . x) s
-    fmap f (OptArg x s) = OptArg (f . x) s
-
-instance Functor OptDescr where
-    fmap f (Option short long argdescr usage) =
-            Option short long (fmap f argdescr) usage
-
rmfile ./src/HConf/Utils.hs
rmdir ./src/HConf
hunk ./src/HConf.hs 1
-{- |
-
-HConf provides functions to manage an Xmonad-style configuration. By
-Xmonad-style configuration we mean the following scheme:
-
-When somebody installs our application, they install the executable, say,
-/usr/bin/app, as well as a library, say, libapp, that our application is based
-on. We will refer to that executable as the "default" executable, because it
-realizes a default, non-customized behaviour, referred to as the default
-configuration.
-
-If the user whishes to customize their installation, they create a configuration
-file ~/.app/app.hs, which is just a Haskell source file that imports our
-library and effectively implements a custom application. Thus it will typically
-look something like this:
-
-    module Main where
-
-    import App
-
-    main = defaultConfig { ... }
-
-(You may prefer to call this file a customization rather than a configuration,
-but this is only a technical distinction.)
-
-Now we want to save the user from the trouble to compile their configuration by
-hand and placing the resulting executable somewhere in their $PATH. That is why
-on every start of the default executable, we check if the user has put a
-configuration in place. If there is none, then we just continue the default
-application. If there is one, we compile it (unless no recompilation is needed)
-and launch the resulting "custom" executable. (Edge case: If there are errors
-on recompilation, we must take care that the user gets at the error message.
-For the case that they do miss it, we log it to ~/.app/app.errors.)
-
-Finally, we also provide a way to reload the configuration without restarting
-the application. This is useful if the user will keep adjusting their
-configuration, or if the application is designed to never exit (think of
-xmonad, a window manager). Restarting is realized by saving the application
-state to a file (~/.app/status), then calling the new custom executable with
-the --resume option. (FIXME: What if two instances of app try to access
-~/.app/status? Also, above, what if to instances of app try and access
-~/.app/app.errors?)
-
--}
-
-{-# LANGUAGE CPP #-}
-module HConf (getHConf, HConf(HConf), HConfParams(..), hconfOptions) where
-
-import Prelude hiding ( catch )
-import Control.OldException (catch, bracket)
-import Control.Applicative
-import Control.Monad.Reader
-import Data.List (intercalate)
-import GHC.Environment (getFullArgs)
-import System.IO
-import System.Info
-#ifndef mingw32_HOST_OS
-#ifdef darwin_HOST_OS
-import System.Posix.Process
-            (getProcessStatus,
-             forkProcess,
-             exitImmediately,
-             ProcessStatus(..))
-import qualified System.Posix.Process as SPP (executeFile)
-import System.Posix.Signals (raiseSignal, sigTSTP)
-#else
-import System.Posix.Process (executeFile)
-#endif
-import Control.OldException (handle)
-#endif
-import System.Process
-import System.Directory
-import System.Exit
-import System.Environment
-import System.Console.GetOpt
-import System.FilePath ((</>), takeDirectory)
-import qualified GHC.Paths
-import HConf.Paths
-import HConf.Utils
-
-import Paths_yi (getBinDir)
-
--- | Input to getHConf
-
-data HConfParams config state = HConfParams
- { projectName          :: String
-    -- ^ the project name ("app" in the example). The default executable
-    --   must be named the same as this, and be in the $PATH.
-    --   FIXME: This is true for a specific interpretation of @restart@,
-    --   cf. there.
- , ghcFlags             :: [String]
-    -- ^ additional options to pass to GHC on recompilation
- , recoverState         :: FilePath -> IO state
-    -- ^ how to recover state from a status file
- , saveState            :: FilePath -> state -> IO ()
-    -- ^ how to write state to a status file
- , showErrorsInConf     :: (String -> config -> config)
-    -- ^ how to report compilation errors to the user (the resulting
-    --   configuration will be passed to the main function)
- , realMain             :: config -> state -> IO ()
-    -- ^ The main function, used on resume, on compilation error, and
-    --   if the user didn't provide a customization. It takes a
-    --   configuration and an initial state.
- }
-
--- | Output of getHConf
-
-data HConf config state = HConf {
-      hConfMainMaster :: IO (),
-        -- ^ Attempts to compile the user configuration and launch it, and if
-        --   there is no user configuration, just continues with the default
-        --   configuration.
-      hConfMainSlave :: config -> IO (),
-        -- ^ Launches the application with a given configuration. Designed to be
-        --   used in the user configuration file.
-      hConfRestart :: state -> IO ()
- }
-
--- | Command-line options
-
-data HConfOption
-    = Action (IO () -> IO ())  -- ^ the argument IO () is the slave
-    | GhcFlags String          -- ^ options to pass to GHC on recompilation
-
-actionDescriptions :: HConfParams config state -> [OptDescr HConfOption]
-actionDescriptions par...@hconfparams {projectName = app} =
-  [ Option [] ["force-recompile"]
-           (NoArg . Action . const $ recompile params True >> return ())
-           ("Force recompile of custom " ++ app ++ " before starting")
-  , Option [] ["resume"]
-           (NoArg $ Action id)
-           ("Resume execution of " ++ app ++ " from previous state")
-  , Option [] ["recompile"]
-           (NoArg . Action . const $ recompileExit params)
-           ("Recompile custom " ++ app ++ " if required then exit")
-  ]
-
-ghcFlagsDescription :: OptDescr HConfOption
-ghcFlagsDescription = Option [] ["ghc-options"] (ReqArg GhcFlags "[flags]") "Flags to pass to GHC"
-
--- | Descriptions of the command-line options that are processed by HConf
-hconfOptions :: HConfParams config state -> [OptDescr HConfOption]
-hconfOptions params = actionDescriptions params ++ [ghcFlagsDescription]
-
--- | Find out what to do from the command-line arguments.
-getActions :: HConfParams config state -> IO [IO () -> IO ()]
-getActions params = do
-    args <- getArgs
-    let (opt_actions, _, _) = getOpt Permute (actionDescriptions params) args
-    return $ map (\(Action x) -> x) opt_actions
-
--- | Find out what additional options to pass to GHC (parse command-line
--- arguments for --ghc-options).
-getGhcFlags :: IO [String]
-getGhcFlags = do
-        args <- getArgs
-        let (opt_flags, _, _) = getOpt Permute [ghcFlagsDescription] args
-        return . shellWords . intercalate " " . map (\(GhcFlags x) -> x)
-               $ opt_flags
-
-getHConf :: HConfParams config state -- ^ general parameters
-        -> config                    -- ^ the (default) configuration
-        -> state                     -- ^ the initial/current application state
-        -> HConf config state
-getHConf params defaultConfig initialState = HConf
- { hConfMainMaster = mainMaster params defaultConfig initialState
- , hConfRestart    = \state -> restart params state
- , hConfMainSlave  = \config -> mainSlave params config initialState
- }
-
--------------------------------------------------------------------------
--- Procedures that do the real work.
--------------------------------------------------------------------------
-
--- | Recompile the user configuration if needed, print any eventual errors to
--- stderr, then exit.
-recompileExit :: HConfParams config state -> IO ()
-recompileExit params = recompile params False >>=
-    maybe exitSuccess (\err -> hPutStrLn stderr err >> exitFailure)
-
--- | The entry point into the application. Attempts to compile any custom main
--- for Project, and if it doesn't find one, just launches the default.
-mainMaster :: HConfParams config state -> config -> state -> IO ()
-mainMaster par...@hconfparams { showErrorsInConf = showErrors, realMain = main }
- defaultConfig initialState = do
-    actions <- getActions params
-    let launch = do
-        maybeErrors <- buildLaunch params
-        case maybeErrors of
-            Nothing     -> main defaultConfig initialState
-            Just errors -> main (showErrors errors defaultConfig) initialState
-    mapM_ ($ launch) actions
-    launch
-
--- | Attempt to restart the application by executing the
--- program @projectn...@. This function will never return.
-restart :: HConfParams config state -> state -> IO ()
-restart HConfParams { projectName = app, saveState = save } state = do
-#ifndef mingw32_HOST_OS
-        f <- getStateFile app
-        createDirectoryIfMissing True (takeDirectory f)
-        save f state
-        let args = ["--resume"]
-        executeFile app True args Nothing -- TODO: catch exceptions
-        -- run the master, who will take care of recompiling; handle errors, etc.
-#else
-        return ()
-#endif
-
--- | The configurable main, to be called from ~/.project/project.hs.
-mainSlave :: HConfParams config state -> config -> state -> IO ()
-mainSlave params userConfig initialState = do
-        args <- getArgs
-        state <- case args of
-            ["--resume"]   -> recover =<< getStateFile app
-            _              -> return initialState
-        main userConfig state
- where
-        HConfParams { projectName  = app
-                    , recoverState = recover
-                    , realMain     = main
-                    } = params
-
--- | 'recompile params force' recompiles ~\/.Project\/Project.hs when any of the
--- following apply:
---      * force is True
---      * the Project executable does not exist
---      * the Project executable is older than Project.hs
---      * the Project executable is older than the libraries from which it was built
---
--- The -i flag is used to restrict recompilation to the Project.hs file only.
---
--- Compilation errors (if any) are logged to
--- ~\/.Project\/Project.errors.  If GHC indicates failure with a
--- non-zero exit code; we read the errors and return them.
---
--- Returns the errors if there were any; otherwise Nothing
---
--- Errors can be returned in any of
--- these cases:
---   * ghc missing
---   * ~\/.Project\/Project.hs missing
---   * Project.hs fails to compile
---      ** wrong ghc in path (fails to compile)
---      ** type error, syntax error, ..
---   * Missing Project dependency packages
---
-recompile :: HConfParams config state -> Bool -> IO (Maybe String)
-recompile HConfParams {projectName = app, ghcFlags = flags} force = do
-    dir <- getProjectDir app
-    err <- getErrorsFile app
-    cabalBinDir <- getBinDir
-    let binn = app ++ "-"++arch++"-"++os
-        bin  = dir </> binn
-        base = dir </> app
-        src  = base ++ ".hs"
-        cabalBin = cabalBinDir </> "yi"
-    srcT <- getModTime src
-    binT <- getModTime bin
-    cabalBinT <- getModTime cabalBin
-    if (force || srcT > binT || cabalBinT > binT)
-      then do
-        if force
-            then putStrLn $ "Forcing recompile of custom " ++ app
-            else putStrLn $ "Recompiling custom " ++ app
-        status <- bracket (openFile err WriteMode) hClose $ \h -> do
-            -- note that since we checked for recompilation ourselves,
-            -- we disable ghc recompilaton checks.
-            flags' <- getGhcFlags
-            let allFlags = ["--make", app ++ ".hs", "-i", "-optl-s",
-                            "-fforce-recomp", "-v0", "-o",binn,"-threaded"
-                           ] ++ flags ++ flags'
-            waitForProcess =<< runProcess GHC.Paths.ghc allFlags (Just dir)
-                                          Nothing Nothing Nothing (Just h)
-            -- note that we use the ghc executable used to build Yi (through GHC.Paths).
-
-        -- now, if GHC fails, return the error message that was written to 'err':
-        if status /= ExitSuccess
-          then do
-            ghcErr <- readFile err
-            let msg = unlines $
-                    ["Error detected while loading " ++ app ++ " configuration file: " ++ src]
-                    ++ lines ghcErr ++ ["","Please check the file for errors."]
-            return $ Just msg
-          else return Nothing
-        else return Nothing
- where getModTime f = catch (Just <$> getModificationTime f) (const $ return Nothing)
-
-
--- | Launch the custom (slave) program.
-
--- Call @recompile False@
-
--- If there is a slave to run, this function does not return.
-
--- If there are errors and the function returns, they are returned in a string;
--- If there are errors and the slave is run, we pass the error file as an argument to it.
-
-buildLaunch :: HConfParams config state -> IO (Maybe String)
-buildLaunch par...@hconfparams{ projectName = app } = do
-    haveConfigFile <- doesFileExist =<< getConfigFile app
-    -- if there is no config file, then we return immediately /with no error/. This is
-    -- a normal situation: the user has not produced a config file.
-    if not haveConfigFile then return Nothing else do
-#ifndef mingw32_HOST_OS
-    errMsg <- recompile params False
-    executable_path <- getCustomExecutable app
-    args <- getFullArgs
-    args' <- case errMsg of
-               Nothing -> return args
-               Just _ -> do errFile <- getErrorsFile app
-                            return (args ++ [errFile])
-    putStrLn $ "Launching custom " ++ app ++ ": " ++ show executable_path
-    let launchFailed = return $ Just
-         ("Custom " ++ app
-          ++ " (" ++ show executable_path ++ ") "
-          ++ "could not be launched!\n") +++ errMsg
-
-    handle (\_exception -> return ())
-       (executeFile executable_path False args' Nothing)
-    -- if we reach this point then exec failed.
-    launchFailed
-
-#else
-    return Nothing
-#endif
-
-#ifdef darwin_HOST_OS
--- Darwin is odd or broken; Take your pick. According to:
---      http://uninformed.org/index.cgi?v=1&a=1&p=16
--- and
---      http://www.cherrypy.org/ticket/581
--- In order to get around a "Operation not supported" error on execv[e] it's
--- required to fork THEN execv[e]. - coconnor
-executeFile :: FilePath -> Bool -> [String] -> Maybe [(String,String)] -> IO ()
-executeFile cmd usePath args cmdEnv = do
-    child_pid <- forkProcess $ SPP.executeFile cmd usePath args cmdEnv
-    forever $ do
-        child_status <- getProcessStatus True True child_pid
-        case child_status of
-            Nothing -> error "executeFile: could not get child process status"
-            Just (Exited code) -> exitImmediately code
-            Just (Terminated _) -> exitImmediately ExitSuccess
-            Just (Stopped _) -> raiseSignal sigTSTP
-#endif
rmfile ./src/HConf.hs
hunk ./src/Main.hs 4
 -- Copyright (C) 2008 JP Bernardy
 -- Copyright (C) 2004 Don Stewart - http://www.cse.unsw.edu.au/~dons
 
--- | "Real" Frontend to the static binary. This is merely calling the driver (see
--- Yi.Boot ~> HConf)
+-- | "Real" Frontend to the static binary.
 
hunk ./src/Main.hs 6
-module Main ( main ) where
+module Main (main) where
 
 import Yi
 
hunk ./src/Main.hs 11
 main :: IO ()
-main = driver
+main = yi defaultConfig
+
hunk ./src/Yi/Boot.hs 2
 -- | Boot process of Yi, as an instanciation of HConf
-module Yi.Boot (driver, yi, reloadEditor, defaultHConfParams, projectName) where
+module Yi.Boot (yi) where
+
+import qualified Config.Dyre as Dyre
+import Config.Dyre.Relaunch
 
hunk ./src/Yi/Boot.hs 7
-import Control.Monad.State
-import qualified Data.Binary
-import HConf (HConf(HConf), getHConf)
-import qualified HConf
 import Yi.Config
hunk ./src/Yi/Boot.hs 8
-import Yi.Debug
-import Yi.Editor (newBufferE, Editor, withEditor)
-import Yi.Keymap (makeAction, withUI, YiM)
-import qualified Yi.UI.Common as UI
+import Yi.Editor
 import qualified Yi.Main
hunk ./src/Yi/Boot.hs 10
-import qualified Yi.Config.Default
-import qualified Data.Rope as R
-
-recoverState :: FilePath -> IO (Maybe Editor)
-recoverState = Data.Binary.decodeFile
-
-saveState :: FilePath -> Maybe Editor -> IO ()
-saveState = Data.Binary.encodeFile
-
-realMain :: Config -> Maybe Editor -> IO ()
-realMain staticConfig state = do
-          when (debugMode staticConfig) $ initDebug ".yi.dbg" 
-          -- initialize here so we can see debug messages early, if
-          -- the flag is set in the static configuration.
-          Yi.Main.main staticConfig state
 
hunk ./src/Yi/Boot.hs 11
-initState :: Maybe Editor
-initState = Nothing
+realMain :: Config -> IO ()
+realMain config = do
+    editor <- restoreBinaryState $ emptyEditor
+    Yi.Main.main config editor
 
hunk ./src/Yi/Boot.hs 16
-reloadEditor :: YiM ()
-reloadEditor = do
-    editor <- withEditor get
-    withUI (flip UI.end False)
-    liftIO $ restart (Just editor)
-
-driver :: IO ()
 yi :: Config -> IO ()
hunk ./src/Yi/Boot.hs 17
-restart :: Maybe Editor -> IO ()
-HConf driver yi restart = getHConf defaultHConfParams Yi.Config.Default.defaultConfig initState
-
-showErrorsInConf :: String -> Config -> Config
-showErrorsInConf errs conf 
-    = conf {startActions = [makeAction $ newBufferE (Left "errors") (R.fromString errs)]}
-
-projectName :: String
-projectName = "yi"
-
-defaultHConfParams :: HConf.HConfParams Config (Maybe Editor)
-defaultHConfParams = HConf.HConfParams
-    { HConf.projectName      = projectName
-    , HConf.recoverState     = recoverState
-    , HConf.saveState        = saveState
-    , HConf.showErrorsInConf = showErrorsInConf
-    , HConf.realMain         = realMain
-        -- monads-fd collide with mtl.
-        -- Could not find module `Control.Monad.Writer':
-        --       it was found in multiple packages: monads-fd-0.0.0.0 mtl-1.1.0.2
-    , HConf.ghcFlags         = ["-hide-package", "mtl"]
+yi = Dyre.wrapMain $ Dyre.defaultParams
+    { Dyre.projectName = "yi"
+    , Dyre.realMain    = realMain
     }
 
hunk ./src/Yi/Boot.hs-boot 1
-module Yi.Boot where
-
-import Yi.Config (Config)
-import Yi.Editor (Editor)
-import Yi.Keymap
-import qualified HConf
-
-reloadEditor :: YiM ()
-projectName :: String
-defaultHConfParams :: HConf.HConfParams Config (Maybe Editor)
rmfile ./src/Yi/Boot.hs-boot
hunk ./src/Yi/Config/Default.hs 8
                           defaultEmacsConfig, defaultVimConfig, defaultCuaConfig,
                           toVimStyleConfig, toEmacsStyleConfig, toCuaStyleConfig) where
 
-import {-# source #-} Yi.Boot (reloadEditor)
+-- import {-# source #-} Yi.Boot (reloadEditor)
 import Control.Monad (forever)
 import Data.Dynamic
 import Data.Either (rights)
hunk ./src/Yi/Config/Default.hs 110
     , ("regionOfB"              , box regionOfB)
     , ("regionOfPartB"          , box regionOfPartB)
     , ("regionOfPartNonEmptyB"  , box regionOfPartNonEmptyB)
-    , ("reloadEditor"           , box reloadEditor)
+    -- , ("reloadEditor"           , box reloadEditor)
     , ("reloadProjectE"         , box reloadProjectE)
     , ("replaceString"          , box replaceString)
     , ("revertE"                , box revertE)
hunk ./src/Yi/Config/Default.hs 225
              char 'e' ?>>  openCfg (extractTopKeymap Emacs.keymap),
              char 'v' ?>>  openCfg (extractTopKeymap Vim.keymapSet),
              char 'q' ?>>! quitEditor,
-             char 'r' ?>>! reloadEditor,
+             -- char 'r' ?>>! reloadEditor,
              char 'h' ?>>! configHelp
             ] 
             <|| (anyEvent >>! errorEditor "Keymap not defined, 'q' to quit, 'h' for help.")
hunk ./src/Yi/Core.hs 105
 -- | Start up the editor, setting any state with the user preferences
 -- and file names passed in, and turning on the UI
 --
-startEditor :: Config -> Maybe Editor -> IO ()
-startEditor cfg st = do
+startEditor :: Config -> Editor -> IO ()
+startEditor cfg editor = do
     let uiStart = startFrontEnd cfg
 
     logPutStrLn "Starting Core"
hunk ./src/Yi/Core.hs 112
 
     -- restore the old state
-    let initEditor = maybe emptyEditor id st
     -- Setting up the 1st window is a bit tricky because most functions assume there exists a "current window"
hunk ./src/Yi/Core.hs 113
-    newSt <- newMVar $ YiVar initEditor [] 1 M.empty
+    newSt <- newMVar $ YiVar editor [] 1 M.empty
     (ui, runYi) <- mdo let handler exception = runYi $ (errorEditor (show exception) >> refreshEditor)
                            inF  ev  = handle handler (runYi (dispatch ev))
                            outF acts = handle handler (runYi (interactive acts))
hunk ./src/Yi/Core.hs 117
-                       ui <- uiStart cfg inF outF initEditor
+                       ui <- uiStart cfg inF outF editor
                        let runYi f = runReaderT (runYiM f) yi
                            yi = Yi ui inF outF cfg newSt 
                        return (ui, runYi)
hunk ./src/Yi/Core.hs 122
   
-    runYi $
+    runYi $ do
+      postActions $ startActions cfg ++ [makeAction showErrors]
+      withEditor $ modA buffersA $ fmap $ recoverMode $ modeTable cfg
+      {-
       if isNothing st 
          then postActions $ startActions cfg ++ [makeAction showErrors] -- process options if booting for the first time
          else withEditor $ modA buffersA (fmap (recoverMode (modeTable cfg))) -- otherwise: recover the mode of buffers
hunk ./src/Yi/Core.hs 129
+      -}
 
     runYi refreshEditor
 
hunk ./src/Yi/Keymap/Vim.hs 63
 import Control.Monad.State hiding (mapM_, mapM, sequence)
 import Control.Arrow hiding (left, right)
 
-import {-# source #-} Yi.Boot
 import Yi.Command (cabalRun)
 import Yi.Core
 import Yi.Dired
hunk ./src/Yi/Keymap/Vim.hs 1502
      --    Needs to occur in another buffer
      --    fn ('!':f) = runProcessWithInput f []
 
-           fn "reload"     = reloadEditor >> return ()    -- not in vim
+           -- fn "reload"     = reloadEditor >> return ()    -- not in vim
 
            fn "redr"       = userForceRefresh
            fn "redraw"     = userForceRefresh
hunk ./src/Yi/Main.hs 9
 -- | This is the main module of Yi, called with configuration from the user.
 -- Here we mainly process command line arguments.
 
-module Yi.Main (main, projectName) where
+module Yi.Main (main) where
 
 import Prelude ()
hunk ./src/Yi/Main.hs 12
-import {-# SOURCE #-} Yi.Boot
+
+import Control.Monad.Error
+import Control.Monad.Trans.Error (Error(..))
+import Data.Char
+import Data.List (intersperse)
+import Distribution.Text (display)
+import System.Console.GetOpt
+import System.Environment (getArgs)
+import System.Exit
+#include "ghcconfig.h"
+
 import Yi.Config
 import Yi.Config.Default
 import Yi.Core
hunk ./src/Yi/Main.hs 27
 import Yi.Dired
-import HConf (hconfOptions)
-import qualified HConf
 import Paths_yi
hunk ./src/Yi/Main.hs 28
-import Distribution.Text (display)
+
 #ifdef TESTING
 import qualified TestSuite
 #endif
hunk ./src/Yi/Main.hs 37
 import HOC (withAutoreleasePool)
 #endif
 
-import Data.Char
-import Data.List                ( intersperse, map )
-import Control.Monad.Error
-import Control.Monad.Trans.Error (Error(..))
-import Control.Monad (foldM)
-import System.Console.GetOpt
-import System.Environment       ( getArgs )
-import System.Exit
-#include "ghcconfig.h"
-
 frontendNames :: [String]
 frontendNames = fmap fst' availableFrontends
   where fst' :: (a,UIBoot) -> a
hunk ./src/Yi/Main.hs 59
           | ConfigFile String
           | SelfCheck
           | Debug
-          | HConfOption
+          | DyreOption
 
 -- | List of editors for which we provide an emulation.
 editors :: [(String,Config -> Config)]
hunk ./src/Yi/Main.hs 80
     Option ['l']  ["line"]        (ReqArg LineNo "[num]") "Start on line number",
     Option []     ["as"]          (ReqArg EditorNm "[editor]")
         ("Start with editor keymap, where editor is one of:\n" ++
-                (concat . intersperse ", " . fmap fst) editors)
-    ] ++ (map (fmap $ const HConfOption) (hconfOptions defaultHConfParams))
+                (concat . intersperse ", " . fmap fst) editors),
+
+    -- Dyre options
+    Option []     ["force-reconf"] (NoArg undefined) "Force reconfiguration",
+    Option []     ["dyre-master-binary"] (ReqArg undefined "binary") "Master binary location"
+    ] -- ++ (map (\arg -> Option [] [arg] (NoArg DyreOption) "Dyre option") $ Dyre.Options.dyreArgs)
+      -- ++ (map (fmap $ const HConfOption) (hconfOptions defaultHConfParams))
 
 -- | usage string.
 usage, versinfo :: String
hunk ./src/Yi/Main.hs 90
-usage = usageInfo ("Usage: " ++ projectName ++ " [option...] [file]") options
+usage = usageInfo ("Usage: yi [option...] [file]") options
 
hunk ./src/Yi/Main.hs 92
-versinfo = projectName ++ ' ' : display version
+versinfo = "yi " ++ display version
 
 -- | Transform the config with options
 do_args :: Config -> [String] -> Either Err Config
hunk ./src/Yi/Main.hs 127
 -- application, and the real front end, in a sense. 'dynamic_main' calls
 -- this after setting preferences passed from the boot loader.
 --
-main :: Config -> Maybe Editor -> IO ()
+main :: Config -> Editor -> IO ()
 main cfg state = do
 #ifdef FRONTEND_COCOA
        withAutoreleasePool $ do
hunk ./yi.cabal 79
 flag testing
   Description: bake-in the self-checks
 
-library
-  hs-source-dirs: src
-  if flag(hacking)
-    exposed-modules:
-           Yi.Monad
-           -- the most insignificant module (with no dep) I can find.
-  else
-    exposed-modules:
-        Yi
-        Yi.Boot
-        Yi.Buffer
-        Yi.Buffer.Basic
-        Yi.Buffer.HighLevel
-        Yi.Buffer.Indent
-        Yi.Buffer.Normal
-        Yi.Buffer.Misc
-        Yi.Buffer.Region
-        Yi.Buffer.Undo
-        Yi.Command
-        Yi.Completion
-        Yi.Config
-        Yi.Config.Default
-        Yi.Core
-        Yi.Debug
-        Yi.Dired
-        Yi.Dynamic
-        Yi.Editor 
-        Yi.Eval
-        Yi.Event
-        Yi.File
-        Yi.History
-        Yi.Hoogle
-        Yi.IReader
-        Yi.IncrementalParse
-        Yi.Interact
-        Yi.Keymap
-        Yi.Keymap.Completion
-        Yi.Keymap.Cua
-        Yi.Keymap.Emacs
-        Yi.Keymap.Emacs.KillRing
-        Yi.Keymap.Emacs.Utils
-        Yi.Keymap.Keys
-        Yi.Keymap.Vim
-        Yi.KillRing
-        Yi.Lexer.Abella
-        Yi.Lexer.Alex
-        Yi.Lexer.Cabal
-        Yi.Lexer.Compilation
-        Yi.Lexer.C
-        Yi.Lexer.ObjectiveC
-        Yi.Lexer.Cplusplus
-        Yi.Lexer.Haskell
-        Yi.Lexer.JavaScript
-        Yi.Lexer.Latex 
-        Yi.Lexer.LiterateHaskell
-        Yi.Lexer.GNUMake
-        Yi.Lexer.OCaml
-        Yi.Lexer.Ott
-        Yi.Lexer.Perl
-        Yi.Lexer.Python
-        Yi.Lexer.Srmc
-        Yi.Lexer.SVNCommit
-        Yi.Lexer.Whitespace
-        Yi.Main
-        Yi.MiniBuffer
-        Yi.Misc
-        Yi.Mode.Abella
-        Yi.Mode.Buffers
-        Yi.Mode.Compilation
-        Yi.Mode.Haskell
-        Yi.Mode.Haskell.Dollarify
-        Yi.Mode.IReader
-        Yi.Mode.Interactive
-        Yi.Mode.JavaScript
-        Yi.Mode.Latex
-        Yi.Modes
-        Yi.Monad
-        Yi.Prelude
-        Yi.Process
-        Yi.Rectangle
-        Yi.Regex
-        Yi.Region
-        Yi.Snippets
-        Yi.Snippets.Haskell
-        Yi.Search
-        Yi.String
-        Yi.Style
-        Yi.Style.Library
-        Yi.Syntax
-        Yi.Syntax.BList
-        Yi.Syntax.Haskell
-        Yi.Syntax.JavaScript
-        Yi.Syntax.Latex
-        Yi.Syntax.Layout
-        Yi.Syntax.OnlineTree
-        Yi.Syntax.Paren
-        Yi.Syntax.Tree
-        Yi.Syntax.Strokes.Haskell
-        Yi.Tag
-        Yi.Templates
-        Yi.TextCompletion,
-        Yi.UI.Common
-        Yi.UI.Batch
-        Yi.UI.Utils
-        Yi.UI.TabBar
-        Yi.Verifier.JavaScript
-        Yi.Window
-        Yi.Char.Unicode
-
-    include-dirs:   src/Yi/Lexer
-    if flag (vty) && !os(windows)
-       cpp-options: -DFRONTEND_VTY
-       exposed-modules: Yi.UI.Vty
-       
-    if flag (pango)
-      cpp-options: -DFRONTEND_PANGO
-      exposed-modules: Yi.UI.Pango
-      other-modules: Yi.UI.Pango.ProjectTree
-                     Yi.UI.Pango.Utils
-      if flag(gnome)
-        cpp-options: -DGNOME_ENABLED
-        exposed-modules: Yi.UI.Pango.Gnome
-
-    if flag (cocoa)
-      cpp-options: -DFRONTEND_COCOA
-      exposed-modules: Yi.UI.Cocoa
-      other-modules: Yi.UI.Cocoa.Application
-                     Yi.UI.Cocoa.TextStorage
-                     Yi.UI.Cocoa.TextView
-                     Yi.UI.Cocoa.Utils
-
-    if flag (ghcInterpreter)
-      cpp-options: -DGHC_INTERPRETER
-    else
-      other-modules:
-         Yi.Interpreter
-
-    if flag (scion)
-      cpp-options: -DSCION
-      exposed-modules:  Yi.Scion
-
-    if flag (ghcAPI)
-      cpp-options: -DGHC_API
-
-      exposed-modules:  Yi.Mode.Shim
-      other-modules:
-        Shim.SHM, Shim.SessionMonad, Shim.Hsinfo, Shim.GhcCompat,
-        Shim.ExprSearch, Yi.GHC
-
-    other-modules:
-        Paths_yi,
-        
-        -- "Internal" modules that the user better not see.
-        HConf
-        HConf.Utils
-        HConf.Paths
-        Yi.Buffer.Implementation
-        Data.Prototype
-
-        -- Should probably be split out to another package.
-        Data.Rope
-        Data.DelayList
-        Data.Trie
-        Parser.Incremental
-        Shim.CabalInfo
-        Shim.Utils 
-        Shim.ProjectContent
-        System.FriendlyPath
-
-        -- Broken.
---                Yi.Keymap.Ee,
---                Yi.Keymap.Gwern,
---                Yi.Keymap.Joe,
---                Yi.Keymap.Mg,
---                Yi.Keymap.Nano,
---                Yi.Keymap.Vi,
-
 executable parserTest
   hs-source-dirs: src
   if !flag(testing)
hunk ./yi.cabal 127
                 Yi.Syntax.Tree
 
                 Yi.Mode.Interactive
-
-                HConf
-                HConf.Utils
-                HConf.Paths
         include-dirs:   src/Yi/Lexer
 
 executable yi
hunk ./yi.cabal 147
         build-depends: data-accessor-monads-fd == 0.2.*
         build-depends: data-accessor-template == 0.2.*
         build-depends: dlist >=0.4.1
+        build-depends: dyre >= 0.5
         build-depends: filepath>=1.1 && <1.2
         build-depends: fingertree >= 0 && <0.1
         build-depends: ghc-paths ==0.1.*
hunk ./yi.cabal 314
            Yi.KillRing
            Yi.IncrementalParse
            Yi.UI.Utils
-           HConf
-           HConf.Utils
-           HConf.Paths
            -- Should probably be split out to another package.
            Data.DelayList
 

Context:

[JS: Fixing Eq instance bug.
deniz.a.m.do...@gmail.com**20090805144840
 Ignore-this: ff39ce625064620d6a1a3af163c3d64d
] 
[JS: Adding "typeof" support and fixing "if" stroking.
deniz.a.m.do...@gmail.com**20090608123516
 Ignore-this: 135f71bef169ed0082f215283588f5c6
] 
[JS: Fixing some error highlighting.
deniz.a.m.do...@gmail.com**20090607150633
 Ignore-this: 54ebf9a3a88852c4fc234b93e42c82d6
 
 Due to lack of proper testing, some errors were not highlighted. There may be
 more errors that are not highlighted, but this is all I have time with for now.
] 
[Fix examples/yi-simple.hs
Jeff Wheeler <jeffwhee...@gmail.com>**20090805150935
 Ignore-this: 3a69c18df58cf16300b677596efe65f4
] 
[Add functions to navigate trees based on paths
jeanphilippe.berna...@gmail.com**20090804182036
 Ignore-this: e68e11a1a68a2ebcd4d87c83a5edea6a
] 
[fix includedRegion
jeanphilippe.berna...@gmail.com**20090804181751
 Ignore-this: 211cb7c0179260e79a6f3bebedf8f0fe
] 
[Syntax/Haskell.hs: Removed unnecessary code
anders...@gmail.com**20090804170049
 Ignore-this: 5a6c6eaa0241133388a68bd002e891dc
] 
[Syntax/Haskell.hs: Fix bug that was introduced in last patch
anders...@gmail.com**20090804164547
 Ignore-this: d48cc9319555101ea8969517e02d1084
 Last patch didn't allow comments after the closing brace in
 data declaration records.
] 
[Syntax/Haskell.hs: Fixed a bugg where comments were allowed in several places in a data declaration
anders...@gmail.com**20090804154238
 Ignore-this: 324075dad772bc9c801e43636d932f88
] 
[Syntax/Haskell.hs: fix bugg in explicit structured do blocks
anders...@gmail.com**20090804145306
 Ignore-this: 49e1493713c6407528a369d36584a28c
] 
[Fix saving files that don't exist yet
Robin Green <gree...@greenrd.org>**20090731091545
 Ignore-this: 14938e3386a5c2bb0689c401f84a6c9b
] 
[work towards some utility functions to find the most relevant node to a given window
jeanphilippe.berna...@gmail.com**20090802113925
 Ignore-this: 6977af749ec47bf1ddac1db5ccc350c9
] 
[support type signatures for multiple ids at once
jeanphilippe.berna...@gmail.com**20090731135859
 Ignore-this: ba0b88fda7ee396e07c8b8a85901fcea
] 
[Eliminate useless parts of the datatype
jeanphilippe.berna...@gmail.com**20090731131337
 Ignore-this: 8b98f51b265e5e2d5b4c019cfa4744ad
] 
[simplify field declarations
jeanphilippe.berna...@gmail.com**20090731125758
 Ignore-this: b4c550fe35065e750c6fb94ee0c650fd
] 
[new rules for type declaration / equation declaration only
jeanphilippe.berna...@gmail.com**20090731125619
 Ignore-this: d232bfe9d2f2d8535fb57f5f9e8d16cb
] 
[simplify "type" declarations
jeanphilippe.berna...@gmail.com**20090731101447
 Ignore-this: 9ce257bcfca7e9196ef356bdfa31d110
] 
[simplify pData and improve support of GADT
jeanphilippe.berna...@gmail.com**20090731100725
 Ignore-this: a785cbafd22d2ff397d159875d9ca6ec
] 
[generalize and simplify class and instance declarations
jeanphilippe.berna...@gmail.com**20090730220426
 Ignore-this: ce61e808ebb1c3ba82405610dfa78342
] 
[define a function for "bare" token parsing (without comments)
jeanphilippe.berna...@gmail.com**20090730214854
 Ignore-this: 5648d78f6e78961c5ec9f3212d11f2c8
  -> use it where suitable
] 
[Simplify pGuard
jeanphilippe.berna...@gmail.com**20090730211615
 Ignore-this: f6092e6fb3949d474ccabe2b7d4ad333
] 
[simplify pFunRHS
jeanphilippe.berna...@gmail.com**20090730210420
 Ignore-this: ae304cbeac6a93955cfcf2891c964c55
] 
[=> are ok in type expressions (contexts)
jeanphilippe.berna...@gmail.com**20090730210019
 Ignore-this: 1afb9ac3eb9d689f2e1f7d046dc0c639
] 
[simplify where blocks
jeanphilippe.berna...@gmail.com**20090730205938
 Ignore-this: 2e088e4c84b9287724e790fdbbce7302
] 
[cleanups
jeanphilippe.berna...@gmail.com**20090730143603
 Ignore-this: b9ce6fbf628e393e58168c15f0855739
] 
[simplify pFunDecl
jeanphilippe.berna...@gmail.com**20090730142650
 Ignore-this: 4c00be1932b55fd9d46d599cc2fdec6d
] 
[add support for type expressions
jeanphilippe.berna...@gmail.com**20090730134720
 Ignore-this: 92de0693f77d59d5c3dedf31d2026766
] 
[separate patterns and expressions
jeanphilippe.berna...@gmail.com**20090730115422
 Ignore-this: 96646209eb90d2c660f4b82f21e69766
] 
[cleanups
jeanphilippe.berna...@gmail.com**20090730081036
 Ignore-this: e34e6869758293bea3926462f3f10740
] 
[Add a rule for Lambda
jeanphilippe.berna...@gmail.com**20090729223826
 Ignore-this: 35fb3ca734551a198af932191c9c7060
] 
[be even more precise about what is noise
jeanphilippe.berna...@gmail.com**20090729221527
 Ignore-this: 7f6629b935af5c1f50ea6bec885e5f43
] 
[make parser test more lazy
jeanphilippe.berna...@gmail.com**20090729215733
 Ignore-this: fa59721b640540722a81d47bea4fc7b2
] 
[Be more precise with what is acceptble as "noise" or not
jeanphilippe.berna...@gmail.com**20090729211655
 Ignore-this: d7e3117a5c81550a953c240a986b2385
] 
[More precise definition of pOf, RHS and cleanups
jeanphilippe.berna...@gmail.com**20090729204812
 Ignore-this: 9a07dfa516657ea99c9741a4f4e41c9c
] 
[comments
jeanphilippe.berna...@gmail.com**20090729183150
 Ignore-this: 7f297536f572451ce21139de9d65df58
] 
[pBlock: support braces
jeanphilippe.berna...@gmail.com**20090729173846
 Ignore-this: 37edc6939928f8ebff2dedad65e1dbf7
] 
[push code in pBlock
jeanphilippe.berna...@gmail.com**20090729172847
 Ignore-this: f68f653b92a9ea71aa7db5fd5f822447
] 
[Add rules for Do and Of
jeanphilippe.berna...@gmail.com**20090729172305
 Ignore-this: ccd4323b8732b2bba40c3e85bbec389f
] 
[Update Makefile (src/ and `build' target for run-inplace)
Jeff Wheeler <jeffwhee...@community.haskell.org>**20090730021443
 Ignore-this: e20ac749846b4b3693116a1ce0af17b5
] 
[renamings, simplify the structure of expressions
jeanphilippe.berna...@gmail.com**20090729150250
 Ignore-this: f185c215051d14f2cda5e2c827efa8bf
] 
[style
jeanphilippe.berna...@gmail.com**20090729143358
 Ignore-this: 9a4f7c3967f2103e0aa866eb3acf02a0
] 
[Preserve permissions
Robin Green <gree...@greenrd.org>**20090728001241
 Ignore-this: a11043e7cd39b82fb8a0435558fbdf
 Fixes bug 281
] 
[improved rule for "let"
jeanphilippe.berna...@gmail.com**20090727122849
 Ignore-this: 4a6629914f28a1d6f7fdb31fa116120c
] 
[style
jeanphilippe.berna...@gmail.com**20090727122840
 Ignore-this: d415bc6bea1c5abbf8e2e93bcb31fd5a
] 
[comments
jeanphilippe.berna...@gmail.com**20090727115657
 Ignore-this: 85eddc0ce96eac04f50d4f9171373495
] 
[one more test case
jeanphilippe.berna...@gmail.com**20090727101357
 Ignore-this: dca46467ad8eb3fe643969ec45434bd7
] 
[More style
jeanphilippe.berna...@gmail.com**20090727101347
 Ignore-this: 2c8acb5ff408eef4c5524bcd1fb5292f
] 
[properly handle set of extra recognized symbols
jeanphilippe.berna...@gmail.com**20090727101202
 Ignore-this: 4bbeed8fa89060d8222cc79aaf9cc366
] 
[style
jeanphilippe.berna...@gmail.com**20090727094938
 Ignore-this: 14d2c01497e0d9f595f01183c9fc9c02
] 
[In is always properly recognized
jeanphilippe.berna...@gmail.com**20090727094912
 Ignore-this: 4d024aa05b07ab95a149091b0d9bf7a4
] 
[Move tests to where they should be; add new test case
jeanphilippe.berna...@gmail.com**20090727094404
 Ignore-this: e093d34bb29fd75a51d66ef6068ea8bb
] 
[The set of "added recognized symbols" can be used in isNoiseErr too
jeanphilippe.berna...@gmail.com**20090726201542
 Ignore-this: a6168a9b0ad0ee0d9474bd1b1bffbc02
] 
[Equal is not properly recognized in record declarations
jeanphilippe.berna...@gmail.com**20090726201226
 Ignore-this: cd6ca20d67e831ec576ba819b35e01dc
 
 As of this patch, there is an error in parsing OnlineTree.hs
] 
[Pipe is normally not a recoverable symbol
jeanphilippe.berna...@gmail.com**20090726195627
 Ignore-this: f5d115de9ce5dce1b937710fdf4cd25a
] 
[simplify isNoiseErr
jeanphilippe.berna...@gmail.com**20090726195326
 Ignore-this: e64e896c3401adb2feb2b18e108d4280
] 
['{' is not noise
jeanphilippe.berna...@gmail.com**20090726195108
 Ignore-this: 50ad62a8cabe23d7032800079dff5119
] 
[renamings
jeanphilippe.berna...@gmail.com**20090726194951
 Ignore-this: cb58110c4c77afc9a5940d861edc413d
] 
[comment
jeanphilippe.berna...@gmail.com**20090726194648
 Ignore-this: f435323a3a956b5d2f3560a8e2f39352
] 
[use the endBlock name if possible
jeanphilippe.berna...@gmail.com**20090726194412
 Ignore-this: 1e586405922ba85141869025777ebf3d
] 
[Syntax/Haskell.hs: Removed the error lists that was sent around
ande...@student.chalmers.se**20090726162902
 Ignore-this: a1ca2964c2c4ca7aca6b4f6102f9fa76
] 
[comment left-factorisation of type and equation
jeanphilippe.berna...@gmail.com**20090726152954
 Ignore-this: e20e8f2d4828128de7779635e5dc476
] 
[Properly classify all reserved operators
jeanphilippe.berna...@gmail.com**20090726152917
 Ignore-this: d860f37687bc82817a67bbb7a8bab974
] 
[Syntax/Haskell.hs: pFunLHS is now called pFunDecl
ande...@student.chalmers.se**20090726124315
 Ignore-this: b86a96e804a054bcc63251db700f125a
] 
[Fix copyright notice and add comments
jeanphilippe.berna...@gmail.com**20090726122521
 Ignore-this: ad993e80c48321e8a1f52e97fd8a974
] 
[remove dead duplicated code
jeanphilippe.berna...@gmail.com**20090726120848
 Ignore-this: c1533705de6aae1aef141902ffde470f
] 
[update pointedlist minimum version
jfo...@gmail.com**20090722145832] 
[Syntax/Haskell.hs: cleanup
ande...@student.chalmers.se**20090716171425
 Ignore-this: f92dc85a1dd3fe46835e4f87dbff9a6d
] 
[Yi.Scion -Wall
Jeff Wheeler <jeffwhee...@gmail.com>**20090720220649
 Ignore-this: 40bc67b9009310e78a7247219c3f8288
] 
[Use cautious-file to save files
Robin Green <gree...@greenrd.org>**20090720054854
 Ignore-this: b05a76ae0e4384df5f0cd05b19c6f2a0
 The cautious-file package tries to reduce the risk of data loss
] 
[scion: experiments
jeanphilippe.berna...@gmail.com**20090719094610
   * Copied stuff from the Server to find things; the functionality to get info
     about the stuff on the cursor is better.
   * Tried cabal load; failed.
] 
[Makefile: add ghc package to interactive rule
jeanphilippe.berna...@gmail.com**20090719094544] 
[cleanup published actions
jeanphilippe.berna...@gmail.com**20090719094502] 
[expose Scion stuff if available
jeanphilippe.berna...@gmail.com**20090719094417] 
[Don't show mini buffer titles for tabs or windows
Jeff Wheeler <jeffwhee...@gmail.com>**20090719025509
 Ignore-this: f13b34599c9545d22e5e9d60f47b9e09
] 
[Use a proper Gtk Statusbar, rather than just a label
Jeff Wheeler <jeffwhee...@gmail.com>**20090718223540
 Ignore-this: 434a6f538c2035aca2d16995ef609692
] 
[Add doc/monads.html, which documents how to run actions in different contexts
Jeff Wheeler <jeffwhee...@gmail.com>**20090718221618
 Ignore-this: 75b3a6f0a2b1349f6e2c4129c17339fa
 
 I'd love if somebody with a better understanding of these monads could mark out which cases are impossible.
] 
[Char.Unicode: add superscripts
Nicolas Pouillard <nicolas.pouill...@gmail.com>**20090718175401
 Ignore-this: 5d6b5ce01b91364604bd02b27231e191
] 
[Move haskell source files into src/
Jeff Wheeler <jeffwhee...@gmail.com>**20090718151803
 Ignore-this: 397bcfe14a6774159d408b76ed67f74c
 
 I think this greatly simplifies the structure of the base directory, since we had so many source directories in the root.
] 
[Store "inserting" attribute in buffer's Attributes
Jeff Wheeler <jeffwhee...@gmail.com>**20090718074250
 Ignore-this: cb3a7bef598aff38f408bda712863b85
] 
[Small -Wall
Jeff Wheeler <jeffwhee...@gmail.com>**20090718074226
 Ignore-this: a4db1393555aeb3d87a84e7c137d1db6
] 
[Support tab abbreviation in Pango
Jeff Wheeler <jeffwhee...@gmail.com>**20090718055856
 Ignore-this: 4c71ae4cedff8d2e8b35de2d05e43390
] 
[Add brief documentation for Yi.Scion.functionType
Jeff Wheeler <jeffwhee...@gmail.com>**20090718055821
 Ignore-this: af358fe0b3156e7fd0503af23133ac53
] 
[Hide left pane entirely until Scion integration is possible
Jeff Wheeler <jeffwhee...@gmail.com>**20090718053340
 Ignore-this: 943257258e7ed7c0c128aa072c050067
] 
[Respect configs to not line-wrap in Pango (adds horizontal scrollbar support)
Jeff Wheeler <jeffwhee...@gmail.com>**20090718043917
 Ignore-this: f85d431996d7941c0eedcc89401f02ab
] 
[Correctly show modeline in Pango (and small -Wall)
Jeff Wheeler <jeffwhee...@gmail.com>**20090718030411
 Ignore-this: 14c66d8a1d6246ea80600970f0e4dedc
] 
[Show modeline in Pango
Jeff Wheeler <jeffwhee...@gmail.com>**20090718022849
 Ignore-this: b73c2b34b677ded1c77a60908e28a58d
] 
[Fix Yi.Config.Default to use functionType scion action by default
Jeff Wheeler <jeffwhee...@gmail.com>**20090718012444
 Ignore-this: d36a0c838d0b0ed9ee1c9fba40a50c4f
] 
[Cleanup in Yi.Scion (and yi.cabal)
Jeff Wheeler <jeffwhee...@gmail.com>**20090717234111
 Ignore-this: ebc69031d112f37be61ab771c597da2a
] 
[Begin Yi.Snippets.Haskell
Jeff Wheeler <jeffwhee...@gmail.com>**20090717223905
 Ignore-this: df637f5aa30b6b11d2af9aecd42484d7
 
 As far as I can tell, dependent bits don't currently work. Is this correct?
] 
[Update my config, based on Yi.Scion
Jeff Wheeler <jeffwhee...@gmail.com>**20090717223116
 Ignore-this: c5aa2626985e47b3b92ecc85d0c5ed25
] 
[Integrate Jeff's scion bindings
jeanphilippe.berna...@gmail.com**20090717210028
 Ignore-this: 846107b07de052d21fea418291d62af7
] 
[add Jeff's config
jeanphilippe.berna...@gmail.com**20090717202115
 Ignore-this: 156fbfba29496d7efc760aed13ce1c4c
] 
[grepFind: fix argument order
jeanphilippe.berna...@gmail.com**20090716094545
 Ignore-this: 43614cb6a300dec516482cd39306ec6a
] 
[Syntax/Haskell.hs: Small improvements
ande...@student.chalmers.se**20090715095310
 Ignore-this: a6846c241b670efb5cc3cc3b0779aa8f
] 
[TAG 0.6.1
Jeff Wheeler <jeffwhee...@gmail.com>**20090714203551
 Ignore-this: 3a5417411f2772b433887f3c80c44627
] 
Patch bundle hash:
f3d7044f85f2c5401838ca5e64e70249743d4faf

Reply via email to