{-# LANGUAGE CPP, DeriveDataTypeable #-}
{-# LANGUAGE Safe #-}
module Data.Text.Encoding.Error
(
UnicodeException(..)
, OnError
, OnDecodeError
, OnEncodeError
, lenientDecode
, strictDecode
, strictEncode
, ignore
, replace
) where
import Control.DeepSeq (NFData (..))
import Control.Exception (Exception, throw)
import Data.Typeable (Typeable)
import Data.Word (Word8)
import Numeric (showHex)
type OnError a b = String -> Maybe a -> Maybe b
type OnDecodeError = OnError Word8 Char
{-# DEPRECATED OnEncodeError "This exception is never used in practice, and will be removed." #-}
type OnEncodeError = OnError Char Word8
data UnicodeException =
DecodeError String (Maybe Word8)
| EncodeError String (Maybe Char)
deriving (UnicodeException -> UnicodeException -> Bool
(UnicodeException -> UnicodeException -> Bool)
-> (UnicodeException -> UnicodeException -> Bool)
-> Eq UnicodeException
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UnicodeException -> UnicodeException -> Bool
$c/= :: UnicodeException -> UnicodeException -> Bool
== :: UnicodeException -> UnicodeException -> Bool
$c== :: UnicodeException -> UnicodeException -> Bool
Eq, Typeable)
{-# DEPRECATED EncodeError "This constructor is never used, and will be removed." #-}
showUnicodeException :: UnicodeException -> String
showUnicodeException :: UnicodeException -> String
showUnicodeException (DecodeError String
desc (Just Word8
w))
= String
"Cannot decode byte '\\x" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Word8 -> String -> String
forall a. (Integral a, Show a) => a -> String -> String
showHex Word8
w (String
"': " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
desc)
showUnicodeException (DecodeError String
desc Maybe Word8
Nothing)
= String
"Cannot decode input: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
desc
showUnicodeException (EncodeError String
desc (Just Char
c))
= String
"Cannot encode character '\\x" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String -> String
forall a. (Integral a, Show a) => a -> String -> String
showHex (Char -> Int
forall a. Enum a => a -> Int
fromEnum Char
c) (String
"': " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
desc)
showUnicodeException (EncodeError String
desc Maybe Char
Nothing)
= String
"Cannot encode input: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
desc
instance Show UnicodeException where
show :: UnicodeException -> String
show = UnicodeException -> String
showUnicodeException
instance Exception UnicodeException
instance NFData UnicodeException where
rnf :: UnicodeException -> ()
rnf (DecodeError String
desc Maybe Word8
w) = String -> ()
forall a. NFData a => a -> ()
rnf String
desc () -> () -> ()
`seq` Maybe Word8 -> ()
forall a. NFData a => a -> ()
rnf Maybe Word8
w () -> () -> ()
`seq` ()
rnf (EncodeError String
desc Maybe Char
c) = String -> ()
forall a. NFData a => a -> ()
rnf String
desc () -> () -> ()
`seq` Maybe Char -> ()
forall a. NFData a => a -> ()
rnf Maybe Char
c () -> () -> ()
`seq` ()
strictDecode :: OnDecodeError
strictDecode :: OnDecodeError
strictDecode String
desc Maybe Word8
c = UnicodeException -> Maybe Char
forall a e. Exception e => e -> a
throw (String -> Maybe Word8 -> UnicodeException
DecodeError String
desc Maybe Word8
c)
lenientDecode :: OnDecodeError
lenientDecode :: OnDecodeError
lenientDecode String
_ Maybe Word8
_ = Char -> Maybe Char
forall a. a -> Maybe a
Just Char
'\xfffd'
{-# DEPRECATED strictEncode "This function always throws an exception, and will be removed." #-}
strictEncode :: OnEncodeError
strictEncode :: OnEncodeError
strictEncode String
desc Maybe Char
c = UnicodeException -> Maybe Word8
forall a e. Exception e => e -> a
throw (String -> Maybe Char -> UnicodeException
EncodeError String
desc Maybe Char
c)
ignore :: OnError a b
ignore :: forall a b. OnError a b
ignore String
_ Maybe a
_ = Maybe b
forall a. Maybe a
Nothing
replace :: b -> OnError a b
replace :: forall b a. b -> OnError a b
replace b
c String
_ Maybe a
_ = b -> Maybe b
forall a. a -> Maybe a
Just b
c