{-# LANGUAGE TemplateHaskell #-}
module Network.MQTT.Lens where
import Control.Lens
import Network.MQTT.Types
class HasProperties c where
properties :: Lens' c [Property]
class HasPktID c where
pktID :: Lens' c PktID
makeLenses ''ConnectRequest
instance HasProperties ConnectRequest where properties :: ([Property] -> f [Property]) -> ConnectRequest -> f ConnectRequest
properties = ([Property] -> f [Property]) -> ConnectRequest -> f ConnectRequest
Lens' ConnectRequest [Property]
connProperties
makeLenses ''LastWill
instance HasProperties LastWill where properties :: ([Property] -> f [Property]) -> LastWill -> f LastWill
properties = ([Property] -> f [Property]) -> LastWill -> f LastWill
Lens' LastWill [Property]
willProps
makeLenses ''PublishRequest
instance HasProperties PublishRequest where properties :: ([Property] -> f [Property]) -> PublishRequest -> f PublishRequest
properties = ([Property] -> f [Property]) -> PublishRequest -> f PublishRequest
Lens' PublishRequest [Property]
pubProps
instance HasPktID PublishRequest where pktID :: (Word16 -> f Word16) -> PublishRequest -> f PublishRequest
pktID = (Word16 -> f Word16) -> PublishRequest -> f PublishRequest
Lens' PublishRequest Word16
pubPktID
makeLenses ''SubOptions
makePrisms ''ConnACKRC
makePrisms ''DiscoReason
makePrisms ''MQTTPkt
makePrisms ''Property
makePrisms ''ProtocolLevel
makePrisms ''QoS
makePrisms ''RetainHandling
makePrisms ''SessionReuse
makePrisms ''SubErr
makePrisms ''UnsubStatus
instance HasProperties AuthRequest where
properties :: ([Property] -> f [Property]) -> AuthRequest -> f AuthRequest
properties = (AuthRequest -> [Property])
-> (AuthRequest -> [Property] -> AuthRequest)
-> Lens' AuthRequest [Property]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens (\(AuthRequest Word8
_ [Property]
ps) -> [Property]
ps) (\(AuthRequest Word8
a [Property]
_) [Property]
p -> Word8 -> [Property] -> AuthRequest
AuthRequest Word8
a [Property]
p)
instance HasProperties ConnACKFlags where
properties :: ([Property] -> f [Property]) -> ConnACKFlags -> f ConnACKFlags
properties = (ConnACKFlags -> [Property])
-> (ConnACKFlags -> [Property] -> ConnACKFlags)
-> Lens' ConnACKFlags [Property]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens (\(ConnACKFlags SessionReuse
_ ConnACKRC
_ [Property]
ps) -> [Property]
ps) (\(ConnACKFlags SessionReuse
a ConnACKRC
b [Property]
_) [Property]
p -> SessionReuse -> ConnACKRC -> [Property] -> ConnACKFlags
ConnACKFlags SessionReuse
a ConnACKRC
b [Property]
p)
instance HasProperties DisconnectRequest where
properties :: ([Property] -> f [Property])
-> DisconnectRequest -> f DisconnectRequest
properties = (DisconnectRequest -> [Property])
-> (DisconnectRequest -> [Property] -> DisconnectRequest)
-> Lens' DisconnectRequest [Property]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens (\(DisconnectRequest DiscoReason
_ [Property]
ps) -> [Property]
ps) (\(DisconnectRequest DiscoReason
a [Property]
_) [Property]
p -> DiscoReason -> [Property] -> DisconnectRequest
DisconnectRequest DiscoReason
a [Property]
p)
instance HasProperties PubACK where
properties :: ([Property] -> f [Property]) -> PubACK -> f PubACK
properties = (PubACK -> [Property])
-> (PubACK -> [Property] -> PubACK) -> Lens' PubACK [Property]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens (\(PubACK Word16
_ Word8
_ [Property]
ps) -> [Property]
ps) (\(PubACK Word16
a Word8
b [Property]
_) [Property]
p -> Word16 -> Word8 -> [Property] -> PubACK
PubACK Word16
a Word8
b [Property]
p)
instance HasPktID PubACK where
pktID :: (Word16 -> f Word16) -> PubACK -> f PubACK
pktID = (PubACK -> Word16)
-> (PubACK -> Word16 -> PubACK) -> Lens' PubACK Word16
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens (\(PubACK Word16
i Word8
_ [Property]
_) -> Word16
i) (\(PubACK Word16
_ Word8
a [Property]
b) Word16
i -> Word16 -> Word8 -> [Property] -> PubACK
PubACK Word16
i Word8
a [Property]
b)
instance HasProperties PubCOMP where
properties :: ([Property] -> f [Property]) -> PubCOMP -> f PubCOMP
properties = (PubCOMP -> [Property])
-> (PubCOMP -> [Property] -> PubCOMP) -> Lens' PubCOMP [Property]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens (\(PubCOMP Word16
_ Word8
_ [Property]
ps) -> [Property]
ps) (\(PubCOMP Word16
a Word8
b [Property]
_) [Property]
p -> Word16 -> Word8 -> [Property] -> PubCOMP
PubCOMP Word16
a Word8
b [Property]
p)
instance HasPktID PubCOMP where
pktID :: (Word16 -> f Word16) -> PubCOMP -> f PubCOMP
pktID = (PubCOMP -> Word16)
-> (PubCOMP -> Word16 -> PubCOMP) -> Lens' PubCOMP Word16
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens (\(PubCOMP Word16
i Word8
_ [Property]
_) -> Word16
i) (\(PubCOMP Word16
_ Word8
a [Property]
b) Word16
i -> Word16 -> Word8 -> [Property] -> PubCOMP
PubCOMP Word16
i Word8
a [Property]
b)
instance HasProperties PubREC where
properties :: ([Property] -> f [Property]) -> PubREC -> f PubREC
properties = (PubREC -> [Property])
-> (PubREC -> [Property] -> PubREC) -> Lens' PubREC [Property]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens (\(PubREC Word16
_ Word8
_ [Property]
ps) -> [Property]
ps) (\(PubREC Word16
a Word8
b [Property]
_) [Property]
p -> Word16 -> Word8 -> [Property] -> PubREC
PubREC Word16
a Word8
b [Property]
p)
instance HasPktID PubREC where
pktID :: (Word16 -> f Word16) -> PubREC -> f PubREC
pktID = (PubREC -> Word16)
-> (PubREC -> Word16 -> PubREC) -> Lens' PubREC Word16
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens (\(PubREC Word16
i Word8
_ [Property]
_) -> Word16
i) (\(PubREC Word16
_ Word8
a [Property]
b) Word16
i -> Word16 -> Word8 -> [Property] -> PubREC
PubREC Word16
i Word8
a [Property]
b)
instance HasProperties PubREL where
properties :: ([Property] -> f [Property]) -> PubREL -> f PubREL
properties = (PubREL -> [Property])
-> (PubREL -> [Property] -> PubREL) -> Lens' PubREL [Property]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens (\(PubREL Word16
_ Word8
_ [Property]
ps) -> [Property]
ps) (\(PubREL Word16
a Word8
b [Property]
_) [Property]
p -> Word16 -> Word8 -> [Property] -> PubREL
PubREL Word16
a Word8
b [Property]
p)
instance HasPktID PubREL where
pktID :: (Word16 -> f Word16) -> PubREL -> f PubREL
pktID = (PubREL -> Word16)
-> (PubREL -> Word16 -> PubREL) -> Lens' PubREL Word16
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens (\(PubREL Word16
i Word8
_ [Property]
_) -> Word16
i) (\(PubREL Word16
_ Word8
a [Property]
b) Word16
i -> Word16 -> Word8 -> [Property] -> PubREL
PubREL Word16
i Word8
a [Property]
b)
instance HasProperties SubscribeRequest where
properties :: ([Property] -> f [Property])
-> SubscribeRequest -> f SubscribeRequest
properties = (SubscribeRequest -> [Property])
-> (SubscribeRequest -> [Property] -> SubscribeRequest)
-> Lens' SubscribeRequest [Property]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens (\(SubscribeRequest Word16
_ [(ByteString, SubOptions)]
_ [Property]
ps) -> [Property]
ps) (\(SubscribeRequest Word16
a [(ByteString, SubOptions)]
b [Property]
_) [Property]
p -> Word16
-> [(ByteString, SubOptions)] -> [Property] -> SubscribeRequest
SubscribeRequest Word16
a [(ByteString, SubOptions)]
b [Property]
p)
instance HasPktID SubscribeRequest where
pktID :: (Word16 -> f Word16) -> SubscribeRequest -> f SubscribeRequest
pktID = (SubscribeRequest -> Word16)
-> (SubscribeRequest -> Word16 -> SubscribeRequest)
-> Lens' SubscribeRequest Word16
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens (\(SubscribeRequest Word16
i [(ByteString, SubOptions)]
_ [Property]
_) -> Word16
i) (\(SubscribeRequest Word16
_ [(ByteString, SubOptions)]
a [Property]
b) Word16
i -> Word16
-> [(ByteString, SubOptions)] -> [Property] -> SubscribeRequest
SubscribeRequest Word16
i [(ByteString, SubOptions)]
a [Property]
b)
instance HasProperties SubscribeResponse where
properties :: ([Property] -> f [Property])
-> SubscribeResponse -> f SubscribeResponse
properties = (SubscribeResponse -> [Property])
-> (SubscribeResponse -> [Property] -> SubscribeResponse)
-> Lens' SubscribeResponse [Property]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens (\(SubscribeResponse Word16
_ [Either SubErr QoS]
_ [Property]
ps) -> [Property]
ps) (\(SubscribeResponse Word16
a [Either SubErr QoS]
b [Property]
_) [Property]
p -> Word16 -> [Either SubErr QoS] -> [Property] -> SubscribeResponse
SubscribeResponse Word16
a [Either SubErr QoS]
b [Property]
p)
instance HasPktID SubscribeResponse where
pktID :: (Word16 -> f Word16) -> SubscribeResponse -> f SubscribeResponse
pktID = (SubscribeResponse -> Word16)
-> (SubscribeResponse -> Word16 -> SubscribeResponse)
-> Lens' SubscribeResponse Word16
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens (\(SubscribeResponse Word16
i [Either SubErr QoS]
_ [Property]
_) -> Word16
i) (\(SubscribeResponse Word16
_ [Either SubErr QoS]
a [Property]
b) Word16
i -> Word16 -> [Either SubErr QoS] -> [Property] -> SubscribeResponse
SubscribeResponse Word16
i [Either SubErr QoS]
a [Property]
b)
instance HasProperties UnsubscribeRequest where
properties :: ([Property] -> f [Property])
-> UnsubscribeRequest -> f UnsubscribeRequest
properties = (UnsubscribeRequest -> [Property])
-> (UnsubscribeRequest -> [Property] -> UnsubscribeRequest)
-> Lens' UnsubscribeRequest [Property]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens (\(UnsubscribeRequest Word16
_ [ByteString]
_ [Property]
ps) -> [Property]
ps) (\(UnsubscribeRequest Word16
a [ByteString]
b [Property]
_) [Property]
p -> Word16 -> [ByteString] -> [Property] -> UnsubscribeRequest
UnsubscribeRequest Word16
a [ByteString]
b [Property]
p)
instance HasPktID UnsubscribeRequest where
pktID :: (Word16 -> f Word16) -> UnsubscribeRequest -> f UnsubscribeRequest
pktID = (UnsubscribeRequest -> Word16)
-> (UnsubscribeRequest -> Word16 -> UnsubscribeRequest)
-> Lens' UnsubscribeRequest Word16
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens (\(UnsubscribeRequest Word16
i [ByteString]
_ [Property]
_) -> Word16
i) (\(UnsubscribeRequest Word16
_ [ByteString]
a [Property]
b) Word16
i -> Word16 -> [ByteString] -> [Property] -> UnsubscribeRequest
UnsubscribeRequest Word16
i [ByteString]
a [Property]
b)
instance HasProperties UnsubscribeResponse where
properties :: ([Property] -> f [Property])
-> UnsubscribeResponse -> f UnsubscribeResponse
properties = (UnsubscribeResponse -> [Property])
-> (UnsubscribeResponse -> [Property] -> UnsubscribeResponse)
-> Lens' UnsubscribeResponse [Property]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens (\(UnsubscribeResponse Word16
_ [Property]
ps [UnsubStatus]
_) -> [Property]
ps) (\(UnsubscribeResponse Word16
a [Property]
_ [UnsubStatus]
b) [Property]
p -> Word16 -> [Property] -> [UnsubStatus] -> UnsubscribeResponse
UnsubscribeResponse Word16
a [Property]
p [UnsubStatus]
b)
instance HasPktID UnsubscribeResponse where
pktID :: (Word16 -> f Word16)
-> UnsubscribeResponse -> f UnsubscribeResponse
pktID = (UnsubscribeResponse -> Word16)
-> (UnsubscribeResponse -> Word16 -> UnsubscribeResponse)
-> Lens' UnsubscribeResponse Word16
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens (\(UnsubscribeResponse Word16
i [Property]
_ [UnsubStatus]
_) -> Word16
i) (\(UnsubscribeResponse Word16
_ [Property]
a [UnsubStatus]
b) Word16
i -> Word16 -> [Property] -> [UnsubStatus] -> UnsubscribeResponse
UnsubscribeResponse Word16
i [Property]
a [UnsubStatus]
b)