{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE Safe #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE UndecidableInstances #-}
module Relude.String.Conversion
(
LText
, LByteString
, ConvertUtf8 (..)
, ToText (..)
, ToLText (..)
, ToString (..)
, LazyStrict (..)
, fromLazy
, fromStrict
, readEither
, show
) where
import GHC.TypeLits (ErrorMessage (..), Symbol, TypeError)
import Prelude (error)
import Relude.Base (Constraint, Type)
import Relude.Function (id, (.))
import Relude.Functor (first, (<$>))
import Relude.Monad.Reexport (Either)
import Relude.String.Reexport (ByteString, IsString, Read, ShortByteString, String, Text, fromShort,
fromString, toShort)
import qualified Data.ByteString.Lazy as LB
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import qualified Data.Text.Encoding.Error as T
import qualified Data.Text.Lazy as LT
import qualified Data.Text.Lazy.Encoding as LT
import qualified GHC.Show as Show (Show (show))
import qualified Text.Read (readEither)
type LText = LT.Text
type LByteString = LB.ByteString
class ConvertUtf8 a b where
encodeUtf8 :: a -> b
decodeUtf8 :: b -> a
decodeUtf8Strict :: b -> Either T.UnicodeException a
instance ConvertUtf8 String ByteString where
encodeUtf8 :: String -> ByteString
encodeUtf8 = T.encodeUtf8 . T.pack
{-# INLINE encodeUtf8 #-}
decodeUtf8 :: ByteString -> String
decodeUtf8 = T.unpack . T.decodeUtf8
{-# INLINE decodeUtf8 #-}
decodeUtf8Strict :: ByteString -> Either T.UnicodeException String
decodeUtf8Strict = (T.unpack <$>) . decodeUtf8Strict
{-# INLINE decodeUtf8Strict #-}
instance ConvertUtf8 Text ByteString where
encodeUtf8 :: Text -> ByteString
encodeUtf8 = T.encodeUtf8
{-# INLINE encodeUtf8 #-}
decodeUtf8 :: ByteString -> Text
decodeUtf8 = T.decodeUtf8With T.lenientDecode
{-# INLINE decodeUtf8 #-}
decodeUtf8Strict :: ByteString -> Either T.UnicodeException Text
decodeUtf8Strict = T.decodeUtf8'
{-# INLINE decodeUtf8Strict #-}
instance ConvertUtf8 LText ByteString where
encodeUtf8 :: LText -> ByteString
encodeUtf8 = LB.toStrict . encodeUtf8
{-# INLINE encodeUtf8 #-}
decodeUtf8 :: ByteString -> LText
decodeUtf8 = LT.decodeUtf8With T.lenientDecode . LB.fromStrict
{-# INLINE decodeUtf8 #-}
decodeUtf8Strict :: ByteString -> Either T.UnicodeException LText
decodeUtf8Strict = decodeUtf8Strict . LB.fromStrict
{-# INLINE decodeUtf8Strict #-}
instance ConvertUtf8 String LByteString where
encodeUtf8 :: String -> LByteString
encodeUtf8 = LT.encodeUtf8 . LT.pack
{-# INLINE encodeUtf8 #-}
decodeUtf8 :: LByteString -> String
decodeUtf8 = LT.unpack . LT.decodeUtf8
{-# INLINE decodeUtf8 #-}
decodeUtf8Strict :: LByteString -> Either T.UnicodeException String
decodeUtf8Strict = (T.unpack <$>) . decodeUtf8Strict
{-# INLINE decodeUtf8Strict #-}
instance ConvertUtf8 Text LByteString where
encodeUtf8 :: Text -> LByteString
encodeUtf8 = LB.fromStrict . T.encodeUtf8
{-# INLINE encodeUtf8 #-}
decodeUtf8 :: LByteString -> Text
decodeUtf8 = T.decodeUtf8With T.lenientDecode . LB.toStrict
{-# INLINE decodeUtf8 #-}
decodeUtf8Strict :: LByteString -> Either T.UnicodeException Text
decodeUtf8Strict = T.decodeUtf8' . LB.toStrict
{-# INLINE decodeUtf8Strict #-}
instance ConvertUtf8 LText LByteString where
encodeUtf8 :: LText -> LByteString
encodeUtf8 = LT.encodeUtf8
{-# INLINE encodeUtf8 #-}
decodeUtf8 :: LByteString -> LText
decodeUtf8 = LT.decodeUtf8With T.lenientDecode
{-# INLINE decodeUtf8 #-}
decodeUtf8Strict :: LByteString -> Either T.UnicodeException LText
decodeUtf8Strict = LT.decodeUtf8'
{-# INLINE decodeUtf8Strict #-}
instance ConvertUtf8 String ShortByteString where
encodeUtf8 :: String -> ShortByteString
encodeUtf8 = toShort . encodeUtf8
{-# INLINE encodeUtf8 #-}
decodeUtf8 :: ShortByteString -> String
decodeUtf8 = decodeUtf8 . fromShort
{-# INLINE decodeUtf8 #-}
decodeUtf8Strict :: ShortByteString -> Either T.UnicodeException String
decodeUtf8Strict = decodeUtf8Strict . fromShort
{-# INLINE decodeUtf8Strict #-}
instance ConvertUtf8 Text ShortByteString where
encodeUtf8 :: Text -> ShortByteString
encodeUtf8 = toShort . encodeUtf8
{-# INLINE encodeUtf8 #-}
decodeUtf8 :: ShortByteString -> Text
decodeUtf8 = decodeUtf8 . fromShort
{-# INLINE decodeUtf8 #-}
decodeUtf8Strict :: ShortByteString -> Either T.UnicodeException Text
decodeUtf8Strict = decodeUtf8Strict . fromShort
{-# INLINE decodeUtf8Strict #-}
instance ConvertUtf8 LText ShortByteString where
encodeUtf8 :: LText -> ShortByteString
encodeUtf8 = toShort . encodeUtf8
{-# INLINE encodeUtf8 #-}
decodeUtf8 :: ShortByteString -> LText
decodeUtf8 = decodeUtf8 . fromShort
{-# INLINE decodeUtf8 #-}
decodeUtf8Strict :: ShortByteString -> Either T.UnicodeException LText
decodeUtf8Strict = decodeUtf8Strict . fromShort
{-# INLINE decodeUtf8Strict #-}
class ToText a where
toText :: a -> Text
instance ToText String where
toText :: String -> Text
toText = T.pack
{-# INLINE toText #-}
instance ToText Text where
toText :: Text -> Text
toText = id
{-# INLINE toText #-}
instance ToText LText where
toText :: LText -> Text
toText = LT.toStrict
{-# INLINE toText #-}
instance EncodingError ToText "ByteString" "Text" => ToText ByteString where
toText :: ByteString -> Text
toText = error "Unreachable ByteString instance of ToText"
instance EncodingError ToText "LByteString" "Text" => ToText LByteString where
toText :: LByteString -> Text
toText = error "Unreachable LByteString instance of ToText"
instance EncodingError ToText "ShortByteString" "Text" => ToText ShortByteString where
toText :: ShortByteString -> Text
toText = error "Unreachable ShortByteString instance of ToText"
class ToLText a where
toLText :: a -> LText
instance ToLText String where
toLText :: String -> LText
toLText = LT.pack
{-# INLINE toLText #-}
instance ToLText Text where
toLText :: Text -> LText
toLText = LT.fromStrict
{-# INLINE toLText #-}
instance ToLText LT.Text where
toLText :: LText -> LText
toLText = id
{-# INLINE toLText #-}
instance EncodingError ToLText "ByteString" "LText" => ToLText ByteString where
toLText :: ByteString -> LText
toLText = error "Unreachable ByteString instance of ToLText"
instance EncodingError ToLText "LByteString" "LText" => ToLText LByteString where
toLText :: LByteString -> LText
toLText = error "Unreachable LByteString instance of ToLText"
instance EncodingError ToLText "ShortByteString" "LText" => ToLText ShortByteString where
toLText :: ShortByteString -> LText
toLText = error "Unreachable ShortByteString instance of ToLText"
class ToString a where
toString :: a -> String
instance ToString String where
toString :: String -> String
toString = id
{-# INLINE toString #-}
instance ToString Text where
toString :: Text -> String
toString = T.unpack
{-# INLINE toString #-}
instance ToString LText where
toString :: LText -> String
toString = LT.unpack
{-# INLINE toString #-}
instance EncodingError ToString "ByteString" "String" => ToString ByteString where
toString :: ByteString -> String
toString = error "Unreachable ByteString instance of ToString"
instance EncodingError ToString "LByteString" "String" => ToString LByteString where
toString :: LByteString -> String
toString = error "Unreachable LByteString instance of ToString"
instance EncodingError ToString "ShortByteString" "String" => ToString ShortByteString where
toString :: ShortByteString -> String
toString = error "Unreachable ShortByteString instance of ToString"
type family EncodingError
(c :: Type -> Constraint)
(from :: Symbol)
(to :: Symbol)
:: Constraint
where
EncodingError c from to = TypeError
( 'Text "Type '" ':<>: 'Text from ':<>: 'Text "' doesn't have instance of '"
':<>: 'ShowType c ':<>: 'Text "'."
':$$: 'Text "Use 'decodeUtf8' or 'decodeUtf8Strict' to convert from UTF-8:"
':$$: 'Text " decodeUtf8 :: " ':<>: 'Text from
':<>: 'Text " -> " ':<>: 'Text to
':$$: 'Text " decodeUtf8Strict :: " ':<>: 'Text from
':<>: 'Text " -> Either UnicodeException " ':<>: 'Text to
)
readEither :: (Read a) => String -> Either Text a
readEither = first toText . Text.Read.readEither
{-# INLINEABLE readEither #-}
show :: forall b a . (Show.Show a, IsString b) => a -> b
show x = fromString (Show.show x)
{-# INLINE show #-}
{-# SPECIALIZE show :: Show.Show a => a -> Text #-}
{-# SPECIALIZE show :: Show.Show a => a -> LText #-}
{-# SPECIALIZE show :: Show.Show a => a -> ByteString #-}
{-# SPECIALIZE show :: Show.Show a => a -> LByteString #-}
{-# SPECIALIZE show :: Show.Show a => a -> String #-}
class LazyStrict l s | l -> s, s -> l where
toLazy :: s -> l
toStrict :: l -> s
fromLazy :: LazyStrict l s => l -> s
fromLazy = toStrict
{-# INLINE fromLazy #-}
{-# SPECIALIZE fromLazy :: LByteString -> ByteString #-}
{-# SPECIALIZE fromLazy :: LText -> Text #-}
fromStrict :: LazyStrict l s => s -> l
fromStrict = toLazy
{-# INLINE fromStrict #-}
{-# SPECIALIZE fromStrict :: ByteString -> LByteString #-}
{-# SPECIALIZE fromStrict :: Text -> LText #-}
instance LazyStrict LByteString ByteString where
toLazy :: ByteString -> LByteString
toLazy = LB.fromStrict
{-# INLINE toLazy #-}
toStrict :: LByteString -> ByteString
toStrict = LB.toStrict
{-# INLINE toStrict #-}
instance LazyStrict LText Text where
toLazy :: Text -> LText
toLazy = LT.fromStrict
{-# INLINE toLazy #-}
toStrict :: LText -> Text
toStrict = LT.toStrict
{-# INLINE toStrict #-}