Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Strings can be encoded as 'Enc "r-ASCII"@ only if they contain only ASCII characters (first 128 characters of the Unicode character set).
This is sometimes referred to as ASCII-7 and future versions of type-encoding
may change "r-ASCII"
symbol annotation to reflect this.
B8.all ((< 128) . ord) . getPayload @ '["r-ASCII"] @() @B.ByteString
>>>
:set -XOverloadedStrings -XMultiParamTypeClasses -XDataKinds
>>>
encodeFAll . toEncoding () $ "Hello World" :: Either EncodeEx (Enc '["r-ASCII"] () T.Text)
Right (MkEnc Proxy () "Hello World")
>>>
encodeFAll . toEncoding () $ "\194\160" :: Either EncodeEx (Enc '["r-ASCII"] () T.Text)
Left (EncodeEx "r-ASCII" (NonAsciiChar '\194'))
Synopsis
- byteString2TextS :: Enc ("r-ASCII" ': ys) c ByteString -> Enc ("r-ASCII" ': ys) c Text
- byteString2TextL :: Enc ("r-ASCII" ': ys) c ByteString -> Enc ("r-ASCII" ': ys) c Text
- text2ByteStringS :: Enc ("r-ASCII" ': ys) c Text -> Enc ("r-ASCII" ': ys) c ByteString
- text2ByteStringL :: Enc ("r-ASCII" ': ys) c Text -> Enc ("r-ASCII" ': ys) c ByteString
- newtype NonAsciiChar = NonAsciiChar Char
- prxyAscii :: Proxy "r-ASCII"
- encodeImpl :: ((Char -> Bool) -> a -> (a, a)) -> (a -> Char) -> (a -> Bool) -> a -> Either NonAsciiChar a
Documentation
>>>
:set -XDataKinds -XTypeApplications
>>>
import Test.QuickCheck
>>>
import Test.QuickCheck.Instances.ByteString()
>>>
:{
instance Arbitrary (Enc '["r-ASCII"] () B.ByteString) where arbitrary = fmap (unsafeSetPayload ()) . flip suchThat (B8.all isAscii) $ arbitrary :}
byteString2TextS :: Enc ("r-ASCII" ': ys) c ByteString -> Enc ("r-ASCII" ': ys) c Text Source #
DEPRECATED use decodeUtf8
Will be removed in 0.3.x.x
This is not type safe, for example, would allow converting
Enc `["r-ASCII", "enc-B64"] c B.ByteString
containing B64 encoded binary
to Enc `["r-ASCII", "enc-B64"] c T.Text
and which then could be decoded causing
unexpected error.
byteString2TextL :: Enc ("r-ASCII" ': ys) c ByteString -> Enc ("r-ASCII" ': ys) c Text Source #
text2ByteStringS :: Enc ("r-ASCII" ': ys) c Text -> Enc ("r-ASCII" ': ys) c ByteString Source #
DEPRECATED use encodeUtf8
Will be removed in 0.3.x.x
text2ByteStringL :: Enc ("r-ASCII" ': ys) c Text -> Enc ("r-ASCII" ': ys) c ByteString Source #
DEPRECATED use encodeUtf8
Will be removed in 0.3.x.x
newtype NonAsciiChar Source #
Instances
Eq NonAsciiChar Source # | |
Defined in Data.TypedEncoding.Instances.Restriction.ASCII (==) :: NonAsciiChar -> NonAsciiChar -> Bool # (/=) :: NonAsciiChar -> NonAsciiChar -> Bool # | |
Show NonAsciiChar Source # | |
Defined in Data.TypedEncoding.Instances.Restriction.ASCII showsPrec :: Int -> NonAsciiChar -> ShowS # show :: NonAsciiChar -> String # showList :: [NonAsciiChar] -> ShowS # |
encodeImpl :: ((Char -> Bool) -> a -> (a, a)) -> (a -> Char) -> (a -> Bool) -> a -> Either NonAsciiChar a Source #
Orphan instances
Superset "r-UTF8" "r-ASCII" Source # | allow to treat ASCII encodings as UTF8 forgetting about B64 encoding UTF-8 is backward compatible on first 128 characters using just one byte to store it. Payload does not change when
|
(RecreateErr f, Applicative f) => RecreateF (f :: Type -> Type) (Enc xs c ByteString :: Type) (Enc ("r-ASCII" ': xs) c ByteString) Source # | |
checkPrevF :: Enc ("r-ASCII" ': xs) c ByteString -> f (Enc xs c ByteString) Source # | |
(RecreateErr f, Applicative f) => RecreateF (f :: Type -> Type) (Enc xs c ByteString :: Type) (Enc ("r-ASCII" ': xs) c ByteString) Source # | |
checkPrevF :: Enc ("r-ASCII" ': xs) c ByteString -> f (Enc xs c ByteString) Source # | |
(RecreateErr f, Applicative f) => RecreateF (f :: Type -> Type) (Enc xs c Text :: Type) (Enc ("r-ASCII" ': xs) c Text) Source # | |
(RecreateErr f, Applicative f) => RecreateF (f :: Type -> Type) (Enc xs c Text :: Type) (Enc ("r-ASCII" ': xs) c Text) Source # | |
(RecreateErr f, Applicative f) => RecreateF (f :: Type -> Type) (Enc xs c String :: Type) (Enc ("r-ASCII" ': xs) c String) Source # | |
Applicative f => DecodeF (f :: Type -> Type) (Enc ("r-ASCII" ': xs) c ByteString) (Enc xs c ByteString :: Type) Source # | |
decodeF :: Enc ("r-ASCII" ': xs) c ByteString -> f (Enc xs c ByteString) Source # | |
Applicative f => DecodeF (f :: Type -> Type) (Enc ("r-ASCII" ': xs) c ByteString) (Enc xs c ByteString :: Type) Source # | |
decodeF :: Enc ("r-ASCII" ': xs) c ByteString -> f (Enc xs c ByteString) Source # | |
Applicative f => DecodeF (f :: Type -> Type) (Enc ("r-ASCII" ': xs) c Text) (Enc xs c Text :: Type) Source # | |
Applicative f => DecodeF (f :: Type -> Type) (Enc ("r-ASCII" ': xs) c Text) (Enc xs c Text :: Type) Source # | |
Applicative f => DecodeF (f :: Type -> Type) (Enc ("r-ASCII" ': xs) c String) (Enc xs c String :: Type) Source # | |
Applicative f => DecodeF (f :: Type -> Type) (Enc ("r-ASCII" ': xs) c Char) (Enc xs c Char :: Type) Source # | |
EncodeF (Either EncodeEx) (Enc xs c ByteString) (Enc ("r-ASCII" ': xs) c ByteString :: Type) Source # | |
encodeF :: Enc xs c ByteString -> Either EncodeEx (Enc ("r-ASCII" ': xs) c ByteString) Source # | |
EncodeF (Either EncodeEx) (Enc xs c ByteString) (Enc ("r-ASCII" ': xs) c ByteString :: Type) Source # | |
encodeF :: Enc xs c ByteString -> Either EncodeEx (Enc ("r-ASCII" ': xs) c ByteString) Source # | |
EncodeF (Either EncodeEx) (Enc xs c Text) (Enc ("r-ASCII" ': xs) c Text :: Type) Source # | |
EncodeF (Either EncodeEx) (Enc xs c Text) (Enc ("r-ASCII" ': xs) c Text :: Type) Source # | |
EncodeF (Either EncodeEx) (Enc xs c String) (Enc ("r-ASCII" ': xs) c String :: Type) Source # | |
EncodeF (Either EncodeEx) (Enc xs c Char) (Enc ("r-ASCII" ': xs) c Char :: Type) Source # | |
Encodings (Either EncodeEx) xs grps c ByteString => Encodings (Either EncodeEx) ("r-ASCII" ': xs) ("r-ASCII" ': grps) c ByteString Source # | |
Encodings (Either EncodeEx) xs grps c ByteString => Encodings (Either EncodeEx) ("r-ASCII" ': xs) ("r-ASCII" ': grps) c ByteString Source # | |
Encodings (Either EncodeEx) xs grps c Text => Encodings (Either EncodeEx) ("r-ASCII" ': xs) ("r-ASCII" ': grps) c Text Source # | |
Encodings (Either EncodeEx) xs grps c Text => Encodings (Either EncodeEx) ("r-ASCII" ': xs) ("r-ASCII" ': grps) c Text Source # | |
Encodings (Either EncodeEx) xs grps c String => Encodings (Either EncodeEx) ("r-ASCII" ': xs) ("r-ASCII" ': grps) c String Source # | |