summaryrefslogtreecommitdiffhomepage
path: root/src/Xmobar/Plugins/QueueReader.hs
blob: cf60c1d70e624f841881835f236f6ae8c1e8bd6d (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
{-# LANGUAGE RecordWildCards #-}
module Xmobar.Plugins.QueueReader
  (QueueReader (..)
  ) where

import Xmobar.Run.Exec (Exec (..))

import Control.Monad (forever)
import qualified Control.Concurrent.STM as STM

-- | A 'QueueReader' displays data from an 'TQueue a' where
-- the data items 'a' are rendered by a user supplied function.
--
-- Like the 'HandleReader' plugin this is only useful if you are
-- running @xmobar@ from other Haskell code.  You should create a
-- new @TQueue a@ and pass it to this plugin.
--
-- @
-- main :: IO
-- main = do
--   q <- STM.newQueueIO @String
--   bar <- forkIO $ xmobar conf
--     { commands = Run (QueueReader q id "Queue") : commands conf }
--   STM.atomically $ STM.writeTQueue q "Some Message"
-- @
data QueueReader a
  = QueueReader
  { qQueue    :: STM.TQueue a
  , qShowItem :: a -> String
  , qName :: String
  }

-- | This cannot be read back.
instance Show (QueueReader a) where
  -- | Only show the name/alias for the queue reader.
  show q = "QueueReader " <> qName q

-- | WARNING: This read instance will throw an exception if used! It is
-- only implemented, because it is required by 'Xmobar.Run` in 'Xmobar.commands'.
instance Read (QueueReader a) where
  -- | Throws an 'error'!
  readsPrec = error "QueueReader: instance is a stub"

-- | Async queue/channel reading.
instance Exec (QueueReader a) where
  -- | Read from queue as data arrives.
  start QueueReader{..} cb =
    forever (STM.atomically (qShowItem <$> STM.readTQueue qQueue) >>= cb)

  alias = qName