summaryrefslogtreecommitdiff
path: root/src/Propellor/Types/ZFS.hs
blob: c68f6ba574778cf0acf689d7ce5d3d8e04b72a7a (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
{-# LANGUAGE ConstrainedClassMethods #-}
-- | Types for ZFS Properties.
--
-- Copyright 2016 Evan Cofsky <evan@theunixman.com>
-- License: BSD 2-clause

module Propellor.Types.ZFS where

import Propellor.Types.ConfigurableValue
import Utility.Split

import Data.String
import qualified Data.Set as Set
import Data.List

-- | A single ZFS filesystem.
data ZFS = ZFS ZPool ZDataset deriving (Show, Eq, Ord)

-- | Represents a zpool.
data ZPool = ZPool String deriving (Show, Eq, Ord)

-- | Represents a dataset in a zpool.
--
-- Can be constructed from a / separated string.
data ZDataset = ZDataset [String] deriving (Eq, Ord)

type ZFSProperties = Set.Set ZFSProperty

fromList :: [ZFSProperty] -> ZFSProperties
fromList = Set.fromList

toPropertyList :: ZFSProperties -> [(String, String)]
toPropertyList = Set.foldr (\p l -> l ++ [toPair p]) []

fromPropertyList :: [(String, String)] -> ZFSProperties
fromPropertyList props =
	Set.fromList $ map fromPair props

zfsName :: ZFS -> String
zfsName (ZFS (ZPool pool) dataset) = intercalate "/" [pool, show dataset]

instance ConfigurableValue ZDataset where
	val (ZDataset paths) = intercalate "/" paths

instance Show ZDataset where
	show = val

instance IsString ZDataset where
	fromString s = ZDataset $ splitc '/' s

instance IsString ZPool where
	fromString p = ZPool p

class Value a where
	toValue :: a -> String
	fromValue :: (IsString a) => String -> a
	fromValue = fromString

data ZFSYesNo = ZFSYesNo Bool deriving (Show, Eq, Ord)
data ZFSOnOff = ZFSOnOff Bool deriving (Show, Eq, Ord)
data ZFSSize = ZFSSize Integer deriving (Show, Eq, Ord)
data ZFSString = ZFSString String deriving (Show, Eq, Ord)

instance Value ZFSYesNo where
	toValue (ZFSYesNo True) = "yes"
	toValue (ZFSYesNo False) = "no"

instance Value ZFSOnOff where
	toValue (ZFSOnOff True) = "on"
	toValue (ZFSOnOff False) = "off"

instance Value ZFSSize where
	toValue (ZFSSize s) = show s

instance Value ZFSString where
	toValue (ZFSString s) = s

instance IsString ZFSString where
	fromString = ZFSString

instance IsString ZFSYesNo where
	fromString "yes" = ZFSYesNo True
	fromString "no" = ZFSYesNo False
	fromString _ = error "Not yes or no"

instance IsString ZFSOnOff where
	fromString "on" = ZFSOnOff True
	fromString "off" = ZFSOnOff False
	fromString _ = error "Not on or off"

data ZFSACLInherit = AIDiscard | AINoAllow | AISecure | AIPassthrough deriving (Show, Eq, Ord)
instance IsString ZFSACLInherit where
	fromString "discard" = AIDiscard
	fromString "noallow" = AINoAllow
	fromString "secure" = AISecure
	fromString "passthrough" = AIPassthrough
	fromString _ = error "Not valid aclpassthrough value"

instance Value ZFSACLInherit where
	toValue AIDiscard = "discard"
	toValue AINoAllow = "noallow"
	toValue AISecure = "secure"
	toValue AIPassthrough = "passthrough"

data ZFSACLMode = AMDiscard | AMGroupmask | AMPassthrough deriving (Show, Eq, Ord)
instance IsString ZFSACLMode where
	fromString "discard" = AMDiscard
	fromString "groupmask" = AMGroupmask
	fromString "passthrough" = AMPassthrough
	fromString _ = error "Invalid zfsaclmode"

instance Value ZFSACLMode where
	toValue AMDiscard = "discard"
	toValue AMGroupmask = "groupmask"
	toValue AMPassthrough = "passthrough"

data ZFSProperty = Mounted ZFSYesNo
	       | Mountpoint ZFSString
	       | ReadOnly ZFSYesNo
	       | ACLInherit ZFSACLInherit
	       | ACLMode ZFSACLMode
	       | StringProperty String ZFSString
	       deriving (Show, Eq, Ord)

toPair :: ZFSProperty -> (String, String)
toPair (Mounted v) = ("mounted", toValue v)
toPair (Mountpoint v) = ("mountpoint", toValue v)
toPair (ReadOnly v) = ("readonly", toValue v)
toPair (ACLInherit v) = ("aclinherit", toValue v)
toPair (ACLMode v) = ("aclmode", toValue v)
toPair (StringProperty s v) = (s, toValue v)

fromPair :: (String, String) -> ZFSProperty
fromPair ("mounted", v) = Mounted (fromString v)
fromPair ("mountpoint", v) = Mountpoint (fromString v)
fromPair ("readonly", v) = ReadOnly (fromString v)
fromPair ("aclinherit", v) = ACLInherit (fromString v)
fromPair ("aclmode", v) = ACLMode (fromString v)
fromPair (s, v) = StringProperty s (fromString v)