summaryrefslogtreecommitdiff
path: root/src/Propellor/Property/Firewall.hs
blob: 62adf33a4d48010c75cbd59732cdc0c96fe00934 (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
-- | 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(..),
	IPWithMask(..),
	fromIPWithMask
) where

import Data.Monoid
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 NoInfo
installed = Apt.installed ["iptables"]

rule :: Chain -> Table -> Target -> Rules -> Property NoInfo
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 $
	fromChain (ruleChain r) :
	toIpTableArg (ruleRules r) ++
	["-t", fromTable (ruleTable r), "-j", fromTarget (ruleTarget r)]

toIpTableArg :: Rules -> [String]
toIpTableArg Everything = []
toIpTableArg (Proto proto) = ["-p", map toLower $ show proto]
toIpTableArg (DPort (Port port)) = ["--dport", show port]
toIpTableArg (DPortRange (Port f, Port t)) =
	["--dport", show f ++ ":" ++ show t]
toIpTableArg (InIFace iface) = ["-i", iface]
toIpTableArg (OutIFace iface) = ["-o", iface]
toIpTableArg (Ctstate states) =
	[ "-m"
	, "conntrack"
	, "--ctstate", intercalate "," (map show states)
	]
toIpTableArg (Source ipwm) =
	[ "-s"
	, intercalate "," (map fromIPWithMask ipwm)
	]
toIpTableArg (Destination ipwm) =
	[ "-d"
	, intercalate "," (map fromIPWithMask ipwm)
	]
toIpTableArg (r :- r') = toIpTableArg r <> toIpTableArg r'

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

fromIPWithMask :: IPWithMask -> String
fromIPWithMask (IPWithNoMask ip) = fromIPAddr ip
fromIPWithMask (IPWithIPMask ip ipm) = fromIPAddr ip ++ "/" ++ fromIPAddr ipm
fromIPWithMask (IPWithNumMask ip m) = fromIPAddr ip ++ "/" ++ show 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)

fromTable :: Table -> String
fromTable Filter = "filter"
fromTable Nat = "nat"
fromTable Mangle = "mangle"
fromTable Raw = "raw"
fromTable Security = "security"

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

fromTarget :: Target -> String
fromTarget ACCEPT = "ACCEPT"
fromTarget REJECT = "REJECT"
fromTarget DROP = "DROP"
fromTarget LOG = "LOG"
fromTarget (TargetCustom t) = t

data Chain = ChainFilter | ChainNat | ChainMangle | ChainRaw | ChainSecurity
	deriving (Eq, Show)

instance FromChain Chain where
	fromChain = fromChain

class FromChain a where
	fromChain :: a -> String

data ChainFilter = INPUT | OUTPUT | FORWARD | FilterCustom String
	deriving (Eq, Show)

instance FromChain ChainFilter where
	fromChain INPUT = "INPUT"
	fromChain OUTPUT = "OUTPUT"
	fromChain FORWARD = "FORWARD"
	fromChain (FilterCustom c) = c

data ChainNat = NatPREROUTING | NatOUTPUT | NatPOSTROUTING | NatCustom String
	deriving (Eq, Show)

instance FromChain ChainNat where
	fromChain NatPREROUTING = "PREROUTING"
	fromChain NatOUTPUT = "OUTPUT"
	fromChain NatPOSTROUTING = "POSTROUTING"
	fromChain (NatCustom f) = f

data ChainMangle = ManglePREROUTING | MangleOUTPUT | MangleINPUT | MangleFORWARD | ManglePOSTROUTING | MangleCustom String
	deriving (Eq, Show)

instance FromChain ChainMangle where
	fromChain ManglePREROUTING = "PREROUTING"
	fromChain MangleOUTPUT = "OUTPUT"
	fromChain MangleINPUT = "INPUT"
	fromChain MangleFORWARD = "FORWARD"
	fromChain ManglePOSTROUTING = "POSTROUTING"
	fromChain (MangleCustom f) = f

data ChainRaw = RawPREROUTING | RawOUTPUT | RawCustom String
	deriving (Eq, Show)

instance FromChain ChainRaw where
	fromChain RawPREROUTING = "PREROUTING"
	fromChain RawOUTPUT = "OUTPUT"
	fromChain (RawCustom f) = f

data ChainSecurity = SecurityINPUT | SecurityOUTPUT | SecurityFORWARD | SecurityCustom String
	deriving (Eq, Show)

instance FromChain ChainSecurity where
	fromChain SecurityINPUT = "INPUT"
	fromChain SecurityOUTPUT = "OUTPUT"
	fromChain SecurityFORWARD = "FORWARD"
	fromChain (SecurityCustom f) = f

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

data ConnectionState = ESTABLISHED | RELATED | NEW | INVALID
	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 ]
	| Source [ IPWithMask ]
	| Destination [ IPWithMask ]
	| Rules :- Rules   -- ^Combine two rules
	deriving (Eq, Show)

infixl 0 :-

instance Monoid Rules where
	mempty  = Everything
	mappend = (:-)