Copyright | (c) Ivan A. Malison |
---|---|
License | BSD3-style (see LICENSE) |
Maintainer | Ivan A. Malison |
Stability | unstable |
Portability | unportable |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- logIO :: Priority -> String -> IO ()
- logT :: MonadTrans t => Priority -> String -> t IO ()
- type Taffy m v = MonadIO m => ReaderT Context m v
- type TaffyIO v = ReaderT Context IO v
- type Listener = Event -> Taffy IO ()
- type SubscriptionList = [(Unique, Listener)]
- data Value = Typeable t => Value t
- fromValue :: forall t. Typeable t => Value -> Maybe t
- data BarConfig = BarConfig {
- strutConfig :: StrutConfig
- widgetSpacing :: Int32
- startWidgets :: [TaffyIO Widget]
- centerWidgets :: [TaffyIO Widget]
- endWidgets :: [TaffyIO Widget]
- barId :: Unique
- type BarConfigGetter = TaffyIO [BarConfig]
- data TaffybarConfig = TaffybarConfig {
- dbusClientParam :: Maybe Client
- startupHook :: TaffyIO ()
- getBarConfigsParam :: BarConfigGetter
- errorMsg :: Maybe String
- appendHook :: TaffyIO () -> TaffybarConfig -> TaffybarConfig
- defaultTaffybarConfig :: TaffybarConfig
- data Context = Context {
- x11ContextVar :: MVar X11Context
- listeners :: MVar SubscriptionList
- contextState :: MVar (Map TypeRep Value)
- existingWindows :: MVar [(BarConfig, Window)]
- sessionDBusClient :: Client
- systemDBusClient :: Client
- getBarConfigs :: BarConfigGetter
- contextBarConfig :: Maybe BarConfig
- buildContext :: TaffybarConfig -> IO Context
- buildEmptyContext :: IO Context
- buildBarWindow :: Context -> BarConfig -> IO Window
- refreshTaffyWindows :: TaffyIO ()
- forceRefreshTaffyWindows :: TaffyIO ()
- asksContextVar :: (r -> MVar b) -> ReaderT r IO b
- runX11 :: X11Property a -> TaffyIO a
- runX11Def :: a -> X11Property a -> TaffyIO a
- runX11Context :: MonadIO m => Context -> a -> X11Property a -> m a
- getState :: forall t. Typeable t => Taffy IO (Maybe t)
- getStateDefault :: Typeable t => Taffy IO t -> Taffy IO t
- putState :: forall t. Typeable t => Taffy IO t -> Taffy IO t
- taffyFork :: ReaderT r IO () -> ReaderT r IO ()
- startX11EventHandler :: Taffy IO ()
- unsubscribe :: Unique -> Taffy IO ()
- subscribeToAll :: Listener -> Taffy IO Unique
- subscribeToEvents :: [String] -> Listener -> Taffy IO Unique
- handleX11Event :: Event -> Taffy IO ()
Documentation
type SubscriptionList = [(Unique, Listener)] Source #
BarConfig | |
|
type BarConfigGetter = TaffyIO [BarConfig] Source #
data TaffybarConfig Source #
TaffybarConfig | |
|
appendHook :: TaffyIO () -> TaffybarConfig -> TaffybarConfig Source #
Context | |
|
buildContext :: TaffybarConfig -> IO Context Source #
refreshTaffyWindows :: TaffyIO () Source #
runX11 :: X11Property a -> TaffyIO a Source #
runX11Def :: a -> X11Property a -> TaffyIO a Source #
runX11Context :: MonadIO m => Context -> a -> X11Property a -> m a Source #
getStateDefault :: Typeable t => Taffy IO t -> Taffy IO t Source #
Like "putState", but avoids aquiring a lock if the value is already in the map.
putState :: forall t. Typeable t => Taffy IO t -> Taffy IO t Source #
Get a value of the type returned by the provided action from the the current taffybar state, unless the state does not exist, in which case the action will be called to populate the state map.
startX11EventHandler :: Taffy IO () Source #