typed-encoding-encoding-0.1.0.0: Bridge between encoding and typed-encoding packages

Safe HaskellNone
LanguageHaskell2010

Data.TypedEncoding.Pkg.Encoding.Warn.Instances

Contents

Description

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

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)

validatingDecS :: forall s c. (DynEnc s, Algorithm s "enc-pkg/encoding") => Decoding (Either UnexpectedDecodeEx) s "enc-pkg/encoding" c String Source #

verifyDynDec Source #

Arguments

:: (KnownSymbol s, Show err1, Show err2) 
=> Proxy s

proxy defining encoding annotation

-> (Proxy s -> Either err1 enc)

finds encoding marker enc for given annotation or fails

-> (enc -> str -> Either err2 str)

decoder based on enc marker

-> 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 #
>>> :{
 fmap Usage.displ .
  Usage.recreateFAll' 
   @'["enc-pkg/encoding"] 
   @'["enc-pkg/encoding:greek"] 
   @(Either Usage.RecreateEx) 
   @() 
   @String . Usage.toEncoding () $ "\193\226\208\226\236\255"
:}
Left (RecreateEx "enc-pkg/encoding:greek" (DecErr (IllegalCharacter 255)))

"Статья" example:

>>> :{
fmap Usage.displ .
  Usage.recreateFAll' 
  @'["enc-pkg/encoding"] 
  @'["enc-pkg/encoding:cyrillic"] 
  @(Either Usage.RecreateEx) 
  @() 
  @String . Usage.toEncoding () $ "\193\226\208\226\236\239"
:}
Right "Enc '[enc-pkg/encoding:cyrillic] () (String \193\226\208\226\236\239)"
Instance details

Methods

validation :: Validation f s "enc-pkg/encoding" c String #