typed-encoding-0.2.2.0: Type safe string transformations

Safe HaskellSafe
LanguageHaskell2010

Data.TypedEncoding.Instances.Restriction.ASCII

Contents

Description

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

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 #

DEPRECATED use decodeUtf8

Will be removed in 0.3.x.x

see byteString2TextS

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

prxyAscii :: Proxy "r-ASCII" Source #

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 ASCII only strings are encoded to UTF8 in types like ByteString.

>>> let Right tstAscii = encodeFAll . toEncoding () $ "Hello World" :: Either EncodeEx (Enc '["r-ASCII"] () T.Text)
>>> displ (inject @ "r-UTF8" tstAscii)
"MkEnc '[r-UTF8] () (Text Hello World)"
Instance details

Methods

inject :: Enc ("r-ASCII" ': xs) c str -> Enc ("r-UTF8" ': xs) c str Source #

(RecreateErr f, Applicative f) => RecreateF (f :: Type -> Type) (Enc xs c ByteString :: Type) (Enc ("r-ASCII" ': xs) c ByteString) Source # 
Instance details

Methods

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 # 
Instance details

Methods

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 # 
Instance details

Methods

checkPrevF :: Enc ("r-ASCII" ': xs) c Text -> f (Enc xs c Text) Source #

(RecreateErr f, Applicative f) => RecreateF (f :: Type -> Type) (Enc xs c Text :: Type) (Enc ("r-ASCII" ': xs) c Text) Source # 
Instance details

Methods

checkPrevF :: Enc ("r-ASCII" ': xs) c Text -> f (Enc xs c Text) Source #

(RecreateErr f, Applicative f) => RecreateF (f :: Type -> Type) (Enc xs c String :: Type) (Enc ("r-ASCII" ': xs) c String) Source # 
Instance details

Methods

checkPrevF :: Enc ("r-ASCII" ': xs) c String -> f (Enc xs c String) Source #

Applicative f => DecodeF (f :: Type -> Type) (Enc ("r-ASCII" ': xs) c ByteString) (Enc xs c ByteString :: Type) Source # 
Instance details

Methods

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 # 
Instance details

Methods

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 # 
Instance details

Methods

decodeF :: Enc ("r-ASCII" ': xs) c Text -> f (Enc xs c Text) Source #

Applicative f => DecodeF (f :: Type -> Type) (Enc ("r-ASCII" ': xs) c Text) (Enc xs c Text :: Type) Source # 
Instance details

Methods

decodeF :: Enc ("r-ASCII" ': xs) c Text -> f (Enc xs c Text) Source #

Applicative f => DecodeF (f :: Type -> Type) (Enc ("r-ASCII" ': xs) c String) (Enc xs c String :: Type) Source # 
Instance details

Methods

decodeF :: Enc ("r-ASCII" ': xs) c String -> f (Enc xs c String) Source #

Applicative f => DecodeF (f :: Type -> Type) (Enc ("r-ASCII" ': xs) c Char) (Enc xs c Char :: Type) Source # 
Instance details

Methods

decodeF :: Enc ("r-ASCII" ': xs) c Char -> f (Enc xs c Char) Source #

EncodeF (Either EncodeEx) (Enc xs c ByteString) (Enc ("r-ASCII" ': xs) c ByteString :: Type) Source # 
Instance details

Methods

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 # 
Instance details

Methods

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 # 
Instance details

Methods

encodeF :: Enc xs c Text -> Either EncodeEx (Enc ("r-ASCII" ': xs) c Text) Source #

EncodeF (Either EncodeEx) (Enc xs c Text) (Enc ("r-ASCII" ': xs) c Text :: Type) Source # 
Instance details

Methods

encodeF :: Enc xs c Text -> Either EncodeEx (Enc ("r-ASCII" ': xs) c Text) Source #

EncodeF (Either EncodeEx) (Enc xs c String) (Enc ("r-ASCII" ': xs) c String :: Type) Source # 
Instance details

Methods

encodeF :: Enc xs c String -> Either EncodeEx (Enc ("r-ASCII" ': xs) c String) Source #

EncodeF (Either EncodeEx) (Enc xs c Char) (Enc ("r-ASCII" ': xs) c Char :: Type) Source # 
Instance details

Methods

encodeF :: Enc xs c Char -> Either EncodeEx (Enc ("r-ASCII" ': xs) c Char) Source #

Encodings (Either EncodeEx) xs grps c ByteString => Encodings (Either EncodeEx) ("r-ASCII" ': xs) ("r-ASCII" ': grps) c ByteString Source # 
Instance details

Methods

encodings :: Encoder (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 # 
Instance details

Methods

encodings :: Encoder (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 # 
Instance details

Methods

encodings :: Encoder (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 # 
Instance details

Methods

encodings :: Encoder (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 # 
Instance details

Methods

encodings :: Encoder (Either EncodeEx) ("r-ASCII" ': xs) ("r-ASCII" ': grps) c String Source #