helic-0.5.2.0: Clipboard Manager
Safe HaskellNone
LanguageHaskell2010

Helic

Description

A clipboard management CLI tool built with Polysemy, Servant and GI.Gtk.

Synopsis

Documentation

Helic is primarily a CLI tool that listens for clipboard events and broadcasts them to other hosts and tmux.

The program is built with Polysemy, so its effects and interpreters may be useful for other developers. Some utilities for interfacing with GTK are exposed as well.

data Agent :: Effect Source #

An agent is an interface to an external entity that can receive clipboard events. The Helic CLI uses agents for remote hosts over network, tmux, and X11.

data AgentTag Source #

Used to disambiguate Agents via Tagged.

type Agents = [Tagged AgentTmux Agent, Tagged AgentX Agent, Tagged AgentNet Agent] Source #

The default agents for the Helic CLI.

XClipboard

data XClipboard :: Effect Source #

Communicate with the X11 clipboard.

Gtk

data Gtk s :: Effect Source #

This effect is a utility for running the GTK main loop in a resource-safe manner.

GtkMain

data GtkMain (s :: Type) :: Effect Source #

This effect is a communication bridge between Gtk and GTK functionality effects like GtkClipboard. It does not directly interact with the GTK API, but allows a scope to ensure that the GTK main loop is running and to access its resource (usually a display handle).

GtkClipboard

data GtkClipboard :: Effect Source #

This effect GtkClipboard allows an app to read from, write to, and subscribe to events from a clipboard. It is intended to be scoped with a GTK display by interpretWithGtk.

Interpreters

interpretAgentNet :: Members [Manager, Reader NetConfig] r => Members [Log, Interrupt, Race, Resource, Async, Embed IO, Final IO] r => InterpreterFor (Tagged AgentNet Agent) r Source #

Interpret Agent using remote hosts as targets. This also starts the HTTP server that listens to network events, which are used both for remote hosts and CLI events.

interpretAgentX :: Members [EventConsumer xr XClipboardEvent, Events er Event, Reader InstanceName, XClipboard !! Text, ChronosTime] r => Members [Events xr XClipboardEvent, Log, Error Text, Race, Resource, Async, Embed IO, Final IO] r => InterpreterFor (Tagged AgentX Agent) r Source #

Interpret Agent using the X11 clipboard as target. This interpreter also runs a thread that converts events generated by the XClipboard interpreter (XClipboardEvent) to the main Event type.

interpretXClipboardGtk :: Members [Scoped resource GtkClipboard !! Text, Log, Embed IO, Final IO] r => InterpreterFor (XClipboard !! Text) r Source #

Interpret XClipboard using a GTK backend. This uses the library gi-gtk to access the X11 clipboard.

interpretGtk :: Members [Resource, Log, Embed IO] r => X11Config -> InterpreterFor (Scoped Display (Gtk Display) !! Text) r Source #

Interpret Gtk natively, using the GI.Gtk and Gi.Gdk libraries. This uses Scoped to bracket the initialization and termination of the GTK environment.

interpretGtkMain :: forall s wait restart r. TimeUnit wait => TimeUnit restart => Members [Resource, Race, Embed IO] r => wait -> restart -> InterpreterFor (GtkMain s) r Source #

Interpret the GTK main loop communication bridge with MVars.

handleGtkMain :: forall s wait restart e m r a. TimeUnit wait => TimeUnit restart => Members [Resource, Sync GtkLock, Sync StartGtkMain, Sync (GtkResource s)] r => wait -> restart -> GtkMain s m a -> Tactical e m r a Source #

Interpret the GTK main loop communication bridge with MVars.

interpretGtkClipboard :: Members [GtkMain Display, Log, Embed IO, Final IO] r => InterpreterFor (Scoped Display GtkClipboard !! Text) r Source #

Native interpreter for GtkClipboard that requires the effect to be used within a withGtkClipboard region.

handleGtkClipboard :: Members [Log, Embed IO, Final IO] r => Display -> GtkClipboard (Sem r0) a -> Tactical effect (Sem r0) (Stop Text ': r) a Source #

This handler for GtkClipboard depends on a Display, which should optimally be provided by a Scoped interpreter to ensure safe acquisition of the resource. The effect then needs to be scoped using withGtkClipboard. The default implementation for this purpose is interpretWithGtk.

Data

data Event Source #

The central data type representing a clipboard event.

Instances

Instances details
Eq Event Source # 
Instance details

Defined in Helic.Data.Event

Methods

(==) :: Event -> Event -> Bool #

(/=) :: Event -> Event -> Bool #

Show Event Source # 
Instance details

Defined in Helic.Data.Event

Methods

showsPrec :: Int -> Event -> ShowS #

show :: Event -> String #

showList :: [Event] -> ShowS #

ToJSON Event Source # 
Instance details

Defined in Helic.Data.Event

FromJSON Event Source # 
Instance details

Defined in Helic.Data.Event

data Selection Source #

This type enumerates the different types of basic clipboards that X11 operates on.

Constructors

Clipboard

Usually the target of explicit copy commands (ctrl-c).

Primary

Stores the cursor selection.

Secondary

Only used in exotic situations.

Utilities

subscribeToClipboard :: Members [Reader Display, Log, Stop Text, Embed IO, Final IO] r => (Selection -> Text -> Sem r ()) -> Selection -> Sem r () Source #

Listen to clipboard events for a specific source, like "primary selection", and pass them to the callback.

gtkMainLoop :: Members [Scoped resource (Gtk s) !! Text, GtkMain s, Log, Race, Resource, Async] r => Sem r () -> Sem r a -> Sem r a Source #

Run loopGtkMain in a thread.

type Api = "event" :> (Get '[JSON] [Event] :<|> ((ReqBody '[JSON] Event :> PostCreated '[JSON] NoContent) :<|> (ReqBody '[JSON] Int :> PutAccepted '[JSON] (Maybe Event)))) Source #

The Servant API of the daemon, providing endpoints for getting all events and creating one.

serve :: Members [History, Reader NetConfig, Sync ServerReady, Log, Interrupt, Final IO] r => Sem r () Source #

Run the daemon API.

listen :: Members [EventConsumer token Event, History, Sync Listening] r => Sem r () Source #

Listen for Event via Events, broadcasting them to agents.

yank :: Members [Reader InstanceName, Client, ChronosTime, Error Text, Embed IO] r => YankConfig -> Sem r () Source #

Send an event to the server.