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

Safe HaskellSafe
LanguageHaskell98

Propellor.Types.Singletons

Description

Simple implementation of singletons, portable back to ghc 7.6.3

Synopsis

Documentation

class kparam ~ KProxy => SingKind (kparam :: KProxy k) where Source #

Associated Types

type DemoteRep kparam :: * Source #

Methods

fromSing :: Sing (a :: k) -> DemoteRep kparam Source #

From singleton to value.

Instances
SingKind (KProxy :: KProxy Bool) Source # 
Instance details

Defined in Propellor.Types.Singletons

Associated Types

type DemoteRep KProxy :: Type Source #

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

Defined in Propellor.Types.MetaTypes

Associated Types

type DemoteRep KProxy :: Type Source #

SingKind (KProxy :: KProxy a) => SingKind (KProxy :: KProxy [a]) Source # 
Instance details

Defined in Propellor.Types.Singletons

Associated Types

type DemoteRep KProxy :: Type Source #

class SingI t where Source #

A class used to pass singleton values implicitly.

Methods

sing :: Sing t Source #

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 #

data family Sing (x :: k) Source #

The data family of singleton types.

Instances
SingI metatypes => Semigroup (Property (MetaTypes metatypes)) Source #

Any type of Property is a Semigroup. When properties x and y are appended together, the resulting property has a description like "x and y". Note that when x fails to be ensured, it will not try to ensure y.

Instance details

Defined in Propellor.Types

Methods

(<>) :: Property (MetaTypes metatypes) -> Property (MetaTypes metatypes) -> Property (MetaTypes metatypes) #

sconcat :: NonEmpty (Property (MetaTypes metatypes)) -> Property (MetaTypes metatypes) #

stimes :: Integral b => b -> Property (MetaTypes metatypes) -> Property (MetaTypes metatypes) #

SingI metatypes => Monoid (Property (MetaTypes metatypes)) Source #

Any type of Property is a Monoid.

Instance details

Defined in Propellor.Types

Methods

mempty :: Property (MetaTypes metatypes) #

mappend :: Property (MetaTypes metatypes) -> Property (MetaTypes metatypes) -> Property (MetaTypes metatypes) #

mconcat :: [Property (MetaTypes metatypes)] -> Property (MetaTypes metatypes) #

(CheckCombinable x y ~ CanCombine, SingI (Combine x y)) => Combines (Property (MetaTypes x)) (Property (MetaTypes y)) Source # 
Instance details

Defined in Propellor.Types

(CheckCombinable x y ~ CanCombine, SingI (Combine x y)) => Combines (Property (MetaTypes x)) (RevertableProperty (MetaTypes y) (MetaTypes y')) Source # 
Instance details

Defined in Propellor.Types

(Semigroup (Property (MetaTypes setupmetatypes)), Semigroup (Property (MetaTypes undometatypes)), SingI setupmetatypes, SingI undometatypes) => Semigroup (RevertableProperty (MetaTypes setupmetatypes) (MetaTypes undometatypes)) Source #

Any type of RevertableProperty is a Semigroup. When revertable properties x and y are appended together, the resulting revertable property has a description like "x and y". Note that when x fails to be ensured, it will not try to ensure y.

Instance details

Defined in Propellor.Types

Methods

(<>) :: RevertableProperty (MetaTypes setupmetatypes) (MetaTypes undometatypes) -> RevertableProperty (MetaTypes setupmetatypes) (MetaTypes undometatypes) -> RevertableProperty (MetaTypes setupmetatypes) (MetaTypes undometatypes) #

sconcat :: NonEmpty (RevertableProperty (MetaTypes setupmetatypes) (MetaTypes undometatypes)) -> RevertableProperty (MetaTypes setupmetatypes) (MetaTypes undometatypes) #

stimes :: Integral b => b -> RevertableProperty (MetaTypes setupmetatypes) (MetaTypes undometatypes) -> RevertableProperty (MetaTypes setupmetatypes) (MetaTypes undometatypes) #

(Monoid (Property (MetaTypes setupmetatypes)), Monoid (Property (MetaTypes undometatypes)), SingI setupmetatypes, SingI undometatypes) => Monoid (RevertableProperty (MetaTypes setupmetatypes) (MetaTypes undometatypes)) Source # 
Instance details

Defined in Propellor.Types

Methods

mempty :: RevertableProperty (MetaTypes setupmetatypes) (MetaTypes undometatypes) #

mappend :: RevertableProperty (MetaTypes setupmetatypes) (MetaTypes undometatypes) -> RevertableProperty (MetaTypes setupmetatypes) (MetaTypes undometatypes) -> RevertableProperty (MetaTypes setupmetatypes) (MetaTypes undometatypes) #

mconcat :: [RevertableProperty (MetaTypes setupmetatypes) (MetaTypes undometatypes)] -> RevertableProperty (MetaTypes setupmetatypes) (MetaTypes undometatypes) #

(CheckCombinable x y ~ CanCombine, SingI (Combine x y)) => Combines (RevertableProperty (MetaTypes x) (MetaTypes x')) (Property (MetaTypes y)) Source # 
Instance details

Defined in Propellor.Types

(CheckCombinable x y ~ CanCombine, CheckCombinable x' y' ~ CanCombine, SingI (Combine x y), SingI (Combine x' y')) => Combines (RevertableProperty (MetaTypes x) (MetaTypes x')) (RevertableProperty (MetaTypes y) (MetaTypes y')) Source # 
Instance details

Defined in Propellor.Types

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

Defined in Propellor.Types.Singletons

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

Defined in Propellor.Types.MetaTypes

data Sing (x :: MetaType) where
data Sing (x :: [k]) Source # 
Instance details

Defined in Propellor.Types.Singletons

data Sing (x :: [k]) where
  • Nil :: forall k (x :: [k]). Sing ([] :: [k])
  • Cons :: forall a (x :: [a]) (x :: a) (xs :: [a]). Sing x -> Sing xs -> Sing (x ': xs)

data KProxy t #

A concrete, promotable proxy type, for use at the kind level There are no instances for this because it is intended at the kind level only

Constructors

KProxy