propellor-3.3.0: 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 # 
Ord MetaType Source # 
Show MetaType Source # 
SingI MetaType WithInfo Source # 

Methods

sing :: Sing WithInfo t Source #

SingKind MetaType (KProxy MetaType) Source # 

Associated Types

type DemoteRep (KProxy MetaType) (kparam :: KProxy (KProxy MetaType)) :: * Source #

SingI MetaType (Targeting OSDebian) Source # 
SingI MetaType (Targeting OSBuntish) Source # 
SingI MetaType (Targeting OSArchLinux) Source # 
SingI MetaType (Targeting OSFreeBSD) Source # 
data Sing MetaType Source # 
type EqT MetaType WithInfo WithInfo Source # 
type EqT MetaType WithInfo (Targeting b) Source # 
type DemoteRep MetaType (KProxy MetaType) Source # 
type EqT MetaType (Targeting a) WithInfo Source # 
type EqT MetaType (Targeting a) (Targeting b) Source # 
type IncludesInfo (MetaTypes [MetaType] l) Source # 

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 :: ab Source #

Convenience type operator to combine two MetaTypes lists.

For example:

HasInfo + Debian

Which is shorthand for this type:

MetaTypes '[WithInfo, Targeting OSDebian]

Instances

type (+) * (MetaTypes [a] a1) (MetaTypes [a] b) Source # 
type (+) * (MetaTypes [a] a1) (MetaTypes [a] b)

sing :: SingI t => Sing t Source #

class SingI t where Source #

A class used to pass singleton values implicitly.

Minimal complete definition

sing

Methods

sing :: Sing t Source #

type family IncludesInfo t :: Bool Source #

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

Instances

type Targets a ([] a) Source # 
type Targets a ([] a) = [] a
type Targets a ((:) a x xs) Source # 
type Targets a ((:) a x xs)

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

Instances

type NonTargets a ([] a) Source # 
type NonTargets a ([] a) = [] a
type NonTargets a ((:) a x xs) Source # 
type NonTargets a ((:) a x xs)

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

Every item in the subset must be in the superset.

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

Instances

type NotSuperset a superset ([] a) Source # 
type NotSuperset a superset ([] a) = CanCombine
type NotSuperset a superset ((:) a s rest) Source # 
type NotSuperset a superset ((:) a s rest)

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

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

Instances

type Combine a list1 list2 Source # 
type Combine a list1 list2

type family CheckCombinable (list1 :: [a]) (list2 :: [a]) :: CheckCombine 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

Instances

type CheckCombinable a list1 ([] a) Source # 
type CheckCombinable a list1 ([] a) = CanCombine
type CheckCombinable a ([] a) list2 Source # 
type CheckCombinable a ([] a) list2 = CanCombine
type CheckCombinable a ((:) a l1 list1) ((:) a l2 list2) Source # 
type CheckCombinable a ((:) a l1 list1) ((:) a l2 list2)

type family (a :: Bool) && (b :: Bool) :: Bool Source #

Instances

type family Not (a :: Bool) :: Bool Source #

Instances

type Not False Source # 
type Not False = True
type Not True Source # 
type Not True = False

type family EqT (a :: t) (b :: t) :: Bool Source #

Type level equality

This is a very clumsy implmentation, but it works back to ghc 7.6.

Instances

type EqT TargetOS OSDebian OSDebian Source # 
type EqT TargetOS OSDebian OSBuntish Source # 
type EqT TargetOS OSDebian OSArchLinux Source # 
type EqT TargetOS OSDebian OSFreeBSD Source # 
type EqT TargetOS OSBuntish OSDebian Source # 
type EqT TargetOS OSBuntish OSBuntish Source # 
type EqT TargetOS OSBuntish OSArchLinux Source # 
type EqT TargetOS OSBuntish OSFreeBSD Source # 
type EqT TargetOS OSArchLinux OSDebian Source # 
type EqT TargetOS OSArchLinux OSBuntish Source # 
type EqT TargetOS OSArchLinux OSArchLinux Source # 
type EqT TargetOS OSArchLinux OSFreeBSD Source # 
type EqT TargetOS OSFreeBSD OSDebian Source # 
type EqT TargetOS OSFreeBSD OSBuntish Source # 
type EqT TargetOS OSFreeBSD OSArchLinux Source # 
type EqT TargetOS OSFreeBSD OSFreeBSD Source # 
type EqT MetaType WithInfo WithInfo Source # 
type EqT MetaType WithInfo (Targeting b) Source # 
type EqT MetaType (Targeting a) WithInfo Source # 
type EqT MetaType (Targeting a) (Targeting b) Source # 

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

Type level union.

Instances

type Union a ([] a) list2 Source # 
type Union a ([] a) list2 = list2
type Union a ((:) a a1 rest) list2 Source # 
type Union a ((:) a a1 rest) list2