{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE NamedFieldPuns #-}
module XMonad.Prompt.Shell
(
Shell (..)
, shellPrompt
, safePrompt
, safeDirPrompt
, unsafePrompt
, prompt
, compgenDirectories
, compgenFiles
, getCommands
, getBrowser
, getEditor
, getShellCompl
, getShellCompl'
, split
) where
import Codec.Binary.UTF8.String (encodeString)
import Control.Exception as E
import Data.Bifunctor (bimap)
import System.Directory (getDirectoryContents)
import System.Environment (getEnv)
import System.Posix.Files (getFileStatus, isDirectory)
import XMonad hiding (config)
import XMonad.Prelude
import XMonad.Prompt
import XMonad.Util.Run
econst :: Monad m => a -> IOException -> m a
econst :: forall (m :: * -> *) a. Monad m => a -> IOException -> m a
econst = forall a b. a -> b -> a
const forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a. Monad m => a -> m a
return
data Shell = Shell
type Predicate = String -> String -> Bool
instance XPrompt Shell where
showXPrompt :: Shell -> String
showXPrompt Shell
Shell = String
"Run: "
completionToCommand :: Shell -> String -> String
completionToCommand Shell
_ = String -> String
escape
shellPrompt :: XPConfig -> X ()
shellPrompt :: XPConfig -> X ()
shellPrompt XPConfig
c = do
[String]
cmds <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
io IO [String]
getCommands
forall p.
XPrompt p =>
p -> XPConfig -> ComplFunction -> (String -> X ()) -> X ()
mkXPrompt Shell
Shell XPConfig
c ([String] -> Predicate -> ComplFunction
getShellCompl [String]
cmds forall a b. (a -> b) -> a -> b
$ XPConfig -> Predicate
searchPredicate XPConfig
c) forall (m :: * -> *). MonadIO m => String -> m ()
spawn
prompt, unsafePrompt, safePrompt :: FilePath -> XPConfig -> X ()
prompt :: String -> XPConfig -> X ()
prompt = String -> XPConfig -> X ()
unsafePrompt
safePrompt :: String -> XPConfig -> X ()
safePrompt String
c XPConfig
config = forall p.
XPrompt p =>
p -> XPConfig -> ComplFunction -> (String -> X ()) -> X ()
mkXPrompt Shell
Shell XPConfig
config ([String] -> Predicate -> ComplFunction
getShellCompl [String
c] forall a b. (a -> b) -> a -> b
$ XPConfig -> Predicate
searchPredicate XPConfig
config) String -> X ()
run
where run :: String -> X ()
run = forall (m :: * -> *). MonadIO m => String -> [String] -> m ()
safeSpawn String
c forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a. Monad m => a -> m a
return
unsafePrompt :: String -> XPConfig -> X ()
unsafePrompt String
c XPConfig
config = forall p.
XPrompt p =>
p -> XPConfig -> ComplFunction -> (String -> X ()) -> X ()
mkXPrompt Shell
Shell XPConfig
config ([String] -> Predicate -> ComplFunction
getShellCompl [String
c] forall a b. (a -> b) -> a -> b
$ XPConfig -> Predicate
searchPredicate XPConfig
config) forall (m :: * -> *). MonadIO m => String -> m ()
run
where run :: String -> m ()
run String
a = forall (m :: * -> *). MonadIO m => String -> m ()
unsafeSpawn forall a b. (a -> b) -> a -> b
$ String
c forall a. [a] -> [a] -> [a]
++ String
" " forall a. [a] -> [a] -> [a]
++ String
a
safeDirPrompt
:: FilePath
-> XPConfig
-> String
-> X ()
safeDirPrompt :: String -> XPConfig -> String -> X ()
safeDirPrompt String
cmd cfg :: XPConfig
cfg@XPC{ Predicate
searchPredicate :: Predicate
searchPredicate :: XPConfig -> Predicate
searchPredicate } String
compgenStr =
forall p.
XPrompt p =>
p -> XPConfig -> ComplFunction -> (String -> X ()) -> X ()
mkXPrompt Shell
Shell XPConfig
cfg ComplFunction
mkCompl (forall (m :: * -> *). MonadIO m => String -> [String] -> m ()
safeSpawn String
cmd forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a. Applicative f => a -> f a
pure)
where
mkCompl :: String -> IO [String]
mkCompl :: ComplFunction
mkCompl String
input =
ComplCaseSensitivity
-> ([String] -> [String]) -> [String] -> String -> ComplFunction
shellComplImpl
ComplCaseSensitivity
CaseSensitive
(forall a. (a -> Bool) -> [a] -> [a]
filter (Predicate
searchPredicate String
ext))
([String] -> Predicate -> String -> [String]
commandCompletionFunction [String
cmd] Predicate
searchPredicate String
input)
(if String
"/" forall a. Eq a => [a] -> [a] -> Bool
`isInfixOf` String
input then String
dir else String
compgenStr)
String
input
where
(String
ext, String
dir) :: (String, String)
= forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap forall a. [a] -> [a]
reverse forall a. [a] -> [a]
reverse forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> Bool) -> [a] -> ([a], [a])
break (forall a. Eq a => a -> a -> Bool
== Char
'/') forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> [a]
reverse forall a b. (a -> b) -> a -> b
$ String
input
getShellCompl :: [String] -> Predicate -> String -> IO [String]
getShellCompl :: [String] -> Predicate -> ComplFunction
getShellCompl = ComplCaseSensitivity -> [String] -> Predicate -> ComplFunction
getShellCompl' ComplCaseSensitivity
CaseSensitive
getShellCompl' :: ComplCaseSensitivity -> [String] -> Predicate -> String -> IO [String]
getShellCompl' :: ComplCaseSensitivity -> [String] -> Predicate -> ComplFunction
getShellCompl' ComplCaseSensitivity
csn [String]
cmds Predicate
p String
input =
ComplCaseSensitivity
-> ([String] -> [String]) -> [String] -> String -> ComplFunction
shellComplImpl ComplCaseSensitivity
csn forall a. a -> a
id ([String] -> Predicate -> String -> [String]
commandCompletionFunction [String]
cmds Predicate
p String
input) String
input String
input
shellComplImpl
:: ComplCaseSensitivity
-> ([String] -> [String])
-> [String]
-> String
-> String
-> IO [String]
shellComplImpl :: ComplCaseSensitivity
-> ([String] -> [String]) -> [String] -> String -> ComplFunction
shellComplImpl ComplCaseSensitivity
csn [String] -> [String]
filterFiles [String]
cmds String
cmpgenStr String
input
| String
input forall a. Eq a => a -> a -> Bool
== String
"" Bool -> Bool -> Bool
|| forall a. [a] -> a
last String
input forall a. Eq a => a -> a -> Bool
== Char
' ' = forall (f :: * -> *) a. Applicative f => a -> f a
pure []
| Bool
otherwise = do
[String]
choices <- [String] -> [String]
filterFiles forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
lines forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ComplCaseSensitivity -> String -> IO String
compgenFiles ComplCaseSensitivity
csn String
cmpgenStr
[String]
files <- case [String]
choices of
[String
x] -> do FileStatus
fs <- String -> IO FileStatus
getFileStatus (String -> String
encodeString String
x)
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ if FileStatus -> Bool
isDirectory FileStatus
fs then [String
x forall a. [a] -> [a] -> [a]
++ String
"/"] else [String
x]
[String]
_ -> forall (f :: * -> *) a. Applicative f => a -> f a
pure [String]
choices
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy String -> String -> Ordering
typedFirst forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Ord a => [a] -> [a]
uniqSort forall a b. (a -> b) -> a -> b
$ [String]
files forall a. [a] -> [a] -> [a]
++ [String]
cmds
where
typedFirst :: String -> String -> Ordering
typedFirst :: String -> String -> Ordering
typedFirst String
x String
y
| String
x Predicate
`startsWith` String
input Bool -> Bool -> Bool
&& Bool -> Bool
not (String
y Predicate
`startsWith` String
input) = Ordering
LT
| String
y Predicate
`startsWith` String
input Bool -> Bool -> Bool
&& Bool -> Bool
not (String
x Predicate
`startsWith` String
input) = Ordering
GT
| Bool
otherwise = String
x forall a. Ord a => a -> a -> Ordering
`compare` String
y
startsWith :: String -> String -> Bool
startsWith :: Predicate
startsWith String
str String
ps = forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toLower String
ps forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toLower String
str
compgenFiles :: ComplCaseSensitivity -> String -> IO String
compgenFiles :: ComplCaseSensitivity -> String -> IO String
compgenFiles ComplCaseSensitivity
csn = ComplCaseSensitivity -> String -> String -> IO String
compgen ComplCaseSensitivity
csn String
"file"
compgenDirectories :: ComplCaseSensitivity -> String -> IO String
compgenDirectories :: ComplCaseSensitivity -> String -> IO String
compgenDirectories ComplCaseSensitivity
csn = ComplCaseSensitivity -> String -> String -> IO String
compgen ComplCaseSensitivity
csn String
"directory"
compgen :: ComplCaseSensitivity -> String -> String -> IO String
compgen :: ComplCaseSensitivity -> String -> String -> IO String
compgen ComplCaseSensitivity
csn String
actionOpt String
s = forall (m :: * -> *).
MonadIO m =>
String -> [String] -> String -> m String
runProcessWithInput String
"bash" [] forall a b. (a -> b) -> a -> b
$
ComplCaseSensitivity -> String
complCaseSensitivityCmd ComplCaseSensitivity
csn forall a. [a] -> [a] -> [a]
++ String
" ; " forall a. [a] -> [a] -> [a]
++ String -> String -> String
compgenCmd String
actionOpt String
s
complCaseSensitivityCmd :: ComplCaseSensitivity -> String
complCaseSensitivityCmd :: ComplCaseSensitivity -> String
complCaseSensitivityCmd ComplCaseSensitivity
CaseSensitive =
String
"bind 'set completion-ignore-case off'"
complCaseSensitivityCmd ComplCaseSensitivity
CaseInSensitive =
String
"bind 'set completion-ignore-case on'"
compgenCmd :: String -> String -> String
compgenCmd :: String -> String -> String
compgenCmd String
actionOpt String
s = String
"compgen -A " forall a. [a] -> [a] -> [a]
++ String
actionOpt forall a. [a] -> [a] -> [a]
++ String
" -- " forall a. [a] -> [a] -> [a]
++ String
s forall a. [a] -> [a] -> [a]
++ String
"\n"
commandCompletionFunction :: [String] -> Predicate -> String -> [String]
commandCompletionFunction :: [String] -> Predicate -> String -> [String]
commandCompletionFunction [String]
cmds Predicate
p String
str | Char
'/' forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` String
str = []
| Bool
otherwise = forall a. (a -> Bool) -> [a] -> [a]
filter (Predicate
p String
str) [String]
cmds
getCommands :: IO [String]
getCommands :: IO [String]
getCommands = do
String
p <- String -> IO String
getEnv String
"PATH" forall e a. Exception e => IO a -> (e -> IO a) -> IO a
`E.catch` forall (m :: * -> *) a. Monad m => a -> IOException -> m a
econst []
let ds :: [String]
ds = forall a. (a -> Bool) -> [a] -> [a]
filter (forall a. Eq a => a -> a -> Bool
/= String
"") forall a b. (a -> b) -> a -> b
$ forall a. Eq a => a -> [a] -> [[a]]
split Char
':' String
p
[[String]]
es <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM [String]
ds forall a b. (a -> b) -> a -> b
$ \String
d -> ComplFunction
getDirectoryContents String
d forall e a. Exception e => IO a -> (e -> IO a) -> IO a
`E.catch` forall (m :: * -> *) a. Monad m => a -> IOException -> m a
econst []
forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Ord a => [a] -> [a]
uniqSort forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String
"." forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf`)) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat forall a b. (a -> b) -> a -> b
$ [[String]]
es
split :: Eq a => a -> [a] -> [[a]]
split :: forall a. Eq a => a -> [a] -> [[a]]
split a
_ [] = []
split a
e [a]
l =
[a]
f forall a. a -> [a] -> [a]
: forall a. Eq a => a -> [a] -> [[a]]
split a
e (forall a. Int -> [a] -> [a]
drop Int
1 [a]
ls)
where
([a]
f,[a]
ls) = forall a. (a -> Bool) -> [a] -> ([a], [a])
span (forall a. Eq a => a -> a -> Bool
/=a
e) [a]
l
escape :: String -> String
escape :: String -> String
escape [] = String
""
escape (Char
x:String
xs)
| Char -> Bool
isSpecialChar Char
x = Char
'\\' forall a. a -> [a] -> [a]
: Char
x forall a. a -> [a] -> [a]
: String -> String
escape String
xs
| Bool
otherwise = Char
x forall a. a -> [a] -> [a]
: String -> String
escape String
xs
isSpecialChar :: Char -> Bool
isSpecialChar :: Char -> Bool
isSpecialChar = forall a b c. (a -> b -> c) -> b -> a -> c
flip forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem String
" &\\@\"'#?$*()[]{};"
env :: String -> String -> IO String
env :: String -> String -> IO String
env String
variable String
fallthrough = String -> IO String
getEnv String
variable forall e a. Exception e => IO a -> (e -> IO a) -> IO a
`E.catch` forall (m :: * -> *) a. Monad m => a -> IOException -> m a
econst String
fallthrough
getBrowser :: IO String
getBrowser :: IO String
getBrowser = String -> String -> IO String
env String
"BROWSER" String
"firefox"
getEditor :: IO String
getEditor :: IO String
getEditor = String -> String -> IO String
env String
"EDITOR" String
"emacs"