Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
'UTF-8' encoding with additional assumption of conforming to Unicode.D76.
"r-UTF-8"
basically defines restriction on ByteString
that is needed for
conversion to Text
to work.
Since: 0.1.0.0
Synopsis
- prxyUtf8 :: Proxy "r-UTF8"
- encUTF8B :: Encoding (Either EncodeEx) "r-UTF8" "r-UTF8" c ByteString
- encUTF8BL :: Encoding (Either EncodeEx) "r-UTF8" "r-UTF8" c ByteString
- verEncoding :: ByteString -> Either err ByteString -> Bool
- implVerifyR :: (a -> Either err b) -> a -> Either err a
Documentation
>>>
:set -XScopedTypeVariables -XKindSignatures -XMultiParamTypeClasses -XDataKinds -XPolyKinds -XPartialTypeSignatures -XFlexibleInstances -XTypeApplications
>>>
import Test.QuickCheck
>>>
import Test.QuickCheck.Instances.Text()
>>>
import Test.QuickCheck.Instances.ByteString()
>>>
import Data.TypedEncoding
>>>
import Data.TypedEncoding.Internal.Util (proxiedId)
>>>
let emptyUTF8B = unsafeSetPayload () "" :: Enc '["r-UTF8"] () B.ByteString
>>>
:{
instance Arbitrary (Enc '["r-UTF8"] () B.ByteString) where arbitrary = fmap (fromRight emptyUTF8B) . flip suchThat isRight . fmap (encodeFAll @'["r-UTF8"] @(Either EncodeEx) @(). toEncoding ()) $ arbitrary :}
Decoding
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
implVerifyR :: (a -> Either err b) -> a -> Either err a Source #
private implementation helper
Orphan instances
(RecreateErr f, Applicative f) => Validate f "r-UTF8" "r-UTF8" c ByteString Source # | |
validation :: Validation f "r-UTF8" "r-UTF8" c ByteString Source # | |
(RecreateErr f, Applicative f) => Validate f "r-UTF8" "r-UTF8" c ByteString Source # | |
validation :: Validation f "r-UTF8" "r-UTF8" c ByteString Source # | |
Applicative f => Decode f "r-UTF8" "r-UTF8" c str Source # | |
Encode (Either EncodeEx) "r-UTF8" "r-UTF8" c ByteString Source # | |
Encode (Either EncodeEx) "r-UTF8" "r-UTF8" c ByteString Source # | UTF8 encodings are defined for ByteString only as that would not make much sense for Text
Following test uses
|