module TextShow.Utils (
i2d
, isInfixTypeCon
, isTupleString
, lengthB
, mtimesDefault
, toString
, toText
, unlinesB
, unwordsB
) where
import Data.Int (Int64)
import Data.Text (Text)
import Data.Monoid.Compat ((<>))
#if MIN_VERSION_semigroups(0,17,0)
import Data.Semigroup (mtimesDefault)
#else
import Data.Semigroup (timesN)
#endif
import Data.Text.Lazy (length, toStrict, unpack)
import Data.Text.Lazy.Builder (Builder, singleton, toLazyText)
import GHC.Exts (Char(C#), Int(I#))
import GHC.Prim ((+#), chr#, ord#)
import Prelude ()
import Prelude.Compat hiding (length)
i2d :: Int -> Char
i2d (I# i#) = C# (chr# (ord# '0'# +# i#))
isInfixTypeCon :: String -> Bool
isInfixTypeCon (':':_) = True
isInfixTypeCon _ = False
isTupleString :: String -> Bool
isTupleString ('(':',':_) = True
isTupleString _ = False
lengthB :: Builder -> Int64
lengthB = length . toLazyText
#if !(MIN_VERSION_semigroups(0,17,0))
mtimesDefault :: (Integral b, Monoid a) => b -> a -> a
mtimesDefault = timesN . fromIntegral
#endif
toString :: Builder -> String
toString = unpack . toLazyText
toText :: Builder -> Text
toText = toStrict . toLazyText
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