{-# LANGUAGE CPP #-}
{-# LANGUAGE MagicHash #-}
module TextShow.Utils (
coerce
, i2d
, isInfixDataCon
, isSymVar
, isTupleString
, lengthB
, toString
, toText
, unlinesB
, unwordsB
) where
import Data.Int (Int64)
import Data.Text (Text)
import Data.Text.Lazy (length, toStrict, unpack)
import Data.Text.Lazy.Builder (Builder, singleton, toLazyText)
import GHC.Exts (Char(C#), Int(I#), (+#), chr#, ord#)
import Prelude ()
import Prelude.Compat hiding (length)
#if __GLASGOW_HASKELL__ >= 708
import qualified Data.Coerce as C (Coercible, coerce)
#else
import Unsafe.Coerce (unsafeCoerce)
#endif
#if defined(MIN_VERSION_ghc_boot_th)
import GHC.Lexeme (startsVarSym)
#else
import Data.Char (isSymbol, ord)
#endif
#if __GLASGOW_HASKELL__ >= 708
coerce :: C.Coercible a b => a -> b
coerce = C.coerce
#else
coerce :: a -> b
coerce = unsafeCoerce
#endif
i2d :: Int -> Char
i2d (I# i#) = C# (chr# (ord# '0'# +# i#))
{-# INLINE i2d #-}
isInfixDataCon :: String -> Bool
isInfixDataCon (':':_) = True
isInfixDataCon _ = False
{-# INLINE isInfixDataCon #-}
isSymVar :: String -> Bool
isSymVar "" = False
isSymVar (c : _) = startsVarSym c
#if !defined(MIN_VERSION_ghc_boot_th)
startsVarSym :: Char -> Bool
startsVarSym c = startsVarSymASCII c || (ord c > 0x7f && isSymbol c)
startsVarSymASCII :: Char -> Bool
startsVarSymASCII c = c `elem` "!#$%&*+./<=>?@\\^|~-"
#endif
isTupleString :: String -> Bool
isTupleString ('(':',':_) = True
isTupleString _ = False
{-# INLINE isTupleString #-}
lengthB :: Builder -> Int64
lengthB = length . toLazyText
{-# INLINE lengthB #-}
toString :: Builder -> String
toString = unpack . toLazyText
{-# INLINE toString #-}
toText :: Builder -> Text
toText = toStrict . toLazyText
{-# INLINE toText #-}
unlinesB :: [Builder] -> Builder
unlinesB (b:bs) = b <> singleton '\n' <> unlinesB bs
unlinesB [] = mempty
unwordsB :: [Builder] -> Builder
unwordsB (b:bs@(_:_)) = b <> singleton ' ' <> unwordsB bs
unwordsB [b] = b
unwordsB [] = mempty