aboutsummaryrefslogblamecommitdiffstats
path: root/SshPrompt.hs
blob: 5bee3b6abf80d48c852f2fe706f3750d1769e30c (plain) (tree)






















                                                                             
                              



































                                                                                    
-----------------------------------------------------------------------------
-- |
-- Module      :  XMonadContrib.SshPrompt
-- Copyright   :  (C) 2007 Andrea Rossato
-- License     :  BSD3
-- 
-- Maintainer  :  andrea.rossato@unibz.it
-- Stability   :  unstable
-- Portability :  unportable
--
-- A ssh prompt for XMonad
--
-----------------------------------------------------------------------------

module XMonadContrib.SshPrompt (
                             -- * Usage
                             -- $usage
                             sshPrompt
                              ) where
{-
usage:
1. In Config.hs add:

> import XMonadContrib.XPrompt
> import XMonadContrib.SshPrompt

3. In your keybindings add something like:

>   , ((modMask .|. controlMask, xK_x), xmonadPrompt defaultPromptConfig)

-}

import XMonad
import XMonadContrib.XPrompt

import Control.Monad
import System.Directory
import System.Environment

data Ssh = Ssh

instance XPrompt Ssh where
    showXPrompt Ssh = "SSH to:   "

sshPrompt :: XPConfig -> X ()
sshPrompt c = do
  sc <- io $ sshComplList
  mkXPrompt Ssh c (mkComplFunFromList sc) ssh

ssh :: String -> X ()
ssh s = spawn $ "exec xterm -e ssh " ++ s
 
sshComplList :: IO [String]
sshComplList = do
  h <- getEnv "HOME"
  let kh = h ++ "/.ssh/known_hosts"
  f <- doesFileExist kh
  if f then do l <- readFile kh
               return $ map (takeWhile (/= ',') . concat . take 1 . words) (lines l)
       else return []