{- Copyright 2017 Joey Hess - - Licensed under the GNU AGPL version 3 or higher. -} module Verify (verify) where import Types import Log import CmdLine import Crypto import Gpg import Hash import PrevActivity import Output import Control.Concurrent.STM import Data.Maybe import Data.ByteString.UTF8 (toString) verify :: VerifyOpts -> IO () verify opts = go 1 startState =<< streamLog (verifyLogFile opts) where go _ _ [] = putStrLn "Log file verified. All signatures and hashes are valid." go lineno st (Right lmsg:rest) = do -- The log may have hashes removed, as it went over the -- wire; restore hashes. let ra = mkRecentActivity st msg <- atomically $ restoreHashes ra $ MissingHashes $ loggedMessage lmsg -- Learn session keys before verifying signatures. st' <- case msg of User (ControlMessage (Control { control = SessionKey sk _ })) -> addSessionKey lineno sk st Developer (ControlMessage (Control { control = SessionKey sk _ })) -> addSessionKey lineno sk st _ -> return st case (verifySigned (sigVerifier st') msg, verifyHashChain msg st') of (True, True) -> return () (False, _) -> lineError lineno "Failed to verify message signature." (_, False) -> lineError lineno "Invalid hash chain." go (succ lineno) (addPrevHash msg st') rest go lineno _ (Left l:_) = lineError lineno $ "Failed to parse a line of the log: " ++ l lineError :: Integer -> String -> a lineError lineno err = error $ "Line " ++ show lineno ++ ": " ++ err data State = State { sigVerifier :: SigVerifier , prevHashes :: [Hash] } deriving (Show) startState :: State startState = State { sigVerifier = mempty , prevHashes = mempty -- ^ in reverse order } mkRecentActivity :: State -> RecentActivity mkRecentActivity st = return (sigVerifier st, prevHashes st) addSessionKey :: Integer -> PerhapsSigned PublicKey -> State -> IO State addSessionKey lineno p@(GpgSigned pk _ _) st = do (mkid, gpgoutput) <- gpgVerify p putStr $ unlines $ map sanitizeForDisplay $ lines $ toString gpgoutput case mkid of Nothing -> lineError lineno "Bad GnuPG signature." Just _ -> do putStrLn "The person above participated in the debug-me session." addSessionKey lineno (UnSigned pk) st addSessionKey _lineno (UnSigned pk) st = do let v = mkSigVerifier pk return $ st { sigVerifier = sigVerifier st `mappend` v } -- | Add the hash of the message to the state. addPrevHash :: AnyMessage -> State -> State addPrevHash am s = case mh of Just h -> s { prevHashes = h : prevHashes s } Nothing -> s where mh = case am of User (ActivityMessage m) -> Just (hash m) User (ControlMessage _) -> Nothing Developer (ActivityMessage m) -> Just (hash m) Developer (ControlMessage _) -> Nothing -- | Verify that prevActivity and prevEntered point to previously -- seen hashes. -- -- While Role.User and Role.Developer enforce rules about which -- hashes they may point to, here we don't check such rules. If the log -- continues with other messages referring to this one, then this message -- must have met the rules, and if it did not, then this message is -- irrelevant. verifyHashChain :: AnyMessage -> State -> Bool verifyHashChain am s = case am of User (ControlMessage _) -> True Developer (ControlMessage _) -> True User (ActivityMessage m) -> checkm m Developer (ActivityMessage m) -> checkm m where checkm m = all (\h -> h `elem` prevHashes s) (catMaybes [prevActivity m, prevEntered m])