summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorjoe <joe@jerkface.net>2017-09-15 06:47:51 -0400
committerjoe <joe@jerkface.net>2017-09-15 06:47:51 -0400
commita4bc159e22b8c270284bb9ad10e511c6a411ebf6 (patch)
tree3f9ce2a288e0f078084362ce6ac16c957b15909d
parent2f937504c7ce372e801e8828746c775b662f1118 (diff)
Deleted obsolete cruft.
-rw-r--r--ToxData.hs23
-rw-r--r--ToxPacket.hs122
2 files changed, 0 insertions, 145 deletions
diff --git a/ToxData.hs b/ToxData.hs
deleted file mode 100644
index 06a9b3b8..00000000
--- a/ToxData.hs
+++ /dev/null
@@ -1,23 +0,0 @@
1module ToxData where
2
3import Crypto
4
5-- data DHTPacketKind = Ping | Pong | GetNodes | SendNodes
6data DHTPacket a = DHTPacket
7 { dhtSender :: PublicKey
8 , dhtEncrypted :: WithNonce24 (Encrypted (WithNonce8 a))
9 }
10
11data WithNonce8 a = WithNonce8 a Nonce8
12
13data WithNonce24 a = WithNonce24 a Nonce24
14
15data AliasedRequest a = AliasedRequest
16 { alias :: PublicKey
17 , aliasPayload :: WithNonce24 (Encrypted (WithNonce8 a))
18 }
19
20data ForwardedRequest a = ForwardedRequest
21 { forwardTo :: PublicKey
22 , forwarded :: AliasedRequest a
23 }
diff --git a/ToxPacket.hs b/ToxPacket.hs
deleted file mode 100644
index 1d848a61..00000000
--- a/ToxPacket.hs
+++ /dev/null
@@ -1,122 +0,0 @@
1{-# LANGUAGE BangPatterns #-}
2{-# LANGUAGE CPP #-}
3{-# LANGUAGE GeneralizedNewtypeDeriving #-}
4{-# LANGUAGE TupleSections #-}
5module ToxPacket where
6
7import Crypto.Tox
8import Data.Serialize as S
9import Data.Aeson as JSON
10import Data.IP
11import qualified Data.ByteString.Char8 as C8
12import qualified Data.ByteString as B
13import Data.Word
14import qualified Data.ByteString.Base16 as Base16
15import Network.Socket
16import Data.ByteArray (ByteArrayAccess)
17import qualified Data.ByteArray as BA
18import Data.Hashable
19import Data.Bits
20import System.IO.Unsafe
21import qualified Text.ParserCombinators.ReadP as RP
22import Foreign.Storable
23import Network.Tox.Address -- import Network.Address hiding (nodePort,nodeInfo)
24import Text.Read
25import Control.Applicative
26import Data.Char
27import Control.Monad
28import Crypto.Error.Types (throwCryptoError)
29
30-- ## DHT Request packets
31--
32-- | Length | Contents |
33-- |:-------|:--------------------------|
34-- | `1` | `uint8_t` (0x20) |
35-- | `32` | receiver's DHT public key |
36-- ... ...
37
38data DHTRequestPacket = DHTRequestPacket
39 { requestTarget :: PublicKey
40 , request :: Assym (Encrypted DHTRequest)
41 }
42
43instance Serialize DHTRequestPacket where
44 get = _todo
45 put = _todo
46
47
48data DHTRequest
49 = NATPing Nonce8
50 | NATPong Nonce8
51 | DHTPK DHTPublicKey
52
53-- | Length | Contents |
54-- |:------------|:------------------------------------|
55-- | `1` | `uint8_t` (0x9c) |
56-- | `8` | `uint64_t` `no_replay` |
57-- | `32` | Our DHT public key |
58-- | `[39, 204]` | Maximum of 4 nodes in packed format |
59data DHTPublicKey = DHTPublicKey
60 { dhtpkNonce :: Nonce8
61 , dhtpk :: PublicKey
62 , dhtpkNodes :: SendNodes
63 }
64
65-- | `32` | sender's DHT public key |
66-- | `24` | nonce |
67-- | `?` | encrypted message |
68data Assym a = Assym
69 { senderKey :: PublicKey
70 , assymNonce :: Nonce24
71 , assymData :: a
72 }
73
74newtype GetNodes = GetNodes NodeId
75 deriving (Eq,Ord,Show,Read,S.Serialize)
76
77newtype SendNodes = SendNodes [NodeInfo]
78 deriving (Eq,Ord,Show,Read)
79
80instance S.Serialize SendNodes where
81 get = do
82 cnt <- S.get :: S.Get Word8
83 ns <- sequence $ replicate (fromIntegral cnt) S.get
84 return $ SendNodes ns
85
86 put (SendNodes ns) = do
87 let ns' = take 4 ns
88 S.put (fromIntegral (length ns') :: Word8)
89 mapM_ S.put ns'
90
91data Ping = Ping deriving Show
92data Pong = Pong deriving Show
93
94instance S.Serialize Ping where
95 get = do w8 <- S.get
96 if (w8 :: Word8) /= 0
97 then fail "Malformed ping."
98 else return Ping
99 put Ping = S.put (0 :: Word8)
100
101instance S.Serialize Pong where
102 get = do w8 <- S.get
103 if (w8 :: Word8) /= 1
104 then fail "Malformed pong."
105 else return Pong
106 put Pong = S.put (1 :: Word8)
107
108newtype CookieRequest = CookieRequest PublicKey
109newtype CookieResponse = CookieResponse Cookie
110
111data Cookie = Cookie Nonce24 (Encrypted CookieData)
112
113instance Sized Cookie where size = ConstSize 112 -- 24 byte nonce + 88 byte cookie data
114
115data CookieData = CookieData -- 16 (mac)
116 { cookieTime :: Word64 -- 8
117 , longTermKey :: PublicKey -- 32
118 , dhtKey :: PublicKey -- + 32
119 } -- = 88 bytes when encrypted.
120
121instance Sized CookieRequest where
122 size = ConstSize 64 -- 32 byte key + 32 byte padding