Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Module defines SomeEnc
- existentially quantified version of Enc
and basic combinators
Synopsis
- data SomeEnc conf str where
- MkSomeEnc :: SymbolList xs => Enc xs conf str -> SomeEnc conf str
- withSomeEnc :: SomeEnc conf str -> (forall xs. SymbolList xs => Enc xs conf str -> r) -> r
- toSome :: SymbolList xs => Enc xs conf str -> SomeEnc conf str
- someToChecked :: SomeEnc conf str -> CheckedEnc conf str
- checkedToSome :: CheckedEnc conf str -> SomeEnc conf str
Documentation
>>>
:set -XOverloadedStrings -XMultiParamTypeClasses -XDataKinds -XAllowAmbiguousTypes
>>>
import qualified Data.Text as T
>>>
import Data.TypedEncoding.Combinators.Unsafe
data SomeEnc conf str where Source #
Existentially quantified quantified Enc
effectively isomorphic to CheckedEnc
Since: 0.2.0.0
MkSomeEnc :: SymbolList xs => Enc xs conf str -> SomeEnc conf str |
withSomeEnc :: SomeEnc conf str -> (forall xs. SymbolList xs => Enc xs conf str -> r) -> r Source #
Since: 0.2.0.0
someToChecked :: SomeEnc conf str -> CheckedEnc conf str Source #
>>>
let enctest = unsafeSetPayload () "hello" :: Enc '["TEST"] () T.Text
>>>
someToChecked . MkSomeEnc $ enctest
UnsafeMkCheckedEnc ["TEST"] () "hello"
Since: 0.2.0.0
checkedToSome :: CheckedEnc conf str -> SomeEnc conf str Source #
>>>
let tst = unsafeCheckedEnc ["TEST"] () "test"
>>>
displ $ checkedToSome tst
"Some (Enc '[TEST] () (String test))"
@since 0.2.0.0 s