summaryrefslogtreecommitdiff
path: root/src/Network/BitTorrent/Tracker/UDP.hs
blob: 13e1298b6f8652f9569cc43d6c880673afec4c60 (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
-- |
--   Copyright   :  (c) Sam T. 2013
--   License     :  MIT
--   Maintainer  :  pxqr.sta@gmail.com
--   Stability   :  experimental
--   Portability :  portable
--
--   This module implement low-level UDP tracker protocol.
--   For more info see: http://www.bittorrent.org/beps/bep_0015.html
--
{-# LANGUAGE RecordWildCards            #-}
{-# LANGUAGE FlexibleInstances          #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Network.BitTorrent.Tracker.UDP
       ( Request(..), Response(..)
       ) where

import Control.Applicative
import Control.Monad
import Data.Serialize
import Data.Word
import Data.Text
import Data.Text.Encoding
import Network.Socket hiding (Connected)
import Network.Socket.ByteString as BS

import Data.Torrent.Metainfo ()
import Network.BitTorrent.Tracker.Protocol


-- | Connection Id is used for entire tracker session.
newtype ConnId  = ConnId  { getConnId  :: Word64 }
                  deriving (Show, Eq, Serialize)

-- | Transaction Id is used for within UDP RPC.
newtype TransId = TransId { getTransId :: Word32 }
                  deriving (Show, Eq, Serialize)

genTransactionId :: IO TransId
genTransactionId = return (TransId 0)

initialConnectionId :: ConnId
initialConnectionId = ConnId 0

data Request  = Connect
              | Announce  AnnounceQuery
              | Scrape    ScrapeQuery

data Response = Connected
              | Announced AnnounceInfo
              | Scraped   [ScrapeInfo]
              | Failed    Text

-- TODO rename to message?
data Transaction a = Transaction
  { connId  :: !ConnId
  , transId :: !TransId
  , body    :: !a
  } deriving Show

type MessageId = Word32

connectId, announceId, scrapeId, errorId :: MessageId
connectId  = 0
announceId = 1
scrapeId   = 2
errorId    = 3

instance Serialize (Transaction Request) where
  put Transaction {..} = do
    case body of
      Connect        -> do
        put connId
        put connectId
        put transId

      Announce query -> do
        put connId
        put announceId
        put transId
        put query

      Scrape   hashes -> do
        put connId
        put announceId
        put transId
        forM_ hashes put

  get = do
    cid <- get
    rid <- getWord32be
    tid <- get
    bod <- getBody rid

    return $ Transaction {
        connId  = cid
      , transId = tid
      , body    = bod
      }
    where
      getBody :: MessageId -> Get Request
      getBody msgId
        | msgId == connectId  = return Connect
        | msgId == announceId = Announce <$> get
        | msgId == scrapeId   = Scrape   <$> many get
        |       otherwise     = fail "unknown message id"

instance Serialize (Transaction Response) where
  put Transaction {..} = do
    case body of
      Connected -> do
        put connId
        put connectId
        put transId

      Announced info -> do
        put connId
        put announceId
        put transId
        put info

      Scraped infos -> do
        put connId
        put scrapeId
        put transId
        forM_ infos put

      Failed info -> do
        put connId
        put errorId
        put transId
        put (encodeUtf8 info)


  get = do
    cid <- get
    rid <- getWord32be
    tid <- get
    bod <- getBody rid

    return $ Transaction {
        connId  = cid
      , transId = tid
      , body    = bod
      }
    where
      getBody :: MessageId -> Get Response
      getBody msgId
        | msgId == connectId  = return $ Connected
        | msgId == announceId = Announced <$> get
        | msgId == scrapeId   = Scraped   <$> many get
        | msgId == errorId    = do
          bs <- get
          case decodeUtf8' bs of
            Left ex   -> fail (show ex)
            Right msg -> return $ Failed msg
        |      otherwise      = fail "unknown message id"

maxPacketSize :: Int
maxPacketSize = 98 -- announce request packet

call :: Request -> IO Response
call request = do
  tid <- genTransactionId
  let trans = Transaction initialConnectionId tid request

  let addr = error "TODO"
  sock <- socket AF_INET Datagram defaultProtocol
  BS.sendAllTo sock (encode trans) addr
  (resp, addr') <- BS.recvFrom sock 4096
  if addr' /= addr
    then error "address mismatch"
    else case decode resp of
      Left msg -> error msg
      Right (Transaction {..}) -> do
        if tid /= transId
          then error "transaction id mismatch"
          else return body

data Connection = Connection

type URI = ()

connectTracker :: URI -> IO Connection
connectTracker = undefined

announceTracker :: Connection -> AnnounceQuery -> IO AnnounceInfo
announceTracker = undefined

scrape :: Connection -> ScrapeQuery -> IO [ScrapeInfo]
scrape = undefined