{-# LANGUAGE CPP #-}
{-# LANGUAGE ExplicitForAll #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeSynonymInstances #-}
module Relude.String.Conversion
(
LText
, LByteString
, ConvertUtf8 (..)
, ToString (..)
, ToLText (..)
, ToText (..)
, LazyStrict (..)
, fromLazy
, fromStrict
, readEither
, show
) where
import Data.Bifunctor (first)
import Data.Either (Either)
import Data.Function (id, (.))
import Data.String (String)
import Relude.Functor ((<$>))
import Relude.String.Reexport (ByteString, IsString, Read, Text, fromString)
import qualified Data.ByteString as B
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 Text.Read (readEither)
import qualified GHC.Show as Show (Show (show))
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 B.ByteString where
encodeUtf8 = T.encodeUtf8 . T.pack
decodeUtf8 = T.unpack . T.decodeUtf8
decodeUtf8Strict = (T.unpack <$>) . decodeUtf8Strict
instance ConvertUtf8 T.Text B.ByteString where
encodeUtf8 = T.encodeUtf8
decodeUtf8 = T.decodeUtf8With T.lenientDecode
decodeUtf8Strict = T.decodeUtf8'
instance ConvertUtf8 LT.Text B.ByteString where
encodeUtf8 = LB.toStrict . encodeUtf8
decodeUtf8 = LT.decodeUtf8With T.lenientDecode . LB.fromStrict
decodeUtf8Strict = decodeUtf8Strict . LB.fromStrict
instance ConvertUtf8 String LB.ByteString where
encodeUtf8 = LT.encodeUtf8 . LT.pack
decodeUtf8 = LT.unpack . LT.decodeUtf8
decodeUtf8Strict = (T.unpack <$>) . decodeUtf8Strict
instance ConvertUtf8 T.Text LB.ByteString where
encodeUtf8 = LB.fromStrict . T.encodeUtf8
decodeUtf8 = T.decodeUtf8With T.lenientDecode . LB.toStrict
decodeUtf8Strict = T.decodeUtf8' . LB.toStrict
instance ConvertUtf8 LT.Text LB.ByteString where
encodeUtf8 = LT.encodeUtf8
decodeUtf8 = LT.decodeUtf8With T.lenientDecode
decodeUtf8Strict = LT.decodeUtf8'
class ToText a where
toText :: a -> T.Text
instance ToText String where
toText = T.pack
instance ToText T.Text where
toText = id
instance ToText LT.Text where
toText = LT.toStrict
class ToLText a where
toLText :: a -> LT.Text
instance ToLText String where
toLText = LT.pack
instance ToLText T.Text where
toLText = LT.fromStrict
instance ToLText LT.Text where
toLText = id
class ToString a where
toString :: a -> String
instance ToString String where
toString = id
instance ToString T.Text where
toString = T.unpack
instance ToString LT.Text where
toString = LT.unpack
readEither :: (ToString a, Read b) => a -> Either Text b
readEither = first toText . Text.Read.readEither . toString
show :: forall b a . (Show.Show a, IsString b) => a -> b
show x = fromString (Show.show x)
{-# 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 = LB.fromStrict
{-# INLINE toLazy #-}
toStrict = LB.toStrict
{-# INLINE toStrict #-}
instance LazyStrict LText Text where
toLazy = LT.fromStrict
{-# INLINE toLazy #-}
toStrict = LT.toStrict
{-# INLINE toStrict #-}