summaryrefslogtreecommitdiffstats
path: root/src/XMonad/Local/Prompt.hs
blob: 5734fc8a1e14280b8e9cd2fc61b7f891fc600d10 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
{-# LANGUAGE DoAndIfThenElse #-}
{-# LANGUAGE UnicodeSyntax   #-}

module XMonad.Local.Prompt (
    digraphPrompt,
    getDigraphForString
) where

import           Control.Exception
import           Control.Monad
import           System.Directory
import           System.IO
import qualified System.IO.Temp      as Temp

import           XMonad
import           XMonad.Prompt

-- local modules **************************************************************
import qualified XMonad.Local.Config as Local
import qualified XMonad.Local.Util   as Local

-- digraph prompt *************************************************************
data Digraph = Digraph

instance XPrompt Digraph where
    showXPrompt Digraph = "Two ASCII characters: "

-- | According to RFC 1345
digraphChars ∷ String
digraphChars = "!\"%'()*+,-./0123456789:;<=>?"
            ++ "ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz"

digraphCompletionFunction ∷ StringIO [String]
digraphCompletionFunction = return . gen
    where
        gen ∷ String[String]
        gen []                                      = [x:"?" | x <- digraphChars]
        gen [x]    |    x `elem` digraphChars       = [[x, y] | y <- '_':digraphChars]
                   |    otherwise                   = []
        gen [x, y] |    x `elem` digraphChars
                     && y `elem` ('_':digraphChars) = [[x, y]]
                   |    otherwise                   = []
        gen _                                       = []

vimEchoDigraphConfig ∷ String
vimEchoDigraphConfig = unlines [
    "set noswapfile",
    "set nocompatible",
    "filetype off",
    "\" load unicode plugin for unicode#Digraph function",
    "set rtp+=" ++ Local.vimBundlePath,
    "call vundle#begin()",
    "Plugin 'chrisbra/unicode.vim'",
    "call vundle#end()"]

vimBinary ∷ String
vimBinary = "/usr/bin/vim"

-- |
-- TODO: make it vim independent
getDigraphForString ∷ String → X String
getDigraphForString str = io $
    Temp.withSystemTempFile "xminad-digraph-config.vimrc" $ \filePath h ->
        finally (runVim filePath h) (removeFile filePath)
    where
        cmdMkDigraph = "+call setline(1, unicode#Digraph(getline(1)[0:1]))"
        cmdWriteAndQuit = "+w!/dev/stderr|q!"

        runVim ∷ FilePathHandleIO String
        runVim filePath h = do
            finally (hPutStr h vimEchoDigraphConfig) (hClose h)
            (_, dg) <- Local.runProcessAndGetOutputs vimBinary
                ["-", "-esbu", filePath, cmdMkDigraph, cmdWriteAndQuit]
                str
            when (null dg) (hPrint stderr $ "failed to get digraph for input '" ++ str ++ "'\n")
            return dg

-- | Prompts for two characters and passes them to vim to get corresponding
-- digraph.
-- NOTE: Even if return value is Just, the string may still be empty if the
-- vim couldn't make digraph out of the input.
digraphPrompt ∷ X (Maybe String)
digraphPrompt = catchX
     (mkXPromptWithReturn Digraph
        Local.xpConfig digraphCompletionFunction getDigraphForString)
     (io $ return Nothing)