summaryrefslogtreecommitdiff
path: root/src/Propellor/Property/Firewall.hs
blob: 7b62558d37f34c978dd8f9bafc2faeaa4ba38827 (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
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
-- | Maintainer: Arnaud Bailly <arnaud.oqube@gmail.com>
--
-- Properties for configuring firewall (iptables) rules

module Propellor.Property.Firewall (
	rule,
	installed,
	Chain(..),
	Table(..),
	Target(..),
	Proto(..),
	Rules(..),
	ConnectionState(..),
	ICMPTypeMatch(..),
	TCPFlag(..),
	Frequency(..),
	IPWithMask(..),
) where

import Data.Monoid
import qualified Data.Semigroup as Sem
import Data.Char
import Data.List

import Propellor.Base
import qualified Propellor.Property.Apt as Apt
import qualified Propellor.Property.Network as Network

installed :: Property DebianLike
installed = Apt.installed ["iptables"]

rule :: Chain -> Table -> Target -> Rules -> Property Linux
rule c tb tg rs = property ("firewall rule: " <> show r) addIpTable
  where
	r = Rule c tb tg rs
	addIpTable = liftIO $ do
		let args = toIpTable r
		exist <- boolSystem "iptables" (chk args)
		if exist
			then return NoChange
			else toResult <$> boolSystem "iptables" (add args)
	add params = Param "-A" : params
	chk params = Param "-C" : params

toIpTable :: Rule -> [CommandParam]
toIpTable r =  map Param $
	val (ruleChain r) :
	["-t", val (ruleTable r), "-j", val (ruleTarget r)] ++
	toIpTableArg (ruleRules r)

toIpTableArg :: Rules -> [String]
toIpTableArg Everything = []
toIpTableArg (Proto proto) = ["-p", map toLower $ show proto]
toIpTableArg (DPort port) = ["--dport", val port]
toIpTableArg (DPortRange (portf, portt)) =
	["--dport", val portf ++ ":" ++ val portt]
toIpTableArg (InIFace iface) = ["-i", iface]
toIpTableArg (OutIFace iface) = ["-o", iface]
toIpTableArg (Ctstate states) =
	[ "-m"
	, "conntrack"
	, "--ctstate", intercalate "," (map show states)
	]
toIpTableArg (ICMPType i) =
	[ "-m"
	, "icmp"
	, "--icmp-type", val i
	]
toIpTableArg (RateLimit f) =
	[ "-m"
	, "limit"
	, "--limit", val f
	]
toIpTableArg (TCPFlags m c) =
	[ "-m"
	, "tcp"
	, "--tcp-flags"
	, intercalate "," (map show m)
	, intercalate "," (map show c)
	]
toIpTableArg TCPSyn = ["--syn"]
toIpTableArg (GroupOwner (Group g)) =
	[ "-m"
	, "owner"
	, "--gid-owner"
	, g
	]
toIpTableArg (Source ipwm) =
	[ "-s"
	, intercalate "," (map val ipwm)
	]
toIpTableArg (Destination ipwm) =
	[ "-d"
	, intercalate "," (map val ipwm)
	]
toIpTableArg (NotDestination ipwm) =
	[ "!"
	, "-d"
	, intercalate "," (map val ipwm)
	]
toIpTableArg (NatDestination ip mport) =
	[ "--to-destination"
	, val ip ++ maybe "" (\p -> ":" ++ val p) mport
	]
toIpTableArg (r :- r') = toIpTableArg r <> toIpTableArg r'

data IPWithMask = IPWithNoMask IPAddr | IPWithIPMask IPAddr IPAddr | IPWithNumMask IPAddr Int
	deriving (Eq, Show)

instance ConfigurableValue IPWithMask where
	val (IPWithNoMask ip) = val ip
	val (IPWithIPMask ip ipm) = val ip ++ "/" ++ val ipm
	val (IPWithNumMask ip m) = val ip ++ "/" ++ val m

data Rule = Rule
	{ ruleChain  :: Chain
	, ruleTable  :: Table
	, ruleTarget :: Target
	, ruleRules  :: Rules
	} deriving (Eq, Show)

data Table = Filter | Nat | Mangle | Raw | Security
	deriving (Eq, Show)

instance ConfigurableValue Table where
	val Filter = "filter"
	val Nat = "nat"
	val Mangle = "mangle"
	val Raw = "raw"
	val Security = "security"

data Target = ACCEPT | REJECT | DROP | LOG | TargetCustom String
	deriving (Eq, Show)

instance ConfigurableValue Target where
	val ACCEPT = "ACCEPT"
	val REJECT = "REJECT"
	val DROP = "DROP"
	val LOG = "LOG"
	val (TargetCustom t) = t

data Chain = INPUT | OUTPUT | FORWARD | PREROUTING | POSTROUTING | ChainCustom String
	deriving (Eq, Show)

instance ConfigurableValue Chain where
	val INPUT = "INPUT"
	val OUTPUT = "OUTPUT"
	val FORWARD = "FORWARD"
	val PREROUTING = "PREROUTING"
	val POSTROUTING = "POSTROUTING"
	val (ChainCustom c) = c

data Proto = TCP | UDP | ICMP
	deriving (Eq, Show)

data ConnectionState = ESTABLISHED | RELATED | NEW | INVALID
	deriving (Eq, Show)

data ICMPTypeMatch = ICMPTypeName String | ICMPTypeCode Int
	deriving (Eq, Show)

instance ConfigurableValue ICMPTypeMatch where
	val (ICMPTypeName t) = t
	val (ICMPTypeCode c) = val c

data Frequency = NumBySecond Int
	deriving (Eq, Show)

instance ConfigurableValue Frequency where
	val (NumBySecond n) = val n ++ "/second"

type TCPFlagMask = [TCPFlag]

type TCPFlagComp = [TCPFlag]

data TCPFlag = SYN | ACK | FIN | RST | URG | PSH | ALL | NONE
	deriving (Eq, Show)

data Rules
	= Everything
	| Proto Proto
	-- ^There is actually some order dependency between proto and port so this should be a specific
	-- data type with proto + ports
	| DPort Port
	| DPortRange (Port, Port)
	| InIFace Network.Interface
	| OutIFace Network.Interface
	| Ctstate [ ConnectionState ]
	| ICMPType ICMPTypeMatch
	| RateLimit Frequency
	| TCPFlags TCPFlagMask TCPFlagComp
	| TCPSyn
	| GroupOwner Group
	| Source [ IPWithMask ]
	| Destination [ IPWithMask ]
	| NotDestination [ IPWithMask ]
	| NatDestination IPAddr (Maybe Port)
	| Rules :- Rules   -- ^Combine two rules
	deriving (Eq, Show)

infixl 0 :-

instance Sem.Semigroup Rules where
	(<>) = (:-)

instance Monoid Rules where
	mempty  = Everything
	mappend = (Sem.<>)