| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Data.Kind.Extra
Synopsis
- type Extends a = (a -> Type :: Type)
 - type Konst (a :: k) = ((:~:) a :: Extends k)
 - data (a :: k) :~: (b :: k) :: forall k. k -> k -> Type
 - type family From (t :: a -> Type) :: a
 - type family Apply (f :: Extends (a -> b)) (x :: a) :: b
 - data Labelled (s :: Symbol) :: Extends a -> Extends a
 - data Named s
 - data Name :: Symbol -> Extends s -> Extends (Named s)
 - type (:#) (name :: Symbol) (x :: Extends s) = Name name x
 - data Anonymous (x :: Extends (Named s)) :: Extends s
 - type ($) f x = Apply f x
 - data (:>>=:) :: Extends a -> Extends (a -> Extends b) -> Extends b
 - data (:>>>:) :: Extends (good -> better) -> Extends (better -> best) -> Extends (good -> best)
 - data (:^>>>:) :: Extends (good -> better) -> Extends (better -> best) -> Extends (Extends good -> best)
 - data (:>>>^:) :: Extends (good -> better) -> Extends (better -> best) -> Extends (good -> Extends best)
 - data Extract :: Extends (Extends x -> x)
 - data Optional :: Extends t -> Extends (s -> Extends t) -> Extends (Maybe s -> Extends t)
 - type family FoldMap (append :: Extends (b -> Extends (b -> b))) (zero :: b) (f :: Extends (a -> b)) (xs :: [(a :: Type)]) :: (b :: Type) where ...
 - data Fun1 :: (a -> Extends b) -> Extends (a -> Extends b)
 - data Fun2 :: (a -> b -> Extends c) -> Extends (a -> Extends (b -> Extends c))
 - data Fun3 :: (a -> b -> c -> Extends d) -> Extends (a -> Extends (b -> Extends (c -> Extends d)))
 - data Fun4 :: (a -> b -> c -> d -> Extends e) -> Extends (a -> Extends (b -> Extends (c -> Extends (d -> Extends e))))
 
Documentation
data (a :: k) :~: (b :: k) :: forall k. k -> k -> Type infix 4 #
Propositional equality. If a :~: b is inhabited by some terminating
 value, then the type a is the same as the type b. To use this equality
 in practice, pattern-match on the a :~: b to get out the Refl constructor;
 in the body of the pattern-match, the compiler knows that a ~ b.
Since: base-4.7.0.0
Instances
| Category ((:~:) :: k -> k -> Type) | Since: base-4.7.0.0  | 
| TestEquality ((:~:) a :: k -> Type) | Since: base-4.7.0.0  | 
Defined in Data.Type.Equality  | |
| HasFunctionBuilder BitBuilder (Proxy nested) => HasFunctionBuilder BitBuilder (Proxy (Konst nested)) Source # | |
Defined in Data.Type.BitRecords.Builder.LazyByteStringBuilder Associated Types type ToFunction BitBuilder (Proxy (Konst nested)) r :: Type # Methods toFunctionBuilder :: Proxy (Konst nested) -> FunctionBuilder BitBuilder r (ToFunction BitBuilder (Proxy (Konst nested)) r) #  | |
| DynamicContent BitBuilder (Proxy nested) rt => DynamicContent BitBuilder (Proxy (Konst nested)) rt Source # | |
Defined in Data.Type.BitRecords.Builder.LazyByteStringBuilder Methods addParameter :: Proxy (Konst nested) -> FunctionBuilder BitBuilder next (rt -> next) #  | |
| a ~ b => Bounded (a :~: b) | Since: base-4.7.0.0  | 
| a ~ b => Enum (a :~: b) | Since: base-4.7.0.0  | 
Defined in Data.Type.Equality Methods succ :: (a :~: b) -> a :~: b # pred :: (a :~: b) -> a :~: b # fromEnum :: (a :~: b) -> Int # enumFrom :: (a :~: b) -> [a :~: b] # enumFromThen :: (a :~: b) -> (a :~: b) -> [a :~: b] # enumFromTo :: (a :~: b) -> (a :~: b) -> [a :~: b] # enumFromThenTo :: (a :~: b) -> (a :~: b) -> (a :~: b) -> [a :~: b] #  | |
| Eq (a :~: b) | Since: base-4.7.0.0  | 
| Ord (a :~: b) | Since: base-4.7.0.0  | 
Defined in Data.Type.Equality  | |
| a ~ b => Read (a :~: b) | Since: base-4.7.0.0  | 
| Show (a :~: b) | Since: base-4.7.0.0  | 
| type From ((:~:) a2 :: a1 -> Type) Source # | |
Defined in Data.Kind.Extra  | |
| type ToFunction BitBuilder (Proxy (Konst nested)) a Source # | |
type family From (t :: a -> Type) :: a Source #
An open type family to turn symbolic type representations created with
 A or Extends into the actual types.
Instances
type family Apply (f :: Extends (a -> b)) (x :: a) :: b Source #
An open family of functions from a to b
Instances
data Labelled (s :: Symbol) :: Extends a -> Extends a Source #
Assign a symbol to any type in a group.
Instances
| HasFunctionBuilder BitBuilder (Proxy nested) => HasFunctionBuilder BitBuilder (Proxy (Labelled l nested)) Source # | |
Defined in Data.Type.BitRecords.Builder.LazyByteStringBuilder Associated Types type ToFunction BitBuilder (Proxy (Labelled l nested)) r :: Type # Methods toFunctionBuilder :: Proxy (Labelled l nested) -> FunctionBuilder BitBuilder r (ToFunction BitBuilder (Proxy (Labelled l nested)) r) #  | |
| DynamicContent BitBuilder (Proxy nested) rt => DynamicContent BitBuilder (Proxy (Labelled l nested)) rt Source # | |
Defined in Data.Type.BitRecords.Builder.LazyByteStringBuilder Methods addParameter :: Proxy (Labelled l nested) -> FunctionBuilder BitBuilder next (rt -> next) #  | |
| type ToFunction BitBuilder (Proxy (Labelled l nested)) a Source # | |
| type From (Labelled s t :: a -> Type) Source # | |
Defined in Data.Kind.Extra  | |
| type SizeInBytes (Labelled l f :: a -> Type) Source # | |
Defined in Data.Type.BitRecords.Core  | |
Phantom type for things that have a name
Instances
| type GetStructureSize (Record (x ': xs)) Source # | |
Defined in Data.Type.BitRecords.Structure type GetStructureSize (Record (x ': xs)) = GetStructureSize (Anonymous x) + GetStructureSize (Record xs)  | |
| type GetStructureSize (Record ([] :: [Extends (Named (Structure FixSize))])) Source # | |
Defined in Data.Type.BitRecords.Structure  | |
data Name :: Symbol -> Extends s -> Extends (Named s) Source #
Assign a name to something that has no name
Instances
| type PrettyStructure (Anonymous (Name name struct) :: Structure sizeType -> Type) Source # | |
Defined in Data.Type.BitRecords.Structure type PrettyStructure (Anonymous (Name name struct) :: Structure sizeType -> Type) = name <:> PrettyStructure struct  | |
| type GetStructureSize (Anonymous (Name name struct)) Source # | |
Defined in Data.Type.BitRecords.Structure  | |
data Anonymous (x :: Extends (Named s)) :: Extends s Source #
Remove tha name of a NamedStructure to get to a Structure
Instances
| type PrettyStructure (Anonymous (Name name struct) :: Structure sizeType -> Type) Source # | |
Defined in Data.Type.BitRecords.Structure type PrettyStructure (Anonymous (Name name struct) :: Structure sizeType -> Type) = name <:> PrettyStructure struct  | |
| type GetStructureSize (Anonymous (Name name struct)) Source # | |
Defined in Data.Type.BitRecords.Structure  | |
data (:>>=:) :: Extends a -> Extends (a -> Extends b) -> Extends b infixl 1 Source #
From and ApplyCompose functions
data (:>>>:) :: Extends (good -> better) -> Extends (better -> best) -> Extends (good -> best) infixl 1 Source #
Compose functions
data (:^>>>:) :: Extends (good -> better) -> Extends (better -> best) -> Extends (Extends good -> best) infixl 1 Source #
From Input & Compose
data (:>>>^:) :: Extends (good -> better) -> Extends (better -> best) -> Extends (good -> Extends best) infixl 1 Source #
Compose and Konst
data Optional :: Extends t -> Extends (s -> Extends t) -> Extends (Maybe s -> Extends t) Source #
Either use the value from Just or return a fallback value(types(kinds))
type family FoldMap (append :: Extends (b -> Extends (b -> b))) (zero :: b) (f :: Extends (a -> b)) (xs :: [(a :: Type)]) :: (b :: Type) where ... Source #
Map over the elements of a list and fold the result.
data Fun3 :: (a -> b -> c -> Extends d) -> Extends (a -> Extends (b -> Extends (c -> Extends d))) Source #