summaryrefslogtreecommitdiff
path: root/src/Network/KRPC/Message.hs
blob: d6279f11ed160233046e350e33ec64ffb8f952de (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
-- |
--   Copyright   :  (c) Sam Truzjan 2013
--   License     :  BSD3
--   Maintainer  :  pxqr.sta@gmail.com
--   Stability   :  experimental
--   Portability :  portable
--
--   KRPC messages types used in communication. All messages are
--   encoded as bencode dictionary.
--
--   Normally, you don't need to import this module.
--
--   See <http://www.bittorrent.org/beps/bep_0005.html#krpc-protocol>
--
{-# LANGUAGE OverloadedStrings      #-}
{-# LANGUAGE FlexibleContexts       #-}
{-# LANGUAGE TypeSynonymInstances   #-}
{-# LANGUAGE MultiParamTypeClasses  #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE DefaultSignatures      #-}
{-# LANGUAGE DeriveDataTypeable     #-}
module Network.KRPC.Message
       ( -- * Transaction
         TransactionId

         -- * Error
       , ErrorCode (..)
       , KError(..)
       , serverError
       , decodeError
       , unknownMethod
       , unknownMessage
       , timeoutExpired

         -- * Query
       , KQuery(..)
       , MethodName

         -- * Response
       , KResponse(..)

         -- * Message
       , KMessage (..)
       ) where

import Control.Applicative
import Control.Exception.Lifted as Lifted
import Data.BEncode as BE
import Data.ByteString as B
import Data.ByteString.Char8 as BC
import Data.Typeable


-- | This transaction ID is generated by the querying node and is
-- echoed in the response, so responses may be correlated with
-- multiple queries to the same node. The transaction ID should be
-- encoded as a short string of binary numbers, typically 2 characters
-- are enough as they cover 2^16 outstanding queries.
type TransactionId = ByteString

unknownTransaction :: TransactionId
unknownTransaction = ""

{-----------------------------------------------------------------------
-- Error messages
-----------------------------------------------------------------------}

-- | Types of RPC errors.
data ErrorCode
    -- | Some error doesn't fit in any other category.
  = GenericError

    -- | Occur when server fail to process procedure call.
  | ServerError

    -- | Malformed packet, invalid arguments or bad token.
  | ProtocolError

    -- | Occur when client trying to call method server don't know.
  | MethodUnknown
    deriving (Show, Read, Eq, Ord, Bounded, Typeable)

-- | According to the table:
-- <http://bittorrent.org/beps/bep_0005.html#errors>
instance Enum ErrorCode where
  fromEnum GenericError  = 201
  fromEnum ServerError   = 202
  fromEnum ProtocolError = 203
  fromEnum MethodUnknown = 204
  {-# INLINE fromEnum #-}

  toEnum 201 = GenericError
  toEnum 202 = ServerError
  toEnum 203 = ProtocolError
  toEnum 204 = MethodUnknown
  toEnum _   = GenericError
  {-# INLINE toEnum #-}

instance BEncode ErrorCode where
  toBEncode = toBEncode . fromEnum
  {-# INLINE toBEncode #-}

  fromBEncode b = toEnum <$> fromBEncode b
  {-# INLINE fromBEncode #-}

-- | Errors are sent when a query cannot be fulfilled. Error message
--   can be send only from server to client but not in the opposite
--   direction.
--
data KError = KError
  { errorCode    :: !ErrorCode     -- ^ the type of error;
  , errorMessage :: !ByteString    -- ^ human-readable text message;
  , errorId      :: !TransactionId -- ^ match to the corresponding 'queryId'.
  } deriving (Show, Read, Eq, Ord, Typeable)

-- | Errors, or KRPC message dictionaries with a \"y\" value of \"e\",
--   contain one additional key \"e\". The value of \"e\" is a
--   list. The first element is an integer representing the error
--   code. The second element is a string containing the error
--   message.
--
--   Example Error Packet:
--
--   > { "t": "aa", "y":"e", "e":[201, "A Generic Error Ocurred"]}
--
--   or bencoded:
--
--   > d1:eli201e23:A Generic Error Ocurrede1:t2:aa1:y1:ee
--
instance BEncode KError where
  toBEncode KError {..} = toDict $
       "e" .=! (errorCode, errorMessage)
    .: "t" .=! errorId
    .: "y" .=! ("e" :: ByteString)
    .: endDict
  {-# INLINE toBEncode #-}

  fromBEncode = fromDict $ do
    lookAhead $ match "y" (BString "e")
    (code, msg) <- field (req "e")
    KError code msg <$>! "t"
  {-# INLINE fromBEncode #-}

instance Exception KError

-- | Happen when some query handler fail.
serverError :: SomeException -> TransactionId -> KError
serverError e = KError ServerError (BC.pack (show e))

-- | Received 'queryArgs' or 'respVals' can not be decoded.
decodeError :: String -> TransactionId -> KError
decodeError msg = KError ProtocolError (BC.pack msg)

-- | If /remote/ node send query /this/ node doesn't know about then
-- this error message should be sent in response.
unknownMethod :: MethodName -> TransactionId -> KError
unknownMethod = KError MethodUnknown

-- | A remote node has send some 'KMessage' this node is unable to
-- decode.
unknownMessage :: String -> KError
unknownMessage msg = KError ProtocolError (BC.pack msg) unknownTransaction

-- | A /remote/ node is not responding to the /our/ request the for
-- specified period of time.
timeoutExpired :: TransactionId -> KError
timeoutExpired = KError GenericError "timeout expired"

{-----------------------------------------------------------------------
-- Query messages
-----------------------------------------------------------------------}

type MethodName = ByteString

-- | Query used to signal that caller want to make procedure call to
-- callee and pass arguments in. Therefore query may be only sent from
-- client to server but not in the opposite direction.
--
data KQuery = KQuery
  { queryArgs   :: !BValue         -- ^ values to be passed to method;
  , queryMethod :: !MethodName     -- ^ method to call;
  , queryId     :: !TransactionId  -- ^ one-time query token.
  } deriving (Show, Read, Eq, Ord, Typeable)

-- | Queries, or KRPC message dictionaries with a \"y\" value of
-- \"q\", contain two additional keys; \"q\" and \"a\". Key \"q\" has
-- a string value containing the method name of the query. Key \"a\"
-- has a dictionary value containing named arguments to the query.
--
--    Example Query packet:
--
--    > { "t" : "aa", "y" : "q", "q" : "ping", "a" : { "msg" : "hi!" } }
--
instance BEncode KQuery where
  toBEncode KQuery {..} = toDict $
       "a" .=! queryArgs
    .: "q" .=! queryMethod
    .: "t" .=! queryId
    .: "y" .=! ("q" :: ByteString)
    .: endDict
  {-# INLINE toBEncode #-}

  fromBEncode = fromDict $ do
    lookAhead $ match "y" (BString "q")
    KQuery <$>! "a" <*>! "q" <*>! "t"
  {-# INLINE fromBEncode #-}

{-----------------------------------------------------------------------
-- Response messages
-----------------------------------------------------------------------}

-- | Response messages are sent upon successful completion of a
-- query:
--
--   * KResponse used to signal that callee successufully process a
--   procedure call and to return values from procedure.
--
--   * KResponse should not be sent if error occurred during RPC,
--   'KError' should be sent instead.
--
--   * KResponse can be only sent from server to client.
--
data KResponse = KResponse
  { respVals :: BValue         -- ^ 'BDict' containing return values;
  , respId   :: TransactionId  -- ^ match to the corresponding 'queryId'.
  } deriving (Show, Read, Eq, Ord, Typeable)

-- | Responses, or KRPC message dictionaries with a \"y\" value of
-- \"r\", contain one additional key \"r\". The value of \"r\" is a
-- dictionary containing named return values.
--
--   Example Response packet:
--
--   > { "t" : "aa", "y" : "r", "r" : { "msg" : "you've sent: hi!" } }
--
instance BEncode KResponse where
  toBEncode KResponse {..} = toDict $
       "r" .=! respVals
    .: "t" .=! respId
    .: "y" .=! ("r" :: ByteString)
    .: endDict
  {-# INLINE toBEncode #-}

  fromBEncode = fromDict $ do
    lookAhead $ match "y" (BString "r")
    KResponse <$>! "r" <*>! "t"
  {-# INLINE fromBEncode #-}

{-----------------------------------------------------------------------
-- Summed messages
-----------------------------------------------------------------------}

-- | Generic KRPC message.
data KMessage
  = Q KQuery
  | R KResponse
  | E KError
    deriving (Show, Eq)

instance BEncode KMessage where
  toBEncode (Q q) = toBEncode q
  toBEncode (R r) = toBEncode r
  toBEncode (E e) = toBEncode e

  fromBEncode b =
        Q <$> fromBEncode b
    <|> R <$> fromBEncode b
    <|> E <$> fromBEncode b
    <|> decodingError "KMessage: unknown message or message tag"