typed-encoding-0.5.2.2: Type safe string transformations

Safe HaskellSafe
LanguageHaskell2010

Data.TypedEncoding.Common.Class.Common

Contents

Description

This module defines SymbolList and Displ type classes using by typed-encoding used for display / testing as well as for construction of untyped versions of Enc (CheckedEnc and UncheckedEnc)

This module is re-exported in Data.TypedEncoding and it is best not to import it directly.

Synopsis

Documentation

>>> :set -XScopedTypeVariables -XTypeApplications -XAllowAmbiguousTypes -XDataKinds

Symbol List

class SymbolList (xs :: [Symbol]) where Source #

Since: 0.2.0.0

Instances
SymbolList ([] :: [Symbol]) Source # 
Instance details

Defined in Data.TypedEncoding.Common.Class.Common

(SymbolList xs, KnownSymbol x) => SymbolList (x ': xs) Source #
>>> symbolVals @ '["FIRST", "SECOND"]
["FIRST","SECOND"]
Instance details

Defined in Data.TypedEncoding.Common.Class.Common

symbolVals_ :: forall xs. SymbolList xs => Proxy xs -> [String] Source #

Display

class Displ x where Source #

Human friendly version of Show

Since: 0.2.0.0

Methods

displ :: x -> String Source #

Instances
Displ String Source # 
Instance details

Defined in Data.TypedEncoding.Common.Class.Common

Methods

displ :: String -> String Source #

Displ ByteString Source # 
Instance details

Defined in Data.TypedEncoding.Common.Class.Common

Displ ByteString Source # 
Instance details

Defined in Data.TypedEncoding.Common.Class.Common

Displ Text Source # 
Instance details

Defined in Data.TypedEncoding.Common.Class.Common

Methods

displ :: Text -> String Source #

Displ Text Source # 
Instance details

Defined in Data.TypedEncoding.Common.Class.Common

Methods

displ :: Text -> String Source #

Displ [EncAnn] Source # 
Instance details

Defined in Data.TypedEncoding.Common.Class.Common

Methods

displ :: [EncAnn] -> String Source #

Displ a => Displ (SimplifiedEmailF a) Source #

Provides easy to read encoding information

Instance details

Defined in Examples.TypedEncoding.ToEncString

Displ a => Displ (IpV4F a) Source #

Provides easy to read encoding information

Instance details

Defined in Examples.TypedEncoding.ToEncString

Methods

displ :: IpV4F a -> String Source #

SymbolList xs => Displ (Proxy xs) Source #
>>> displ (Proxy :: Proxy ["FIRST", "SECOND"])
"[FIRST,SECOND]"
Instance details

Defined in Data.TypedEncoding.Common.Class.Common

Methods

displ :: Proxy xs -> String Source #

(Show c, Displ str) => Displ (UncheckedEnc c str) Source #
>>> displ $ MkUncheckedEnc ["TEST"] () ("hello" :: T.Text)
"MkUncheckedEnc [TEST] () (Text hello)"
Instance details

Defined in Data.TypedEncoding.Common.Types.UncheckedEnc

Methods

displ :: UncheckedEnc c str -> String Source #

(Show c, Displ str) => Displ (CheckedEnc c str) Source #
>>> displ $ unsafeCheckedEnc ["TEST"] () ("hello" :: T.Text)
"UnsafeMkCheckedEnc [TEST] () (Text hello)"
Instance details

Defined in Data.TypedEncoding.Common.Types.CheckedEnc

Methods

displ :: CheckedEnc c str -> String Source #

(Show c, Displ str) => Displ (SomeEnc c str) Source #
>>> let enctest = unsafeSetPayload () "hello" :: Enc '["TEST"] () T.Text
>>> displ $ MkSomeEnc enctest
"Some (Enc '[TEST] () (Text hello))"
Instance details

Defined in Examples.TypedEncoding.SomeEnc

Methods

displ :: SomeEnc c str -> String Source #

(SymbolList xs, Show c, Displ str) => Displ (Enc xs c str) Source #
>>> let disptest = UnsafeMkEnc Proxy () "hello" :: Enc '["TEST"] () T.Text
>>> displ disptest
"Enc '[TEST] () (Text hello)"
Instance details

Defined in Data.TypedEncoding.Common.Types.Enc

Methods

displ :: Enc xs c str -> String Source #