typed-encoding-0.2.0.0: Type safe string transformations

Safe HaskellSafe
LanguageHaskell2010

Data.TypedEncoding.Instances.Restriction.ASCII

Contents

Description

Strings can move to 'Enc "r-ASCII' only if they contain only ascii characters. they always decode back >>> :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

byteString2TextS :: Enc ("r-ASCII" ': ys) c ByteString -> Enc ("r-ASCII" ': ys) c Text Source #

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 #

text2ByteStringL :: Enc ("r-ASCII" ': ys) c Text -> Enc ("r-ASCII" ': ys) c ByteString Source #

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

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

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