[Xmonad] a ghci prompt for xmonad
Andrea Rossato
mailing_list at istitutocolli.org
Thu Aug 30 09:24:39 EDT 2007
Hi,
I wanted to write this prompt from the very beginning. A prompt to
evaluate Haskell expressions...
At first I couldn't get hs-plugins to compile. Then I could compile
hs-plugin but I thought it was quite a difficult requirement for such
a prompt. I knew about that mysterious ghc-api, something to come in
the future... NO! GHC-API is there since 6.5, and can be easily used.
So, here's the prompt. It's just the a proof of concept, right now. It
uses the completions window to display the result and the ghc-api is
linked from XMonad itself, which makes the xmonad binary a huge file.
A lot of memory consumption is the obvious consequence.
I have a small program that can evaluate expressions from outside of
xmonad, but I'm not able to run it interactively from xmonad:
http://www.haskell.org/pipermail/haskell-cafe/2007-August/031167.html
I know how to compile Haskell code at runtime but I don't know how to
run a process interactively...:(
If you can help....
Follow the instruction of the attached modules (to be saved in
XMonadContrib. BE CAREFUL and edit ghcPath to fit your system
environment otherwise the prompt and XMonad will crash!!!
(the is one of the many reasons I want an external application to run
the statements!)
Hope you'll enjoy.
Andrea
ps: no error reports for the time being. I repeat it: this is just a
proof of concept. We need the external evaluator to work interactively
with the prompt.
-------------- 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.Dynamic
import Data.List
import Data.Maybe
import XMonad
import XMonadContrib.XPrompt
import GHC
import DynFlags
import PackageConfig
-- $usage
-- 1. In xmonad.cabal change:
--
-- > build-depends: base>=2.0, X11>=1.2.1, X11-extras>=0.2, mtl>=1.0, unix>=1.0
--
-- to
--
-- > build-depends: base>=2.0, X11>=1.2.1, X11-extras>=0.2, mtl>=1.0, unix>=1.0, ghc>= 6.6
--
-- 2. In Config.hs add:
--
-- > import XMonadContrib.XPrompt
-- > import XMonadContrib.GhcPrompt
--
-- 3. In your keybindings add something like:
--
-- > , ((modMask .|. controlMask, xK_h), ghcPrompt defaultXPConfig)
--
-- 4. edit the ghcPath below to fit your system!
-- EDIT TO FIR YOUR SYSTEM!!
ghcPath :: String
ghcPath = "/usr/lib/ghc-6.6.1"
data Ghc = Ghc
instance XPrompt Ghc where
showXPrompt Ghc = "Eval: "
ghcPrompt :: XPConfig -> X ()
ghcPrompt conf = do
ses <- io initSession
mkXPrompt Ghc conf (mkComplFunFromList []) (ghc conf ses)
ghc :: XPConfig -> Session -> String -> X ()
ghc conf ses s
-- exit
| s == ":quit" || s == ":q" || s == [] = return ()
-- "let: " update session
| "let " `isPrefixOf` s = do
io $ runStmt ses s
mkXPrompt Ghc conf (mkComplFunFromList []) (ghc conf ses)
-- something to eval
| otherwise = do
res <- io $ dynCompileExpr ses ("show $ "++ s)
case res of
Just x -> do
let res' = fromDynamic x :: Maybe String
io $ putStrLn (show res')
mkXPrompt Ghc conf (\_ -> return [fromMaybe "" res']) (ghc conf ses)
_ -> do io $ putStrLn "fallito"
mkXPrompt Ghc conf (\_ -> return ["failed"]) (ghc conf ses)
initSession :: IO Session
initSession = do --defaultErrorHandler defaultDynFlags $ do
session <- newSession Interactive (Just ghcPath)
setSessionDynFlags session =<< getSessionDynFlags session
setContext session [] [mkModule (stringToPackageId "base") (mkModuleName "Prelude")]
return session
More information about the Xmonad
mailing list