propellor-3.3.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

data family Sing (x :: k) Source #

The data family of singleton types.

Instances

((~) CheckCombine (CheckCombinable a x y) CanCombine, SingI [a] (Combine a x y)) => Combines (Property (MetaTypes [a] x)) (Property (MetaTypes [a] y)) Source # 
((~) CheckCombine (CheckCombinable a x y) CanCombine, SingI [a] (Combine a x y)) => Combines (Property (MetaTypes [a] x)) (RevertableProperty (MetaTypes [a] y) (MetaTypes k y')) Source # 
((~) CheckCombine (CheckCombinable a x y) CanCombine, SingI [a] (Combine a x y)) => Combines (RevertableProperty (MetaTypes [a] x) (MetaTypes k x')) (Property (MetaTypes [a] y)) Source # 
((~) CheckCombine (CheckCombinable a1 x y) CanCombine, (~) CheckCombine (CheckCombinable a x' y') CanCombine, SingI [a1] (Combine a1 x y), SingI [a] (Combine a x' y')) => Combines (RevertableProperty (MetaTypes [a1] x) (MetaTypes [a] x')) (RevertableProperty (MetaTypes [a1] y) (MetaTypes [a] y')) Source # 
data Sing Bool Source # 
data Sing MetaType Source # 
data Sing [k] Source # 
data Sing [k] where
type CombinedType (Property (MetaTypes [a] x)) (Property (MetaTypes [a] y)) Source # 
type CombinedType (Property (MetaTypes [a] x)) (Property (MetaTypes [a] y)) = Property (MetaTypes [a] (Combine a x y))
type CombinedType (Property (MetaTypes [a] x)) (RevertableProperty (MetaTypes [a] y) (MetaTypes k y')) Source # 
type (+) * (MetaTypes [a] a1) (MetaTypes [a] b) Source # 
type (+) * (MetaTypes [a] a1) (MetaTypes [a] b)
type IncludesInfo (MetaTypes [MetaType] l) Source # 
type CombinedType (RevertableProperty (MetaTypes [a] x) (MetaTypes k x')) (Property (MetaTypes [a] y)) Source # 
type CombinedType (RevertableProperty (MetaTypes [a1] x) (MetaTypes [a] x')) (RevertableProperty (MetaTypes [a1] y) (MetaTypes [a] y')) Source # 
type CombinedType (RevertableProperty (MetaTypes [a1] x) (MetaTypes [a] x')) (RevertableProperty (MetaTypes [a1] y) (MetaTypes [a] y')) = RevertableProperty (MetaTypes [a1] (Combine a1 x y)) (MetaTypes [a] (Combine a x' y'))

class SingI t where Source #

A class used to pass singleton values implicitly.

Minimal complete definition

sing

Methods

sing :: Sing t Source #

class kparam ~ KProxy => SingKind kparam where Source #

Minimal complete definition

fromSing

Associated Types

type DemoteRep kparam :: * Source #

Methods

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

From singleton to value.

Instances

SingKind Bool (KProxy Bool) Source # 

Associated Types

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

Methods

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

SingKind MetaType (KProxy MetaType) Source # 

Associated Types

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

SingKind a (KProxy a) => SingKind [a] (KProxy [a]) Source # 

Associated Types

type DemoteRep (KProxy [a]) (kparam :: KProxy (KProxy [a])) :: * Source #

Methods

fromSing :: Sing (KProxy [a]) a -> DemoteRep (KProxy [a]) kparam Source #

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