-- This file is part of htalkat -- Copyright (C) 2021 Martin Bays -- -- This program is free software: you can redistribute it and/or modify -- it under the terms of version 3 of the GNU General Public License as -- published by the Free Software Foundation, or any later version. -- -- You should have received a copy of the GNU General Public License -- along with this program. If not, see http://www.gnu.org/licenses/. {-# LANGUAGE CPP #-} module Notify where import Control.Monad (void) import System.Directory (doesFileExist) import System.FilePath (()) import System.Process #ifndef WINDOWS import System.Posix.Files (ownerModes, setFileMode) #endif import Certificate import Fingerprint import Petname import Util notifyOfIncoming :: FilePath -> Certificate -> Petname -> IO () notifyOfIncoming ddir cert petname = do case petname of Named name -> putStrLn $ "Talk request from '" <> name <> "'; accept with: htalkat a "<> shellQuotePetname (Named name) <>"" p@(Unnamed _) -> do putStrLn $ "Talk request from unknown caller " <> showPetname p putStrLn $ " Fingerprint: " <> showFingerprint (spkiFingerprint cert) putStrLn $ " Public name: " <> certCN cert putStrLn $ "Accept with: htalkat a " <> shellQuotePetname p createNotifyScriptIfNecessary ddir void $ rawSystem (notifyScriptPath ddir) [ showPetname petname , showFingerprint $ spkiFingerprint cert , certCN cert ] notifyScriptPath :: FilePath -> FilePath notifyScriptPath = ( "notify.sh") createNotifyScriptIfNecessary :: FilePath -> IO () createNotifyScriptIfNecessary ddir = let spath = notifyScriptPath ddir in doesFileExist spath >>! do writeFile spath defaultNotifyScript #ifndef WINDOWS setFileMode spath ownerModes -- chmod 700 #endif defaultNotifyScript :: String defaultNotifyScript = unlines [ "#!/usr/bin/env bash" , "# This script is called when someone connects to the talkat server." , "# The following positional arguments are given to this script:" , "# $1: assigned name of caller, or +N for an unknown caller" , "# $2: fingerprint of caller's public key" , "# $3: \"public name\" set in CN field of caller's certificate" , "" , "# Example:" , "#announce=\"$(echo -n \"Talkat request from $1\"; \\" , "# [[ \"$1\" =~ ^\\+ ]] && echo -n \" $2 (\\\"$3\\\")\")\"" , "#write $USER <<<\"$announce\"" , "#mail -s \"$announce\" $USER <<<\"Answer with htalkat a '$1'\"" , "#notify-send \"$announce\"" ]