module I3IPC.Reply where
import GHC.Generics
import Control.Monad ( mzero )
import Data.Aeson
import Data.Aeson.Encoding ( text )
import qualified Data.ByteString.Lazy as BL
import Data.Int
import Data.Map.Strict ( Map )
import Data.Vector ( Vector )
import Data.Text ( Text )
data MsgReply =
RunCommand !Success
| Workspaces !WorkspaceReply
| Subscribe !Success
| Outputs !OutputsReply
| Tree !Node
| Marks !MarksReply
| BarConfig !BarConfigReply
| Version !VersionReply
| BindingModes !BindingModesReply
| Config !ConfigReply
| Tick !Success
| Sync !Success
deriving (Show, Eq)
toMsgReply' :: Int -> BL.ByteString -> Either String MsgReply
toMsgReply' 0 = (RunCommand <$>) . eitherDecode'
toMsgReply' 1 = (Workspaces <$>) . eitherDecode'
toMsgReply' 2 = (Subscribe <$>) . eitherDecode'
toMsgReply' 3 = (Outputs <$>) . eitherDecode'
toMsgReply' 4 = (Tree <$>) . eitherDecode'
toMsgReply' 5 = (Marks <$>) . eitherDecode'
toMsgReply' 6 = (BarConfig <$>) . eitherDecode'
toMsgReply' 7 = (Version <$>) . eitherDecode'
toMsgReply' 8 = (BindingModes <$>) . eitherDecode'
toMsgReply' 9 = (Config <$>) . eitherDecode'
toMsgReply' 10 = (Tick <$>) . eitherDecode'
toMsgReply' 11 = (Sync <$>) . eitherDecode'
toMsgReply' _ = error "Unknown Event type found"
toMsgReply :: Int -> BL.ByteString -> Either String MsgReply
toMsgReply 0 = (RunCommand <$>) . eitherDecode
toMsgReply 1 = (Workspaces <$>) . eitherDecode
toMsgReply 2 = (Subscribe <$>) . eitherDecode
toMsgReply 3 = (Outputs <$>) . eitherDecode
toMsgReply 4 = (Tree <$>) . eitherDecode
toMsgReply 5 = (Marks <$>) . eitherDecode
toMsgReply 6 = (BarConfig <$>) . eitherDecode
toMsgReply 7 = (Version <$>) . eitherDecode
toMsgReply 8 = (BindingModes <$>) . eitherDecode
toMsgReply 9 = (Config <$>) . eitherDecode
toMsgReply 10 = (Tick <$>) . eitherDecode
toMsgReply 11 = (Sync <$>) . eitherDecode
toMsgReply _ = error "Unknown Event type found"
decodeBarIds :: BL.ByteString -> Either String BarIds
decodeBarIds = eitherDecode
data Success = Success {
success :: !Bool
} deriving (Eq, Show, Generic, FromJSON)
instance ToJSON Success where
toEncoding = genericToEncoding defaultOptions
data WorkspaceReply = WorkspaceReply !(Vector Workspace) deriving (Eq, Generic, Show)
instance ToJSON WorkspaceReply where
toEncoding = genericToEncoding defaultOptions
instance FromJSON WorkspaceReply where
parseJSON = genericParseJSON defaultOptions
data Workspace = Workspace {
ws_num :: !Int32
, ws_name :: !Text
, ws_visible :: !Bool
, ws_focused :: !Bool
, ws_urgent :: !Bool
, ws_rect :: !Rect
, ws_output :: !Text
} deriving (Eq, Generic, Show)
instance ToJSON Workspace where
toEncoding =
genericToEncoding defaultOptions { fieldLabelModifier = drop 3 }
instance FromJSON Workspace where
parseJSON = genericParseJSON defaultOptions { fieldLabelModifier = drop 3 }
data OutputsReply = OutputsReply !(Vector Output) deriving (Eq, Generic, Show)
instance ToJSON OutputsReply where
toEncoding = genericToEncoding defaultOptions
instance FromJSON OutputsReply where
parseJSON = genericParseJSON defaultOptions
data Output = Output {
output_name :: !Text
, output_active :: !Bool
, output_primary :: !Bool
, output_current_workspace :: !(Maybe Text)
, output_rect :: !Rect
} deriving (Eq, Show, Generic)
instance ToJSON Output where
toEncoding =
genericToEncoding defaultOptions { fieldLabelModifier = drop 7 }
instance FromJSON Output where
parseJSON = genericParseJSON defaultOptions { fieldLabelModifier = drop 7 }
data Node = Node {
node_id :: !Int
, node_name :: !(Maybe Text)
, node_type :: !NodeType
, node_output :: !(Maybe Text)
, node_orientation :: !NodeOrientation
, node_border :: !NodeBorder
, node_current_border_width :: !Int32
, node_layout :: !NodeLayout
, node_percent :: !(Maybe Float)
, node_rect :: !Rect
, node_window_rect :: !Rect
, node_deco_rect :: !Rect
, node_geometry :: !Rect
, node_window :: !(Maybe Int32)
, node_window_properties :: !(Maybe (Map WindowProperty (Maybe Text)))
, node_urgent :: !Bool
, node_focused :: !Bool
, node_focus :: !(Vector Int64)
, node_sticky :: !Bool
, node_floating_nodes :: !(Vector Node)
, node_nodes :: !(Vector Node)
} deriving (Eq, Generic, Show)
data NodeOrientation =
Horizontal
| Vertical
| OrientNone
deriving (Eq, Generic, Show)
instance FromJSON NodeOrientation where
parseJSON (String s) = pure $! case s of
"none" -> OrientNone
"horizontal" -> Horizontal
"vertical" -> Vertical
_ -> error "Unrecognized NodeOrientation"
parseJSON _ = mzero
instance ToJSON NodeOrientation where
toEncoding = \case
OrientNone -> text "none"
Vertical -> text "vertical"
Horizontal -> text "horizontal"
instance ToJSON Node where
toEncoding =
genericToEncoding defaultOptions { fieldLabelModifier = drop 5 }
instance FromJSON Node where
parseJSON = genericParseJSON defaultOptions { fieldLabelModifier = drop 5 }
data WindowProperty =
Title
| Instance
| Class
| WindowRole
| TransientFor
deriving (Eq, Enum, Ord, Generic, Show)
instance FromJSONKey WindowProperty where
fromJSONKey = FromJSONKeyText f
where
f x = case x of
"title" -> Title
"instance" -> Instance
"class" -> Class
"window_role" -> WindowRole
"transient_for" -> TransientFor
_ -> error "Unrecognized window property"
instance ToJSONKey WindowProperty where
toJSONKey = ToJSONKeyText f g
where
f x = case x of
Title -> "title"
Instance -> "instance"
Class -> "class"
WindowRole -> "window_role"
TransientFor -> "transient_for"
g x = case x of
Title -> text "title"
Instance -> text "instance"
Class -> text "class"
WindowRole -> text "window_role"
TransientFor -> text "transient_for"
instance FromJSON WindowProperty where
parseJSON (String s) = pure $! case s of
"title" -> Title
"instance" -> Instance
"class" -> Class
"window_role" -> WindowRole
"transient_for" -> TransientFor
_ -> error "Unrecognized WindowProperty variant found"
parseJSON _ = mzero
instance ToJSON WindowProperty where
toEncoding = \case
Title -> text "title"
Instance -> text "instance"
Class -> text "class"
WindowRole -> text "window_role"
TransientFor -> text "transient_for"
data MarksReply = MarksReply !(Vector Text) deriving (Eq, Generic, Show, FromJSON)
instance ToJSON MarksReply where
toEncoding = genericToEncoding defaultOptions
data NodeBorder =
Normal
| None
| Pixel
deriving (Eq, Generic, Show)
instance ToJSON NodeBorder where
toEncoding = \case
Normal -> text "normal"
None -> text "none"
Pixel -> text "pixel"
instance FromJSON NodeBorder where
parseJSON (String s) = pure $! case s of
"normal" -> Normal
"none" -> None
"pixel" -> Pixel
_ -> error "Unrecognized NodeBorder found"
parseJSON _ = mzero
data Rect = Rect {
x :: !Int32
, y :: !Int32
, width :: !Int32
, height :: !Int32
} deriving (Eq, Generic, Show, FromJSON)
instance ToJSON Rect where
toEncoding = genericToEncoding defaultOptions
data NodeType =
RootType
| OutputType
| ConType
| FloatingConType
| WorkspaceType
| DockAreaType
deriving (Eq, Generic, Show)
instance ToJSON NodeType where
toEncoding = \case
RootType -> text "root"
OutputType -> text "output"
ConType -> text "con"
FloatingConType -> text "floating_con"
WorkspaceType -> text "workspace"
DockAreaType -> text "dockarea"
instance FromJSON NodeType where
parseJSON (String s) = pure $! case s of
"root" -> RootType
"output" -> OutputType
"con" -> ConType
"floating_con" -> FloatingConType
"workspace" -> WorkspaceType
"dockarea" -> DockAreaType
_ -> error "Received unrecognized NodeType"
parseJSON _ = mzero
data NodeLayout =
SplitHorizontalLayout
| SplitVerticalLayout
| StackedLayout
| TabbedLayout
| DockAreaLayout
| OutputLayout
deriving (Eq, Generic, Show)
instance ToJSON NodeLayout where
toEncoding = \case
SplitHorizontalLayout -> text "splith"
SplitVerticalLayout -> text "splitv"
StackedLayout -> text "stacked"
TabbedLayout -> text "tabbed"
DockAreaLayout -> text "dockarea"
OutputLayout -> text "output"
instance FromJSON NodeLayout where
parseJSON (String s) = pure $! case s of
"splith" -> SplitHorizontalLayout
"splitv" -> SplitVerticalLayout
"stacked" -> StackedLayout
"tabbed" -> TabbedLayout
"dockarea" -> DockAreaLayout
"output" -> OutputLayout
_ -> error "Received unrecognized NodeLayout"
parseJSON _ = mzero
data BarIds = BarIds !(Vector Text) deriving (Eq, Generic, Show)
instance ToJSON BarIds where
toEncoding = genericToEncoding defaultOptions
instance FromJSON BarIds where
parseJSON = genericParseJSON defaultOptions
data BarConfigReply = BarConfigReply {
bar_id :: !Text
, bar_mode :: !Text
, bar_position :: !Text
, bar_status_command :: !Text
, bar_font :: !Text
, bar_workspace_buttons :: !Bool
, bar_binding_mode_indicator :: !Bool
, bar_verbose :: !Bool
, bar_colors :: !(Map BarPart Text)
} deriving (Eq, Generic, Show)
instance ToJSON BarConfigReply where
toEncoding =
genericToEncoding defaultOptions { fieldLabelModifier = drop 4 }
instance FromJSON BarConfigReply where
parseJSON = genericParseJSON defaultOptions { fieldLabelModifier = drop 4 }
data BarPart =
Background
| Statusline
| Separator
| FocusedBackground
| FocusedStatusline
| FocusedSeparator
| FocusedWorkspaceText
| FocusedWorkspaceBg
| FocusedWorkspaceBorder
| ActiveWorkspaceText
| ActiveWorkspaceBg
| ActiveWorkspaceBorder
| InactiveWorkspaceText
| InactiveWorkspaceBg
| InactiveWorkspaceBorder
| UrgentWorkspaceText
| UrgentWorkspaceBg
| UrgentWorkspaceBorder
| BindingModeText
| BindingModeBg
| BindingModeBorder
deriving (Eq, Enum, Ord, Generic, Show, FromJSONKey)
instance ToJSONKey BarPart where
toJSONKey = ToJSONKeyText f g
where
f x = case x of
Background -> "background"
Statusline -> "statusline"
Separator -> "separator"
FocusedBackground -> "focused_background"
FocusedStatusline -> "focused_statusline"
FocusedSeparator -> "focused_separator"
FocusedWorkspaceText -> "focused_workspace_text"
FocusedWorkspaceBg -> "focused_workspace_bg"
FocusedWorkspaceBorder -> "focused_workspace_border"
ActiveWorkspaceText -> "active_workspace_text"
ActiveWorkspaceBg -> "active_workspace_bg"
ActiveWorkspaceBorder -> "active_workspace_border"
InactiveWorkspaceText -> "inactive_workspace_text"
InactiveWorkspaceBg -> "inactive_workspace_bg"
InactiveWorkspaceBorder -> "inactive_workspace_border"
UrgentWorkspaceText -> "urgent_workspace_text"
UrgentWorkspaceBg -> "urgent_workspace_bg"
UrgentWorkspaceBorder -> "urgent_workspace_border"
BindingModeText -> "binding_mode_text"
BindingModeBg -> "binding_mode_bg"
BindingModeBorder -> "binding_mode_border"
g x = case x of
Background -> text "background"
Statusline -> text "statusline"
Separator -> text "separator"
FocusedBackground -> text "focused_background"
FocusedStatusline -> text "focused_statusline"
FocusedSeparator -> text "focused_separator"
FocusedWorkspaceText -> text "focused_workspace_text"
FocusedWorkspaceBg -> text "focused_workspace_bg"
FocusedWorkspaceBorder -> text "focused_workspace_border"
ActiveWorkspaceText -> text "active_workspace_text"
ActiveWorkspaceBg -> text "active_workspace_bg"
ActiveWorkspaceBorder -> text "active_workspace_border"
InactiveWorkspaceText -> text "inactive_workspace_text"
InactiveWorkspaceBg -> text "inactive_workspace_bg"
InactiveWorkspaceBorder -> text "inactive_workspace_border"
UrgentWorkspaceText -> text "urgent_workspace_text"
UrgentWorkspaceBg -> text "urgent_workspace_bg"
UrgentWorkspaceBorder -> text "urgent_workspace_border"
BindingModeText -> text "binding_mode_text"
BindingModeBg -> text "binding_mode_bg"
BindingModeBorder -> text "binding_mode_border"
instance FromJSON BarPart where
parseJSON (String s) = pure $! case s of
"background" -> Background
"statusline" -> Statusline
"separator" -> Separator
"focused_background" -> FocusedBackground
"focused_statusline" -> FocusedStatusline
"focused_separator" -> FocusedSeparator
"focused_workspace_text" -> FocusedWorkspaceText
"focused_workspace_bg" -> FocusedWorkspaceBg
"focused_workspace_border" -> FocusedWorkspaceBorder
"active_workspace_text" -> ActiveWorkspaceText
"active_workspace_bg" -> ActiveWorkspaceBg
"active_workspace_border" -> ActiveWorkspaceBorder
"inactive_workspace_text" -> InactiveWorkspaceText
"inactive_workspace_bg" -> InactiveWorkspaceBg
"inactive_workspace_border" -> InactiveWorkspaceBorder
"urgent_workspace_text" -> UrgentWorkspaceText
"urgent_workspace_bg" -> UrgentWorkspaceBg
"urgent_workspace_border" -> UrgentWorkspaceBorder
"binding_mode_text" -> BindingModeText
"binding_mode_bg" -> BindingModeBg
"binding_mode_border" -> BindingModeBorder
_ -> error "Unrecognized BarPart variant found"
parseJSON _ = mzero
instance ToJSON BarPart where
toEncoding = \case
Background -> text "background"
Statusline -> text "statusline"
Separator -> text "separator"
FocusedBackground -> text "focused_background"
FocusedStatusline -> text "focused_statusline"
FocusedSeparator -> text "focused_separator"
FocusedWorkspaceText -> text "focused_workspace_text"
FocusedWorkspaceBg -> text "focused_workspace_bg"
FocusedWorkspaceBorder -> text "focused_workspace_border"
ActiveWorkspaceText -> text "active_workspace_text"
ActiveWorkspaceBg -> text "active_workspace_bg"
ActiveWorkspaceBorder -> text "active_workspace_border"
InactiveWorkspaceText -> text "inactive_workspace_text"
InactiveWorkspaceBg -> text "inactive_workspace_bg"
InactiveWorkspaceBorder -> text "inactive_workspace_border"
UrgentWorkspaceText -> text "urgent_workspace_text"
UrgentWorkspaceBg -> text "urgent_workspace_bg"
UrgentWorkspaceBorder -> text "urgent_workspace_border"
BindingModeText -> text "binding_mode_text"
BindingModeBg -> text "binding_mode_bg"
BindingModeBorder -> text "binding_mode_border"
data VersionReply = VersionReply {
v_major :: !Int32
, v_minor :: !Int32
, v_patch :: !Int32
, v_human_readable :: !Text
, v_loaded_config_file_name :: !Text
} deriving (Eq, Generic, Show)
instance ToJSON VersionReply where
toEncoding =
genericToEncoding defaultOptions { fieldLabelModifier = drop 2 }
instance FromJSON VersionReply where
parseJSON = genericParseJSON defaultOptions { fieldLabelModifier = drop 2 }
data BindingModesReply = BindingModesReply !(Vector Text) deriving (Eq, Generic, Show)
instance ToJSON BindingModesReply where
toEncoding = genericToEncoding defaultOptions
instance FromJSON BindingModesReply where
parseJSON = genericParseJSON defaultOptions
data ConfigReply = ConfigReply {
c_config :: !Text
} deriving (Eq, Generic, Show)
instance ToJSON ConfigReply where
toEncoding =
genericToEncoding defaultOptions { fieldLabelModifier = drop 2 }
instance FromJSON ConfigReply where
parseJSON = genericParseJSON defaultOptions { fieldLabelModifier = drop 2 }