-- | Provides universal conversions between any two string-like types. -- Out-of-the-box, @Text@ (both lazy and strict), @ByteString@ (both lazy and -- strict), and String, are supported. -- -- To hook custom string types into the conversion mechanism, implement both -- @IsString@ and @ToString@ for your type. {-#LANGUAGE FlexibleInstances #-} module Text.StringConvert ( IsString , fromString , ToString , toString , s ) where import qualified Data.Text as Text import qualified Data.Text.Lazy as LText import qualified Data.ByteString.UTF8 as UTF8 import qualified Data.ByteString.Lazy.UTF8 as LUTF8 import qualified Data.ByteString.Lazy as LBS import Data.String (IsString (..)) -- | Defines how a given type should be converted to String. -- If at all possible, the conversion should be loss-less, and if encodings are -- involved, UTF-8 should be the default. class ToString a where toString :: a -> String instance ToString [Char] where toString = id instance ToString LText.Text where toString = LText.unpack instance ToString Text.Text where toString = Text.unpack instance ToString UTF8.ByteString where toString = UTF8.toString instance ToString LUTF8.ByteString where toString = LUTF8.toString -- if the conversion is a no-op, rewrite it as id {-# RULES "s/same-type" s = id #-} -- conversions between strict and lazy texts can be done directly {-# RULES "s/LText->Text" s = LText.toStrict #-} {-# RULES "s/Text->LText" s = LText.fromStrict #-} -- conversions between strict and lazy bytestrings can be done directly {-# RULES "s/LBS->BS" s = LBS.toStrict #-} {-# RULES "s/BS->LBS" s = LBS.fromStrict #-} -- conversions to and from string can be done through the ToString / IsString -- classes {-# RULES "s/->String" s = toString #-} {-# RULES "s/String->" s = fromString #-} {-# NOINLINE s #-} s :: (ToString a, IsString b) => a -> b s = fromString . toString