{-# LANGUAGE OverloadedStrings, RankNTypes, FlexibleContexts #-} module Main where import Types import Hash import Pty import Memory import CmdLine import Log import Graphviz import Replay import Session import Crypto import Control.Concurrent import Control.Concurrent.Async import Control.Concurrent.STM import System.IO import System.Process import System.Exit import qualified Data.ByteString as B import Data.List import Data.List.NonEmpty (NonEmpty(..), toList) import Data.Monoid import Data.Time.Clock.POSIX main :: IO () main = do c <- getCmdLine case mode c of Test -> test Graphviz g -> graphviz g Replay r -> replay r test :: IO () test = do exitstatus <- go startSession sessionDone exitWith exitstatus where go startmsg = runWithPty "dash" [] $ \(p, ph) -> do ichan <- newTChanIO ochan <- newTChanIO dthread <- async (developer ichan ochan) uthread <- async (user startmsg p ichan ochan) exitstatus <- waitForProcess ph cancel dthread cancel uthread return exitstatus networkDelay :: IO () networkDelay = threadDelay 800000 -- 800 ms ; the latency to geosync orbit -- networkDelay = threadDelay 150000 -- 150 ms ; transatlantic latency developer :: TChan (Message Entered) -> TChan (Message Seen) -> IO () developer ichan ochan = withLogger "debug-me-developer.log" $ \logger -> do startmsg <- atomically $ readTChan ochan logger $ User startmsg starthash <- case startmsg of ActivityMessage act@(Activity (Seen (Val b)) Nothing sig) -> do B.hPut stdout b hFlush stdout return (hash act) _ -> protocolError $ "Unexpected startup: " ++ show startmsg devstate <- newTVarIO $ DeveloperState { lastSeen = starthash , sentSince = mempty , enteredSince = mempty , lastActivity = starthash } _ <- sendTtyInput ichan devstate logger `concurrently` sendTtyOutput ochan devstate logger return () data DeveloperState = DeveloperState { lastSeen :: Hash , sentSince :: [B.ByteString] , enteredSince :: [Hash] , lastActivity :: Hash } deriving (Show) -- | Read things typed by the developer, and forward them to the TChan. sendTtyInput :: TChan (Message Entered) -> TVar DeveloperState -> Logger -> IO () sendTtyInput ichan devstate logger = go where go = do b <- B.hGetSome stdin 1024 if b == B.empty then return () else send b send b = do act <- atomically $ do ds <- readTVar devstate let ed = if lastActivity ds == lastSeen ds then B.concat $ sentSince ds else case reverse (sentSince ds) of [] -> mempty (lb:_) -> lb let entered = Entered { enteredData = Val b , echoData = Val ed } let act = Activity entered (Just $ lastActivity ds) dummySignature writeTChan ichan (ActivityMessage act) let acth = hash act let ds' = ds { sentSince = sentSince ds ++ [b] , enteredSince = enteredSince ds ++ [acth] , lastActivity = acth } writeTVar devstate ds' return act logger $ Developer $ ActivityMessage act go -- | Read activity from the TChan and display it to the developer. sendTtyOutput :: TChan (Message Seen) -> TVar DeveloperState -> Logger -> IO () sendTtyOutput ochan devstate logger = go where go = do (v, msg) <- atomically $ processOutput ochan devstate logger $ User msg case v of ProtocolError e -> protocolError e TtyOutput b -> do B.hPut stdout b hFlush stdout go Beep -> do B.hPut stdout "\a" hFlush stdout go NoOutput -> go data Output = TtyOutput B.ByteString | Beep | ProtocolError String | NoOutput processOutput :: TChan (Message Seen) -> TVar DeveloperState -> STM (Output, Message Seen) processOutput ochan devstate = do msg <- readTChan ochan ds <- readTVar devstate -- TODO check sig before doing anything else o <- case msg of ActivityMessage act@(Activity (Seen (Val b)) _ _) -> do let (legal, ds') = isLegalSeen act ds if legal then do writeTVar devstate ds' return (TtyOutput b) else return (ProtocolError $ "Illegal Seen value: " ++ show (act, hash act) ++ "\n" ++ show ds) ControlMessage (Control c _) -> case c of Rejected _ -> do -- When they rejected a message we sent, -- anything we sent subsequently will -- also be rejected, so forget about it. let ds' = ds { sentSince = mempty , enteredSince = mempty } writeTVar devstate ds' return Beep SessionKey _ -> return NoOutput SessionKeyAccepted _ -> return NoOutput SessionKeyRejected _ -> return NoOutput return (o, msg) -- | Check if the Seen activity is legal, forming a chain with previous -- ones, and returns an updated DeveloperState. isLegalSeen :: Activity Seen -> DeveloperState -> (Bool, DeveloperState) isLegalSeen act@(Activity (Seen (Val b)) (Just hp) sig) ds -- Does it chain to the last Seen activity? | hp == lastSeen ds = -- Trim sentSince and enteredSince to -- values after the Seen value. let ss = sentSince ds es = enteredSince ds n = B.length b (ss', es') = if b `B.isPrefixOf` mconcat ss then (drop n ss, drop n es) else (mempty, mempty) in yes $ DeveloperState { lastSeen = acth , sentSince = ss' , enteredSince = es' , lastActivity = acth } -- Does it chain to something we've entered since the last Seen -- value? Eg, user sent A, we replied B C, and the user has -- now replied to B. -- If so, we can drop B (and anything before it) from -- enteredSince and sentSince. | otherwise = case elemIndex hp (enteredSince ds) of Nothing -> (False, ds) Just i -> let ss = sentSince ds es = enteredSince ds ss' = drop (i+1) ss es' = drop (i+1) es in yes $ DeveloperState { lastSeen = acth , sentSince = ss' , enteredSince = es' , lastActivity = acth } where acth = hash act yes ds' = (True, ds') isLegalSeen (Activity _ Nothing _) ds = (False, ds) user :: B.ByteString -> Pty -> TChan (Message Entered) -> TChan (Message Seen) -> IO () user starttxt p ichan ochan = withLogger "debug-me.log" $ \logger -> do let act = Activity (Seen (Val (starttxt <> "\r\n"))) Nothing dummySignature let startmsg = ActivityMessage act logger $ User startmsg l <- mkLog (User startmsg) <$> getPOSIXTime atomically $ writeTChan ochan startmsg us <- newTVarIO $ UserState { backLog = l :| [] } _ <- sendPtyOutput p ochan us logger `concurrently` sendPtyInput ichan ochan p us logger return () -- | Log of recent Activity, with the most recent first. type Backlog = NonEmpty Log data UserState = UserState { backLog :: Backlog } deriving (Show) -- | Forward things written to the Pty out the TChan. sendPtyOutput :: Pty -> TChan (Message Seen) -> TVar UserState -> Logger -> IO () sendPtyOutput p ochan us logger = go where go = do b <- readPty p now <- getPOSIXTime l <- atomically $ do let seen = Seen (Val b) sendDeveloper ochan us seen now logger $ User l go class SendableToDeveloper t where sendDeveloper :: TChan (Message Seen) -> TVar UserState -> t -> POSIXTime -> STM (Message Seen) instance SendableToDeveloper Seen where sendDeveloper ochan us seen now = do st <- readTVar us let bl@(prev :| _) = backLog st let msg = ActivityMessage $ Activity seen (loggedHash prev) dummySignature let l = mkLog (User msg) now writeTChan ochan msg writeTVar us $ st { backLog = l :| toList bl } return msg instance SendableToDeveloper ControlAction where sendDeveloper ochan _us c _now = do let msg = ControlMessage $ Control c dummySignature -- Control messages are not kept in the backlog. writeTChan ochan msg return msg -- | Read things to be entered from the TChan, verify if they're legal, -- and send them to the Pty. sendPtyInput :: TChan (Message Entered) -> TChan (Message Seen) -> Pty -> TVar UserState -> Logger -> IO () sendPtyInput ichan ochan p us logger = go where go = do networkDelay now <- getPOSIXTime v <- atomically $ do msg <- readTChan ichan st <- readTVar us -- TODO check signature first case msg of ActivityMessage entered -> do -- Don't need to retain backlog before the Activity -- that entered references. let bl' = reduceBacklog $ truncateBacklog (backLog st) entered if isLegalEntered entered (st { backLog = bl' }) then do let l = mkLog (Developer msg) now writeTVar us (st { backLog = l :| toList bl' }) return (Right msg) else do let reject = Rejected entered Left <$> sendDeveloper ochan us reject now ControlMessage (Control _ _) -> return (Right msg) case v of Right (ActivityMessage entered) -> do logger $ Developer $ ActivityMessage entered writePty p $ val $ enteredData $ activity entered go Right (ControlMessage (Control c _)) -> case c of Rejected r -> protocolError $ "User side received a Rejected: " ++ show r SessionKey _ -> protocolError "Adding session keys to running session not supported yet" SessionKeyAccepted _ -> protocolError "User side received a SessionKeyAccepted" SessionKeyRejected _ -> protocolError "User side received a SessionKeyRejected" Left rejact -> do logger $ User rejact go -- | Truncate the Backlog to remove entries older than the one -- that the Activity Entered refers to, but only if the referred -- to Activity is an Activity Seen. -- -- Once the developer has referred to a given Activity Seen in -- their Activity Entered, they cannot refer backwards to anything -- that came before it. -- -- If the Activity refers to an item not in the backlog, no truncation is -- done. truncateBacklog :: Backlog -> Activity Entered -> Backlog truncateBacklog (b :| l) (Activity _ (Just hp) _) | truncationpoint b = b :| [] | otherwise = b :| go [] l where go c [] = reverse c go c (x:xs) | truncationpoint x = reverse (x:c) | otherwise = go (x:c) xs truncationpoint x@(Log { loggedMessage = User {}}) = loggedHash x == Just hp truncationpoint _ = False truncateBacklog bl (Activity _ Nothing _) = bl -- | To avoid DOS attacks that try to fill up the backlog and so use all -- memory, don't let the backlog contain more than 1000 items, or -- more than 16 megabytes of total data. (Excluding the most recent -- item). reduceBacklog :: Backlog -> Backlog reduceBacklog (b :| l) = b :| go 0 (take 1000 l) where go _ [] = [] go n (x:xs) | n > 16777216 = [] | otherwise = x : go (n + dataSize x) xs -- | Entered activity is legal when it points to the last logged activity, -- because this guarantees that the person who entered it saw -- the current state of the system before manipulating it. -- -- To support typeahead on slow links, some echoData may be provided -- in the Entered activity. If the Entered activity points -- to an older activity, then the echoData must match the -- concatenation of all Seen activities after that one, up to the -- last logged activity. -- -- Activities that do not enter data point to the first message -- sent in the debug-me session. isLegalEntered :: Activity Entered -> UserState -> Bool isLegalEntered (Activity _ Nothing _) _ = False isLegalEntered (Activity a (Just hp) sig) us | loggedHash lastact == Just hp = True | B.null (val (echoData a)) = False -- optimisation | any (== Just hp) (map loggedHash bl) = let sincehp = reverse (lastact : takeWhile (\l -> loggedHash l /= Just hp) bl) in echoData a == mconcat (map (getseen . loggedMessage) sincehp) | otherwise = False where (lastact :| bl) = backLog us getseen (User (ActivityMessage as)) = seenData $ activity as getseen _ = mempty -- | Temporary hack while user and developer share a process. protocolError :: String -> IO a protocolError e = do hPutStrLn stderr e hFlush stderr _ <- exitWith (ExitFailure 101) error e