module Network.MQTT.Types
(
Message(..)
, SomeMessage(..)
, MqttHeader(..)
, setDup
, MessageBody(..)
, Will(..)
, QoS(..)
, MsgID
, getMsgID
, Topic
, matches
, fromTopic
, toTopic
, getLevels
, fromLevels
, MqttText(..)
, ConnectError(..)
, toConnectError
, MsgType(..)
, toMsgType
, toMsgType'
, toSMsgType
, SMsgType
, withSomeSingI
, Sing( SCONNECT
, SCONNACK
, SPUBLISH
, SPUBACK
, SPUBREC
, SPUBREL
, SPUBCOMP
, SSUBSCRIBE
, SSUBACK
, SUNSUBSCRIBE
, SUNSUBACK
, SPINGREQ
, SPINGRESP
, SDISCONNECT)
) where
import Control.Exception (Exception)
import Data.ByteString (ByteString)
import Data.Singletons
import Data.Singletons.TH
import Data.String (IsString(..))
import Data.Text (Text)
import qualified Data.Text as T
import Data.Typeable (Typeable)
import Data.Word
data Message (t :: MsgType)
= Message
{ header :: MqttHeader
, body :: MessageBody t
}
data SomeMessage where
SomeMessage :: SingI t => Message t -> SomeMessage
data MqttHeader
= Header
{ dup :: Bool
, qos :: QoS
, retain :: Bool
}
deriving (Eq, Ord, Show)
setDup :: Message t -> Message t
setDup (Message h b) = Message h { dup = True } b
data MessageBody (t :: MsgType) where
Connect :: { cleanSession :: Bool
, will :: Maybe Will
, clientID :: MqttText
, username :: Maybe MqttText
, password :: Maybe MqttText
, keepAlive :: Word16
} -> MessageBody 'CONNECT
ConnAck :: { returnCode :: Word8 } -> MessageBody 'CONNACK
Publish :: { topic :: Topic
, pubMsgID :: Maybe MsgID
, payload :: ByteString
} -> MessageBody 'PUBLISH
PubAck :: { pubAckMsgID :: MsgID } -> MessageBody 'PUBACK
PubRec :: { pubRecMsgID :: MsgID } -> MessageBody 'PUBREC
PubRel :: { pubRelMsgID :: MsgID } -> MessageBody 'PUBREL
PubComp :: { pubCompMsgID :: MsgID } -> MessageBody 'PUBCOMP
Subscribe :: { subscribeMsgID :: MsgID
, subTopics :: [(Topic, QoS)]
} -> MessageBody 'SUBSCRIBE
SubAck :: { subAckMsgID :: MsgID
, granted :: [QoS]
} -> MessageBody 'SUBACK
Unsubscribe :: { unsubMsgID :: MsgID
, unsubTopics :: [Topic]
} -> MessageBody 'UNSUBSCRIBE
UnsubAck :: { unsubAckMsgID :: MsgID } -> MessageBody 'UNSUBACK
PingReq :: MessageBody 'PINGREQ
PingResp :: MessageBody 'PINGRESP
Disconnect :: MessageBody 'DISCONNECT
data QoS
= NoConfirm
| Confirm
| Handshake
deriving (Eq, Ord, Enum, Show)
data Will
= Will
{ wRetain :: Bool
, wQoS :: QoS
, wTopic :: Topic
, wMsg :: MqttText
}
deriving (Eq, Show)
newtype MqttText = MqttText { text :: Text }
deriving (Eq, Show, IsString)
type MsgID = Word16
getMsgID :: MessageBody t -> Maybe MsgID
getMsgID (Connect{}) = Nothing
getMsgID (ConnAck{}) = Nothing
getMsgID (Publish _ mMsgid _) = mMsgid
getMsgID (PubAck msgid) = Just msgid
getMsgID (PubRec msgid) = Just msgid
getMsgID (PubRel msgid) = Just msgid
getMsgID (PubComp msgid) = Just msgid
getMsgID (Subscribe msgid _) = Just msgid
getMsgID (SubAck msgid _) = Just msgid
getMsgID (Unsubscribe msgid _) = Just msgid
getMsgID (UnsubAck msgid) = Just msgid
getMsgID PingReq = Nothing
getMsgID PingResp = Nothing
getMsgID Disconnect = Nothing
data Topic = Topic { levels :: [Text], orig :: Text }
instance Show Topic where
show (Topic _ t) = show t
instance Eq Topic where
Topic _ t1 == Topic _ t2 = t1 == t2
matches :: Topic -> Topic -> Bool
matches (Topic t1 _) (Topic t2 _) = go t1 t2
where
go [] [] = True
go [] (l:_) = l == "#"
go (l:_) [] = l == "#"
go (l1:ls1) (l2:ls2) = l1 == "#" || l2 == "#"
|| ((l1 == "+" || l2 == "+" || l1 == l2)
&& go ls1 ls2)
toTopic :: MqttText -> Topic
toTopic (MqttText txt) = Topic (T.split (== '/') txt) txt
fromTopic :: Topic -> MqttText
fromTopic = MqttText . orig
getLevels :: Topic -> [Text]
getLevels = levels
fromLevels :: [Text] -> Topic
fromLevels ls = Topic ls (T.intercalate "/" ls)
instance IsString Topic where
fromString str = let txt = T.pack str in
Topic (T.split (== '/') txt) txt
data ConnectError
= WrongProtocolVersion
| IdentifierRejected
| ServerUnavailable
| BadLogin
| Unauthorized
| UnrecognizedReturnCode
| InvalidResponse
deriving (Show, Typeable)
instance Exception ConnectError where
toConnectError :: Word8 -> ConnectError
toConnectError 1 = WrongProtocolVersion
toConnectError 2 = IdentifierRejected
toConnectError 3 = ServerUnavailable
toConnectError 4 = BadLogin
toConnectError 5 = Unauthorized
toConnectError _ = UnrecognizedReturnCode
data MsgType
= CONNECT
| CONNACK
| PUBLISH
| PUBACK
| PUBREC
| PUBREL
| PUBCOMP
| SUBSCRIBE
| SUBACK
| UNSUBSCRIBE
| UNSUBACK
| PINGREQ
| PINGRESP
| DISCONNECT
deriving (Eq, Enum, Ord, Show)
genSingletons [''MsgType]
singDecideInstance ''MsgType
toMsgType :: SingI t => Message t -> MsgType
toMsgType = fromSing . toSMsgType
toMsgType' :: SomeMessage -> MsgType
toMsgType' (SomeMessage msg) = toMsgType msg
toSMsgType :: SingI t => Message t -> SMsgType t
toSMsgType _ = sing
withSomeSingI :: MsgType -> (forall t. SingI t => SMsgType t -> r) -> r
withSomeSingI t f = withSomeSing t $ \s -> withSingI s $ f s