summaryrefslogtreecommitdiff
path: root/Connection/Tox.hs
blob: 00d15aa73f7aae06be132fb7c9f5c12a7192cf7b (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
{-# LANGUAGE GADTs #-}
module Connection.Tox where

import qualified Connection   as G
         ;import Connection   (Manager (..), Policy (..))
import Control.Concurrent.STM
-- import Crypto.Tox
import Data.Dependent.Sum
import Data.Functor.Identity
import qualified Data.Map     as Map
-- import Data.Maybe
import Network.Tox
import Network.Tox.NodeId
import PingMachine
import Text.Read


-- | This type indicates the progress of a tox encrypted friend link
-- connection.  Two scenarios are illustrated below.  The parenthesis show the
-- current 'G.Status' 'ToxProgress' of the session.
--
--
-- Perfect handshake scenario:
--
--  Peer 1                                  Peer 2
--  (InProgress AcquiringCookie)            (Dormant/InProgress AcquiringCookie)
--                     Cookie request ->
--                                       <- Cookie response
--  (InProgress AwaitingHandshake)          (Dormant/InProgress AcquiringCookie)
--                   Handshake packet ->
--                                          * accepts connection
--                                          (InProgress AwaitingSessionPacket)
--                                       <- Handshake packet
--  *accepts connection
--  (InProgress AwaitingSessionPacket)
--                   Encrypted packet -> <- Encrypted packet
--  *confirms connection                    *confirms connection
--  (Established)                           (Established)
--
--                           Connection successful.
--
--                  Encrypted packets -> <- Encrypted packets
--
--
--
--
--  More realistic handshake scenario:
--  Peer 1                                  Peer 2
--  (InProgress AcquiringCookie)            (Dormant/InProgress AcquiringCookie)
--                      Cookie request ->   *packet lost*
--                      Cookie request ->
--                                        <- Cookie response
--  (InProgress AwaitingHandshake)           (Dormant/InProgress AcquiringCookie)
--
--                                           *Peer 2 randomly starts new connection to peer 1
--                                           (InProgress AcquiringCookie)
--                                        <- Cookie request
--                     Cookie response ->
--                                           (InProgress AwaitingHandshake)
--
--                    Handshake packet -> <- Handshake packet
--  *accepts connection                      * accepts connection
--  (InProgress AwaitingSessionPacket)      (InProgress AwaitingSessionPacket)
--
--                    Encrypted packet -> <- Encrypted packet
--  *confirms connection                     *confirms connection
--  (Established)                           (Established)
--
--                              Connection successful.
--
--                   Encrypted packets -> <- Encrypted packets
data ToxProgress
    = AwaitingDHTKey        -- ^ Waiting to receive their DHT key.
    | AcquiringIPAddress    -- ^ Searching DHT to obtain their node's IP & port.
    | AcquiringCookie       -- ^ Attempting to obtain a cookie.
    | AwaitingHandshake     -- ^ Waiting to receive a handshake.
    | AwaitingSessionPacket -- ^ Connection is "accepted" but not yet "confirmed".
    deriving (Eq,Ord,Enum,Show)


data Parameters = Parameters
    { -- | Various Tox transports and clients.
      toxTransports :: Tox
      -- | Thread to be forked when a connection is established.
      -- TODO: this function should accept relevant parameters.
    , onToxSession  :: IO ()
    }

data Key = Key NodeId{-me-} NodeId{-them-}

instance Show Key where show = show . showKey_


-- | A conneciton status that is tagged with a state type that is specific to
-- the status.
data Transient a where
    IsDormant               :: Transient ()
    IsAwaitingDHTKey        :: Transient ()
    IsAcquiringIPAddress    :: Transient ()
    IsAcquiringCookie       :: Transient ()
    IsAwaitingHandshake     :: Transient ()
    IsAwaitingSessionPacket :: Transient ()
    IsEstablished           :: Transient ()


untag :: DSum Transient Identity -> G.Status ToxProgress
untag (IsDormant               :=> _) = G.Dormant
untag (IsAwaitingDHTKey        :=> _) = G.InProgress AwaitingDHTKey
untag (IsAcquiringIPAddress    :=> _) = G.InProgress AcquiringIPAddress
untag (IsAcquiringCookie       :=> _) = G.InProgress AcquiringCookie
untag (IsAwaitingHandshake     :=> _) = G.InProgress AwaitingHandshake
untag (IsAwaitingSessionPacket :=> _) = G.InProgress AwaitingSessionPacket
untag (IsEstablished           :=> _) = G.Established


data SessionState = SessionState
    { transient     :: TVar (DSum Transient Identity)
    , connPolicy    :: TVar Policy
    , connPingLogic :: PingMachine
    }

sessionStatus :: SessionState -> G.Connection ToxProgress
sessionStatus st = G.Connection
    { G.connStatus    = untag <$> readTVar (transient st)
    , G.connPolicy    = readTVar (connPolicy st)
    , G.connPingLogic = connPingLogic st
    }


-- | This function will fork threads as necessary.
setToxPolicy :: Parameters
             -> TVar (Map.Map Key SessionState)
             -> Key
             -> Policy
             -> IO ()
setToxPolicy params conmap k policy = case policy of
    TryingToConnect -> do
        -- TODO initiate connecting if we haven't already
        -- When established, invoke 'onToxSession'.
        return ()
    RefusingToConnect -> do
        -- TODO disconnect or cancel any pending connection
        return ()
    OpenToConnect -> do
        -- TODO passively accept connections if they initiate.
        return ()


showKey_ :: Key -> String
showKey_ (Key me them) = show me ++ ":" ++ show them

stringToKey_ :: String -> Maybe Key
stringToKey_ s = let (xs,ys) = break (==':') s
                 in if null ys then Nothing
                               else do me <- readMaybe xs
                                       them <- readMaybe (drop 1 ys)
                                       return $ Key me them

toxManager :: Parameters -> IO (Manager ToxProgress Key)
toxManager params = do
    conmap <- newTVarIO Map.empty
    return Manager
        { setPolicy    = setToxPolicy params conmap             -- k -> Policy -> IO ()
        , connections  = fmap sessionStatus <$> readTVar conmap -- STM (Map k (Connection status))
        , stringToKey  = stringToKey_                           -- String -> Maybe k
        , showProgress = show                                   -- status -> String
        , showKey      = showKey_                               -- k -> String
        }