signal-messaging-dbus-1.0.0.2: Bindings for signal-cli's DBus interface
Copyright(c) Lia Lenckowski 2022
LicenseAGPL
Maintainerlialenck@protonmail.com
Stabilitystable
PortabilityGNU/Linux, MacOS
Safe HaskellNone
LanguageHaskell2010

SignalDBus

Description

This module is the main entry point for this library.

To get started, install and set up signal-cli, and make sure it's running in daemon mode, with the dbus interface enabled. Then, as an example, you could use the following code to react with "💀" to every message received from a specific user either via PM or in groups you're a member of:

import Control.Monad (forever, when)
import SignalDBus

reactWithSkull :: Timestamp -> String -> Maybe Group -> SignalConn -> IO Timestamp
reactWithSkull ts n mayG sc =
    case mayG of
        Nothing -> sendMessageReaction "💀" False n ts n sc
        Just g -> sendGroupMessageReaction "💀" False n ts g sc

-- react with 💀 to every message received by a specific user
main :: IO ()
main = do
    let num = "[insert phone number with country code]"
    withConn $ \sc -> do
        n <- getSelfNumber sc
        putStrLn $ "Running on: " ++ show n
        withReceiveMessages sc $ \getMsg -> forever $ do
            getMsg >>= \case
                Receipt _ _ -> return ()
                SyncMessage _ _ _ _ _ -> return ()
                Message ts n g _ _ -> when (n == num) $ do
                    reactWithSkull ts num g sc
                    return ()

    return ()

All of the functions exported may fail with a ClientError if something goes wrong. None of the functions should throw any other exception.

Quite a few of these functions have a scary-looking "UNTESTED" in their documentation. If you end up using any of those, and they work, please tell me so I can remove that disclaimer.

This package aims to provide somewhat direct bindings for all methods described by https://github.com/AsamK/signal-cli/blob/master/man/signal-cli-dbus.5.adoc. In cases where methods are overloaded, this library almost always chooses to implement the more general ones. Some functionality of the dbus interface of signal-cli isn't implemented, as it's either not documented or not often useful; if you require any of that, I'd recommend looking at SignalDBus.Interface.

Synopsis

Opening connections

withConn :: MonadUnliftIO m => (SignalConn -> m a) -> m a Source #

Run an action that requires a signal connection, and return its result

withConnNum :: MonadUnliftIO m => String -> (SignalConn -> m a) -> m a Source #

Like withConn, but you have to manually specify a phone number to use, which is useful if the signal daemon doesn't have a default number. This may not be used with a signal-cli daemon that has a default number configured.

Receiving Messages

withReceiveMessages :: MonadUnliftIO m => SignalConn -> (m ReceivedMessage -> m a) -> m a Source #

Run an action that receives a callback to receive new messages, and return its result. This will not yield messages that were received prior to calling this.

Control interface

These methods are only available if the signal-cli daemon was started in multi-account mode.

link :: MonadIO m => String -> SignalConn -> m String Source #

UNTESTED. Link this as a new device, identified by the given string.

listAccounts :: MonadIO m => SignalConn -> m [String] Source #

List accounts attached to this signal-cli instance

register :: MonadIO m => String -> Bool -> SignalConn -> m () Source #

UNTESTED. Register this as the primary device for the given number. Set the second argument to True to request voice verification instead of SMS verification.

registerWithCaptcha :: MonadIO m => String -> Bool -> String -> SignalConn -> m () Source #

UNTESTED. Same as register, but include a Captcha string.

verify Source #

Arguments

:: MonadIO m 
=> String

Phone number

-> String

Verification code

-> SignalConn

Connection object

-> m () 

UNTESTED. Verify your phone number after requesting registration via register or registerWithCaptcha

verifyWithPin Source #

Arguments

:: MonadIO m 
=> String

Phone number

-> String

Verification code

-> String

Pin

-> SignalConn

Connection object

-> m () 

UNTESTED. Same as verify, but include a registration pin for protected accounts

Account interface

These methods may only be called on a connection object that knows which account to use; that is, either the signal daemon has a default account, and you've used withConn, or it doesn't, and you've used withConnNum.

getContactName :: MonadIO m => String -> SignalConn -> m String Source #

Takes a number, and returns the name of the contact, empty if unknown

getContactNumber :: MonadIO m => String -> SignalConn -> m [String] Source #

Takes a contact name, and returns known numbers, both as strings

getSelfNumber :: MonadIO m => SignalConn -> m String Source #

Returns your own number

isContactBlocked :: MonadIO m => String -> SignalConn -> m Bool Source #

