{- |
Module      :  XMonad.Prompt.Zsh
Description :  Zsh-specific version of "XMonad.Prompt.Shell".
Copyright   :  (C) 2020 Zubin Duggal
License     :  BSD3

Maintainer  :  zubin.duggal@gmail.com
Stability   :  unstable
Portability :  unportable

A version of "XMonad.Prompt.Shell" that lets you access the awesome power of Zsh
completions in your xmonad prompt
-}

module XMonad.Prompt.Zsh
    ( -- * Usage
      -- $usage
      Zsh (..)
    , zshPrompt
    -- * Utility functions
    , getZshCompl
    , stripZsh
    ) where

import XMonad
import XMonad.Prompt
import XMonad.Util.Run

{- $usage
1. Grab the @capture.zsh@ script to capture zsh completions from <https://github.com/Valodim/zsh-capture-completion>
2. In your @~\/.xmonad\/xmonad.hs@:

> import XMonad.Prompt
> import XMonad.Prompt.Zsh

3. In your keybindings add something like:

>   , ((modm .|. controlMask, xK_x), zshPrompt def "/path/to/capture.zsh")

For detailed instruction on editing the key binding see
"XMonad.Doc.Extending#Editing_key_bindings". -}

data Zsh = Zsh

instance XPrompt Zsh where
    showXPrompt :: Zsh -> String
showXPrompt Zsh
Zsh       = String
"Run: "
    completionToCommand :: Zsh -> String -> String
completionToCommand Zsh
_ = String -> String
stripZsh
    commandToComplete :: Zsh -> String -> String
commandToComplete Zsh
_ String
s = String
s
    nextCompletion :: Zsh -> String -> [String] -> String
nextCompletion Zsh
_ String
s [String]
cs = String -> [String] -> String
getNextCompletion String
s ((String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map String -> String
stripZsh [String]
cs)

zshPrompt :: XPConfig -> FilePath -> X ()
zshPrompt :: XPConfig -> String -> X ()
zshPrompt XPConfig
c String
capture = Zsh -> XPConfig -> ComplFunction -> (String -> X ()) -> X ()
forall p.
XPrompt p =>
p -> XPConfig -> ComplFunction -> (String -> X ()) -> X ()
mkXPrompt Zsh
Zsh XPConfig
c (String -> ComplFunction
getZshCompl String
capture) (\String
x -> String -> [String] -> X ()
forall (m :: * -> *). MonadIO m => String -> [String] -> m ()
safeSpawn String
"zsh" [String
"-c",String
x])

getZshCompl :: FilePath -> String -> IO [String]
getZshCompl :: String -> ComplFunction
getZshCompl String
capture String
s
  | String
s String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
""   = [String] -> IO [String]
forall (m :: * -> *) a. Monad m => a -> m a
return []
  | Bool
otherwise = String -> [String]
processCompls (String -> [String]) -> IO String -> IO [String]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> [String] -> String -> IO String
forall (m :: * -> *).
MonadIO m =>
String -> [String] -> String -> m String
runProcessWithInput String
capture [String
s] String
""
    where processCompls :: String -> [String]
processCompls = (String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (\String
x -> String -> String
skipLastWord String
s String -> String -> String
forall a. [a] -> [a] -> [a]
++ (Char -> Bool) -> String -> String
forall a. (a -> Bool) -> [a] -> [a]
filter (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'\r') String
x) ([String] -> [String])
-> (String -> [String]) -> String -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
lines

-- | Removes the argument description from the zsh completion
stripZsh :: String -> String
stripZsh :: String -> String
stripZsh String
"" = String
""
stripZsh (Char
' ':Char
'-':Char
'-':Char
' ':String
_) = String
""
stripZsh (Char
x:String
xs) = Char
x Char -> String -> String
forall a. a -> [a] -> [a]
: String -> String
stripZsh String
xs