Skip to content

Commit 8e2aaed

Browse files
committed
typed-protocols:test - added prop_anncodec for ReqResp mini-protocol
1 parent fa9c4d4 commit 8e2aaed

File tree

4 files changed

+83
-3
lines changed

4 files changed

+83
-3
lines changed

typed-protocols/examples/Network/TypedProtocol/ReqResp/Codec.hs

Lines changed: 63 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,5 @@
1+
{-# LANGUAGE BlockArguments #-}
2+
13
module Network.TypedProtocol.ReqResp.Codec where
24

35
import Network.TypedProtocol.Codec
@@ -43,6 +45,67 @@ codecReqResp =
4345
where failure = CodecFailure ("unexpected server message: " ++ str)
4446

4547

48+
data WithBytes a = WithBytes {
49+
bytes :: String,
50+
message :: a
51+
}
52+
deriving (Show, Eq)
53+
54+
mkWithBytes :: Show a => a -> WithBytes a
55+
mkWithBytes message = WithBytes { bytes = show message, message }
56+
57+
anncodecReqResp ::
58+
forall req resp m
59+
. (Monad m, Show req, Show resp, Read req, Read resp)
60+
=> AnnotatedCodec (ReqResp (WithBytes req) (WithBytes resp)) CodecFailure m String
61+
anncodecReqResp =
62+
Codec{encode, decode}
63+
where
64+
encode :: forall req' resp'
65+
(st :: ReqResp (WithBytes req') (WithBytes resp'))
66+
(st' :: ReqResp (WithBytes req') (WithBytes resp'))
67+
. ( Show req'
68+
, Show resp'
69+
)
70+
=> Message (ReqResp (WithBytes req') (WithBytes resp')) st st'
71+
-> String
72+
-- NOTE: we're not using 'Show (Message ...)' instance. If `req ~ Int`,
73+
-- then negative numbers will be surrounded with braces (e.g. @"(-1)"@) and
74+
-- the `Read` type class doesn't have a way to see that brackets were consumed
75+
-- from the input string.
76+
encode (MsgReq WithBytes { message })
77+
= "MsgReq " ++ show message ++ "\n"
78+
encode (MsgResp WithBytes { message })
79+
= "MsgResp " ++ show message ++ "\n"
80+
encode MsgDone
81+
= "MsgDone" ++ "\n"
82+
83+
decode :: forall req' resp' m'
84+
(st :: ReqResp (WithBytes req') (WithBytes resp'))
85+
. (Monad m', Read req', Read resp', ActiveState st)
86+
=> StateToken st
87+
-> m' (DecodeStep String CodecFailure m' (Annotator String st))
88+
decode stok =
89+
decodeTerminatedFrame '\n' $ \str trailing ->
90+
case (stok, break (==' ') str) of
91+
(SingIdle, ("MsgReq", str'))
92+
| Just req <- readMaybe @req' str'
93+
-> DecodeDone (Annotator \str'' ->
94+
let used = init $ drop 7 str'' in
95+
SomeMessage (MsgReq (WithBytes used req))) trailing
96+
(SingIdle, ("MsgDone", ""))
97+
-> DecodeDone (Annotator \_str'' -> SomeMessage MsgDone) trailing
98+
(SingBusy, ("MsgResp", str'))
99+
| Just resp <- readMaybe @resp' str'
100+
-> DecodeDone (Annotator \str'' ->
101+
let used = init $ drop 8 str'' in
102+
SomeMessage (MsgResp (WithBytes used resp))) trailing
103+
104+
(_ , _ ) -> DecodeFail failure
105+
where failure = CodecFailure ("unexpected server message: " ++ str)
106+
107+
108+
46109
codecReqRespId ::
47110
forall req resp m
48111
. (Monad m, Show req, Show resp)

typed-protocols/examples/Network/TypedProtocol/ReqResp/Type.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -28,9 +28,9 @@ instance StateTokenI StDone where
2828
instance Protocol (ReqResp req resp) where
2929

3030
data Message (ReqResp req resp) from to where
31-
MsgReq :: req -> Message (ReqResp req resp) StIdle StBusy
32-
MsgResp :: resp -> Message (ReqResp req resp) StBusy StIdle
33-
MsgDone :: Message (ReqResp req resp) StIdle StDone
31+
MsgReq :: forall req resp. req -> Message (ReqResp req resp) StIdle StBusy
32+
MsgResp :: forall req resp. resp -> Message (ReqResp req resp) StBusy StIdle
33+
MsgDone :: forall req resp. Message (ReqResp req resp) StIdle StDone
3434

3535
type StateAgency StIdle = ClientAgency
3636
type StateAgency StBusy = ServerAgency

typed-protocols/test/Network/TypedProtocol/ReqResp/Tests.hs

Lines changed: 16 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -73,6 +73,9 @@ tests = testGroup "Network.TypedProtocol.ReqResp"
7373
, testProperty "codec 3-splits" $ withMaxSuccess 30 prop_codec_cbor_splits3_ReqResp
7474
]
7575
]
76+
, testGroup "AnnotatedCodec"
77+
[ testProperty "codec" prop_anncodec_ReqResp
78+
]
7679
]
7780

7881

@@ -360,3 +363,16 @@ prop_codec_cbor_splits3_ReqResp msg =
360363
splits3BS
361364
CBOR.codecReqResp
362365
msg
366+
367+
368+
instance (Show a, Arbitrary a) => Arbitrary (WithBytes a) where
369+
arbitrary = mkWithBytes <$> arbitrary
370+
shrink WithBytes { message } = mkWithBytes <$> shrink message
371+
372+
prop_anncodec_ReqResp
373+
:: AnyMessage (ReqResp (WithBytes Int) (WithBytes Int))
374+
-> Property
375+
prop_anncodec_ReqResp =
376+
prop_anncodec
377+
runIdentity
378+
anncodecReqResp

typed-protocols/typed-protocols.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -53,6 +53,7 @@ library
5353

5454
library codec-properties
5555
import: GHC
56+
visibility: public
5657
exposed-modules: Network.TypedProtocol.Codec.Properties
5758
Network.TypedProtocol.Stateful.Codec.Properties
5859
build-depends: base >=4.12 && <4.22,

0 commit comments

Comments
 (0)