diff options
-rw-r--r-- | Mainline.hs | 38 |
1 files changed, 32 insertions, 6 deletions
diff --git a/Mainline.hs b/Mainline.hs index e2ab2d7f..d24b3376 100644 --- a/Mainline.hs +++ b/Mainline.hs | |||
@@ -7,6 +7,8 @@ | |||
7 | module Mainline where | 7 | module Mainline where |
8 | 8 | ||
9 | import Control.Arrow | 9 | import Control.Arrow |
10 | import Control.Concurrent.STM | ||
11 | import Crypto.Random | ||
10 | import Data.BEncode as BE | 12 | import Data.BEncode as BE |
11 | import Data.BEncode.BDict as BE | 13 | import Data.BEncode.BDict as BE |
12 | import Data.Bool | 14 | import Data.Bool |
@@ -16,6 +18,7 @@ import Data.ByteString as B | |||
16 | import Data.ByteString.Lazy (toStrict) | 18 | import Data.ByteString.Lazy (toStrict) |
17 | import Data.Data | 19 | import Data.Data |
18 | import Data.IP | 20 | import Data.IP |
21 | import Data.Maybe | ||
19 | import Data.Monoid | 22 | import Data.Monoid |
20 | import qualified Data.Serialize as S | 23 | import qualified Data.Serialize as S |
21 | import Data.Typeable | 24 | import Data.Typeable |
@@ -84,7 +87,7 @@ data Error = Error | |||
84 | , errorMessage :: !ByteString -- ^ Human-readable text message. | 87 | , errorMessage :: !ByteString -- ^ Human-readable text message. |
85 | } deriving ( Show, Eq, Ord, Typeable, Data, Read ) | 88 | } deriving ( Show, Eq, Ord, Typeable, Data, Read ) |
86 | 89 | ||
87 | newtype TransactionId = TransactionId Word16 | 90 | newtype TransactionId = TransactionId ByteString |
88 | deriving (Eq, Ord, Show, BEncode) | 91 | deriving (Eq, Ord, Show, BEncode) |
89 | 92 | ||
90 | newtype Method = Method ByteString | 93 | newtype Method = Method ByteString |
@@ -145,26 +148,49 @@ encodePacket :: Message BValue -> NodeInfo -> (ByteString, SockAddr) | |||
145 | encodePacket msg ni = ( toStrict $ BE.encode msg | 148 | encodePacket msg ni = ( toStrict $ BE.encode msg |
146 | , nodeAddr ni ) | 149 | , nodeAddr ni ) |
147 | 150 | ||
151 | newClient :: | ||
152 | SockAddr -> IO (Client String Method TransactionId NodeInfo (Message BValue)) | ||
148 | newClient addr = do | 153 | newClient addr = do |
149 | udp <- udpTransport addr | 154 | udp <- udpTransport addr |
155 | nid <- error "todo: tentative node id" | ||
156 | self <- atomically $ newTVar | ||
157 | $ NodeInfo nid (fromMaybe (toEnum 0) $ fromSockAddr addr) | ||
158 | (fromMaybe 0 $ sockAddrPort addr) | ||
159 | -- drg <- getSystemDRG | ||
150 | let net = layerTransport parsePacket encodePacket udp | 160 | let net = layerTransport parsePacket encodePacket udp |
151 | return net | 161 | dispatch tbl = DispatchMethods |
162 | { classifyInbound = classify | ||
163 | , lookupHandler = handlers | ||
164 | , tableMethods = tbl | ||
165 | } | ||
166 | mapT = transactionMethods mapMethods gen | ||
167 | gen :: Word16 -> (TransactionId, Word16) | ||
168 | gen cnt = (TransactionId $ S.encode cnt, cnt+1) | ||
169 | map_var <- atomically $ newTVar (0, mempty) | ||
170 | return Client | ||
171 | { clientNet = net | ||
172 | , clientDispatcher = dispatch mapT | ||
173 | , clientErrorReporter = ignoreErrors -- TODO | ||
174 | , clientPending = map_var | ||
175 | , clientAddress = atomically (readTVar self) | ||
176 | , clientResponseId = return | ||
177 | } | ||
152 | 178 | ||
153 | classify :: Message BValue -> MessageClass String Method TransactionId | 179 | classify :: Message BValue -> MessageClass String Method TransactionId |
154 | classify (Q { msgID = tid, qryMethod = meth }) = IsQuery meth tid | 180 | classify (Q { msgID = tid, qryMethod = meth }) = IsQuery meth tid |
155 | classify (R { msgID = tid }) = IsResponse tid | 181 | classify (R { msgID = tid }) = IsResponse tid |
156 | 182 | ||
157 | encodePayload () tid self dest b = R (nodeId self) tid (Right $ BE.toBEncode b) (Just $ nodeAddr dest) | 183 | encodePayload tid self dest b = R (nodeId self) tid (Right $ BE.toBEncode b) (Just $ nodeAddr dest) |
158 | 184 | ||
159 | errorPayload () tid self dest e = R (nodeId self) tid (Left e) (Just $ nodeAddr dest) | 185 | errorPayload tid self dest e = R (nodeId self) tid (Left e) (Just $ nodeAddr dest) |
160 | 186 | ||
161 | decodePayload :: BEncode a => Message BValue -> Either String a | 187 | decodePayload :: BEncode a => Message BValue -> Either String a |
162 | decodePayload msg = BE.fromBEncode $ qryPayload msg | 188 | decodePayload msg = BE.fromBEncode $ qryPayload msg |
163 | 189 | ||
164 | handler f = Just $ MethodHandler decodePayload encodePayload f | 190 | handler f = Just $ MethodHandler decodePayload encodePayload f |
165 | 191 | ||
166 | handlers :: Method -> Maybe (MethodHandler String TransactionId NodeInfo (Message BValue) ()) | 192 | handlers :: Method -> Maybe (MethodHandler String TransactionId NodeInfo (Message BValue)) |
167 | handlers (Method "ping" ) = handler pingH | 193 | handlers (Method "ping" ) = error "handler pingH" |
168 | handlers (Method "find_node") = error "find_node" | 194 | handlers (Method "find_node") = error "find_node" |
169 | handlers (Method "get_peers") = error "get_peers" | 195 | handlers (Method "get_peers") = error "get_peers" |
170 | handlers (Method meth ) = Just $ MethodHandler decodePayload errorPayload (defaultH meth) | 196 | handlers (Method meth ) = Just $ MethodHandler decodePayload errorPayload (defaultH meth) |