Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module provides a datatype and convenience functions for parsing, manipulating, and rendering deviantART Message Network messages.
Synopsis
- data Message = Message {}
- data SubMessage = SubMessage {}
- data MessageBody
- bodyBytes :: MessageBody -> ByteString
- type Formatter m = Either Text Lump -> m
- bodyWithFormat :: Monoid s => Formatter s -> MessageBody -> s
- toBody :: ByteString -> MessageBody
- toBodyText :: Text -> MessageBody
- subMessage :: MessageBody -> forall m. Monad m => m SubMessage
- pattern SubM :: SubMessage -> Maybe MessageBody
- parseMessage :: ByteString -> Either String Message
- messageP :: Parser Message
- render :: Message -> ByteString
- data Lump
- = A ByteString ByteString
- | C_A
- | Abbr ByteString
- | C_Abbr
- | Acro ByteString
- | C_Acro
- | Avatar ByteString ByteString
- | B
- | C_B
- | Bcode
- | C_Bcode
- | Br
- | Code
- | C_Code
- | Dev ByteString ByteString
- | Embed ByteString ByteString ByteString
- | C_Embed
- | Emote ByteString ByteString ByteString ByteString ByteString
- | I
- | C_I
- | Iframe ByteString ByteString ByteString
- | C_Iframe
- | Img ByteString ByteString ByteString
- | Li
- | C_Li
- | Link ByteString (Maybe ByteString)
- | Ol
- | C_Ol
- | P
- | C_P
- | S
- | C_S
- | Sub
- | C_Sub
- | Sup
- | C_Sup
- | Thumb ByteString ByteString ByteString ByteString ByteString ByteString
- | U
- | C_U
- | Ul
- | C_Ul
Datatypes
A top-level dAmn message.
General syntax for a message:
name arg attr1=val1 attr2=val2 body
As reflected in the field types of Message
, the arg
and body
are
both optional.
Attribute values are considered to be textual data and generally consist
of part reasons, privclass names, users' "taglines" and so on. The
message body can either be treated as text or as a SubMessage
(see
MessageBody
).
Note that dAmn is a primarily browser-based platform; it deals with only ISO-8859-1 output and input and inserts chat messages directly into the DOM. As a consequence, correctly displaying characters past the ASCII block requires the use of HTML entities.
All functions in this module transparently convert HTML entities
embedded in ByteString
s to Text
(and back; see toBodyText
). Thus,
when Text
appears in fields of this record or of SubMessage
, you can
assume that the HTML entity decoding step has already been handled.
Message | |
|
data SubMessage Source #
A second-level dAmn message. Note that this message can omit the name/argument pair.
Instances
Eq SubMessage Source # | |
Defined in Network.Damn (==) :: SubMessage -> SubMessage -> Bool # (/=) :: SubMessage -> SubMessage -> Bool # | |
Show SubMessage Source # | |
Defined in Network.Damn showsPrec :: Int -> SubMessage -> ShowS # show :: SubMessage -> String # showList :: [SubMessage] -> ShowS # |
data MessageBody Source #
The body of a message, which can be converted to various formats
(bodyWithFormat
) or parsed as a SubMessage
(subMessage
).
Instances
Eq MessageBody Source # | |
Defined in Network.Damn (==) :: MessageBody -> MessageBody -> Bool # (/=) :: MessageBody -> MessageBody -> Bool # | |
Show MessageBody Source # | |
Defined in Network.Damn showsPrec :: Int -> MessageBody -> ShowS # show :: MessageBody -> String # showList :: [MessageBody] -> ShowS # | |
IsString MessageBody Source # | |
Defined in Network.Damn fromString :: String -> MessageBody # |
Working with message bodies
bodyBytes :: MessageBody -> ByteString Source #
View the original binary content of a MessageBody
.
To interpret this as textual data, use
bodyWithFormat
.
bodyWithFormat :: Monoid s => Formatter s -> MessageBody -> s Source #
Convert a MessageBody
to some stringlike representation using the
given Formatter
. (See damnFormat
).
toBody :: ByteString -> MessageBody Source #
MessageBody
smart constructor.
toBodyText :: Text -> MessageBody Source #
Like toBody
, but convert codepoints outside the ASCII range to HTML
entities.
Note that this is NOT equivalent to toBody . encodeUtf8
.
Working with sub-messages
subMessage :: MessageBody -> forall m. Monad m => m SubMessage Source #
Try to parse a MessageBody
as a SubMessage
.
pattern SubM :: SubMessage -> Maybe MessageBody Source #
subMessage
as a pattern.
case messageBody of Sub (SubMessage name args attrs body)) -> ... _ -> error "No parse"
Can be nested:
isJoinPacket :: Message -> Bool isJoinPacket (Message "recv" room _ (Sub (SubMessage (Just "join") (Just uname) _ (Sub (SubMessage Nothing Nothing userAttrs _))))) = True isJoinPacket _ = False
Parsing
Rendering
render :: Message -> ByteString Source #
Convert a Message
back into a ByteString
to send to dAmn. The null
byte is appended. In addition, all characters outside the ASCII block
are converted to HTML entities, thus
>>>
render (Message "foo" (Just "bar") [("attr1", "☭")] Nothing)
"foo bar\nattr1=☭\n\NUL"
Tablumps
Tokens representing tablumps.
These constructors are defined first in order of arity, then alphabetically.