diff options
| author | Reto Hablützel <rethab@rethab.ch> | 2014-08-09 18:32:02 +0200 | 
|---|---|---|
| committer | Reto Hablützel <rethab@rethab.ch> | 2014-08-09 18:32:02 +0200 | 
| commit | 56b31659dfb6dffc166b4e9645cfa825996cb3cb (patch) | |
| tree | 27b439540ef86cb5a2bac2c8dd8470ca8ad31b9f /src/Plugins | |
| parent | 2d3638b8e0905b156b58fb65826ff7c272f4b615 (diff) | |
| download | xmobar-56b31659dfb6dffc166b4e9645cfa825996cb3cb.tar.gz xmobar-56b31659dfb6dffc166b4e9645cfa825996cb3cb.tar.bz2 | |
New Plugin MarqueePipeReader
    Display a long text from a pipe with marquee. It wraps around
    with a given separator and the length may be specified as well
    as the delay in 10th seconds. See readme for an example.
Diffstat (limited to 'src/Plugins')
| -rw-r--r-- | src/Plugins/MarqueePipeReader.hs | 68 | 
1 files changed, 68 insertions, 0 deletions
| diff --git a/src/Plugins/MarqueePipeReader.hs b/src/Plugins/MarqueePipeReader.hs new file mode 100644 index 0000000..babcfb6 --- /dev/null +++ b/src/Plugins/MarqueePipeReader.hs @@ -0,0 +1,68 @@ +----------------------------------------------------------------------------- +-- | +-- Module      :  Plugins.MarqueePipeReader +-- Copyright   :  (c) Reto Habluetzel +-- License     :  BSD-style (see LICENSE) +-- +-- Maintainer  :  Jose A. Ortega Ruiz <jao@gnu.org> +-- Stability   :  unstable +-- Portability :  unportable +-- +-- A plugin for reading from named pipes for long texts with marquee +-- +----------------------------------------------------------------------------- + +module Plugins.MarqueePipeReader where + +import System.IO (openFile, IOMode(ReadWriteMode), Handle) +import Plugins (tenthSeconds, Exec(alias, start), hGetLineSafe) +import System.Posix.Files (getFileStatus, isNamedPipe) +import Control.Concurrent(forkIO, threadDelay) +import Control.Concurrent.STM (TChan, atomically, writeTChan, tryReadTChan, newTChan) +import Control.Exception +import Control.Monad(forever, unless) + +type Length = Int       -- length of the text to display +type Rate = Int         -- delay in tenth seconds  +type Seperator = String -- if text wraps around, use separator + +data MarqueePipeReader = MarqueePipeReader String (Length, Rate, Seperator) String +    deriving (Read, Show) + +instance Exec MarqueePipeReader where +    alias (MarqueePipeReader _ _ a)    = a +    start (MarqueePipeReader p (len, rate, sep) _) cb = do +        let (def, pipe) = split ':' p +        unless (null def) (cb def) +        checkPipe pipe +        h <- openFile pipe ReadWriteMode +        line <- hGetLineSafe h +        chan <- atomically newTChan +        forkIO $ writer (toInfTxt line sep) sep len rate chan cb +        forever $ pipeToChan h chan +      where +        split c xs | c `elem` xs = let (pre, post) = span (c /=) xs +                                   in (pre, dropWhile (c ==) post) +                   | otherwise   = ([], xs) + +pipeToChan :: Handle -> TChan String -> IO () +pipeToChan h chan = do +    line <- hGetLineSafe h  +    atomically $ writeTChan chan line + +writer :: String -> Seperator -> Length -> Rate -> TChan String -> (String -> IO ()) -> IO () +writer txt sep len rate chan cb = do  +    cb (take len txt) +    mbnext <- atomically $ tryReadTChan chan +    case mbnext of +        Just new -> writer (toInfTxt new sep) sep len rate chan cb +        Nothing -> tenthSeconds rate >> writer (drop 1 txt) sep len rate chan cb  + +toInfTxt :: String -> String -> String +toInfTxt line sep = concat (repeat $ line ++ " " ++ sep ++ " ") + +checkPipe :: FilePath -> IO () +checkPipe file = handle (\(SomeException _) -> waitForPipe) $ do +                    status <- getFileStatus file +                    unless (isNamedPipe status) waitForPipe +    where waitForPipe = threadDelay 1000 >> checkPipe file | 
