summaryrefslogtreecommitdiff
path: root/src/Propellor/Types
diff options
context:
space:
mode:
Diffstat (limited to 'src/Propellor/Types')
-rw-r--r--src/Propellor/Types/Bootloader.hs12
-rw-r--r--src/Propellor/Types/Chroot.hs2
-rw-r--r--src/Propellor/Types/CmdLine.hs1
-rw-r--r--src/Propellor/Types/ConfigurableValue.hs44
-rw-r--r--src/Propellor/Types/Core.hs7
-rw-r--r--src/Propellor/Types/Dns.hs23
-rw-r--r--src/Propellor/Types/Docker.hs2
-rw-r--r--src/Propellor/Types/Info.hs23
-rw-r--r--src/Propellor/Types/MetaTypes.hs28
-rw-r--r--src/Propellor/Types/OS.hs29
-rw-r--r--src/Propellor/Types/PartSpec.hs66
-rw-r--r--src/Propellor/Types/Result.hs3
-rw-r--r--src/Propellor/Types/ZFS.hs79
13 files changed, 246 insertions, 73 deletions
diff --git a/src/Propellor/Types/Bootloader.hs b/src/Propellor/Types/Bootloader.hs
new file mode 100644
index 00000000..4a75503a
--- /dev/null
+++ b/src/Propellor/Types/Bootloader.hs
@@ -0,0 +1,12 @@
+{-# LANGUAGE FlexibleInstances, DeriveDataTypeable #-}
+
+module Propellor.Types.Bootloader where
+
+import Propellor.Types.Info
+
+-- | Boot loader installed on a host.
+data BootloaderInstalled = GrubInstalled
+ deriving (Typeable, Show)
+
+instance IsInfo [BootloaderInstalled] where
+ propagateInfo _ = PropagateInfo False
diff --git a/src/Propellor/Types/Chroot.hs b/src/Propellor/Types/Chroot.hs
index fc049603..da912120 100644
--- a/src/Propellor/Types/Chroot.hs
+++ b/src/Propellor/Types/Chroot.hs
@@ -16,7 +16,7 @@ data ChrootInfo = ChrootInfo
deriving (Show, Typeable)
instance IsInfo ChrootInfo where
- propagateInfo _ = False
+ propagateInfo _ = PropagateInfo False
instance Monoid ChrootInfo where
mempty = ChrootInfo mempty mempty
diff --git a/src/Propellor/Types/CmdLine.hs b/src/Propellor/Types/CmdLine.hs
index 558c6e8b..d712a456 100644
--- a/src/Propellor/Types/CmdLine.hs
+++ b/src/Propellor/Types/CmdLine.hs
@@ -28,4 +28,5 @@ data CmdLine
| ChrootChain HostName FilePath Bool Bool
| GitPush Fd Fd
| Check
+ | Build
deriving (Read, Show, Eq)
diff --git a/src/Propellor/Types/ConfigurableValue.hs b/src/Propellor/Types/ConfigurableValue.hs
new file mode 100644
index 00000000..1414be5f
--- /dev/null
+++ b/src/Propellor/Types/ConfigurableValue.hs
@@ -0,0 +1,44 @@
+{-# LANGUAGE TypeSynonymInstances, FlexibleInstances #-}
+
+module Propellor.Types.ConfigurableValue where
+
+import Data.Word
+
+-- | A value that can be used in a configuration file, or otherwise used to
+-- configure a program.
+--
+-- Unlike Show, there should only be instances of this type class for
+-- values that have a standard serialization that is understood outside of
+-- Haskell code.
+--
+-- When converting a type alias such as "type Foo = String" or "type Foo = Int"
+-- to a newtype, it's unsafe to derive a Show instance, because there may
+-- be code that shows the type to configure a value. Instead, define a
+-- ConfigurableValue instance.
+class ConfigurableValue t where
+ val :: t -> String
+
+-- | val String does not do any quoting, unlike show String
+instance ConfigurableValue String where
+ val = id
+
+instance ConfigurableValue Int where
+ val = show
+
+instance ConfigurableValue Integer where
+ val = show
+
+instance ConfigurableValue Float where
+ val = show
+
+instance ConfigurableValue Double where
+ val = show
+
+instance ConfigurableValue Word8 where
+ val = show
+
+instance ConfigurableValue Word16 where
+ val = show
+
+instance ConfigurableValue Word32 where
+ val = show
diff --git a/src/Propellor/Types/Core.hs b/src/Propellor/Types/Core.hs
index 6fedc47e..a805f561 100644
--- a/src/Propellor/Types/Core.hs
+++ b/src/Propellor/Types/Core.hs
@@ -48,9 +48,10 @@ instance LiftPropellor Propellor where
instance LiftPropellor IO where
liftPropellor = liftIO
+-- | When two actions are appended together, the second action
+-- is only run if the first action does not fail.
instance Monoid (Propellor Result) where
mempty = return NoChange
- -- | The second action is only run if the first action does not fail.
mappend x y = do
rx <- x
case rx of
@@ -71,7 +72,7 @@ data Props metatypes = Props [ChildProperty]
-- | Since there are many different types of Properties, they cannot be put
-- into a list. The simplified ChildProperty can be put into a list.
-data ChildProperty = ChildProperty Desc (Propellor Result) Info [ChildProperty]
+data ChildProperty = ChildProperty Desc (Maybe (Propellor Result)) Info [ChildProperty]
instance Show ChildProperty where
show p = "property " ++ show (getDesc p)
@@ -92,7 +93,7 @@ class IsProp p where
-- | Gets the action that can be run to satisfy a Property.
-- You should never run this action directly. Use
-- 'Propellor.EnsureProperty.ensureProperty` instead.
- getSatisfy :: p -> Propellor Result
+ getSatisfy :: p -> Maybe (Propellor Result)
instance IsProp ChildProperty where
setDesc (ChildProperty _ a i c) d = ChildProperty d a i c
diff --git a/src/Propellor/Types/Dns.hs b/src/Propellor/Types/Dns.hs
index 8f15d156..87756d81 100644
--- a/src/Propellor/Types/Dns.hs
+++ b/src/Propellor/Types/Dns.hs
@@ -5,12 +5,13 @@ module Propellor.Types.Dns where
import Propellor.Types.OS (HostName)
import Propellor.Types.Empty
import Propellor.Types.Info
+import Propellor.Types.ConfigurableValue
+import Utility.Split
import Data.Word
import qualified Data.Map as M
import qualified Data.Set as S
import Data.List
-import Data.String.Utils (split, replace)
import Data.Monoid
import Prelude
@@ -19,15 +20,15 @@ type Domain = String
data IPAddr = IPv4 String | IPv6 String
deriving (Read, Show, Eq, Ord)
-fromIPAddr :: IPAddr -> String
-fromIPAddr (IPv4 addr) = addr
-fromIPAddr (IPv6 addr) = addr
+instance ConfigurableValue IPAddr where
+ val (IPv4 addr) = addr
+ val (IPv6 addr) = addr
newtype AliasesInfo = AliasesInfo (S.Set HostName)
deriving (Show, Eq, Ord, Monoid, Typeable)
instance IsInfo AliasesInfo where
- propagateInfo _ = False
+ propagateInfo _ = PropagateInfo False
toAliasesInfo :: [HostName] -> AliasesInfo
toAliasesInfo l = AliasesInfo (S.fromList l)
@@ -44,7 +45,7 @@ toDnsInfo = DnsInfo
-- | DNS Info is propagated, so that eg, aliases of a container
-- are reflected in the dns for the host where it runs.
instance IsInfo DnsInfo where
- propagateInfo _ = True
+ propagateInfo _ = PropagateInfo True
-- | Represents a bind 9 named.conf file.
data NamedConf = NamedConf
@@ -101,14 +102,14 @@ data Record
type ReverseIP = String
reverseIP :: IPAddr -> ReverseIP
-reverseIP (IPv4 addr) = intercalate "." (reverse $ split "." addr) ++ ".in-addr.arpa"
-reverseIP addr@(IPv6 _) = reverse (intersperse '.' $ replace ":" "" $ fromIPAddr $ canonicalIP addr) ++ ".ip6.arpa"
+reverseIP (IPv4 addr) = intercalate "." (reverse $ splitc '.' addr) ++ ".in-addr.arpa"
+reverseIP addr@(IPv6 _) = reverse (intersperse '.' $ replace ":" "" $ val $ canonicalIP addr) ++ ".ip6.arpa"
-- | Converts an IP address (particularly IPv6) to canonical, fully
-- expanded form.
canonicalIP :: IPAddr -> IPAddr
canonicalIP (IPv4 addr) = IPv4 addr
-canonicalIP (IPv6 addr) = IPv6 $ intercalate ":" $ map canonicalGroup $ split ":" $ replaceImplicitGroups addr
+canonicalIP (IPv6 addr) = IPv6 $ intercalate ":" $ map canonicalGroup $ splitc ':' $ replaceImplicitGroups addr
where
canonicalGroup g
| l <= 4 = replicate (4 - l) '0' ++ g
@@ -116,7 +117,7 @@ canonicalIP (IPv6 addr) = IPv6 $ intercalate ":" $ map canonicalGroup $ split ":
where
l = length g
emptyGroups n = iterate (++ ":") "" !! n
- numberOfImplicitGroups a = 8 - length (split ":" $ replace "::" "" a)
+ numberOfImplicitGroups a = 8 - length (splitc ':' $ replace "::" "" a)
replaceImplicitGroups a = concat $ aux $ split "::" a
where
aux [] = []
@@ -156,7 +157,7 @@ newtype NamedConfMap = NamedConfMap (M.Map Domain NamedConf)
deriving (Eq, Ord, Show, Typeable)
instance IsInfo NamedConfMap where
- propagateInfo _ = False
+ propagateInfo _ = PropagateInfo False
-- | Adding a Master NamedConf stanza for a particulr domain always
-- overrides an existing Secondary stanza for that domain, while a
diff --git a/src/Propellor/Types/Docker.hs b/src/Propellor/Types/Docker.hs
index f3cc4a52..6ff340e5 100644
--- a/src/Propellor/Types/Docker.hs
+++ b/src/Propellor/Types/Docker.hs
@@ -16,7 +16,7 @@ data DockerInfo = DockerInfo
deriving (Show, Typeable)
instance IsInfo DockerInfo where
- propagateInfo _ = False
+ propagateInfo _ = PropagateInfo False
instance Monoid DockerInfo where
mempty = DockerInfo mempty mempty
diff --git a/src/Propellor/Types/Info.hs b/src/Propellor/Types/Info.hs
index 2e188ae5..6716c403 100644
--- a/src/Propellor/Types/Info.hs
+++ b/src/Propellor/Types/Info.hs
@@ -1,13 +1,14 @@
{-# LANGUAGE GADTs, DeriveDataTypeable, GeneralizedNewtypeDeriving #-}
module Propellor.Types.Info (
- Info,
+ Info(..),
+ InfoEntry(..),
IsInfo(..),
+ PropagateInfo(..),
addInfo,
toInfo,
fromInfo,
mapInfo,
- propagatableInfo,
InfoVal(..),
fromInfoVal,
Typeable,
@@ -16,6 +17,7 @@ module Propellor.Types.Info (
import Data.Dynamic
import Data.Maybe
import Data.Monoid
+import qualified Data.Typeable as T
import Prelude
-- | Information about a Host, which can be provided by its properties.
@@ -34,7 +36,7 @@ instance Show InfoEntry where
-- Extracts the value from an InfoEntry but only when
-- it's of the requested type.
extractInfoEntry :: Typeable v => InfoEntry -> Maybe v
-extractInfoEntry (InfoEntry v) = cast v
+extractInfoEntry (InfoEntry v) = T.cast v
-- | Values stored in Info must be members of this class.
--
@@ -44,7 +46,13 @@ extractInfoEntry (InfoEntry v) = cast v
class (Typeable v, Monoid v, Show v) => IsInfo v where
-- | Should info of this type be propagated out of a
-- container to its Host?
- propagateInfo :: v -> Bool
+ propagateInfo :: v -> PropagateInfo
+
+data PropagateInfo
+ = PropagateInfo Bool
+ | PropagatePrivData
+ -- ^ Info about PrivData generally will be propigated even in cases
+ -- where other Info is not, so it treated specially.
-- | Any value in the `IsInfo` type class can be added to an Info.
addInfo :: IsInfo v => Info -> v -> Info
@@ -68,11 +76,6 @@ mapInfo f (Info l) = Info (map go l)
Nothing -> i
Just v -> InfoEntry (f v)
--- | Filters out parts of the Info that should not propagate out of a
--- container.
-propagatableInfo :: Info -> Info
-propagatableInfo (Info l) = Info (filter (\(InfoEntry a) -> propagateInfo a) l)
-
-- | Use this to put a value in Info that is not a monoid.
-- The last value set will be used. This info does not propagate
-- out of a container.
@@ -85,7 +88,7 @@ instance Monoid (InfoVal v) where
mappend v NoInfoVal = v
instance (Typeable v, Show v) => IsInfo (InfoVal v) where
- propagateInfo _ = False
+ propagateInfo _ = PropagateInfo False
fromInfoVal :: InfoVal v -> Maybe v
fromInfoVal NoInfoVal = Nothing
diff --git a/src/Propellor/Types/MetaTypes.hs b/src/Propellor/Types/MetaTypes.hs
index e064d76f..19d1998e 100644
--- a/src/Propellor/Types/MetaTypes.hs
+++ b/src/Propellor/Types/MetaTypes.hs
@@ -7,6 +7,7 @@ module Propellor.Types.MetaTypes (
DebianLike,
Debian,
Buntish,
+ ArchLinux,
FreeBSD,
HasInfo,
MetaTypes,
@@ -35,14 +36,26 @@ data MetaType
deriving (Show, Eq, Ord)
-- | Any unix-like system
-type UnixLike = MetaTypes '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish, 'Targeting 'OSFreeBSD ]
+type UnixLike = MetaTypes
+ '[ 'Targeting 'OSDebian
+ , 'Targeting 'OSBuntish
+ , 'Targeting 'OSArchLinux
+ , 'Targeting 'OSFreeBSD
+ ]
+
-- | Any linux system
-type Linux = MetaTypes '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish ]
+type Linux = MetaTypes
+ '[ 'Targeting 'OSDebian
+ , 'Targeting 'OSBuntish
+ , 'Targeting 'OSArchLinux
+ ]
+
-- | Debian and derivatives.
type DebianLike = MetaTypes '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish ]
type Debian = MetaTypes '[ 'Targeting 'OSDebian ]
type Buntish = MetaTypes '[ 'Targeting 'OSBuntish ]
type FreeBSD = MetaTypes '[ 'Targeting 'OSFreeBSD ]
+type ArchLinux = MetaTypes '[ 'Targeting 'OSArchLinux ]
-- | Used to indicate that a Property adds Info to the Host where it's used.
type HasInfo = MetaTypes '[ 'WithInfo ]
@@ -58,16 +71,19 @@ data instance Sing (x :: MetaType) where
OSDebianS :: Sing ('Targeting 'OSDebian)
OSBuntishS :: Sing ('Targeting 'OSBuntish)
OSFreeBSDS :: Sing ('Targeting 'OSFreeBSD)
+ OSArchLinuxS :: Sing ('Targeting 'OSArchLinux)
WithInfoS :: Sing 'WithInfo
instance SingI ('Targeting 'OSDebian) where sing = OSDebianS
instance SingI ('Targeting 'OSBuntish) where sing = OSBuntishS
instance SingI ('Targeting 'OSFreeBSD) where sing = OSFreeBSDS
+instance SingI ('Targeting 'OSArchLinux) where sing = OSArchLinuxS
instance SingI 'WithInfo where sing = WithInfoS
instance SingKind ('KProxy :: KProxy MetaType) where
type DemoteRep ('KProxy :: KProxy MetaType) = MetaType
fromSing OSDebianS = Targeting OSDebian
fromSing OSBuntishS = Targeting OSBuntish
fromSing OSFreeBSDS = Targeting OSFreeBSD
+ fromSing OSArchLinuxS = Targeting OSArchLinux
fromSing WithInfoS = WithInfo
-- | Convenience type operator to combine two `MetaTypes` lists.
@@ -186,6 +202,14 @@ type instance EqT 'OSBuntish 'OSDebian = 'False
type instance EqT 'OSBuntish 'OSFreeBSD = 'False
type instance EqT 'OSFreeBSD 'OSDebian = 'False
type instance EqT 'OSFreeBSD 'OSBuntish = 'False
+type instance EqT 'OSArchLinux 'OSArchLinux = 'True
+type instance EqT 'OSArchLinux 'OSDebian = 'False
+type instance EqT 'OSArchLinux 'OSBuntish = 'False
+type instance EqT 'OSArchLinux 'OSFreeBSD = 'False
+type instance EqT 'OSDebian 'OSArchLinux = 'False
+type instance EqT 'OSBuntish 'OSArchLinux = 'False
+type instance EqT 'OSFreeBSD 'OSArchLinux = 'False
+
-- More modern version if the combinatiorial explosion gets too bad later:
--
-- type family Eq (a :: MetaType) (b :: MetaType) where
diff --git a/src/Propellor/Types/OS.hs b/src/Propellor/Types/OS.hs
index b569a6e8..01d777a4 100644
--- a/src/Propellor/Types/OS.hs
+++ b/src/Propellor/Types/OS.hs
@@ -18,10 +18,11 @@ module Propellor.Types.OS (
Group(..),
userGroup,
Port(..),
- fromPort,
systemToTargetOS,
) where
+import Propellor.Types.ConfigurableValue
+
import Network.BSD (HostName)
import Data.Typeable
import Data.String
@@ -33,6 +34,7 @@ data System = System Distribution Architecture
data Distribution
= Debian DebianKernel DebianSuite
| Buntish Release -- ^ A well-known Debian derivative founded by a space tourist. The actual name of this distribution is not used in Propellor per <http://joeyh.name/blog/entry/trademark_nonsense/>
+ | ArchLinux
| FreeBSD FreeBSDRelease
deriving (Show, Eq)
@@ -41,12 +43,14 @@ data Distribution
data TargetOS
= OSDebian
| OSBuntish
+ | OSArchLinux
| OSFreeBSD
deriving (Show, Eq, Ord)
systemToTargetOS :: System -> TargetOS
systemToTargetOS (System (Debian _ _) _) = OSDebian
systemToTargetOS (System (Buntish _) _) = OSBuntish
+systemToTargetOS (System (ArchLinux) _) = OSArchLinux
systemToTargetOS (System (FreeBSD _) _) = OSFreeBSD
-- | Most of Debian ports are based on Linux. There also exist hurd-i386,
@@ -55,7 +59,7 @@ data DebianKernel = Linux | KFreeBSD | Hurd
deriving (Show, Eq)
-- | Debian has several rolling suites, and a number of stable releases,
--- such as Stable "jessie".
+-- such as Stable "stretch".
data DebianSuite = Experimental | Unstable | Testing | Stable Release
deriving (Show, Eq)
@@ -72,10 +76,13 @@ instance IsString FBSDVersion where
fromString "9.3-RELEASE" = FBSD093
fromString _ = error "Invalid FreeBSD release"
+instance ConfigurableValue FBSDVersion where
+ val FBSD101 = "10.1-RELEASE"
+ val FBSD102 = "10.2-RELEASE"
+ val FBSD093 = "9.3-RELEASE"
+
instance Show FBSDVersion where
- show FBSD101 = "10.1-RELEASE"
- show FBSD102 = "10.2-RELEASE"
- show FBSD093 = "9.3-RELEASE"
+ show = val
isStable :: DebianSuite -> Bool
isStable (Stable _) = True
@@ -135,15 +142,21 @@ type UserName = String
newtype User = User UserName
deriving (Eq, Ord, Show)
+instance ConfigurableValue User where
+ val (User n) = n
+
newtype Group = Group String
deriving (Eq, Ord, Show)
+instance ConfigurableValue Group where
+ val (Group n) = n
+
-- | Makes a Group with the same name as the User.
userGroup :: User -> Group
userGroup (User u) = Group u
newtype Port = Port Int
- deriving (Eq, Show)
+ deriving (Eq, Ord, Show)
-fromPort :: Port -> String
-fromPort (Port p) = show p
+instance ConfigurableValue Port where
+ val (Port p) = show p
diff --git a/src/Propellor/Types/PartSpec.hs b/src/Propellor/Types/PartSpec.hs
new file mode 100644
index 00000000..2b0a8787
--- /dev/null
+++ b/src/Propellor/Types/PartSpec.hs
@@ -0,0 +1,66 @@
+-- | Partition specification combinators.
+
+module Propellor.Types.PartSpec where
+
+import Propellor.Base
+import Propellor.Property.Parted.Types
+import Propellor.Property.Mount
+import Propellor.Property.Partition
+
+-- | Specifies a mount point, mount options, and a constructor for a
+-- Partition that determines its size.
+type PartSpec t = (Maybe MountPoint, MountOpts, PartSize -> Partition, t)
+
+-- | Specifies a partition with a given filesystem.
+--
+-- The partition is not mounted anywhere by default; use the combinators
+-- below to configure it.
+partition :: Monoid t => Fs -> PartSpec t
+partition fs = (Nothing, mempty, mkPartition fs, mempty)
+
+-- | Specifies a swap partition of a given size.
+swapPartition :: Monoid t => PartSize -> PartSpec t
+swapPartition sz = (Nothing, mempty, const (mkPartition LinuxSwap sz), mempty)
+
+-- | Specifies where to mount a partition.
+mountedAt :: PartSpec t -> FilePath -> PartSpec t
+mountedAt (_, o, p, t) mp = (Just mp, o, p, t)
+
+-- | Specify a fixed size for a partition.
+setSize :: PartSpec t -> PartSize -> PartSpec t
+setSize (mp, o, p, t) sz = (mp, o, const (p sz), t)
+
+-- | Specifies a mount option, such as "noexec"
+mountOpt :: ToMountOpts o => PartSpec t -> o -> PartSpec t
+mountOpt (mp, o, p, t) o' = (mp, o <> toMountOpts o', p, t)
+
+-- | Mount option to make a partition be remounted readonly when there's an
+-- error accessing it.
+errorReadonly :: MountOpts
+errorReadonly = toMountOpts "errors=remount-ro"
+
+-- | Sets the percent of the filesystem blocks reserved for the super-user.
+--
+-- The default is 5% for ext2 and ext4. Some filesystems may not support
+-- this.
+reservedSpacePercentage :: PartSpec t -> Int -> PartSpec t
+reservedSpacePercentage s percent = adjustp s $ \p ->
+ p { partMkFsOpts = ("-m"):show percent:partMkFsOpts p }
+
+-- | Sets a flag on the partition.
+setFlag :: PartSpec t -> PartFlag -> PartSpec t
+setFlag s f = adjustp s $ \p -> p { partFlags = (f, True):partFlags p }
+
+-- | Makes a MSDOS partition be Extended, rather than Primary.
+extended :: PartSpec t -> PartSpec t
+extended s = adjustp s $ \p -> p { partType = Extended }
+
+adjustp :: PartSpec t -> (Partition -> Partition) -> PartSpec t
+adjustp (mp, o, p, t) f = (mp, o, f . p, t)
+
+adjustt :: PartSpec t -> (t -> t) -> PartSpec t
+adjustt (mp, o, p, t) f = (mp, o, p, f t)
+
+-- | Default partition size when not otherwize specified is 128 MegaBytes.
+defSz :: PartSize
+defSz = MegaBytes 128
diff --git a/src/Propellor/Types/Result.hs b/src/Propellor/Types/Result.hs
index e8510abf..5209094b 100644
--- a/src/Propellor/Types/Result.hs
+++ b/src/Propellor/Types/Result.hs
@@ -24,6 +24,9 @@ instance ToResult Bool where
toResult False = FailedChange
toResult True = MadeChange
+instance ToResult Result where
+ toResult = id
+
-- | Results of actions, with color.
class ActionResult a where
getActionResult :: a -> (String, ColorIntensity, Color)
diff --git a/src/Propellor/Types/ZFS.hs b/src/Propellor/Types/ZFS.hs
index 3ce4b22c..c68f6ba5 100644
--- a/src/Propellor/Types/ZFS.hs
+++ b/src/Propellor/Types/ZFS.hs
@@ -6,9 +6,11 @@
module Propellor.Types.ZFS where
+import Propellor.Types.ConfigurableValue
+import Utility.Split
+
import Data.String
import qualified Data.Set as Set
-import qualified Data.String.Utils as SU
import Data.List
-- | A single ZFS filesystem.
@@ -32,24 +34,27 @@ toPropertyList = Set.foldr (\p l -> l ++ [toPair p]) []
fromPropertyList :: [(String, String)] -> ZFSProperties
fromPropertyList props =
- Set.fromList $ map fromPair 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 (ZDataset paths) = intercalate "/" paths
+ show = val
instance IsString ZDataset where
- fromString s = ZDataset $ SU.split "/" s
+ fromString s = ZDataset $ splitc '/' s
instance IsString ZPool where
- fromString p = ZPool p
+ fromString p = ZPool p
class Value a where
- toValue :: a -> String
- fromValue :: (IsString a) => String -> a
- fromValue = fromString
+ 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)
@@ -57,57 +62,57 @@ 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"
+ toValue (ZFSYesNo True) = "yes"
+ toValue (ZFSYesNo False) = "no"
instance Value ZFSOnOff where
- toValue (ZFSOnOff True) = "on"
- toValue (ZFSOnOff False) = "off"
+ toValue (ZFSOnOff True) = "on"
+ toValue (ZFSOnOff False) = "off"
instance Value ZFSSize where
- toValue (ZFSSize s) = show s
+ toValue (ZFSSize s) = show s
instance Value ZFSString where
- toValue (ZFSString s) = s
+ toValue (ZFSString s) = s
instance IsString ZFSString where
- fromString = ZFSString
+ fromString = ZFSString
instance IsString ZFSYesNo where
- fromString "yes" = ZFSYesNo True
- fromString "no" = ZFSYesNo False
- fromString _ = error "Not yes or no"
+ 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"
+ 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"
+ 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"
+ 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"
+ 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"
+ toValue AMDiscard = "discard"
+ toValue AMGroupmask = "groupmask"
+ toValue AMPassthrough = "passthrough"
data ZFSProperty = Mounted ZFSYesNo
| Mountpoint ZFSString