Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
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'))
Documentation
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 #
data NonAsciiChar Source #
Instances
Eq NonAsciiChar Source # | |
Defined in Data.TypedEncoding.Instances.ASCII (==) :: NonAsciiChar -> NonAsciiChar -> Bool # (/=) :: NonAsciiChar -> NonAsciiChar -> Bool # | |
Show NonAsciiChar Source # | |
Defined in Data.TypedEncoding.Instances.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
Subset "r-ASCII" "r-UTF8" Source # | allow to treat ASCII encodings as UTF8 forgetting about B64 encoding
|
(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 # | |
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 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 Char) (Enc ("r-ASCII" ': xs) c Char :: Type) Source # | |