Skip to content

Commit 516b253

Browse files
committed
Improved haddocks, removed unused pragmas (extensions)
1 parent 3fa36ec commit 516b253

File tree

17 files changed

+349
-278
lines changed

17 files changed

+349
-278
lines changed

typed-protocols-cborg/src/Network/TypedProtocol/Codec/CBOR.hs

Lines changed: 18 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -1,17 +1,19 @@
11
{-# LANGUAGE DataKinds #-}
22
{-# LANGUAGE FlexibleContexts #-}
3+
{-# LANGUAGE LambdaCase #-}
34
{-# LANGUAGE MonoLocalBinds #-}
45
{-# LANGUAGE PolyKinds #-}
56
{-# LANGUAGE RankNTypes #-}
67
{-# LANGUAGE ScopedTypeVariables #-}
78

89
module Network.TypedProtocol.Codec.CBOR
910
( module Network.TypedProtocol.Codec
10-
, DeserialiseFailure
1111
, mkCodecCborLazyBS
1212
, mkCodecCborStrictBS
1313
, convertCborDecoderBS
1414
, convertCborDecoderLBS
15+
-- * Re-exports
16+
, CBOR.DeserialiseFailure (..)
1517
) where
1618

1719
import Control.Monad.Class.MonadST (MonadST (..))
@@ -31,8 +33,6 @@ import Network.TypedProtocol.Codec
3133
import Network.TypedProtocol.Core
3234

3335

34-
type DeserialiseFailure = CBOR.DeserialiseFailure
35-
3636
-- | Construct a 'Codec' for a CBOR based serialisation format, using strict
3737
-- 'BS.ByteString's.
3838
--
@@ -52,13 +52,15 @@ mkCodecCborStrictBS
5252
StateTokenI st
5353
=> ActiveState st
5454
=> Message ps st st' -> CBOR.Encoding)
55+
-- ^ cbor encoder
5556

5657
-> (forall (st :: ps) s.
5758
ActiveState st
5859
=> StateToken st
5960
-> CBOR.Decoder s (SomeMessage st))
61+
-- ^ cbor decoder
6062

61-
-> Codec ps DeserialiseFailure m BS.ByteString
63+
-> Codec ps CBOR.DeserialiseFailure m BS.ByteString
6264
mkCodecCborStrictBS cborMsgEncode cborMsgDecode =
6365
Codec {
6466
encode = \msg -> convertCborEncoder cborMsgEncode msg,
@@ -72,19 +74,21 @@ mkCodecCborStrictBS cborMsgEncode cborMsgDecode =
7274

7375
convertCborDecoder
7476
:: (forall s. CBOR.Decoder s a)
75-
-> m (DecodeStep BS.ByteString DeserialiseFailure m a)
77+
-> m (DecodeStep BS.ByteString CBOR.DeserialiseFailure m a)
7678
convertCborDecoder cborDecode = convertCborDecoderBS cborDecode stToIO
7779

7880
convertCborDecoderBS
7981
:: forall s m a. Functor m
80-
=> (CBOR.Decoder s a)
82+
=> CBOR.Decoder s a
83+
-- ^ cbor decoder
8184
-> (forall b. ST s b -> m b)
82-
-> m (DecodeStep BS.ByteString DeserialiseFailure m a)
85+
-- ^ lift ST computation (e.g. 'Control.Monad.ST.stToIO', 'stToPrim', etc)
86+
-> m (DecodeStep BS.ByteString CBOR.DeserialiseFailure m a)
8387
convertCborDecoderBS cborDecode liftST =
8488
go <$> liftST (CBOR.deserialiseIncremental cborDecode)
8589
where
8690
go :: CBOR.IDecode s a
87-
-> DecodeStep BS.ByteString DeserialiseFailure m a
91+
-> DecodeStep BS.ByteString CBOR.DeserialiseFailure m a
8892
go (CBOR.Done trailing _ x)
8993
| BS.null trailing = DecodeDone x Nothing
9094
| otherwise = DecodeDone x (Just trailing)
@@ -107,11 +111,13 @@ mkCodecCborLazyBS
107111
StateTokenI st
108112
=> ActiveState st
109113
=> Message ps st st' -> CBOR.Encoding)
114+
-- ^ cbor encoder
110115

111116
-> (forall (st :: ps) s.
112117
ActiveState st
113118
=> StateToken st
114119
-> CBOR.Decoder s (SomeMessage st))
120+
-- ^ cbor decoder
115121

116122
-> Codec ps CBOR.DeserialiseFailure m LBS.ByteString
117123
mkCodecCborLazyBS cborMsgEncode cborMsgDecode =
@@ -134,8 +140,10 @@ mkCodecCborLazyBS cborMsgEncode cborMsgDecode =
134140

135141
convertCborDecoderLBS
136142
:: forall s m a. Monad m
137-
=> (CBOR.Decoder s a)
143+
=> CBOR.Decoder s a
144+
-- ^ cbor decoder
138145
-> (forall b. ST s b -> m b)
146+
-- ^ lift ST computation (e.g. 'Control.Monad.ST.stToIO', 'stToPrim', etc)
139147
-> m (DecodeStep LBS.ByteString CBOR.DeserialiseFailure m a)
140148
convertCborDecoderLBS cborDecode liftST =
141149
go [] =<< liftST (CBOR.deserialiseIncremental cborDecode)
@@ -155,7 +163,7 @@ convertCborDecoderLBS cborDecode liftST =
155163
-- We keep a bunch of chunks and supply the CBOR decoder with them
156164
-- until we run out, when we go get another bunch.
157165
go (c:cs) (CBOR.Partial k) = go cs =<< liftST (k (Just c))
158-
go [] (CBOR.Partial k) = return $ DecodePartial $ \mbs -> case mbs of
166+
go [] (CBOR.Partial k) = return $ DecodePartial $ \case
159167
Nothing -> go [] =<< liftST (k Nothing)
160168
Just bs -> go cs (CBOR.Partial k)
161169
where cs = LBS.toChunks bs

typed-protocols-examples/src/Network/TypedProtocol/PingPong/Type.hs

Lines changed: 3 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -42,12 +42,9 @@ data SPingPong (st :: PingPong) where
4242

4343
deriving instance Show (SPingPong st)
4444

45-
instance StateTokenI StIdle where
46-
stateToken = SingIdle
47-
instance StateTokenI StBusy where
48-
stateToken = SingBusy
49-
instance StateTokenI StDone where
50-
stateToken = SingDone
45+
instance StateTokenI StIdle where stateToken = SingIdle
46+
instance StateTokenI StBusy where stateToken = SingBusy
47+
instance StateTokenI StDone where stateToken = SingDone
5148

5249
instance Protocol PingPong where
5350

typed-protocols-stateful-cborg/src/Network/TypedProtocol/Stateful/Codec/CBOR.hs

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -49,12 +49,14 @@ mkCodecCborStrictBS
4949
StateTokenI st
5050
=>ActiveState st
5151
=> f st' -> Message ps st st' -> CBOR.Encoding)
52+
-- ^ cbor encoder
5253

5354
-> (forall (st :: ps) s.
5455
ActiveState st
5556
=> StateToken st
5657
-> f st
5758
-> CBOR.Decoder s (SomeMessage st))
59+
-- ^ cbor decoder
5860

5961
-> Codec ps DeserialiseFailure f m BS.ByteString
6062
mkCodecCborStrictBS cborMsgEncode cborMsgDecode =
@@ -90,12 +92,14 @@ mkCodecCborLazyBS
9092
=> ActiveState st
9193
=> f st'
9294
-> Message ps st st' -> CBOR.Encoding)
95+
-- ^ cbor encoder
9396

9497
-> (forall (st :: ps) s.
9598
ActiveState st
9699
=> StateToken st
97100
-> f st
98101
-> CBOR.Decoder s (SomeMessage st))
102+
-- ^ cbor decoder
99103

100104
-> Codec ps CBOR.DeserialiseFailure f m LBS.ByteString
101105
mkCodecCborLazyBS cborMsgEncode cborMsgDecode =

typed-protocols-stateful/src/Network/TypedProtocol/Stateful/Codec.hs

Lines changed: 13 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -24,16 +24,23 @@ module Network.TypedProtocol.Stateful.Codec
2424
, isoCodec
2525
, mapFailureCodec
2626
, liftCodec
27-
-- ** Related types
28-
, ActiveState
29-
, PeerRole (..)
30-
, SomeMessage (..)
31-
, CodecFailure (..)
3227
-- ** Incremental decoding
3328
, DecodeStep (..)
3429
, runDecoder
3530
, runDecoderPure
36-
-- ** Codec properties
31+
-- ** Related types
32+
-- *** SomeMessage
33+
, SomeMessage (..)
34+
-- *** StateToken
35+
, StateToken
36+
, StateTokenI (..)
37+
-- *** ActiveState
38+
, ActiveState
39+
-- *** PeerRole
40+
, PeerRole (..)
41+
-- * CodecFailure
42+
, CodecFailure (..)
43+
-- * Testing codec properties
3744
, AnyMessage (..)
3845
, pattern AnyMessageAndAgency
3946
, prop_codecM
@@ -42,9 +49,6 @@ module Network.TypedProtocol.Stateful.Codec
4249
, prop_codec_splits
4350
, prop_codecs_compatM
4451
, prop_codecs_compat
45-
-- ** StateToken
46-
, StateToken
47-
, StateTokenI (..)
4852
) where
4953

5054
import Data.Kind (Type)

typed-protocols-stateful/src/Network/TypedProtocol/Stateful/Driver.hs

Lines changed: 5 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -13,12 +13,13 @@
1313
-- imported qualified.
1414
--
1515
module Network.TypedProtocol.Stateful.Driver
16-
( -- * Running a peer
17-
runPeerWithDriver
16+
( -- * DriverIngerface
17+
Driver (..)
18+
-- * Running a peer
19+
, runPeerWithDriver
1820
-- * Re-exports
19-
, DecodeStep (..)
20-
, Driver (..)
2121
, SomeMessage (..)
22+
, DecodeStep (..)
2223
) where
2324

2425
import Control.Monad.Class.MonadSTM
@@ -46,12 +47,6 @@ data Driver ps (pr :: PeerRole) bytes failure dstate f m =
4647

4748
, -- | Receive a message, a blocking action which reads from the network
4849
-- and runs the incremental decoder until a full message is decoded.
49-
-- As an input it might receive a 'DecodeStep' previously started with
50-
-- 'tryRecvMessage'.
51-
--
52-
-- It could be implemented in terms of 'recvMessageSTM', but in some
53-
-- cases it can be easier (or more performant) to have a different
54-
-- implementation.
5550
--
5651
recvMessage :: forall (st :: ps).
5752
StateTokenI st

typed-protocols-stateful/src/Network/TypedProtocol/Stateful/Peer.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -46,8 +46,8 @@ import Network.TypedProtocol.Core as Core
4646
--
4747
-- For example:
4848
--
49-
-- > pingPongClientExample :: Int -> Peer PingPong AsClient StIdle m ()
50-
-- > pingPongServerExample :: Peer PingPong AsServer StIdle m Int
49+
-- > pingPongClientExample :: Peer PingPong AsClient StIdle m ()
50+
-- > pingPongServerExample :: Peer PingPong AsServer StIdle m Int
5151
--
5252
-- The actions that a peer can take are:
5353
--

typed-protocols-stateful/src/Network/TypedProtocol/Stateful/Peer/Client.hs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -12,7 +12,8 @@
1212
-- singleton.
1313
--
1414
module Network.TypedProtocol.Stateful.Peer.Client
15-
( Client
15+
( -- * Client type alias and its pattern synonyms
16+
Client
1617
, pattern Effect
1718
, pattern Yield
1819
, pattern Await

typed-protocols-stateful/src/Network/TypedProtocol/Stateful/Peer/Server.hs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -12,7 +12,8 @@
1212
-- singleton.
1313
--
1414
module Network.TypedProtocol.Stateful.Peer.Server
15-
( Server
15+
( -- * Server type alias and its pattern synonyms
16+
Server
1617
, pattern Effect
1718
, pattern Yield
1819
, pattern Await

typed-protocols/src/Network/TypedProtocol.hs

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -8,7 +8,6 @@ module Network.TypedProtocol
88
-- * Defining and implementing protocols
99
-- $defining
1010
module Network.TypedProtocol.Core
11-
, module Network.TypedProtocol.Peer
1211
-- ** Protocol proofs and tests
1312
-- $tests
1413
, module Network.TypedProtocol.Proofs
@@ -19,7 +18,6 @@ module Network.TypedProtocol
1918

2019
import Network.TypedProtocol.Core
2120
import Network.TypedProtocol.Driver
22-
import Network.TypedProtocol.Peer
2321
import Network.TypedProtocol.Proofs
2422

2523

0 commit comments

Comments
 (0)