taffybar-4.1.0: A desktop bar similar to xmobar, but with more GUI
Copyright(c) Ivan A. Malison
LicenseBSD3-style (see LICENSE)
MaintainerIvan A. Malison
Stabilityunstable
Portabilityunportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

System.Taffybar.Util

Description

 
Synopsis

Configuration

GTK concurrency

postGUISync :: IO a -> IO a #

Queue an action to be run in the GTK event loop. If called from the same process as the event loop, this runs the action directly. Otherwise, this queues it in GTK's event loop and blocks until the action is complete

You must call setGUIThread or setCurrentThreadAsGUIThread before this.

Equivalent to postGUISyncWithPriority PRIORITY_DEFAULT_IDLE

postGUIASync :: IO () -> IO () #

Queue an action to be run in the GTK event loop. This function queues the event regardless of what process it is called from, and returns immidietly.

Equivalent to postGUIASyncWithPriority PRIORITY_DEFAULT_IDLE

GLib

Logging

logPrintF :: (MonadIO m, Show t) => String -> Priority -> String -> t -> m () Source #

Text

Resources

Logic Combinators

(<||>) :: Monad m => (t -> m (Maybe a)) -> (t -> m (Maybe a)) -> t -> m (Maybe a) infixl 3 Source #

(<|||>) :: Monad m => (t -> t1 -> m (Maybe a)) -> (t -> t1 -> m (Maybe a)) -> t -> t1 -> m (Maybe a) infixl 3 Source #

forkM :: Monad m => (c -> m a) -> (c -> m b) -> c -> m (a, b) Source #

ifM :: Monad m => m Bool -> m a -> m a -> m a Source #

anyM :: Monad m => (a -> m Bool) -> [a] -> m Bool Source #

maybeTCombine :: Monad m => m (Maybe a) -> m (Maybe a) -> m (Maybe a) Source #

maybeToEither :: b -> Maybe a -> Either b a Source #

Control

foreverWithVariableDelay :: (MonadIO m, RealFrac d) => IO d -> m ThreadId Source #

Execute the provided IO action, and use the value it returns to decide how long to wait until executing it again. The value returned by the action is interpreted as a number of seconds.

foreverWithDelay :: (MonadIO m, RealFrac d) => d -> IO () -> m ThreadId Source #

Execute the provided IO action at the provided interval.

Process control

runCommand :: MonadIO m => FilePath -> [String] -> m (Either String String) Source #

Run the provided command with the provided arguments.

If the command filename does not contain a slash, then the PATH environment variable is searched for the executable.

onSigINT Source #

Arguments

:: IO a

The main loop IO action

-> IO ()

Callback for SIGINT

-> IO a 

Installs a useful posix signal handler for sigINT (i.e. Ctrl-C) for cases when the UserInterrupt exception gets swallowed within a main loop, preventing the program from exiting.

The given callback should be a command which causes the main loop action to exit. For example:

Gtk.main `onSigINT` Gtk.mainQuit

If the signal handler was invoked, the program will exit with status 130 after the main loop action returns.

maybeHandleSigHUP :: IO () -> IO a -> IO a Source #

Installs the given function as a handler for SIGHUP, but only if this process is not running in a terminal (i.e. runnning as a daemon).

If not running as a daemon, then no handler is installed by maybeHandleSigHUP. The default handler for sigHUP exits the program, which is the correct thing to do.

handlePosixSignal :: Signal -> IO () -> IO a -> IO a Source #

Install a handler for the given POSIX Signal while the given IO action is running, then restore the original handler.

This function is for handling non-critical signals.

The given callback function won't be run immediately within the sigaction handler, but will instead be posted to the GLib main loop.

Resource management

rebracket :: IO (IO (), r) -> (IO r -> IO a) -> IO a Source #

A variant of bracket which allows for reloading.

The first parameter is an allocation function which returns a newly created value of type r, paired with an IO action which will destroy that value.

The second parameter is the action to run. It is passed a "reload" function which will run the allocation function and return the newly created value.

Initially, there is no value. Reloading will cause the previous value (if any) to be destroyed. When the action completes, the current value (if any) will be destroyed.

rebracket_ :: IO (IO ()) -> (IO () -> IO a) -> IO a Source #

A variant of rebracket where the resource value isn't needed.

And because the resource value isn't needed, this variant will automatically allocate the resource before running the enclosed action.

Deprecated

logPrintFDebug :: (MonadIO m, Show t) => String -> String -> t -> m () Source #

Deprecated: Use logPrintF instead

liftReader :: Monad m => (m1 a -> m b) -> ReaderT r m1 a -> ReaderT r m b Source #

Deprecated: Use Control.Monad.Trans.Reader.mapReaderT instead

liftActionTaker :: Monad m => ((a -> m a) -> m b) -> (a -> ReaderT c m a) -> ReaderT c m b Source #

(??) :: Functor f => f (a -> b) -> a -> f b infixl 4 Source #

Deprecated: Use f * pure a instead

runCommandFromPath :: MonadIO m => FilePath -> [String] -> m (Either String String) Source #

Deprecated: Use runCommand instead