#if MIN_VERSION_base(4,4,0)
#endif
#if __GLASGOW_HASKELL__ >= 708
#endif
module Text.Show.Text.Classes where
#if !(MIN_VERSION_base(4,8,0))
import Control.Applicative (Applicative((<*>), pure))
import Data.Foldable (Foldable)
import Data.Monoid (Monoid)
import Data.Traversable (Traversable)
#endif
import Control.Monad.Fix (MonadFix(..))
#if MIN_VERSION_base(4,4,0)
import Control.Monad.Zip (MonadZip(..))
#endif
import Data.Bits (Bits)
#if MIN_VERSION_base(4,7,0)
import Data.Bits (FiniteBits)
#endif
import Data.Data (Data, Typeable)
import Data.Functor ((<$>))
import Data.Ix (Ix)
import Data.Semigroup (Semigroup)
import Data.String (IsString)
import Data.Text as TS (Text)
import qualified Data.Text.IO as TS (putStrLn, hPutStrLn)
import qualified Data.Text.Lazy as TL (Text)
import qualified Data.Text.Lazy.IO as TL (putStrLn, hPutStrLn)
import Data.Text.Lazy (toStrict)
import Data.Text.Lazy.Builder (Builder, fromString, toLazyText)
import Foreign.Storable (Storable)
#if __GLASGOW_HASKELL__ >= 708
import GHC.Exts (IsList(Item, fromList, toList))
#endif
#if MIN_VERSION_base(4,4,0)
import GHC.Generics (Generic)
# if __GLASGOW_HASKELL__ >= 706
import GHC.Generics (Generic1)
# endif
#endif
import GHC.Show (appPrec, appPrec1)
import Prelude hiding (Show(show, showList))
import System.IO (Handle)
import Text.Printf (PrintfArg, PrintfType)
import Text.Read (Read(..), readListPrecDefault)
import qualified Text.Show as S (Show(showsPrec))
import Text.Show.Text.Utils ((<>), s, toString)
#include "inline.h"
class Show a where
showbPrec :: Int
-> a
-> Builder
showb :: a -> Builder
showbList :: [a] -> Builder
showbPrec _ = showb
showb = showbPrec 0
showbList = showbListDefault showb
#if __GLASGOW_HASKELL__ >= 708
#endif
class Show1 f where
showbPrec1 :: Show a => Int -> f a -> Builder
show :: Show a => a -> TS.Text
show = toStrict . showLazy
showLazy :: Show a => a -> TL.Text
showLazy = toLazyText . showb
showPrec :: Show a => Int -> a -> TS.Text
showPrec p = toStrict . showPrecLazy p
showPrecLazy :: Show a => Int -> a -> TL.Text
showPrecLazy p = toLazyText . showbPrec p
showList :: Show a => [a] -> TS.Text
showList = toStrict . showListLazy
showListLazy :: Show a => [a] -> TL.Text
showListLazy = toLazyText . showbList
showbParen :: Bool -> Builder -> Builder
showbParen p builder | p = s '(' <> builder <> s ')'
| otherwise = builder
showbSpace :: Builder
showbSpace = s ' '
showbListDefault :: (a -> Builder) -> [a] -> Builder
showbListDefault _ [] = "[]"
showbListDefault showbx (x:xs) = s '[' <> showbx x <> go xs
where
go (y:ys) = s ',' <> showbx y <> go ys
go [] = s ']'
showbUnary :: Show a => Builder -> Int -> a -> Builder
showbUnary nameB p x = showbParen (p > appPrec) $
nameB <> showbSpace <> showbPrec appPrec1 x
showbUnary1 :: (Show1 f, Show a) => Builder -> Int -> f a -> Builder
showbUnary1 nameB p x = showbParen (p > appPrec) $
nameB <> showbSpace <> showbPrec1 appPrec1 x
showbBinary1 :: (Show1 f, Show1 g, Show a) => Builder -> Int -> f a -> g a -> Builder
showbBinary1 nameB p x y = showbParen (p > appPrec) $ nameB
<> showbSpace <> showbPrec1 appPrec1 x
<> showbSpace <> showbPrec1 appPrec1 y
print :: Show a => a -> IO ()
print = TS.putStrLn . show
printLazy :: Show a => a -> IO ()
printLazy = TL.putStrLn . showLazy
hPrint :: Show a => Handle -> a -> IO ()
hPrint h = TS.hPutStrLn h . show
hPrintLazy :: Show a => Handle -> a -> IO ()
hPrintLazy h = TL.hPutStrLn h . showLazy
newtype FromStringShow a = FromStringShow { fromStringShow :: a }
deriving ( Bits
, Bounded
, Data
, Enum
, Eq
#if MIN_VERSION_base(4,7,0)
, FiniteBits
#endif
, Floating
, Foldable
, Fractional
, Functor
#if MIN_VERSION_base(4,4,0)
, Generic
# if __GLASGOW_HASKELL__ >= 706
, Generic1
# endif
#endif
, Integral
, IsString
, Ix
, Monoid
, Num
, Ord
, PrintfArg
, PrintfType
, Real
, RealFloat
, RealFrac
, Semigroup
, Storable
, Traversable
, Typeable
)
instance Applicative FromStringShow where
pure = FromStringShow
INLINE_INST_FUN(pure)
FromStringShow f <*> FromStringShow x = FromStringShow $ f x
INLINE_INST_FUN((<*>))
#if __GLASGOW_HASKELL__ >= 708
instance IsList a => IsList (FromStringShow a) where
type Item (FromStringShow a) = Item a
fromList = FromStringShow . fromList
toList = toList . fromStringShow
#endif
instance Monad FromStringShow where
return = FromStringShow
INLINE_INST_FUN(return)
FromStringShow a >>= f = f a
INLINE_INST_FUN((>>=))
instance MonadFix FromStringShow where
mfix f = FromStringShow $ let FromStringShow a = f a in a
INLINE_INST_FUN(mfix)
#if MIN_VERSION_base(4,4,0)
instance MonadZip FromStringShow where
mzip (FromStringShow a) (FromStringShow b) = FromStringShow (a, b)
INLINE_INST_FUN(mzip)
mzipWith f (FromStringShow a) (FromStringShow b) = FromStringShow $ f a b
INLINE_INST_FUN(mzipWith)
munzip (FromStringShow (a, b)) = (FromStringShow a, FromStringShow b)
INLINE_INST_FUN(munzip)
#endif
instance Read a => Read (FromStringShow a) where
readPrec = FromStringShow <$> readPrec
INLINE_INST_FUN(readPrec)
readListPrec = readListPrecDefault
INLINE_INST_FUN(readListPrec)
instance S.Show a => Show (FromStringShow a) where
showbPrec p (FromStringShow x) = fromString $ S.showsPrec p x ""
INLINE_INST_FUN(showbPrec)
instance S.Show a => S.Show (FromStringShow a) where
showsPrec p (FromStringShow x) = showsPrec p x
INLINE_INST_FUN(showsPrec)
newtype FromTextShow a = FromTextShow { fromTextShow :: a }
deriving ( Bits
, Bounded
, Data
, Enum
, Eq
#if MIN_VERSION_base(4,7,0)
, FiniteBits
#endif
, Floating
, Foldable
, Fractional
, Functor
#if MIN_VERSION_base(4,4,0)
, Generic
# if __GLASGOW_HASKELL__ >= 706
, Generic1
# endif
#endif
, Integral
, IsString
, Ix
, Monoid
, Num
, Ord
, PrintfArg
, PrintfType
, Real
, RealFloat
, RealFrac
, Semigroup
, Show
, Storable
, Traversable
, Typeable
)
instance Applicative FromTextShow where
pure = FromTextShow
INLINE_INST_FUN(pure)
FromTextShow f <*> FromTextShow x = FromTextShow $ f x
INLINE_INST_FUN((<*>))
#if __GLASGOW_HASKELL__ >= 708
instance IsList a => IsList (FromTextShow a) where
type Item (FromTextShow a) = Item a
fromList = FromTextShow . fromList
toList = toList . fromTextShow
#endif
instance Monad FromTextShow where
return = FromTextShow
INLINE_INST_FUN(return)
FromTextShow a >>= f = f a
INLINE_INST_FUN((>>=))
instance MonadFix FromTextShow where
mfix f = FromTextShow $ let FromTextShow a = f a in a
INLINE_INST_FUN(mfix)
#if MIN_VERSION_base(4,4,0)
instance MonadZip FromTextShow where
mzip (FromTextShow a) (FromTextShow b) = FromTextShow (a, b)
INLINE_INST_FUN(mzip)
mzipWith f (FromTextShow a) (FromTextShow b) = FromTextShow $ f a b
INLINE_INST_FUN(mzipWith)
munzip (FromTextShow (a, b)) = (FromTextShow a, FromTextShow b)
INLINE_INST_FUN(munzip)
#endif
instance Read a => Read (FromTextShow a) where
readPrec = FromTextShow <$> readPrec
INLINE_INST_FUN(readPrec)
readListPrec = readListPrecDefault
INLINE_INST_FUN(readListPrec)
instance Show a => S.Show (FromTextShow a) where
showsPrec p (FromTextShow x) str = toString (showbPrec p x) ++ str
INLINE_INST_FUN(showsPrec)
instance Show1 FromTextShow where
showbPrec1 = showbPrec
INLINE_INST_FUN(showbPrec1)