Returns true if you blocked this number

isRegistered :: MonadIO m => [String] -> SignalConn -> m [Bool] Source #

For each given number, returns whether that user is registered on Signal

listNumbers :: MonadIO m => SignalConn -> m [String] Source #

List all known numbers (e.g. group members and senders of received messages)

removePin :: MonadIO m => SignalConn -> m () Source #

UNTESTED. Removes registration pin protection.

sendEndSessionMessage :: MonadIO m => SignalConn -> m () Source #

UNTESTED. No idea what this accomplishes, so hmu if you know. It's implemented though

sendMessage Source #

Arguments

:: MonadIO m 
=> String

Message content

-> [String]

Paths to attachments. Resolves using the working dir of the signal-cli daemon, not this process

-> [String]

Recipients

-> SignalConn

Connection object

-> m Timestamp

Timestamp of sent message

Sends a message, possibly with attachments, to a number of recipients

sendMessageReaction Source #

Arguments

:: MonadIO m 
=> String

Unicode grapheme cluster. Only tested with "😂"

-> Bool

Whether to remove a previously sent reaction instead of adding one

-> String

Author of the message you want to react to

-> Timestamp

Timestamp of message to react to

-> String

Phone numbers of recipient

-> SignalConn

Connection object

-> m Timestamp

Timestamp of reaction

Reacts to a message

sendNoteToSelfMessage Source #

Arguments

:: MonadIO m 
=> String

Message

-> [String]

Paths to attachments. Resolves using the working dir of the signal-cli daemon, not this process

-> SignalConn

Connection object

-> m Timestamp

Timestamp of sent message

Sends a message to yourself

sendReadReceipt :: MonadIO m => String -> [Timestamp] -> SignalConn -> m () Source #

Sends read receipts for the messages with the specified timestamps to the given phone number. These timestamps must belong to messages you received from that number.

sendViewedReceipt :: MonadIO m => String -> [Timestamp] -> SignalConn -> m () Source #

Sends viewed receipts for the messages with the specified timestamps to the given phone number. This is probably not what you want; sendReadReceipt seems to be the way to go.

sendRemoteDeleteMessage Source #

Arguments

:: MonadIO m 
=> Timestamp

Timestamp of message to delete

-> [String]

Recipients

-> SignalConn

Connection object

-> m Timestamp

Timestamp, can be used to identify corresponding replies

Delete one of you own private messages; also deletes them remotely on supported clients (Signal-desktop, Android/IOS apps, ...)

sendTyping :: MonadIO m => String -> Bool -> SignalConn -> m () Source #

Send updates about whether you're typing to the given number. NOTE: the boolean argument should be False to indicate you're typing, and True to clear the typing state

setContactBlocked :: MonadIO m => String -> Bool -> SignalConn -> m () Source #

UNTESTED. Sets whether a contact is blocked. This is only done locally, so this just disabled messages from that number from being forwarded via DBus.

setContactName :: a Source #

Not implemented, as the documentation doesn't state the type of the name (probably a String, but I dont feel like testing stuff rn)

deleteContact :: MonadIO m => String -> SignalConn -> m () Source #

UNTESTED. Probably deletes a contact, given by a phone number, or something.

deleteRecipient :: MonadIO m => String -> SignalConn -> m () Source #

UNTESTED. Idk what this does, but tell me if you know/have used this.

setExpirationTimer :: (MonadIO m, Integral i) => String -> i -> SignalConn -> m () Source #

Set seconds until messages to this recipient dissapear (on supported clients). Set to 0 to disable.

setPin :: MonadIO m => String -> SignalConn -> m () Source #

UNTESTED. Set registration pin to prevent others from registering your number.

submitRateLimitChallenge :: MonadIO m => String -> String -> SignalConn -> m () Source #

UNTESTED. Idk but seems to be useful for lifting rate limits

updateProfile Source #

Arguments

:: MonadIO m 
=> String

Given name

-> String

Family name

-> String

About message

-> String

Emoji for profile

-> String

Avatar file name. Resolves using the working dir of the signal-cli daemon, not this process

-> Bool

True if the avatar should be removed

-> SignalConn

Connection object

-> m () 

Update parts of your profile. You can leave any string field empty to keep the old value.

uploadStickerPack :: MonadIO m => String -> SignalConn -> m String Source #

UNTESTED. Uploads a sticker pack, given by the path to a manifest.json or zip file, and return the URL of the pack.

version :: MonadIO m => SignalConn -> m String Source #

