diff options
Diffstat (limited to 'src/Xmobar')
| -rw-r--r-- | src/Xmobar/Plugins/BufferedPipeReader.hs | 3 | ||||
| -rw-r--r-- | src/Xmobar/Plugins/CommandReader.hs | 3 | ||||
| -rw-r--r-- | src/Xmobar/Plugins/HandleReader.hs | 4 | ||||
| -rw-r--r-- | src/Xmobar/Plugins/MarqueePipeReader.hs | 7 | ||||
| -rw-r--r-- | src/Xmobar/Plugins/PipeReader.hs | 3 | ||||
| -rw-r--r-- | src/Xmobar/Plugins/StdinReader.hs | 3 | ||||
| -rw-r--r-- | src/Xmobar/Run/Command.hs | 5 | ||||
| -rw-r--r-- | src/Xmobar/System/Utils.hs | 14 | 
8 files changed, 12 insertions, 30 deletions
| diff --git a/src/Xmobar/Plugins/BufferedPipeReader.hs b/src/Xmobar/Plugins/BufferedPipeReader.hs index f98d0d4..cf5a071 100644 --- a/src/Xmobar/Plugins/BufferedPipeReader.hs +++ b/src/Xmobar/Plugins/BufferedPipeReader.hs @@ -23,7 +23,6 @@ import System.IO.Unsafe(unsafePerformIO)  import Xmobar.Run.Exec  import Xmobar.System.Signal  import Xmobar.System.Environment -import Xmobar.System.Utils(hGetLineSafe)  data BufferedPipeReader = BufferedPipeReader String [(Int, Bool, String)]      deriving (Read, Show) @@ -55,7 +54,7 @@ instance Exec BufferedPipeReader where          reader :: (Int, Bool, FilePath) -> TChan (Int, Bool, String) -> IO ()          reader p@(to, tg, fp) tc = do              fp' <- expandEnv fp -            openFile fp' ReadWriteMode >>= hGetLineSafe >>= \dt -> +            openFile fp' ReadWriteMode >>= hGetLine >>= \dt ->                  atomically $ writeTChan tc (to, tg, dt)              reader p tc diff --git a/src/Xmobar/Plugins/CommandReader.hs b/src/Xmobar/Plugins/CommandReader.hs index 9cf6d0e..a54377a 100644 --- a/src/Xmobar/Plugins/CommandReader.hs +++ b/src/Xmobar/Plugins/CommandReader.hs @@ -17,7 +17,6 @@ module Xmobar.Plugins.CommandReader(CommandReader(..)) where  import System.IO  import Xmobar.Run.Exec -import Xmobar.System.Utils (hGetLineSafe)  import System.Process(runInteractiveCommand, getProcessExitCode)  data CommandReader = CommandReader String String @@ -31,7 +30,7 @@ instance Exec CommandReader where          hClose hstderr          hSetBinaryMode hstdout False          hSetBuffering hstdout LineBuffering -        forever ph (hGetLineSafe hstdout >>= cb) +        forever ph (hGetLine hstdout >>= cb)          where forever ph a =                    do a                       ec <- getProcessExitCode ph diff --git a/src/Xmobar/Plugins/HandleReader.hs b/src/Xmobar/Plugins/HandleReader.hs index e1ee6a5..4e5c30e 100644 --- a/src/Xmobar/Plugins/HandleReader.hs +++ b/src/Xmobar/Plugins/HandleReader.hs @@ -19,10 +19,10 @@ where  import           System.IO                      ( Handle                                                  , hIsEOF +                                                , hGetLine                                                  )  import           Xmobar.Run.Exec                ( Exec(..) ) -import           Xmobar.System.Utils            ( hGetLineSafe )  -- | A HandleReader displays any text received from a Handle. @@ -59,7 +59,7 @@ instance Read HandleReader where  instance Exec HandleReader where      -- | Read from the 'Handle' until it is closed.      start (HandleReader handle _) cb = -        untilM (hIsEOF handle) $ hGetLineSafe handle >>= cb +        untilM (hIsEOF handle) $ hGetLine handle >>= cb      -- | Use the 2nd argument to HandleReader as its alias.      alias (HandleReader _ a) = a diff --git a/src/Xmobar/Plugins/MarqueePipeReader.hs b/src/Xmobar/Plugins/MarqueePipeReader.hs index 084331b..f1fdee0 100644 --- a/src/Xmobar/Plugins/MarqueePipeReader.hs +++ b/src/Xmobar/Plugins/MarqueePipeReader.hs @@ -14,10 +14,9 @@  module Xmobar.Plugins.MarqueePipeReader(MarqueePipeReader(..)) where -import System.IO (openFile, IOMode(ReadWriteMode), Handle) +import System.IO (openFile, IOMode(ReadWriteMode), Handle, hGetLine)  import Xmobar.System.Environment  import Xmobar.Run.Exec(Exec(alias, start), tenthSeconds) -import Xmobar.System.Utils(hGetLineSafe)  import System.Posix.Files (getFileStatus, isNamedPipe)  import Control.Concurrent(forkIO, threadDelay)  import Control.Concurrent.STM (TChan, atomically, writeTChan, tryReadTChan, newTChan) @@ -39,7 +38,7 @@ instance Exec MarqueePipeReader where          unless (null def) (cb def)          checkPipe pipe          h <- openFile pipe ReadWriteMode -        line <- hGetLineSafe h +        line <- hGetLine h          chan <- atomically newTChan          forkIO $ writer (toInfTxt line sep) sep len rate chan cb          forever $ pipeToChan h chan @@ -50,7 +49,7 @@ instance Exec MarqueePipeReader where  pipeToChan :: Handle -> TChan String -> IO ()  pipeToChan h chan = do -    line <- hGetLineSafe h +    line <- hGetLine h      atomically $ writeTChan chan line  writer :: String -> Separator -> Length -> Rate -> TChan String -> (String -> IO ()) -> IO () diff --git a/src/Xmobar/Plugins/PipeReader.hs b/src/Xmobar/Plugins/PipeReader.hs index 9c6e628..1a10abf 100644 --- a/src/Xmobar/Plugins/PipeReader.hs +++ b/src/Xmobar/Plugins/PipeReader.hs @@ -16,7 +16,6 @@ module Xmobar.Plugins.PipeReader(PipeReader(..)) where  import System.IO  import Xmobar.Run.Exec(Exec(..)) -import Xmobar.System.Utils(hGetLineSafe)  import Xmobar.System.Environment(expandEnv)  import System.Posix.Files  import Control.Concurrent(threadDelay) @@ -34,7 +33,7 @@ instance Exec PipeReader where          unless (null def) (cb def)          checkPipe pipe          h <- openFile pipe ReadWriteMode -        forever (hGetLineSafe h >>= cb) +        forever (hGetLine h >>= cb)        where          split c xs | c `elem` xs = let (pre, post) = span (c /=) xs                                     in (pre, dropWhile (c ==) post) diff --git a/src/Xmobar/Plugins/StdinReader.hs b/src/Xmobar/Plugins/StdinReader.hs index 4b80044..5a8b2be 100644 --- a/src/Xmobar/Plugins/StdinReader.hs +++ b/src/Xmobar/Plugins/StdinReader.hs @@ -25,7 +25,6 @@ import System.IO  import Control.Exception (SomeException(..), handle)  import Xmobar.Run.Exec  import Xmobar.X11.Actions (stripActions) -import Xmobar.System.Utils (hGetLineSafe)  data StdinReader = StdinReader | UnsafeStdinReader    deriving (Read, Show) @@ -33,7 +32,7 @@ data StdinReader = StdinReader | UnsafeStdinReader  instance Exec StdinReader where    start stdinReader cb = do      s <- handle (\(SomeException e) -> do hPrint stderr e; return "") -                (hGetLineSafe stdin) +                (hGetLine stdin)      cb $ escape stdinReader s      eof <- isEOF      if eof diff --git a/src/Xmobar/Run/Command.hs b/src/Xmobar/Run/Command.hs index e6153c1..430d142 100644 --- a/src/Xmobar/Run/Command.hs +++ b/src/Xmobar/Run/Command.hs @@ -20,8 +20,7 @@ module Xmobar.Run.Command where  import Control.Exception (handle, SomeException(..))  import System.Process  import System.Exit -import System.IO (hClose) -import Xmobar.System.Utils (hGetLineSafe) +import System.IO (hClose, hGetLine)  import Xmobar.Run.Exec @@ -47,7 +46,7 @@ instance Exec Command where                  exit <- waitForProcess p                  let closeHandles = hClose o >> hClose i >> hClose e                      getL = handle (\(SomeException _) -> return "") -                                  (hGetLineSafe o) +                                  (hGetLine o)                  case exit of                    ExitSuccess -> do str <- getL                                      closeHandles diff --git a/src/Xmobar/System/Utils.hs b/src/Xmobar/System/Utils.hs index d4bdd78..227850d 100644 --- a/src/Xmobar/System/Utils.hs +++ b/src/Xmobar/System/Utils.hs @@ -17,7 +17,7 @@  ------------------------------------------------------------------------------ -module Xmobar.System.Utils (expandHome, changeLoop, hGetLineSafe) +module Xmobar.System.Utils (expandHome, changeLoop)  where  import Control.Monad @@ -27,18 +27,6 @@ import System.Environment  import System.FilePath  import System.IO -#if defined XFT || defined UTF8 -import qualified System.IO as S (hGetLine) -#endif - -hGetLineSafe :: Handle -> IO String -#if defined XFT || defined UTF8 -hGetLineSafe = S.hGetLine -#else -hGetLineSafe = hGetLine -#endif - -  expandHome :: FilePath -> IO FilePath  expandHome ('~':'/':path) = fmap (</> path) (getEnv "HOME")  expandHome p = return p | 
