module Xmobar.X11.Actions (Action(..), runAction, stripActions) where
import System.Process (system)
import Control.Monad (void)
import Text.Regex (Regex, subRegex, mkRegex, matchRegex)
import Graphics.X11.Types (Button)
data Action = Spawn [Button] String
deriving (Action -> Action -> Bool
(Action -> Action -> Bool)
-> (Action -> Action -> Bool) -> Eq Action
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Action -> Action -> Bool
$c/= :: Action -> Action -> Bool
== :: Action -> Action -> Bool
$c== :: Action -> Action -> Bool
Eq)
runAction :: Action -> IO ()
runAction :: Action -> IO ()
runAction (Spawn [Button]
_ String
s) = IO ExitCode -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IO ExitCode -> IO ()) -> IO ExitCode -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> IO ExitCode
system (String
s String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"&")
stripActions :: String -> String
stripActions :: String -> String
stripActions String
s = case Regex -> String -> Maybe [String]
matchRegex Regex
actionRegex String
s of
Maybe [String]
Nothing -> String
s
Just [String]
_ -> String -> String
stripActions String
strippedOneLevel
where
strippedOneLevel :: String
strippedOneLevel = Regex -> String -> String -> String
subRegex Regex
actionRegex String
s String
"[action=\\1\\2]\\3[/action]"
actionRegex :: Regex
actionRegex :: Regex
actionRegex = String -> Regex
mkRegex String
"<action=`?([^>`]*)`?( +button=[12345]+)?>(.+)</action>"