Return version string of signal-cli. This also works for multi-account connections.

createGroup Source #

Arguments

:: MonadIO m 
=> String

Group name

-> [String]

Initial members

-> String

Avatar file name. Resolves using the working dir of the signal-cli daemon, not this process

-> SignalConn

Connection object

-> m Group

Group object

Create a group

getGroup :: MonadIO m => ByteString -> SignalConn -> m Group Source #

Get DBus object path for a group, given by its signal-internal binary identifier.

joinGroup :: MonadIO m => String -> SignalConn -> m () Source #

UNTESTED. Join a group given by an invite link. Behaviour of this depends on properties of the group; see "joinGroup" on https://github.com/AsamK/signal-cli/blob/master/man/signal-cli-dbus.5.adoc (latest commit while writing this: 34cc64f8ce97a63c859bd95faf6783422f14df61)

listGroups :: MonadIO m => SignalConn -> m [(Group, ByteString, String)] Source #

List known groups, represented as (group object, internal identifier, group name)

sendGroupMessage Source #

Arguments

:: MonadIO m 
=> String

Message content

-> [String]

Paths to attachments. Resolves using the working dir of the signal-cli daemon, not this process

-> Group

Group in which to send a message

-> SignalConn

Connection object

-> m Timestamp

Timestamp of sent message

Sends a message, possibly with attachments, to a group

sendGroupTyping :: MonadIO m => Group -> Bool -> SignalConn -> m () Source #

Send updates about whether you're typing to the given group. NOTE: the boolean argument should be False to indicate you're typing, and True to clear the typing state

sendGroupMessageReaction Source #

Arguments

:: MonadIO m 
=> String

Unicode grapheme cluster. Only tested with "😂"

-> Bool

Whether to remove a previously sent reaction instead of adding one

-> String

Author of the message you want to react to

-> Timestamp

Timestamp of message to react to

-> Group

Group in which to react

-> SignalConn

Connection object

-> m Timestamp

Timestamp of reaction

Reacts to a message

sendGroupRemoteDeleteMessage Source #

Arguments

:: MonadIO m 
=> Timestamp

Timestamp of message to delete

-> Group

Group in which to delete your message

-> SignalConn

Connection object

-> m Timestamp

Timestamp, can be used to identify corresponding replies

Delete one of you own group messages; also deletes them remotely on supported clients (Signal-desktop, Android/IOS apps, ...)

addDevice :: MonadIO m => String -> SignalConn -> m () Source #

UNTESTED. Add a device that wants to link to this account using a link

getDevice :: MonadIO m => Int64 -> SignalConn -> m ObjectPath Source #

Get DBus object path for a device given by a device ID

listDevices :: MonadIO m => SignalConn -> m [(ObjectPath, Int64, String)] Source #

List devices linked with this account, represented as (object path, device id, device name)

Group interface

getGroupId :: MonadIO m => Group -> SignalConn -> m ByteString Source #

Byte array representing the internal group identifier

getGroupName :: MonadIO m => Group -> SignalConn -> m String Source #

Display name

getGroupIsBlocked :: MonadIO m => Group -> SignalConn -> m Bool Source #

UNTESTED. If true, messages won't be forwarded via DBus

getGroupIsAdmin :: MonadIO m => Group -> SignalConn -> m Bool Source #

Whether this account is a group admin

getGroupMessageExpirationTimer :: MonadIO m => Group -> SignalConn -> m Int Source #

Message expiration timer. 0 if disabled

getGroupMembers :: MonadIO m => Group -> SignalConn -> m [String] Source #

List of group members' phone numbers

getGroupPendingMembers :: MonadIO m => Group -> SignalConn -> m [String] Source #

UNTESTED. List of pending group members; I don't know what this does, but I imagine you're probably looking for getGroupRequestingMembers

getGroupRequestingMembers :: MonadIO m => Group -> SignalConn -> m [String] Source #

List of phone numbers requesting to join the group, if theres an invite link set to require admin approval

getGroupAdmins :: MonadIO m => Group -> SignalConn -> m [String] Source #

List of group admins' phone numbers

getGroupPermissionAddMember :: MonadIO m => Group -> SignalConn -> m String Source #

String representing who has permission to add members (one of ONLY_ADMINS, EVERY_MEMBER)

getGroupPermissionEditDetails :: MonadIO m => Group -> SignalConn -> m String Source #

String representing who has permission to edit group description (one of ONLY_ADMINS, EVERY_MEMBER)

getGroupPermissionSendMessage :: MonadIO m => Group -> SignalConn -> m String Source #

