----------------------------------------------------------------------------- -- | -- Module : XMonadContrib.GhcPrompt -- Copyright : (C) 2007 Andrea Rossato -- License : BSD3 -- -- Maintainer : andrea.rossato@unibz.it -- Stability : unstable -- Portability : unportable -- -- A ssh prompt for XMonad -- ----------------------------------------------------------------------------- module XMonadContrib.GhcPrompt ( -- * Usage -- $usage ghcPrompt ) where import Data.List import XMonad import XMonadContrib.XPrompt import Control.Concurrent import Control.Exception import System.Process import System.IO import System.Exit -- $usage -- 1. In Config.hs add: -- -- > import XMonadContrib.XPrompt -- > import XMonadContrib.GhcPrompt -- -- 2. In your keybindings add something like: -- -- > , ((modMask .|. controlMask, xK_h), ghcPrompt defaultXPConfig) -- -- You also need heval, which comes with xmonad-utils: -- darcs get http://gorgias.mine.nu/repos/xmonad-utils/ data Ghc = Ghc instance XPrompt Ghc where showXPrompt Ghc = "Eval: " ghcPrompt :: XPConfig -> X () ghcPrompt c = do mkXPrompt Ghc c (mkComplFunFromList []) (ghc c []) type Expr = String ghc :: XPConfig -> [Expr] -> String -> X () ghc conf exps s | s == ":quit" || s == ":q" || s == [] = return () | otherwise = do let exps' = exps ++ [s] run = "heval" (i,o,e,p) <- io $ runInteractiveCommand $ run io $ hPutStr i (show exps') >> hClose i exit <- io $ waitForProcess p case exit of ExitSuccess -> do out <- io $ hGetContents o -- get err and out oMVar <- io $ newEmptyMVar io $ forkIO $ evaluate (length out) >> putMVar oMVar () -- wait io $ takeMVar oMVar io $ mapM_ hClose [o,e] mkXPrompt Ghc conf (\_ -> return $ formatResult out) (ghc conf (sanitizeHistory exps')) _ -> do io $ mapM_ hClose [i,o,e] mkXPrompt Ghc conf (mkComplFunFromList []) (ghc conf (sanitizeHistory exps')) formatResult :: String -> [String] formatResult str = lastLine : mkLines str where lastLine = take 120 $ repeat ' ' mkLines str = lines str sanitizeHistory :: [String] -> [String] sanitizeHistory e | "let " `isPrefixOf` (last e) = e | otherwise = init e