Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Synopsis
- emptyUTF8B :: c -> Enc '["r-UTF8"] c ByteString
- text2ByteStringS :: Enc ys c Text -> Enc ("r-UTF8" ': ys) c ByteString
- byteString2TextS :: Enc ("r-UTF8" ': ys) c ByteString -> Enc ys c Text
- txtBsSIdProp :: Proxy (ys :: [Symbol]) -> Enc ys c Text -> Enc ys c Text
- bsTxtIdProp :: Proxy (ys :: [Symbol]) -> Enc ("r-UTF8" ': ys) c ByteString -> Enc ("r-UTF8" ': ys) c ByteString
- text2ByteStringL :: Enc ys c Text -> Enc ("r-UTF8" ': ys) c ByteString
- byteString2TextL :: Enc ("r-UTF8" ': ys) c ByteString -> Enc ys c Text
- prxyUtf8 :: Proxy "r-UTF8"
- verEncoding :: ByteString -> Either err ByteString -> Bool
Documentation
>>>
:set -XScopedTypeVariables -XKindSignatures -XMultiParamTypeClasses -XDataKinds -XPolyKinds -XPartialTypeSignatures -XFlexibleInstances
>>>
import Test.QuickCheck
>>>
import Test.QuickCheck.Instances.Text()
>>>
import Test.QuickCheck.Instances.ByteString()
>>>
import Data.TypedEncoding.Internal.Utils (proxiedId)
>>>
let prxyArb = Proxy :: Proxy (Either EncodeEx (Enc '["r-UTF8"] () B.ByteString))
>>>
:{
>>>
instance Arbitrary (Enc '["r-UTF8"] () B.ByteString) where
arbitrary = fmap (fromRight (emptyUTF8B ())) . flip suchThat isRight . fmap (proxiedId prxyArb . encodeFAll . toEncoding ()) $ arbitrary :}
emptyUTF8B :: c -> Enc '["r-UTF8"] c ByteString Source #
empty string is valid utf8
text2ByteStringS :: Enc ys c Text -> Enc ("r-UTF8" ': ys) c ByteString Source #
Type-safer version of Data.Text.Encoding.encodeUtf8
>>>
displ $ text2ByteStringS $ toEncoding () ("text" :: T.Text)
"MkEnc '[r-UTF8] () (ByteString text)"
byteString2TextS :: Enc ("r-UTF8" ': ys) c ByteString -> Enc ys c Text Source #
Type-safer version of Data.Text.Encoding.decodeUtf8
>>>
let Right tst = encodeFAll . toEncoding () $ "Hello World" :: Either EncodeEx (Enc '["r-UTF8"] () B.ByteString)
>>>
displ $ byteString2TextS tst
"MkEnc '[] () (Text Hello World)"
txtBsSIdProp :: Proxy (ys :: [Symbol]) -> Enc ys c Text -> Enc ys c Text Source #
Identity property "byteString2TextS . text2ByteStringS == id" prop> t -> t == (fromEncoding . txtBsSIdProp (Proxy :: Proxy '[]) . toEncoding () $ t)
bsTxtIdProp :: Proxy (ys :: [Symbol]) -> Enc ("r-UTF8" ': ys) c ByteString -> Enc ("r-UTF8" ': ys) c ByteString Source #
Identity property "text2ByteStringS . byteString2TextS == id".
\(t :: Enc '["r-UTF8"] () B.ByteString) -> t == (bsTxtIdProp (Proxy :: Proxy '[]) $ t)
text2ByteStringL :: Enc ys c Text -> Enc ("r-UTF8" ': ys) c ByteString Source #
byteString2TextL :: Enc ("r-UTF8" ': ys) c ByteString -> Enc ys c Text Source #
verEncoding :: ByteString -> Either err ByteString -> Bool Source #
helper function checks that given ByteString, if is encoded as Left is must be not Utf8 decodable is is encoded as Right is must be Utf8 encodable
Orphan instances
(RecreateErr f, Applicative f) => RecreateF (f :: Type -> Type) (Enc xs c ByteString :: Type) (Enc ("r-UTF8" ': xs) c ByteString) Source # | |
checkPrevF :: Enc ("r-UTF8" ': xs) c ByteString -> f (Enc xs c ByteString) Source # | |
(RecreateErr f, Applicative f) => RecreateF (f :: Type -> Type) (Enc xs c ByteString :: Type) (Enc ("r-UTF8" ': xs) c ByteString) Source # | |
checkPrevF :: Enc ("r-UTF8" ': xs) c ByteString -> f (Enc xs c ByteString) Source # | |
Applicative f => DecodeF (f :: Type -> Type) (Enc ("r-UTF8" ': xs) c ByteString) (Enc xs c ByteString :: Type) Source # | |
decodeF :: Enc ("r-UTF8" ': xs) c ByteString -> f (Enc xs c ByteString) Source # | |
Applicative f => DecodeF (f :: Type -> Type) (Enc ("r-UTF8" ': xs) c ByteString) (Enc xs c ByteString :: Type) Source # | |
decodeF :: Enc ("r-UTF8" ': xs) c ByteString -> f (Enc xs c ByteString) Source # | |
EncodeF (Either EncodeEx) (Enc xs c ByteString) (Enc ("r-UTF8" ': xs) c ByteString :: Type) Source # | |
encodeF :: Enc xs c ByteString -> Either EncodeEx (Enc ("r-UTF8" ': xs) c ByteString) Source # | |
EncodeF (Either EncodeEx) (Enc xs c ByteString) (Enc ("r-UTF8" ': xs) c ByteString :: Type) Source # | UTF8 encodings are defined for ByteString only as that would not make much sense for Text
Following test uses \(b :: B.ByteString) -> verEncoding b (fmap (fromEncoding . decodeAll . proxiedId (Proxy :: Proxy (Enc '["r-UTF8"] _ _))) . (encodeFAll :: _ -> Either EncodeEx _). toEncoding () $ b) |
encodeF :: Enc xs c ByteString -> Either EncodeEx (Enc ("r-UTF8" ': xs) c ByteString) Source # |