remove decodeInput/encodeOutput

see http://code.google.com/p/xmonad/issues/detail?id=348
they are just synonyms for 2 utf8-string functions, and don't really help
This commit is contained in:
gwern0
2010-06-14 23:23:00 +00:00
parent 955dd48153
commit 6472683476
4 changed files with 65 additions and 81 deletions

View File

@@ -54,27 +54,26 @@ module XMonad.Hooks.DynamicLog (
) where
--
-- Useful imports
--
import XMonad
import Control.Monad
import Codec.Binary.UTF8.String (encodeString)
import Control.Monad (liftM2)
import Data.Char ( isSpace, ord )
import Data.List (intersperse, isPrefixOf, sortBy)
import Data.Maybe ( isJust, catMaybes )
import Data.List
import qualified Data.Map as M
import Data.Ord ( comparing )
import qualified Data.Map as M
import qualified XMonad.StackSet as S
import System.IO
import Foreign.C (CChar)
import XMonad
import XMonad.Util.WorkspaceCompare
import XMonad.Util.NamedWindows
import XMonad.Util.Run
import XMonad.Layout.LayoutModifier
import XMonad.Util.Font
import XMonad.Hooks.UrgencyHook
import XMonad.Hooks.ManageDocks
@@ -277,7 +276,7 @@ dynamicLogString pp = do
-- run extra loggers, ignoring any that generate errors.
extras <- mapM (flip catchX (return Nothing)) $ ppExtras pp
return $ encodeOutput . sepBy (ppSep pp) . ppOrder pp $
return $ encodeString . sepBy (ppSep pp) . ppOrder pp $
[ ws
, ppLayout pp ld
, ppTitle pp wt

View File

@@ -52,8 +52,6 @@ module XMonad.Prompt
, splitInSubListsAt
, breakAtSpace
, uniqSort
, decodeInput
, encodeOutput
, historyCompletion
, historyCompletionP
-- * History filters
@@ -75,22 +73,21 @@ import XMonad.Util.Types
import XMonad.Util.XSelection (getSelection)
import XMonad.Util.XUtils (fi)
import Codec.Binary.UTF8.String (decodeString)
import Control.Applicative ((<$>))
import Control.Arrow ((&&&),first)
import Control.Concurrent (threadDelay)
import Control.Monad.Reader
import Control.Exception.Extensible hiding (handle)
import Control.Monad.State
import Control.Applicative ((<$>))
import Data.Char
import Data.Bits
import Data.Maybe
import Data.List
import Data.Char (isSpace)
import Data.IORef
import Data.List
import Data.Maybe (fromMaybe)
import Data.Set (fromList, toList)
import System.Directory
import System.Directory (getAppUserDataDirectory)
import System.IO
import System.Posix.Files
import Control.Exception.Extensible hiding (handle)
import qualified Data.Map as M
-- $usage
@@ -452,7 +449,7 @@ keyPressHandle m (ks,str) = do
Nothing -> case str of
"" -> eventLoop handle
_ -> when (mask .&. controlMask == 0) $ do
insertString (decodeInput str)
insertString (decodeString str)
updateWindows
completed <- tryAutoComplete
when completed $ setSuccess True >> setDone True

View File

@@ -1,16 +1,14 @@
-----------------------------------------------------------------------------
-- |
-- Module : XMonad.Prompt.Shell
-- Copyright : (C) 2007 Andrea Rossato
-- License : BSD3
--
-- Maintainer : andrea.rossato@unibz.it
-- Stability : unstable
-- Portability : unportable
--
-- A shell prompt for XMonad
--
-----------------------------------------------------------------------------
{- |
Module : XMonad.Prompt.Shell
Copyright : (C) 2007 Andrea Rossato
License : BSD3
Maintainer : andrea.rossato@unibz.it
Stability : unstable
Portability : unportable
A shell prompt for XMonad
-}
module XMonad.Prompt.Shell
( -- * Usage
@@ -26,27 +24,29 @@ module XMonad.Prompt.Shell
, safePrompt
) where
import System.Environment
import Control.Monad
import Data.List
import System.Directory
import System.Posix.Files
import Codec.Binary.UTF8.String (decodeString, encodeString)
import Control.Monad (forM)
import Data.List (isPrefixOf)
import System.Directory (doesDirectoryExist, getDirectoryContents)
import System.Environment (getEnv)
import System.Posix.Files (getFileStatus, isDirectory)
import XMonad.Util.Run
import XMonad hiding (config)
import XMonad.Prompt
-- $usage
-- 1. In your @~\/.xmonad\/xmonad.hs@:
--
-- > import XMonad.Prompt
-- > import XMonad.Prompt.Shell
--
-- 2. In your keybindings add something like:
--
-- > , ((modm .|. controlMask, xK_x), shellPrompt defaultXPConfig)
--
-- For detailed instruction on editing the key binding see
-- "XMonad.Doc.Extending#Editing_key_bindings".
{- $usage
1. In your @~\/.xmonad\/xmonad.hs@:
> import XMonad.Prompt
> import XMonad.Prompt.Shell
2. In your keybindings add something like:
> , ((modm .|. controlMask, xK_x), shellPrompt defaultXPConfig)
For detailed instruction on editing the key binding see
"XMonad.Doc.Extending#Editing_key_bindings". -}
data Shell = Shell
@@ -57,39 +57,39 @@ instance XPrompt Shell where
shellPrompt :: XPConfig -> X ()
shellPrompt c = do
cmds <- io getCommands
mkXPrompt Shell c (getShellCompl cmds) (spawn . encodeOutput)
mkXPrompt Shell c (getShellCompl cmds) (spawn . encodeString)
-- | See safe and unsafeSpawn. prompt is an alias for safePrompt;
-- safePrompt and unsafePrompt work on the same principles, but will use
-- XPrompt to interactively query the user for input; the appearance is
-- set by passing an XPConfig as the second argument. The first argument
-- is the program to be run with the interactive input.
-- You would use these like this:
--
-- > , ((modm, xK_b), safePrompt "firefox" greenXPConfig)
-- > , ((modm .|. shiftMask, xK_c), prompt ("xterm" ++ " -e") greenXPConfig)
--
-- Note that you want to use safePrompt for Firefox input, as Firefox
-- wants URLs, and unsafePrompt for the XTerm example because this allows
-- you to easily start a terminal executing an arbitrary command, like
-- 'top'.
{- | See safe and unsafeSpawn. prompt is an alias for safePrompt;
safePrompt and unsafePrompt work on the same principles, but will use
XPrompt to interactively query the user for input; the appearance is
set by passing an XPConfig as the second argument. The first argument
is the program to be run with the interactive input.
You would use these like this:
> , ((modm, xK_b), safePrompt "firefox" greenXPConfig)
> , ((modm .|. shiftMask, xK_c), prompt ("xterm" ++ " -e") greenXPConfig)
Note that you want to use safePrompt for Firefox input, as Firefox
wants URLs, and unsafePrompt for the XTerm example because this allows
you to easily start a terminal executing an arbitrary command, like
'top'. -}
prompt, unsafePrompt, safePrompt :: FilePath -> XPConfig -> X ()
prompt = unsafePrompt
safePrompt c config = mkXPrompt Shell config (getShellCompl [c]) run
where run = safeSpawn c . return . encodeOutput
where run = safeSpawn c . return . encodeString
unsafePrompt c config = mkXPrompt Shell config (getShellCompl [c]) run
where run a = unsafeSpawn $ c ++ " " ++ encodeOutput a
where run a = unsafeSpawn $ c ++ " " ++ encodeString a
getShellCompl :: [String] -> String -> IO [String]
getShellCompl cmds s | s == "" || last s == ' ' = return []
| otherwise = do
f <- fmap lines $ runProcessWithInput "bash" [] ("compgen -A file " ++ encodeOutput s ++ "\n")
f <- fmap lines $ runProcessWithInput "bash" [] ("compgen -A file " ++ encodeString s ++ "\n")
files <- case f of
[x] -> do fs <- getFileStatus x
if isDirectory fs then return [x ++ "/"]
else return [x]
_ -> return f
return . map decodeInput . uniqSort $ files ++ commandCompletionFunction cmds s
return . map decodeString . uniqSort $ files ++ commandCompletionFunction cmds s
commandCompletionFunction :: [String] -> String -> [String]
commandCompletionFunction cmds str | '/' `elem` str = []

View File

@@ -29,8 +29,6 @@ module XMonad.Util.Font
, textExtentsXMF
, printStringXMF
, stringToPixel
, decodeInput
, encodeOutput
) where
import XMonad
@@ -44,9 +42,6 @@ import Graphics.X11.Xft
import Graphics.X11.Xrender
#endif
import Codec.Binary.UTF8.String (encodeString, decodeString)
-- Hide the Core Font/Xft switching here
data XMonadFont = Core FontStruct
| Utf8 FontSet
@@ -64,7 +59,6 @@ stringToPixel d s = fromMaybe fallBack <$> io getIt
where getIt = initColor d s
fallBack = blackPixel d (defaultScreen d)
-- | Given a fontname returns the font structure. If the font name is
-- not valid the default font will be loaded and returned.
initCoreFont :: String -> X FontStruct
@@ -192,12 +186,6 @@ printStringXMF dpy drw fs@(Xft font) gc fc bc x y s = do
\color -> xftDrawString draw color font x y s
#endif
decodeInput :: String -> String
decodeInput = decodeString
encodeOutput :: String -> String
encodeOutput = encodeString
-- | Short-hand for 'fromIntegral'
fi :: (Integral a, Num b) => a -> b
fi = fromIntegral