|
| 1 | +{-# LANGUAGE BlockArguments #-} |
| 2 | + |
1 | 3 | module Network.TypedProtocol.ReqResp.Codec where
|
2 | 4 |
|
3 | 5 | import Network.TypedProtocol.Codec
|
@@ -43,6 +45,67 @@ codecReqResp =
|
43 | 45 | where failure = CodecFailure ("unexpected server message: " ++ str)
|
44 | 46 |
|
45 | 47 |
|
| 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 | + |
46 | 109 | codecReqRespId ::
|
47 | 110 | forall req resp m
|
48 | 111 | . (Monad m, Show req, Show resp)
|
|
0 commit comments