i3ipc-0.2.0.0: A type-safe wrapper around i3's IPC

Copyright(c) 2019 Evan Cameron
LicenseBSD3
MaintainerEvan Cameron <cameron.evan@gmail.com>
Safe HaskellNone
LanguageHaskell2010

I3IPC

Contents

Description

Types and functions for interacting with i3's IPC mechanism

Synopsis

Subscribe to events

Commonly, you just want to subscribe to a set of event types and do something with the response:

import qualified I3IPC.Subscribe               as Sub
import           I3IPC.Event
import           I3IPC                          ( subscribe )
import           Control.Monad.IO.Class 

main :: IO ()
main = liftIO $ subscribe handle [Sub.Workspace, Sub.Window]
 where
  handle :: Either String Event -> IO ()
  handle (Right evt) = case evt of
    Workspace WorkspaceEvent { wrk_current } -> print wrk_current
    Window WindowEvent { win_container } -> print win_container
    _ -> error "No other event types"
  handle (Left err) = error err

Sending messages

Other times, you want to send some kind of command to i3, or get a specific response as a one-time action.

import           I3IPC              ( connecti3
                                    , getWorkspaces
                                    )
import           Control.Monad.IO.Class 

main :: IO ()
main = do
    soc <- liftIO $ connecti3
    print getWorkspaces

Convenience functions

All of the "getX" functions are provided for convenience, but also exported are the building blocks to write whatever you like. There are strict and non-strict variants provided, the tick (') implies strict. For instance, the above could be written as:

import qualified I3IPC.Message     as Msg
import           I3IPC              ( connecti3
                                    , receiveMsg
                                    )
import           Control.Monad.IO.Class 

main :: IO ()
main = do
    soc <- liftIO $ connecti3
    print $ Msg.sendMsg soc Msg.Workspaces >> receiveMsg soc

getSocketPath :: MonadIO m => m (Maybe ByteString) Source #

Get a new unix socket path from i3

getSwaySocketPath :: MonadIO m => m (Maybe ByteString) Source #

Get a new unix socket path from sway

data Response Source #

Useful for when you are receiving Events or Messages.

Constructors

Message MsgReply 
Event Event 
Instances
Eq Response Source # 
Instance details

Defined in I3IPC

Show Response Source # 
Instance details

Defined in I3IPC

subscribe :: (MonadThrow m, MonadIO m) => (Either String Event -> m ()) -> [Subscribe] -> m () Source #

Subscribe with a list of Subscribe types, and subscribe will to respond with specific Event

subscribeM :: (MonadThrow m, MonadIO m) => (Either String Event -> m ()) -> [Subscribe] -> m () Source #

A version of subscribe that allows the use of any monad transformer on top of MonadIO (kept around for backwards compatibility)

receive :: MonadIO m => Socket -> m (Either String Response) Source #

Parse response from socket, returning either an error or a Response, representing a sum type of a MsgReply or Event

receive' :: MonadIO m => Socket -> m (Either String Response) Source #

Like receive but strict-- will use eitherDecode' under the hood to parse

receiveMsg :: MonadIO m => Socket -> m (Either String MsgReply) Source #

Receive but specifically for msgs, for when you know the response won't include any Events

receiveMsg' :: MonadIO m => Socket -> m (Either String MsgReply) Source #

Like receiveMsg but strict-- uses eitherDecode'

getReply :: MonadIO m => Socket -> m (Either String (Int, ByteString)) Source #

Get and parse the response using i3's IPC

connecti3 :: (MonadThrow m, MonadIO m) => m Socket Source #

Connect to an i3 socket and return it

connectsway :: (MonadThrow m, MonadIO m) => m Socket Source #

Connect to SWAY socket and return it

receiveEvent :: MonadIO m => Socket -> m (Either String Event) Source #

receive specifically for Event

receiveEvent' :: MonadIO m => Socket -> m (Either String Event) Source #

like receiveEvent but strict-- uses eitherDecode'

runCommand :: MonadIO m => Socket -> ByteString -> m (Either String MsgReply) Source #

Run a command represented as a ByteString, all the following functions are convenience wrappers around

Msg.sendMsgPayload soc Msg.X b >> receiveMsg soc

Or, if there is no message body:

Msg.sendMsg soc Msg.X >> receiveMsg soc

getBarConfig :: MonadIO m => Socket -> ByteString -> m (Either String MsgReply) Source #

Get a bar's config based on it's id