Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
This module contains typeclasses and type families that are used by typed-encoding to define subset / superset relationships between different encodings.
This module is re-exported in Data.TypedEncoding and it is best not to import it directly.
Synopsis
- type family IsSuperset (y :: Symbol) (x :: Symbol) :: Bool where ...
- type family IsSupersetOpen (big :: Symbol) (nm :: Symbol) (alg :: Symbol) (nmltrs :: [Symbol]) :: Bool
- type Superset big small = IsSuperset big small ~ True
- injectInto :: forall y x xs c str. IsSuperset y x ~ True => Enc (x ': xs) c str -> Enc (y ': xs) c str
- propSuperset' :: forall algb algs b s str. (Superset b s, Eq str) => Encoding (Either EncodeEx) b algb () str -> Encoding (Either EncodeEx) s algs () str -> str -> Bool
- propSuperset_ :: forall b s str algb algs. (Superset b s, Eq str, AlgNm b ~ algb, AlgNm s ~ algs) => Encoding (Either EncodeEx) b algb () str -> Encoding (Either EncodeEx) s algs () str -> str -> Bool
- propSupersetCheck :: forall algb algs b s str. Eq str => Encoding (Either EncodeEx) b algb () str -> Encoding (Either EncodeEx) s algs () str -> str -> Bool
- 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
- propEncodesInto_ :: forall b r str algb algr. (EncodingSuperset b, r ~ EncSuperset b, Eq str, AlgNm b ~ algb, AlgNm r ~ algr) => Encoding (Either EncodeEx) b algb () str -> Encoding (Either EncodeEx) r algr () str -> str -> Bool
- propEncodesIntoCheck :: forall algb algr b r str. Eq str => Encoding (Either EncodeEx) b algb () str -> Encoding (Either EncodeEx) r algr () str -> str -> Bool
- propCompEncoding :: forall algb algr b r str. Encoding (Either EncodeEx) b algb () str -> Encoding (Either EncodeEx) r algr () str -> str -> Bool
- class AllEncodeInto (superset :: Symbol) (encnms :: [Symbol])
- tstChar8Encodable :: forall nms. AllEncodeInto "r-CHAR8" nms => String
- tstD76Encodable :: forall nms. AllEncodeInto "r-UNICODE.D76" nms => String
- tstUTF8Encodable :: forall nms. AllEncodeInto "r-UTF8" nms => String
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
Note, no IsSuperset "r-UNICODE.D76" "r-CHAR8" even though the numeric range of D76 includes all CHAR8 bytes. This is more nominal decision that prevents certain unwanted conversions from being possible.
This is not fully transitive to conserve compilation cost. @since 0.2.2.0
IsSuperset "r-B64" "r-B64" = True | |
IsSuperset "r-ASCII" "r-ASCII" = True | |
IsSuperset "r-ASCII" "r-B64" = True | |
IsSuperset "r-UNICODE.D76" "r-UNICODE.D76" = True | |
IsSuperset "r-UNICODE.D76" x = Or (IsSuperset "r-ASCII" x) (IsSupersetOpen "r-UNICODE.D76" x (TakeUntil x ":") (ToList x)) | |
IsSuperset "r-UTF8" "r-UTF8" = True | |
IsSuperset "r-UTF8" x = Or (IsSuperset "r-ASCII" x) (IsSupersetOpen "r-UTF8" x (TakeUntil x ":") (ToList x)) | |
IsSuperset "r-CHAR8" "r-ByteRep" = True | |
IsSuperset "r-CHAR8" x = Or (IsSuperset "r-ASCII" x) (IsSupersetOpen "r-CHAR8" x (TakeUntil x ":") (ToList x)) | |
IsSuperset y x = IsSupersetOpen y x (TakeUntil x ":") (ToList x) |
type family IsSupersetOpen (big :: Symbol) (nm :: Symbol) (alg :: Symbol) (nmltrs :: [Symbol]) :: Bool Source #
Since: 0.2.2.0
Instances
type IsSupersetOpen "r-ASCII" x "r-ban" xs Source # | |
type Superset big small = IsSuperset big small ~ True 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
propSuperset' :: forall algb algs b s str. (Superset b s, Eq str) => Encoding (Either EncodeEx) b algb () str -> Encoding (Either EncodeEx) s algs () str -> str -> Bool Source #
Deprecated: Use propSupersetCheck or propSuperset_
propSuperset_ :: forall b s str algb algs. (Superset b s, Eq str, AlgNm b ~ algb, AlgNm s ~ algs) => Encoding (Either EncodeEx) b algb () str -> Encoding (Either EncodeEx) s algs () str -> str -> Bool Source #
propSupersetCheck :: forall algb algs b s str. Eq str => Encoding (Either EncodeEx) b algb () str -> Encoding (Either EncodeEx) s algs () str -> str -> Bool Source #
Test for Supersets defined in this module
Actual tests in the project test suite.
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 # | |
EncodingSuperset "enc-B64-len" Source # |
|
Defined in Data.TypedEncoding.Instances.Enc.Base64 type EncSuperset "enc-B64-len" :: Symbol Source # implEncInto :: Enc ("enc-B64-len" ': xs) c str -> Enc (EncSuperset "enc-B64-len" ': ("enc-B64-len" ': 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 #
propEncodesInto_ :: forall b r str algb algr. (EncodingSuperset b, r ~ EncSuperset b, Eq str, AlgNm b ~ algb, AlgNm r ~ algr) => Encoding (Either EncodeEx) b algb () str -> Encoding (Either EncodeEx) r algr () str -> str -> Bool Source #
propEncodesIntoCheck :: forall algb algr b r str. Eq str => Encoding (Either EncodeEx) b algb () str -> Encoding (Either EncodeEx) r algr () str -> str -> Bool Source #
validates superset restriction
Actual tests are in the project test suite.
propCompEncoding :: forall algb algr b r str. Encoding (Either EncodeEx) b algb () str -> Encoding (Either EncodeEx) r algr () str -> str -> Bool Source #
Checks if first encoding exceptions less often than second (has bigger domain).
class AllEncodeInto (superset :: Symbol) (encnms :: [Symbol]) Source #
Aggregate version of EncodingSuperset
It is used to assure type safety of conversion functions in Data.TypedEncoding.Conv. This approach is not ideal since it produces an overly conservative restriction on encoding stack.
The issue is that this enforces restriction on the co-domain or each encoding and it does not take into account the fact that the domain is already restricted, e.g. it will prevent adding id transformation to the stack.
Since: 0.4.0.0
Instances
AllEncodeInto "r-CHAR8" ([] :: [Symbol]) Source # | |
Defined in Data.TypedEncoding.Common.Class.Superset | |
AllEncodeInto "r-UNICODE.D76" ([] :: [Symbol]) Source # | |
Defined in Data.TypedEncoding.Common.Class.Superset | |
AllEncodeInto "r-UTF8" ([] :: [Symbol]) Source # | |
Defined in Data.TypedEncoding.Common.Class.Superset | |
(AllEncodeInto "r-CHAR8" xs, IsSuperset "r-CHAR8" r ~ True, EncodingSuperset enc, r ~ EncSuperset enc) => AllEncodeInto "r-CHAR8" (enc ': xs) Source # | |
Defined in Data.TypedEncoding.Common.Class.Superset | |
(AllEncodeInto "r-UNICODE.D76" xs, IsSuperset "r-UNICODE.D76" r ~ True, EncodingSuperset enc, r ~ EncSuperset enc) => AllEncodeInto "r-UNICODE.D76" (enc ': xs) Source # | |
Defined in Data.TypedEncoding.Common.Class.Superset | |
(AllEncodeInto "r-UTF8" xs, IsSuperset "r-UTF8" r ~ True, EncodingSuperset enc, r ~ EncSuperset enc) => AllEncodeInto "r-UTF8" (enc ': xs) Source # | |
Defined in Data.TypedEncoding.Common.Class.Superset |
tstChar8Encodable :: forall nms. AllEncodeInto "r-CHAR8" nms => String Source #
tstD76Encodable :: forall nms. AllEncodeInto "r-UNICODE.D76" nms => String Source #
tstUTF8Encodable :: forall nms. AllEncodeInto "r-UTF8" nms => String Source #