{-# LANGUAGE CPP #-} {-# LANGUAGE OverloadedStrings #-} {-# OPTIONS_HADDOCK show-extensions #-} -- | -- Module : Yi.Boot -- License : GPL-2 -- Maintainer : yi-devel@googlegroups.com -- Stability : experimental -- Portability : portable -- -- Boot process of Yi. -- -- Uses Dyre to implement the XMonad-style dynamic reconfiguration. module Yi.Boot (configMain, yi, yiDriver, yiDriver', reload) where import qualified Config.Dyre as Dyre import qualified Config.Dyre.Options as Dyre import qualified Config.Dyre.Params as Dyre import Config.Dyre.Relaunch import Control.Monad.State hiding (modify, get) import Lens.Micro.Platform import Data.Text () import qualified Data.Text.IO as T (putStrLn) import System.Environment import System.Exit import Yi.Boot.Internal import Yi.Buffer.Misc (BufferId(..)) import Yi.Config import Yi.Config.Simple.Types import Yi.Editor import Yi.Keymap import Yi.Main import Yi.Option (OptionError(..)) import Yi.Paths (getCustomConfigPath) import Yi.Rope (fromString) -- | Once the custom yi is compiled this restores the editor state (if -- requested) then proceeds to run the editor. realMain :: (Config, ConsoleConfig) -> IO () realMain configs = restoreBinaryState Nothing >>= main configs -- | If the custom yi compile produces errors or warnings then the -- messages are presented as a separate activity in the editor. -- -- The use of a separate activity prevents any other initial actions -- from immediately masking the output. showErrorsInConf :: (Config, ConsoleConfig) -> String -> (Config, ConsoleConfig) showErrorsInConf c errs = c & _1 . initialActionsA %~ (makeAction openErrBuf :) where openErrBuf = splitE >> newBufferE (MemBuffer "*errors*") (fromString errs) -- | Starts with the given initial config, makes the described -- modifications, then starts yi. configMain :: Config -> ConfigM () -> IO () configMain c m = yi =<< execStateT (runConfigM m) c -- | Handy alias for 'yiDriver'. yi :: Config -> IO () yi = yiDriver -- | Called from the yi built with the user's configuration. Does not -- ignore unknown arguments. yiDriver :: Config -> IO () yiDriver = yiDriver' False -- | Used by both the yi executable and the custom yi that is built -- from the user's configuration. The yi executable uses a default -- config. yiDriver' :: Bool -> Config -> IO () yiDriver' ignoreUnknownArgs cfg = do args <- Dyre.withDyreOptions Dyre.defaultParams getArgs -- we do the arg processing before dyre, so we can extract -- '--ghc-option=' and '--help' and so on. case do_args ignoreUnknownArgs cfg args of Left (OptionError err code) -> T.putStrLn err >> exitWith code Right (finalCfg, cfgcon) -> do modules <- getCustomConfigPath (userConfigDir cfgcon) "modules" let yiParams = Dyre.defaultParams { Dyre.projectName = "yi" , Dyre.realMain = realMain , Dyre.showError = showErrorsInConf , Dyre.configDir = Just $ userConfigDir cfgcon , Dyre.ghcOpts = ["-threaded", "-O2", "-rtsopts"] ++ ["-i" ++ modules] ++ profilingParams ++ ghcOptions cfgcon , Dyre.includeCurrentDirectory = False , Dyre.rtsOptsHandling = Dyre.RTSAppend ["-I5"] } Dyre.wrapMain yiParams (finalCfg, cfgcon) -- | CPP-guarded profiling params. profilingParams :: [String] profilingParams = #ifdef EVENTLOG ["-eventlog", "-rtsopts"] ++ #endif #ifdef PROFILING ["-prof", "-auto-all", "-rtsopts" , "-osuf=p_o", "-hisuf=p_hi"] ++ #endif []