propellor-5.6.1: property-based host configuration management in haskell

Safe HaskellNone
LanguageHaskell98

Propellor.Types.MetaTypes

Synopsis

Documentation

data MetaType Source #

Constructors

Targeting TargetOS

A target OS of a Property

WithInfo

Indicates that a Property has associated Info

Instances
Eq MetaType Source # 
Instance details

Defined in Propellor.Types.MetaTypes

Ord MetaType Source # 
Instance details

Defined in Propellor.Types.MetaTypes

Show MetaType Source # 
Instance details

Defined in Propellor.Types.MetaTypes

SingI WithInfo Source # 
Instance details

Defined in Propellor.Types.MetaTypes

SingKind (KProxy :: KProxy MetaType) Source # 
Instance details

Defined in Propellor.Types.MetaTypes

Associated Types

type DemoteRep KProxy :: Type Source #

SingI (Targeting OSDebian) Source # 
Instance details

Defined in Propellor.Types.MetaTypes

SingI (Targeting OSBuntish) Source # 
Instance details

Defined in Propellor.Types.MetaTypes

SingI (Targeting OSArchLinux) Source # 
Instance details

Defined in Propellor.Types.MetaTypes

SingI (Targeting OSFreeBSD) Source # 
Instance details

Defined in Propellor.Types.MetaTypes

data Sing (x :: MetaType) Source # 
Instance details

Defined in Propellor.Types.MetaTypes

data Sing (x :: MetaType) where
type DemoteRep (KProxy :: KProxy MetaType) Source # 
Instance details

Defined in Propellor.Types.MetaTypes

type DebianLike = MetaTypes '[Targeting OSDebian, Targeting OSBuntish] Source #

Debian and derivatives.

type HasInfo = MetaTypes '[WithInfo] Source #

Used to indicate that a Property adds Info to the Host where it's used.

type family a + b :: * where ... Source #

Convenience type operator to combine two MetaTypes lists.

For example:

HasInfo + Debian

Which is shorthand for this type:

MetaTypes '[WithInfo, Targeting OSDebian]

Equations

(MetaTypes a) + (MetaTypes b) = MetaTypes (Concat a b) 

sing :: SingI t => Sing t Source #

class SingI t Source #

A class used to pass singleton values implicitly.

Minimal complete definition

sing

Instances
SingI False Source # 
Instance details

Defined in Propellor.Types.Singletons

Methods

sing :: Sing False Source #

SingI True Source # 
Instance details

Defined in Propellor.Types.Singletons

Methods

sing :: Sing True Source #

SingI WithInfo Source # 
Instance details

Defined in Propellor.Types.MetaTypes

SingI (Targeting OSDebian) Source # 
Instance details

Defined in Propellor.Types.MetaTypes

SingI (Targeting OSBuntish) Source # 
Instance details

Defined in Propellor.Types.MetaTypes

SingI (Targeting OSArchLinux) Source # 
Instance details

Defined in Propellor.Types.MetaTypes

SingI (Targeting OSFreeBSD) Source # 
Instance details

Defined in Propellor.Types.MetaTypes

SingI ([] :: [k]) Source # 
Instance details

Defined in Propellor.Types.Singletons

Methods

sing :: Sing [] Source #

(SingI x, SingI xs) => SingI (x ': xs :: [a]) Source # 
Instance details

Defined in Propellor.Types.Singletons

Methods

sing :: Sing (x ': xs) Source #

type family IncludesInfo t :: Bool where ... Source #

Equations

IncludesInfo (MetaTypes l) = Elem WithInfo l 

type family Targets (l :: [a]) :: [a] where ... Source #

Equations

Targets '[] = '[] 
Targets (x ': xs) = If (IsTarget x) (x ': Targets xs) (Targets xs) 

type family NonTargets (l :: [a]) :: [a] where ... Source #

Equations

NonTargets '[] = '[] 
NonTargets (x ': xs) = If (IsTarget x) (NonTargets xs) (x ': NonTargets xs) 

type family NotSuperset (superset :: [a]) (subset :: [a]) :: CheckCombine where ... Source #

Every item in the subset must be in the superset.

The name of this was chosen to make type errors more understandable.

Equations

NotSuperset superset '[] = CanCombine 
NotSuperset superset (s ': rest) = If (Elem s superset) (NotSuperset superset rest) CannotCombineTargets 

type family Combine (list1 :: [a]) (list2 :: [a]) :: [a] where ... Source #

Combine two MetaTypes lists, yielding a list that has targets present in both, and nontargets present in either.

Equations

Combine (list1 :: [a]) (list2 :: [a]) = Concat (NonTargets list1 `Union` NonTargets list2) (Targets list1 `Intersect` Targets list2) 

type family CheckCombinable (list1 :: [a]) (list2 :: [a]) :: CheckCombine where ... Source #

Checks if two MetaTypes lists can be safely combined.

This should be used anywhere Combine is used, as an additional constraint. For example:

foo :: (CheckCombinable x y ~ 'CanCombine) => x -> y -> Combine x y

Equations

CheckCombinable '[] list2 = CanCombine 
CheckCombinable list1 '[] = CanCombine 
CheckCombinable (l1 ': list1) (l2 ': list2) = CheckCombinable' (Combine (l1 ': list1) (l2 ': list2)) 

type family (a :: Bool) && (b :: Bool) :: Bool where ... infixr 3 #

Type-level "and"

Equations

False && a = False 
True && a = a 
a && False = False 
a && True = a 
a && a = a 

type family Not (a :: Bool) = (res :: Bool) | res -> a where ... #

Type-level "not". An injective type family since 4.10.0.0.

Since: base-4.7.0.0

Equations

Not False = True 
Not True = False 

type family EqT (a :: MetaType) (b :: MetaType) where ... Source #

Type level equality of metatypes.

Equations

EqT a a = True 
EqT a b = False 

type family Union (list1 :: [a]) (list2 :: [a]) :: [a] where ... Source #

Type level union.

Equations

Union '[] list2 = list2 
Union (a ': rest) list2 = If (Elem a list2 || Elem a rest) (Union rest list2) (a ': Union rest list2)