[Xmonad] a safer ghci prompt

Andrea Rossato mailing_list at istitutocolli.org
Mon Sep 3 08:54:36 EDT 2007


On Thu, Aug 30, 2007 at 08:21:41PM +0200, Andrea Rossato wrote:
> Hi,

Hi,

this should be a prompt that doesn't crash, whatever your what you
write (I hope...,-). It uses heval, an external application that comes
with xmonad-utils:

http://gorgias.mine.nu/repos/xmonad-utils/src/Heval.hs
or
darcs get http://gorgias.mine.nu/repos/xmonad-utils/

I'm not submitting it as a patch yet because I want to work on the
output, especially in case of errors. Right now there are some issues
with that.

Hope you'll enjoy.

Andrea

ps: I used Eval/RunPlugs (lambdabot), plugs, hs-plugins and,
obviously, GHC code and commentary as examples to follow. Hope I
followed them correctly.
-------------- next part --------------
-----------------------------------------------------------------------------
-- |
-- Module      :  XMonadContrib.GhcPrompt
-- Copyright   :  (C) 2007 Andrea Rossato
-- License     :  BSD3
-- 
-- Maintainer  :  andrea.rossato at 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


More information about the Xmonad mailing list