Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Synopsis
- type family IsSuperset (y :: Symbol) (x :: Symbol) :: Bool where ...
- type family IsSupersetOpen (y :: Symbol) (x :: Symbol) (xs :: [Symbol]) :: Bool
- injectInto :: forall y x xs c str. IsSuperset y x ~ True => Enc (x ': xs) c str -> Enc (y ': xs) c str
- class EncodingSuperset (enc :: Symbol) where
- type EncSuperset enc :: Symbol
- implEncInto :: forall xs c str. Enc (enc ': xs) c str -> Enc (EncSuperset enc ': (enc ': xs)) c str
- _encodesInto :: forall y enc xs c str r. (IsSuperset y r ~ True, EncodingSuperset enc, r ~ EncSuperset enc) => Enc (enc ': xs) c str -> Enc (y ': (enc ': xs)) c str
Documentation
>>>
:set -XOverloadedStrings -XMultiParamTypeClasses -XDataKinds -XTypeApplications
>>>
import Data.TypedEncoding
>>>
import Data.TypedEncoding.Instances.Restriction.UTF8 ()
>>>
import Data.TypedEncoding.Instances.Restriction.ASCII ()
>>>
import Data.Text as T
type family IsSuperset (y :: Symbol) (x :: Symbol) :: Bool where ... Source #
Replaces previous Superset
typeclass.
Subsets are useful for restriction encodings
like r-UFT8 but should not be used for other encodings as
this would be dangerous. For example, considering "enc-" encoding as a superset of "r-" encoding would
permit converting encoded binary
"Enc '["enc-"] c ByteString
to "Enc '["r-ASCII"] c ByteString
and then to "Enc '["r-ASCII"] c Text
,
which could result in runtime errors.
The requirement is that that the decoding in the superset can replace the decoding from injected subset.
IsSuperset bigger smaller
reads as bigger
is a superset of smaller
Since: 0.2.2.0
IsSuperset "r-ASCII" "r-ASCII" = True | |
IsSuperset "r-UTF8" "r-ASCII" = True | |
IsSuperset "r-UTF8" "r-UTF8" = True | |
IsSuperset y x = IsSupersetOpen y (TakeUntil x ":") (ToList x) |
type family IsSupersetOpen (y :: Symbol) (x :: Symbol) (xs :: [Symbol]) :: Bool Source #
Since: 0.2.2.0
Instances
type IsSupersetOpen "r-ASCII" "r-ban" xs Source # | |
injectInto :: forall y x xs c str. IsSuperset y x ~ True => Enc (x ': xs) c str -> Enc (y ': xs) c str Source #
>>>
let Right tstAscii = encodeFAll . toEncoding () $ "Hello World" :: Either EncodeEx (Enc '["r-ASCII"] () T.Text)
>>>
displ (injectInto @ "r-UTF8" tstAscii)
"Enc '[r-UTF8] () (Text Hello World)"
Since: 0.2.2.0
class EncodingSuperset (enc :: Symbol) where Source #
IsSuperset is not intended for "enc-"
encodings. This class is.
It allows to specify constraints that say, for example, that Base 64 encodes into a subset of ASCII.
Since: 0.3.0.0
Nothing
type EncSuperset enc :: Symbol Source #
implEncInto :: forall xs c str. Enc (enc ': xs) c str -> Enc (EncSuperset enc ': (enc ': xs)) c str Source #
Warning: Using this method at the call site may not be backward compatible between minor version upgrades, use _encodesInto instead.
Instances
EncodingSuperset "enc-B64" Source # | This is not precise, actually Base 64 uses a subset of ASCII
and that would require a new definition This instance likely to be changed / corrected in the future if
Since: 0.3.0.0 |
Defined in Data.TypedEncoding.Instances.Enc.Base64 type EncSuperset "enc-B64" :: Symbol Source # implEncInto :: Enc ("enc-B64" ': xs) c str -> Enc (EncSuperset "enc-B64" ': ("enc-B64" ': xs)) c str Source # |
_encodesInto :: forall y enc xs c str r. (IsSuperset y r ~ True, EncodingSuperset enc, r ~ EncSuperset enc) => Enc (enc ': xs) c str -> Enc (y ': (enc ': xs)) c str Source #