Skip to content
Snippets Groups Projects
Commit 2bcc086a authored by Mr. Snow Ball / projects's avatar Mr. Snow Ball / projects :arrows_counterclockwise:
Browse files

Add animation on click to qubesCount

parent 82c6ac15
No related branches found
No related tags found
No related merge requests found
......@@ -3,7 +3,7 @@ module QBar.Blocks.Qubes where
import QBar.BlockHelper
import QBar.BlockOutput
import QBar.Core
import QBar.Qubes.AdminAPI (qubesUsageOfDefaultPool, qubesMonitorProperty, qubesGetProperty, qubesEvents, QubesPropertyInfo (..), qubesListVMsP, QubesVMState (..), vmState)
import QBar.Qubes.AdminAPI (qubesUsageOfDefaultPool, qubesMonitorProperty, qubesGetProperty, qubesEvents, QubesPropertyInfo (..), qubesListVMs, qubesListVMsP, QubesVMState (..), vmState)
import Control.Concurrent.Async
import Control.Monad.Reader (runReaderT)
......@@ -79,13 +79,12 @@ pipeBlockWithEvents prod block = do
qubesMonitorPropertyBlock :: BL.ByteString -> Block
qubesMonitorPropertyBlock name = pipeBlockWithEvents (qubesMonitorProperty qubesEvents name >> exitBlock) handle
where
handle = handle' <=< either (const $ liftIO $ qubesGetProperty name) return
handle' QubesPropertyInfo {propValue, propIsDefault} = return $ Just $ mkBlockOutput $ normalText $ decode propValue <> (if propIsDefault then " (D)" else "")
handle = fmap handle' . either (const $ liftIO $ qubesGetProperty name) return
handle' QubesPropertyInfo {propValue, propIsDefault} = Just $ mkBlockOutput $ normalText $ decode propValue <> (if propIsDefault then " (D)" else "")
decode = decodeUtf8With lenientDecode
qubesVMCountBlock :: Block
qubesVMCountBlock = qubesListVMsP >-> P.map countVMs >> exitBlock where
countVMs = wrap . format . M.size . M.filterWithKey isRunningVM
qubesVMCountBlock = pipeBlockWithEvents (qubesListVMsP >> exitBlock) $ fmap countVMs . either (const $ liftIO $ qubesListVMs) return where
countVMs = Just . format . M.size . M.filterWithKey isRunningVM
isRunningVM name x = vmState x == VMRunning && name /= "dom0"
format n = mkBlockOutput $ normalText $ T.pack (show n) <> " Qube" <> (if n /= 1 then "s" else "")
wrap x = (Just (x, Nothing), DefaultUpdate)
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment