diff options
Diffstat (limited to 'Presence/Presence.hs')
-rw-r--r-- | Presence/Presence.hs | 34 |
1 files changed, 28 insertions, 6 deletions
diff --git a/Presence/Presence.hs b/Presence/Presence.hs index 97b9d5b8..198012de 100644 --- a/Presence/Presence.hs +++ b/Presence/Presence.hs | |||
@@ -5,7 +5,9 @@ | |||
5 | {-# LANGUAGE TupleSections #-} | 5 | {-# LANGUAGE TupleSections #-} |
6 | module Presence where | 6 | module Presence where |
7 | 7 | ||
8 | import System.Directory | ||
8 | import System.Environment | 9 | import System.Environment |
10 | import System.IO.Error | ||
9 | import System.Posix.Signals | 11 | import System.Posix.Signals |
10 | import Control.Concurrent (threadDelay,forkIO,forkOS,killThread,throwTo) | 12 | import Control.Concurrent (threadDelay,forkIO,forkOS,killThread,throwTo) |
11 | import Control.Concurrent.STM | 13 | import Control.Concurrent.STM |
@@ -15,6 +17,7 @@ import Control.Monad.Trans | |||
15 | import Control.Monad.IO.Class (MonadIO, liftIO) | 17 | import Control.Monad.IO.Class (MonadIO, liftIO) |
16 | import Network.Socket ( SockAddr(..), PortNumber ) | 18 | import Network.Socket ( SockAddr(..), PortNumber ) |
17 | import System.Endian (fromBE32) | 19 | import System.Endian (fromBE32) |
20 | import Data.Char | ||
18 | import Data.List (nub, (\\), intersect, groupBy, sort, sortBy ) | 21 | import Data.List (nub, (\\), intersect, groupBy, sort, sortBy ) |
19 | import Data.Ord (comparing ) | 22 | import Data.Ord (comparing ) |
20 | import Data.Monoid ( (<>), Sum(..), getSum ) | 23 | import Data.Monoid ( (<>), Sum(..), getSum ) |
@@ -46,6 +49,7 @@ import Crypto.Error | |||
46 | #endif | 49 | #endif |
47 | import Crypto.PubKey.Curve25519 (SecretKey,toPublic) | 50 | import Crypto.PubKey.Curve25519 (SecretKey,toPublic) |
48 | import Text.Read (readMaybe) | 51 | import Text.Read (readMaybe) |
52 | import System.IO | ||
49 | 53 | ||
50 | import LockedChan (LockedChan) | 54 | import LockedChan (LockedChan) |
51 | import TraversableT | 55 | import TraversableT |
@@ -57,7 +61,7 @@ import ConsoleWriter | |||
57 | import ClientState | 61 | import ClientState |
58 | import Util | 62 | import Util |
59 | import qualified Connection | 63 | import qualified Connection |
60 | import Network.Tox.NodeId (id2key) | 64 | import Network.Tox.NodeId (id2key,key2id) |
61 | import Crypto.Tox (decodeSecret) | 65 | import Crypto.Tox (decodeSecret) |
62 | 66 | ||
63 | isPeerKey :: ConnectionKey -> Bool | 67 | isPeerKey :: ConnectionKey -> Bool |
@@ -124,11 +128,22 @@ newPresenceState cw toxman xmpp = atomically $ do | |||
124 | } | 128 | } |
125 | 129 | ||
126 | 130 | ||
131 | nameForClient :: PresenceState -> ConnectionKey -> IO Text | ||
132 | nameForClient state k = do | ||
133 | mc <- atomically $ do | ||
134 | cmap <- readTVar (clients state) | ||
135 | return $ Map.lookup k cmap | ||
136 | case mc of | ||
137 | Nothing -> textHostName | ||
138 | Just client -> case clientProfile client of | ||
139 | "." -> textHostName | ||
140 | profile -> return profile | ||
141 | |||
127 | presenceHooks :: PresenceState -> Int -> Maybe PortNumber -> XMPPServerParameters | 142 | presenceHooks :: PresenceState -> Int -> Maybe PortNumber -> XMPPServerParameters |
128 | presenceHooks state verbosity mport = XMPPServerParameters | 143 | presenceHooks state verbosity mport = XMPPServerParameters |
129 | { xmppChooseResourceName = chooseResourceName state | 144 | { xmppChooseResourceName = chooseResourceName state |
130 | , xmppTellClientHisName = tellClientHisName state | 145 | , xmppTellClientHisName = tellClientHisName state |
131 | , xmppTellMyNameToClient = textHostName | 146 | , xmppTellMyNameToClient = nameForClient state |
132 | , xmppTellMyNameToPeer = \addr -> return $ addrToText addr | 147 | , xmppTellMyNameToPeer = \addr -> return $ addrToText addr |
133 | , xmppTellPeerHisName = return . peerKeyToText | 148 | , xmppTellPeerHisName = return . peerKeyToText |
134 | , xmppTellClientNameOfPeer = flip peerKeyToResolvedName | 149 | , xmppTellClientNameOfPeer = flip peerKeyToResolvedName |
@@ -212,22 +227,29 @@ chooseResourceName state k addr clientsNameForMe desired = do | |||
212 | status <- atomically $ newTVar Nothing | 227 | status <- atomically $ newTVar Nothing |
213 | flgs <- atomically $ newTVar 0 | 228 | flgs <- atomically $ newTVar 0 |
214 | profile <- fmap (fromMaybe ".") | 229 | profile <- fmap (fromMaybe ".") |
215 | $ forM ((,) <$> clientsNameForMe <*> toxManager state) $ \(wanted_profile,toxman) -> | 230 | $ forM ((,) <$> clientsNameForMe <*> toxManager state) $ \(wanted_profile0,toxman) -> |
216 | case Text.splitAt 43 wanted_profile of | 231 | case Text.splitAt 43 wanted_profile0 of |
217 | (pub,".tox") -> do | 232 | (pub,".tox") -> do |
218 | -- TODO: Tox key profile. | 233 | cdir <- ConfigFiles.configPath (L.fromChunks [Text.encodeUtf8 user]) "." "" |
234 | cfs <- map Text.pack <$> listDirectory cdir `catchIOError` (\e -> return []) | ||
235 | let profiles = filter (\f -> Text.toLower f == Text.toLower wanted_profile0) cfs | ||
236 | -- hPutStrLn stderr $ "Toxmpp profile " ++ show (user,wanted_profile0,profiles,cfs) | ||
237 | let wanted_profile = head $ profiles ++ [wanted_profile0] | ||
219 | secs <- configText ConfigFiles.getSecrets user wanted_profile | 238 | secs <- configText ConfigFiles.getSecrets user wanted_profile |
220 | case secs of | 239 | case secs of |
221 | sec:_ | Just s <- decodeSecret (Text.encodeUtf8 sec) | 240 | sec:_ | Just s <- decodeSecret (Text.encodeUtf8 sec) |
222 | , Just (toPublic s) == fmap id2key (readMaybe $ Text.unpack pub) | 241 | , map toLower (show $ key2id $ toPublic s) == map toLower (Text.unpack pub) |
223 | -> do activateAccount toxman k wanted_profile s | 242 | -> do activateAccount toxman k wanted_profile s |
243 | hPutStrLn stderr $ "loaded tox secret " ++ show sec | ||
224 | return wanted_profile | 244 | return wanted_profile |
225 | _ -> do | 245 | _ -> do |
226 | -- XXX: We should probably fail to connect when an | 246 | -- XXX: We should probably fail to connect when an |
227 | -- invalid Tox profile is used. For now, we'll | 247 | -- invalid Tox profile is used. For now, we'll |
228 | -- fall back to the Unix account login. | 248 | -- fall back to the Unix account login. |
249 | hPutStrLn stderr "failed to find tox secret" | ||
229 | return "." | 250 | return "." |
230 | ("*.tox","") -> do | 251 | ("*.tox","") -> do |
252 | hPutStrLn stderr $ "TODO: Match single tox key profile or generate first." | ||
231 | -- TODO: Match single tox key profile or generate first. | 253 | -- TODO: Match single tox key profile or generate first. |
232 | _todo | 254 | _todo |
233 | _ -> return "." | 255 | _ -> return "." |