scuttlebutt-types-0.4.0: generic types for Secure Scuttlebutt

Safe HaskellNone
LanguageHaskell2010

Ssb.Types.Message

Synopsis

Documentation

data Message a Source #

Instances

Functor Message Source # 

Methods

fmap :: (a -> b) -> Message a -> Message b #

(<$) :: a -> Message b -> Message a #

Eq a => Eq (Message a) Source # 

Methods

(==) :: Message a -> Message a -> Bool #

(/=) :: Message a -> Message a -> Bool #

Show a => Show (Message a) Source # 

Methods

showsPrec :: Int -> Message a -> ShowS #

show :: Message a -> String #

showList :: [Message a] -> ShowS #

Generic (Message a) Source # 

Associated Types

type Rep (Message a) :: * -> * #

Methods

from :: Message a -> Rep (Message a) x #

to :: Rep (Message a) x -> Message a #

FromJSON a => FromJSON (Message a) Source # 
type Rep (Message a) Source # 

data AnyContent Source #

Parsing a Message AnyContent allows parsing the message envelope, regardless of the type of content in the message.

Constructors

AnyContent 

contentType :: Message AnyContent -> Text Source #

Get the declared type of content in a Message AnyContent.

parseMessage :: FromJSON a => ByteString -> Maybe (Hashed (Message a)) Source #

Parses a JSON formatted message, and accompanies it with the hash that was originally used for the message.

narrowParse :: FromJSON a => Message AnyContent -> Parser (Message a) Source #

For best efficiency when the type of a message is not known, first parse to a Message AnyContent, and then use this function with parseMaybe or parseEither to try to further parse that to different message types.

For example:

Just somemsg = decode b :: Maybe Message AnyContent
case parseMaybe narrowParse somemsg :: Maybe (Message Post) of
  Just postmsg -> ...
  Nothing -> case parseMaybe narrowParse somemsg :: Maybe (Message PrivateContent) of
    Just privmsg -> ...
    Nothing -> ...

data Post Source #

A post is a text-based message, for a public or private audience. It can be a reply to other posts.

Constructors

Post 

data UserLink Source #

A link to a user, sometimes including a name.

Constructors

UserLink 

data About Source #

About-messages set attributes about someone or something. They can be used to set a name or picture for users, files, or messages. However, they're most commonly published about users.

Constructors

About 

data AboutImage Source #

Instances

Eq AboutImage Source # 
Show AboutImage Source # 
Generic AboutImage Source # 

Associated Types

type Rep AboutImage :: * -> * #

FromJSON AboutImage Source #

AboutImage can be encoded as either a JSON object or as a string, which is the BlobLink.

type Rep AboutImage Source # 
type Rep AboutImage = D1 * (MetaData "AboutImage" "Ssb.Types.Message" "scuttlebutt-types-0.4.0-4uC52VfwcjR3IQF06ZafXe" False) (C1 * (MetaCons "AboutImage" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "aboutImageLink") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * BlobLink)) (S1 * (MetaSel (Just Symbol "aboutImageSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Int)))) ((:*:) * (S1 * (MetaSel (Just Symbol "aboutImageType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "aboutImageWidth") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Int))) (S1 * (MetaSel (Just Symbol "aboutImageHeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Int)))))))

data Contact Source #

Contact-messages determine who you are following or blocking.

Constructors

Contact 

Instances

data Vote Source #

Vote-messages signal approval about someone or something. Votes can be on users, messages, or blobs.

Constructors

Vote 

Instances

Eq Vote Source # 

Methods

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

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

Show Vote Source # 

Methods

showsPrec :: Int -> Vote -> ShowS #

show :: Vote -> String #

showList :: [Vote] -> ShowS #

Generic Vote Source # 

Associated Types

type Rep Vote :: * -> * #

Methods

from :: Vote -> Rep Vote x #

to :: Rep Vote x -> Vote #

FromJSON Vote Source # 
type Rep Vote Source # 
type Rep Vote = D1 * (MetaData "Vote" "Ssb.Types.Message" "scuttlebutt-types-0.4.0-4uC52VfwcjR3IQF06ZafXe" False) (C1 * (MetaCons "Vote" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "voteLink") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Link)) ((:*:) * (S1 * (MetaSel (Just Symbol "voteValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "voteExpression") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Text))))))

data Pub Source #

Constructors

Pub 

Fields

Instances

Eq Pub Source # 

Methods

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

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

Show Pub Source # 

Methods

showsPrec :: Int -> Pub -> ShowS #

show :: Pub -> String #

showList :: [Pub] -> ShowS #

Generic Pub Source # 

Associated Types

type Rep Pub :: * -> * #

Methods

from :: Pub -> Rep Pub x #

to :: Rep Pub x -> Pub #

FromJSON Pub Source # 
type Rep Pub Source # 
type Rep Pub = D1 * (MetaData "Pub" "Ssb.Types.Message" "scuttlebutt-types-0.4.0-4uC52VfwcjR3IQF06ZafXe" False) (C1 * (MetaCons "Pub" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "pubHost") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)) ((:*:) * (S1 * (MetaSel (Just Symbol "pubPort") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "pubKey") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * FeedLink)))))

parseMessageType :: Text -> (Value -> Parser a) -> Value -> Parser a Source #

Parse the content of a message using the provided Parser, which will typically be genericParseJSON defaultOptions.

The "type" field must contain the specified Text for the parse to succeed.