{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE Safe #-}

-- | Non-partial text conversion typeclass and functions.
-- For an alternative with partial conversions import 'Protolude.Conv'.
module Protolude.ConvertText (
  ConvertText (toS)
, toUtf8
, toUtf8Lazy
) where

import qualified Data.ByteString      as B
import qualified Data.ByteString.Lazy as LB
import qualified Data.Text            as T
import qualified Data.Text.Lazy       as LT

import Data.Function (id, (.))
import Data.String (String)
import Data.Text.Encoding (encodeUtf8)

-- | Convert from one Unicode textual type to another. Not for serialization/deserialization,
-- so doesn't have instances for bytestrings.
class ConvertText a b where
  toS :: a -> b

instance ConvertText String String where toS :: String -> String
toS = String -> String
forall a. a -> a
id
instance ConvertText String T.Text where toS :: String -> Text
toS = String -> Text
T.pack
instance ConvertText String LT.Text where toS :: String -> Text
toS = String -> Text
LT.pack

instance ConvertText T.Text String where toS :: Text -> String
toS = Text -> String
T.unpack
instance ConvertText T.Text LT.Text where toS :: Text -> Text
toS = Text -> Text
LT.fromStrict
instance ConvertText T.Text T.Text where toS :: Text -> Text
toS = Text -> Text
forall a. a -> a
id

instance ConvertText LT.Text String where toS :: Text -> String
toS = Text -> String
LT.unpack
instance ConvertText LT.Text T.Text where toS :: Text -> Text
toS = Text -> Text
LT.toStrict
instance ConvertText LT.Text LT.Text where toS :: Text -> Text
toS = Text -> Text
forall a. a -> a
id

instance ConvertText LB.ByteString B.ByteString where toS :: ByteString -> ByteString
toS = ByteString -> ByteString
LB.toStrict
instance ConvertText LB.ByteString LB.ByteString where toS :: ByteString -> ByteString
toS = ByteString -> ByteString
forall a. a -> a
id

instance ConvertText B.ByteString B.ByteString where toS :: ByteString -> ByteString
toS = ByteString -> ByteString
forall a. a -> a
id
instance ConvertText B.ByteString LB.ByteString where toS :: ByteString -> ByteString
toS = ByteString -> ByteString
LB.fromStrict

toUtf8 :: ConvertText a T.Text => a -> B.ByteString
toUtf8 :: a -> ByteString
toUtf8 =
  Text -> ByteString
encodeUtf8 (Text -> ByteString) -> (a -> Text) -> a -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Text
forall a b. ConvertText a b => a -> b
toS

toUtf8Lazy :: ConvertText a T.Text => a -> LB.ByteString
toUtf8Lazy :: a -> ByteString
toUtf8Lazy =
  ByteString -> ByteString
LB.fromStrict (ByteString -> ByteString) -> (a -> ByteString) -> a -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
encodeUtf8 (Text -> ByteString) -> (a -> Text) -> a -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Text
forall a b. ConvertText a b => a -> b
toS