Safe Haskell | None |
---|---|
Language | Haskell2010 |
Warning: Not optimized for performance
There seems to be no easy ways to verify encoding using the encoding package.
decode functions implemented in encoding are very forgiving and work on invalid encoded inputs. This forces this package to resort to checking that
Encoding.encodeXyz . Encoding.decodeXyz
acts as the identity. This is obviously quite expensive.
This module provides such implementation and hence the warning.
>>>
Encoding.decodeStrictByteStringExplicit EncUTF8.UTF8 "\192\NUL"
Right "\NUL"
>>>
Encoding.encodeStrictByteStringExplicit EncUTF8.UTF8 "\NUL"
Right "\NUL"
Synopsis
- data DecodeOrEncodeException
- validatingDecS :: forall s c. (DynEnc s, Algorithm s "enc-pkg/encoding") => Decoding (Either UnexpectedDecodeEx) s "enc-pkg/encoding" c String
- verifyDynDec :: forall s str err1 err2 enc a. (KnownSymbol s, Show err1, Show err2) => Proxy s -> (Proxy s -> Either err1 enc) -> (enc -> str -> Either err2 str) -> str -> Either UnexpectedDecodeEx str
Documentation
>>>
:set -XOverloadedStrings -XDataKinds -XTypeApplications -XFlexibleContexts
>>>
import Data.Functor.Identity
>>>
import qualified Data.TypedEncoding as Usage
>>>
import Data.Encoding.UTF8 as EncUTF8
Validation Combinators (Slow)
data DecodeOrEncodeException Source #
Instances
validatingDecS :: forall s c. (DynEnc s, Algorithm s "enc-pkg/encoding") => Decoding (Either UnexpectedDecodeEx) s "enc-pkg/encoding" c String Source #
:: (KnownSymbol s, Show err1, Show err2) | |
=> Proxy s | proxy defining encoding annotation |
-> (Proxy s -> Either err1 enc) | finds encoding marker |
-> (enc -> str -> Either err2 str) | decoder based on |
-> str | |
-> Either UnexpectedDecodeEx str |
Orphan instances
(KnownSymbol s, DynEnc s, Algorithm s "enc-pkg/encoding", RecreateErr f, Applicative f) => Validate f s "enc-pkg/encoding" c String Source # |
|
validation :: Validation f s "enc-pkg/encoding" c String # |