Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
This module should be merged with Data.TypedEncoding.Common.Util.TypeLits
Since both provide type level helpers
Synopsis
- class SymbolList (xs :: [Symbol]) where
- symbolVals :: [String]
- symbolVals_ :: forall xs. SymbolList xs => Proxy xs -> [String]
- class Displ x where
- type family Append (xs :: [k]) (ys :: [k]) :: [k] where ...
- class HasA a c where
- has :: c -> a
Documentation
>>>
:set -XScopedTypeVariables -XTypeApplications -XAllowAmbiguousTypes -XDataKinds
Symbol List
class SymbolList (xs :: [Symbol]) where Source #
Since: 0.2.0.0
symbolVals :: [String] Source #
Instances
SymbolList ([] :: [Symbol]) Source # | |
Defined in Data.TypedEncoding.Common.Class.Util symbolVals :: [String] Source # | |
(SymbolList xs, KnownSymbol x) => SymbolList (x ': xs) Source # |
|
Defined in Data.TypedEncoding.Common.Class.Util symbolVals :: [String] Source # |
symbolVals_ :: forall xs. SymbolList xs => Proxy xs -> [String] Source #
Display
Human friendly version of Show
Since: 0.2.0.0
Instances
Displ String Source # | |
Displ ByteString Source # | |
Defined in Data.TypedEncoding.Common.Class.Util displ :: ByteString -> String Source # | |
Displ ByteString Source # | |
Defined in Data.TypedEncoding.Common.Class.Util displ :: ByteString -> String Source # | |
Displ Text Source # | |
Displ Text Source # | |
Displ [EncAnn] Source # | |
Displ a => Displ (SimplifiedEmailF a) Source # | Provides easy to read encoding information |
Defined in Examples.TypedEncoding.ToEncString displ :: SimplifiedEmailF a -> String Source # | |
Displ a => Displ (IpV4F a) Source # | Provides easy to read encoding information |
SymbolList xs => Displ (Proxy xs) Source # |
|
(Show c, Displ str) => Displ (UncheckedEnc c str) Source # |
|
Defined in Data.TypedEncoding.Common.Types.UncheckedEnc displ :: UncheckedEnc c str -> String Source # | |
(Show c, Displ str) => Displ (CheckedEnc c str) Source # |
|
Defined in Data.TypedEncoding.Common.Types.CheckedEnc displ :: CheckedEnc c str -> String Source # | |
(Show c, Displ str) => Displ (SomeEnc c str) Source # |
|
(SymbolList xs, Show c, Displ str) => Displ (Enc xs c str) Source # |
|
Other
type family Append (xs :: [k]) (ys :: [k]) :: [k] where ... Source #
Type level list append
Since: 0.1.0.0
Polymorphic data payloads used to encode/decode
Since: 0.1.0.0