summaryrefslogtreecommitdiff
path: root/src/Propellor/Ssh.hs
blob: a8f50ed0bfbd9a683b8ffa92f83c2f233b5594ee (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
module Propellor.Ssh where

import Propellor.Base
import Utility.UserInfo
import Utility.FileSystemEncoding

import System.PosixCompat
import Data.Time.Clock.POSIX
import Data.Hashable

-- Parameters can be passed to both ssh and scp, to enable a ssh connection
-- caching socket.
--
-- If the socket already exists, check if its mtime is older than 10
-- minutes, and if so stop that ssh process, in order to not try to
-- use an old stale connection. (atime would be nicer, but there's
-- a good chance a laptop uses noatime)
sshCachingParams :: HostName -> IO [CommandParam]
sshCachingParams hn = do
	home <- myHomeDir
	let socketfile = socketFile home hn
	createDirectoryIfMissing False (takeDirectory socketfile)
	let ps =
		[ Param "-o"
		, Param ("ControlPath=" ++ socketfile)
		, Param "-o", Param "ControlMaster=auto"
		, Param "-o", Param "ControlPersist=yes"
		]

	maybe noop (expireold ps socketfile)
		=<< catchMaybeIO (getFileStatus socketfile)
	
	return ps
		
  where
	expireold ps f s = do
		now <- truncate <$> getPOSIXTime :: IO Integer
		if modificationTime s > fromIntegral now - tenminutes
			then touchFile f
			else do
				void $ boolSystem "ssh" $
					[ Param "-O", Param "stop" ] ++ ps ++
					[ Param "localhost" ]
				nukeFile f
	tenminutes = 600

-- Generate a socket filename inside the home directory.
--
-- There's a limit in the size of unix domain sockets, of approximately
-- 100 bytes. Try to never construct a filename longer than that.
--
-- When space allows, include the full hostname in the socket filename.
-- Otherwise, a checksum of the hostname is included in the name, to
-- avoid using the same socket file for multiple hosts.
socketFile :: FilePath -> HostName -> FilePath
socketFile home hn = selectSocketFile
	[ sshdir </> hn ++ ".sock"
	, sshdir </> hn
	, sshdir </> take 10 hn ++ "-" ++ checksum
	, sshdir </> checksum
	]
	(home </> ".propellor-" ++ checksum)
  where
	sshdir = home </> ".ssh" </> "propellor"
	checksum = take 9 $ show $ abs $ hash hn

selectSocketFile :: [FilePath] -> FilePath -> FilePath
selectSocketFile [] d = d
selectSocketFile (f:fs) d
	| valid_unix_socket_path f = f
	| otherwise = selectSocketFile fs d

valid_unix_socket_path :: FilePath -> Bool
valid_unix_socket_path f = length (decodeW8 f) < 100 - reservedbyssh
  where
	-- ssh tacks on 17 or so characters when making a socket
	reservedbyssh = 18