Safe Haskell | None |
---|---|
Language | Haskell98 |
- data MetaType
- type UnixLike = MetaTypes '[Targeting OSDebian, Targeting OSBuntish, Targeting OSArchLinux, Targeting OSFreeBSD]
- type Linux = MetaTypes '[Targeting OSDebian, Targeting OSBuntish, Targeting OSArchLinux]
- type DebianLike = MetaTypes '[Targeting OSDebian, Targeting OSBuntish]
- type Debian = MetaTypes '[Targeting OSDebian]
- type Buntish = MetaTypes '[Targeting OSBuntish]
- type ArchLinux = MetaTypes '[Targeting OSArchLinux]
- type FreeBSD = MetaTypes '[Targeting OSFreeBSD]
- type HasInfo = MetaTypes '[WithInfo]
- type MetaTypes = Sing
- type family a + b :: ab
- sing :: SingI t => Sing t
- class SingI t where
- type family IncludesInfo t :: Bool
- type family Targets (l :: [a]) :: [a]
- type family NonTargets (l :: [a]) :: [a]
- type family NotSuperset (superset :: [a]) (subset :: [a]) :: CheckCombine
- type family Combine (list1 :: [a]) (list2 :: [a]) :: [a]
- data CheckCombine
- type family CheckCombinable (list1 :: [a]) (list2 :: [a]) :: CheckCombine
- type family (a :: Bool) && (b :: Bool) :: Bool
- type family Not (a :: Bool) :: Bool
- type family EqT (a :: t) (b :: t) :: Bool
- type family Union (list1 :: [a]) (list2 :: [a]) :: [a]
Documentation
Eq MetaType Source # | |
Ord MetaType Source # | |
Show MetaType Source # | |
SingI MetaType WithInfo Source # | |
SingKind MetaType (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 UnixLike = MetaTypes '[Targeting OSDebian, Targeting OSBuntish, Targeting OSArchLinux, Targeting OSFreeBSD] Source #
Any unix-like system
type Linux = MetaTypes '[Targeting OSDebian, Targeting OSBuntish, Targeting OSArchLinux] Source #
Any linux system
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]
A class used to pass singleton values implicitly.
SingI Bool False Source # | |
SingI Bool True Source # | |
SingI MetaType WithInfo Source # | |
SingI MetaType (Targeting OSDebian) Source # | |
SingI MetaType (Targeting OSBuntish) Source # | |
SingI MetaType (Targeting OSArchLinux) Source # | |
SingI MetaType (Targeting OSFreeBSD) Source # | |
SingI [k] ([] k) Source # | |
(SingI a x, SingI [a] xs) => SingI [a] ((:) a x xs) Source # | |
type family IncludesInfo t :: Bool Source #
type IncludesInfo (MetaTypes [MetaType] l) Source # | |
type family NonTargets (l :: [a]) :: [a] Source #
type NonTargets a ([] a) Source # | |
type NonTargets a ((:) a x xs) Source # | |
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.
type NotSuperset a superset ([] a) Source # | |
type NotSuperset a superset ((:) a s rest) Source # | |
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.
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
type CheckCombinable a list1 ([] a) Source # | |
type CheckCombinable a ([] a) list2 Source # | |
type CheckCombinable a ((:) a l1 list1) ((:) a l2 list2) Source # | |
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.
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 # | |