String representing who has permission to send messages (one of ONLY_ADMINS, EVERY_MEMBER)

getGroupInviteLink :: MonadIO m => Group -> SignalConn -> m String Source #

Group invitation link. Empty if disabled

setGroupName :: MonadIO m => String -> Group -> SignalConn -> m () Source #

Display name

setGroupDescription :: MonadIO m => String -> Group -> SignalConn -> m () Source #

Description

setGroupAvatar :: MonadIO m => String -> Group -> SignalConn -> m () Source #

Filename of group avatar. Resolves using the working dir of the signal-cli daemon, not this process

setGroupIsBlocked :: MonadIO m => Bool -> Group -> SignalConn -> m () Source #

UNTESTED. If true, messages won't be forwarded via DBus

setGroupMessageExpirationTimer :: MonadIO m => Int -> Group -> SignalConn -> m () Source #

Message expiration timer. 0 to disable

setGroupPermissionAddMember :: MonadIO m => String -> Group -> SignalConn -> m () Source #

String representing who has permission to add members (one of ONLY_ADMINS, EVERY_MEMBER)

setGroupPermissionEditDetails :: MonadIO m => String -> Group -> SignalConn -> m () Source #

String representing who has permission to edit group description (one of ONLY_ADMINS, EVERY_MEMBER)

setGroupPermissionSendMessage :: MonadIO m => String -> Group -> SignalConn -> m () Source #

String representing who has permission to send messages (one of ONLY_ADMINS, EVERY_MEMBER)

groupAddAdmins :: MonadIO m => [String] -> Group -> SignalConn -> m () Source #

Add admins

groupAddMembers :: MonadIO m => [String] -> Group -> SignalConn -> m () Source #

Add numbers who are pending members to the group, and other numbers to requesting members list

groupDisableLink :: MonadIO m => Group -> SignalConn -> m () Source #

Disable group invitation link

groupEnableLink :: MonadIO m => Bool -> Group -> SignalConn -> m () Source #

Enable group invitation link. If the argument is true, users cannot join directly, but are added to the requesting members list first.

groupQuit :: MonadIO m => Group -> SignalConn -> m () Source #

Quit the group

groupRemoveAdmins :: MonadIO m => [String] -> Group -> SignalConn -> m () Source #

Remove admins

groupRemoveMembers :: MonadIO m => [String] -> Group -> SignalConn -> m () Source #

Remove numbers from the group

groupResetLink :: MonadIO m => Group -> SignalConn -> m () Source #

Reset the group invitation link

Types

data SignalConn Source #

Opaque connection object, aquired by withConn or withConnNum

data Timestamp Source #

Timestamp, represented as an ms-precision unix timestamp

data Device Source #

Opaque object representing a linked device

Instances

Instances details
Eq Device Source # 
Instance details

Defined in SignalDBus.Types

Methods

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

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

Read Device Source # 
Instance details

Defined in SignalDBus.Types

Show Device Source # 
Instance details

Defined in SignalDBus.Types

IsVariant Device Source # 
Instance details

Defined in SignalDBus.Types

IsValue Device Source # 
Instance details

Defined in SignalDBus.Types

data Group Source #

Opaque Group object, aquired by listGroups or getGroup

Instances

Instances details
Eq Group Source # 
Instance details

Defined in SignalDBus.Types

Methods

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

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

Ord Group Source # 
Instance details

Defined in SignalDBus.Types

Methods

compare :: Group -> Group -> Ordering #

(<) :: Group -> Group -> Bool #

(<=) :: Group -> Group -> Bool #

(>) :: Group -> Group -> Bool #

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

max :: Group -> Group -> Group #

min :: Group -> Group -> Group #

Read Group Source # 
Instance details

Defined in SignalDBus.Types

Show Group Source # 
Instance details

Defined in SignalDBus.Types

Methods

showsPrec :: Int -> Group -> ShowS #

show :: Group -> String #

showList :: [Group] -> ShowS #

IsVariant Group Source # 
Instance details

Defined in SignalDBus.Types

IsValue Group Source # 
Instance details

Defined in SignalDBus.Types

data ReceivedMessage Source #

Received message

Constructors

SyncMessage

Message sent by a linked device to someone else

Fields

  • Timestamp

    When this message was sent

  • String

    Message sender (TODO: always yourself?)

  • (Maybe Group)

    If sent in a group, corresponding group object

  • String

    Message text

  • [String]

    Paths to stored attachments

Receipt

Read receipt sent by someone else in response to one of your messages

Fields

Message

Message sent to you by someone else

Fields