propellor-3.0.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 Source

The data family of singleton types.

Instances

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

class SingI t where Source

A class used to pass singleton values implicitly.

Methods

sing :: Sing t Source

class (kparam ~ KProxy) => SingKind kparam where Source

Associated Types

type DemoteRep kparam :: * Source

Methods

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

From singleton to value.

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