summaryrefslogtreecommitdiff
path: root/main/Main.hs
diff options
context:
space:
mode:
Diffstat (limited to 'main/Main.hs')
-rw-r--r--main/Main.hs142
1 files changed, 92 insertions, 50 deletions
diff --git a/main/Main.hs b/main/Main.hs
index 3f78db1..403e5e9 100644
--- a/main/Main.hs
+++ b/main/Main.hs
@@ -11,6 +11,7 @@ import Control.Monad.Except
import Control.Monad.Reader
import Control.Monad.State
import Control.Monad.Trans.Maybe
+import Control.Monad.Writer
import Crypto.Random
@@ -61,6 +62,7 @@ import State
import Terminal
import Test
import Version
+import WebSocket
data Options = Options
{ optServer :: ServerOptions
@@ -68,6 +70,7 @@ data Options = Options
, optStorage :: StorageOption
, optChatroomAutoSubscribe :: Maybe Int
, optDmBotEcho :: Maybe Text
+ , optWebSocketServer :: Maybe Int
, optShowHelp :: Bool
, optShowVersion :: Bool
}
@@ -90,6 +93,7 @@ defaultOptions = Options
, optStorage = DefaultStorage
, optChatroomAutoSubscribe = Nothing
, optDmBotEcho = Nothing
+ , optWebSocketServer = Nothing
, optShowHelp = False
, optShowVersion = False
}
@@ -110,7 +114,7 @@ availableServices =
True "peer discovery"
]
-options :: [OptDescr (Options -> Options)]
+options :: [ OptDescr (Options -> Writer [ String ] Options) ]
options =
[ Option ['p'] ["port"]
(ReqArg (\p -> so $ \opts -> opts { serverPort = read p }) "<port>")
@@ -119,57 +123,81 @@ options =
(NoArg (so $ \opts -> opts { serverLocalDiscovery = False }))
"do not send announce packets for local discovery"
, Option [] [ "storage" ]
- (ReqArg (\path -> \opts -> opts { optStorage = FilesystemStorage path }) "<path>")
+ (ReqArg (\path -> \opts -> return opts { optStorage = FilesystemStorage path }) "<path>")
"use storage in <path>"
, Option [] [ "memory-storage" ]
- (NoArg (\opts -> opts { optStorage = MemoryStorage }))
+ (NoArg (\opts -> return opts { optStorage = MemoryStorage }))
"use memory storage"
, Option [] ["chatroom-auto-subscribe"]
- (ReqArg (\count -> \opts -> opts { optChatroomAutoSubscribe = Just (read count) }) "<count>")
+ (ReqArg (\count -> \opts -> return opts { optChatroomAutoSubscribe = Just (read count) }) "<count>")
"automatically subscribe for up to <count> chatrooms"
#ifdef ENABLE_ICE_SUPPORT
, Option [] [ "discovery-stun-port" ]
- (ReqArg (\value -> serviceAttr $ \attrs -> attrs { discoveryStunPort = Just (read value) }) "<port>")
+ (ReqArg (\value -> serviceAttr $ \attrs -> return attrs { discoveryStunPort = Just (read value) }) "<port>")
"offer specified <port> to discovery peers for STUN protocol"
, Option [] [ "discovery-stun-server" ]
- (ReqArg (\value -> serviceAttr $ \attrs -> attrs { discoveryStunServer = Just (read value) }) "<server>")
+ (ReqArg (\value -> serviceAttr $ \attrs -> return attrs { discoveryStunServer = Just (read value) }) "<server>")
"offer <server> (domain name or IP address) to discovery peers for STUN protocol"
, Option [] [ "discovery-turn-port" ]
- (ReqArg (\value -> serviceAttr $ \attrs -> attrs { discoveryTurnPort = Just (read value) }) "<port>")
+ (ReqArg (\value -> serviceAttr $ \attrs -> return attrs { discoveryTurnPort = Just (read value) }) "<port>")
"offer specified <port> to discovery peers for TURN protocol"
, Option [] [ "discovery-turn-server" ]
- (ReqArg (\value -> serviceAttr $ \attrs -> attrs { discoveryTurnServer = Just (read value) }) "<server>")
+ (ReqArg (\value -> serviceAttr $ \attrs -> return attrs { discoveryTurnServer = Just (read value) }) "<server>")
"offer <server> (domain name or IP address) to discovery peers for TURN protocol"
#endif
+ , Option [] [ "discovery-tunnel" ]
+ (OptArg (\value -> \opts -> do
+ fun <- provideTunnelFun value
+ serviceAttr (\attrs -> return attrs { discoveryProvideTunnel = fun }) opts) "<peer-type>")
+ "offer to provide tunnel for peers of given <peer-type>, possible values: all, none, websocket"
, Option [] ["dm-bot-echo"]
- (ReqArg (\prefix -> \opts -> opts { optDmBotEcho = Just (T.pack prefix) }) "<prefix>")
+ (ReqArg (\prefix -> \opts -> return opts { optDmBotEcho = Just (T.pack prefix) }) "<prefix>")
"automatically reply to direct messages with the same text prefixed with <prefix>"
+ , Option [] [ "websocket-server" ]
+ (ReqArg (\value -> \opts -> return opts { optWebSocketServer = Just (read value) }) "<port>")
+ "start WebSocket server on given port"
, Option ['h'] ["help"]
- (NoArg $ \opts -> opts { optShowHelp = True })
+ (NoArg $ \opts -> return opts { optShowHelp = True })
"show this help and exit"
, Option ['V'] ["version"]
- (NoArg $ \opts -> opts { optShowVersion = True })
+ (NoArg $ \opts -> return opts { optShowVersion = True })
"show version and exit"
]
where
- so f opts = opts { optServer = f $ optServer opts }
+ so f opts = return opts { optServer = f $ optServer opts }
- updateService :: Service s => (ServiceAttributes s -> ServiceAttributes s) -> SomeService -> SomeService
+ updateService :: (Service s, Monad m, Typeable m) => (ServiceAttributes s -> m (ServiceAttributes s)) -> SomeService -> m SomeService
updateService f some@(SomeService proxy attrs)
- | Just f' <- cast f = SomeService proxy (f' attrs)
- | otherwise = some
-
- serviceAttr :: Service s => (ServiceAttributes s -> ServiceAttributes s) -> Options -> Options
- serviceAttr f opts = opts { optServices = map (\sopt -> sopt { soptService = updateService f (soptService sopt) }) (optServices opts) }
-
-servicesOptions :: [OptDescr (Options -> Options)]
+ | Just f' <- cast f = SomeService proxy <$> f' attrs
+ | otherwise = return some
+
+ serviceAttr :: (Service s, Monad m, Typeable m) => (ServiceAttributes s -> m (ServiceAttributes s)) -> Options -> m Options
+ serviceAttr f opts = do
+ services' <- forM (optServices opts) $ \sopt -> do
+ service <- updateService f (soptService sopt)
+ return sopt { soptService = service }
+ return opts { optServices = services' }
+
+ provideTunnelFun :: Maybe String -> Writer [ String ] (Peer -> Bool)
+ provideTunnelFun Nothing = return $ const True
+ provideTunnelFun (Just "all") = return $ const True
+ provideTunnelFun (Just "none") = return $ const False
+ provideTunnelFun (Just "websocket") = return $ \peer ->
+ case peerAddress peer of
+ CustomPeerAddress addr | Just WebSocketAddress {} <- cast addr -> True
+ _ -> False
+ provideTunnelFun (Just name) = do
+ tell [ "Invalid value of --discovery-tunnel: ‘" <> name <> "’\n" ]
+ return $ const False
+
+servicesOptions :: [ OptDescr (Options -> Writer [ String ] Options) ]
servicesOptions = concatMap helper $ "all" : map soptName availableServices
where
helper name =
- [ Option [] ["enable-" <> name] (NoArg $ so $ change name $ \sopt -> sopt { soptEnabled = True }) ""
- , Option [] ["disable-" <> name] (NoArg $ so $ change name $ \sopt -> sopt { soptEnabled = False }) ""
+ [ Option [] [ "enable-" <> name ] (NoArg $ so $ change name $ \sopt -> sopt { soptEnabled = True }) ""
+ , Option [] [ "disable-" <> name ] (NoArg $ so $ change name $ \sopt -> sopt { soptEnabled = False }) ""
]
- so f opts = opts { optServices = f $ optServices opts }
+ so f opts = return opts { optServices = f $ optServices opts }
change :: String -> (ServiceOption -> ServiceOption) -> [ServiceOption] -> [ServiceOption]
change name f (s : ss)
| soptName s == name || name == "all"
@@ -187,13 +215,16 @@ getDefaultStorageDir = do
main :: IO ()
main = do
- (opts, args) <- (getOpt RequireOrder (options ++ servicesOptions) <$> getArgs) >>= \case
- (o, args, []) -> do
- return (foldl (flip id) defaultOptions o, args)
- (_, _, errs) -> do
+ let printErrors errs = do
progName <- getProgName
hPutStrLn stderr $ concat errs <> "Try `" <> progName <> " --help' for more information."
exitFailure
+ (opts, args) <- (getOpt RequireOrder (options ++ servicesOptions) <$> getArgs) >>= \case
+ (wo, args, []) ->
+ case runWriter (foldM (flip ($)) defaultOptions wo) of
+ ( o, [] ) -> return ( o, args )
+ ( _, errs ) -> printErrors errs
+ (_, _, errs) -> printErrors errs
st <- liftIO $ case optStorage opts of
DefaultStorage -> openStorage =<< getDefaultStorageDir
@@ -362,6 +393,10 @@ interactiveLoop st opts = withTerminal commandCompletion $ \term -> do
startServer (optServer opts) erebosHead extPrintLn $
map soptService $ filter soptEnabled $ optServices opts
+ case optWebSocketServer opts of
+ Just port -> startWebsocketServer server "::" port extPrintLn
+ Nothing -> return ()
+
void $ liftIO $ forkIO $ void $ forever $ do
peer <- getNextPeerChange server
peerIdentity peer >>= \case
@@ -493,7 +528,10 @@ getSelectedChatroom = gets csContext >>= \case
_ -> throwOtherError "no chatroom selected"
getSelectedConversation :: CommandM Conversation
-getSelectedConversation = gets csContext >>= \case
+getSelectedConversation = gets csContext >>= getConversationFromContext
+
+getConversationFromContext :: CommandContext -> CommandM Conversation
+getConversationFromContext = \case
SelectedPeer peer -> peerIdentity peer >>= \case
PeerIdentityFull pid -> directMessageConversation $ finalOwner pid
_ -> throwOtherError "incomplete peer identity"
@@ -507,6 +545,13 @@ getSelectedConversation = gets csContext >>= \case
SelectedConversation conv -> reloadConversation conv
_ -> throwOtherError "no contact, peer or conversation selected"
+getSelectedOrManualContext :: CommandM CommandContext
+getSelectedOrManualContext = do
+ asks ciLine >>= \case
+ "" -> gets csContext
+ str | all isDigit str -> getContextByIndex (read str)
+ _ -> throwOtherError "invalid index"
+
commands :: [(String, Command)]
commands =
[ ("history", cmdHistory)
@@ -628,19 +673,22 @@ cmdMembers = do
forM_ (chatroomMembers room) $ \x -> do
cmdPutStrLn $ maybe "<unnamed>" T.unpack $ idName x
+getContextByIndex :: Int -> CommandM CommandContext
+getContextByIndex n = do
+ join (asks ciContextOptions) >>= \ctxs -> if
+ | n > 0, (ctx : _) <- drop (n - 1) ctxs -> return ctx
+ | otherwise -> throwOtherError "invalid index"
cmdSelectContext :: Command
cmdSelectContext = do
n <- read <$> asks ciLine
- join (asks ciContextOptions) >>= \ctxs -> if
- | n > 0, (ctx : _) <- drop (n - 1) ctxs -> do
- modify $ \s -> s { csContext = ctx }
- case ctx of
- SelectedChatroom rstate -> do
- when (not (roomStateSubscribe rstate)) $ do
- chatroomSetSubscribe (head $ roomStateData rstate) True
- _ -> return ()
- | otherwise -> throwOtherError "invalid index"
+ ctx <- getContextByIndex n
+ modify $ \s -> s { csContext = ctx }
+ case ctx of
+ SelectedChatroom rstate -> do
+ when (not (roomStateSubscribe rstate)) $ do
+ chatroomSetSubscribe (head $ roomStateData rstate) True
+ _ -> return ()
cmdSend :: Command
cmdSend = void $ do
@@ -654,12 +702,12 @@ cmdSend = void $ do
cmdDelete :: Command
cmdDelete = void $ do
- deleteConversation =<< getSelectedConversation
+ deleteConversation =<< getConversationFromContext =<< getSelectedOrManualContext
modify $ \s -> s { csContext = NoContext }
cmdHistory :: Command
cmdHistory = void $ do
- conv <- getSelectedConversation
+ conv <- getConversationFromContext =<< getSelectedOrManualContext
case conversationHistory conv of
thread@(_:_) -> do
tzone <- liftIO $ getCurrentTimeZone
@@ -824,7 +872,7 @@ cmdConversations = do
cmdDetails :: Command
cmdDetails = do
- gets csContext >>= \case
+ getSelectedOrManualContext >>= \case
SelectedPeer peer -> do
cmdPutStrLn $ unlines
[ "Network peer:"
@@ -900,17 +948,11 @@ cmdDiscoveryInit = void $ do
cmdDiscovery :: Command
cmdDiscovery = void $ do
- Just peer <- gets csIcePeer
- st <- getStorage
+ server <- asks ciServer
sref <- asks ciLine
- eprint <- asks ciPrint
- liftIO $ readRef st (BC.pack sref) >>= \case
- Nothing -> error "ref does not exist"
- Just ref -> do
- res <- runExceptT $ sendToPeer peer $ DiscoverySearch ref
- case res of
- Right _ -> return ()
- Left err -> eprint err
+ case readRefDigest (BC.pack sref) of
+ Nothing -> throwOtherError "failed to parse ref"
+ Just dgst -> discoverySearch server dgst
#ifdef ENABLE_ICE_SUPPORT