#if __GLASGOW_HASKELL__ >= 702
#endif
#if __GLASGOW_HASKELL__ >= 706
#endif
#if __GLASGOW_HASKELL__ >= 800
#endif
module TextShow.Generic (
genericShowt
, genericShowtl
, genericShowtPrec
, genericShowtlPrec
, genericShowtList
, genericShowtlList
, genericShowb
, genericShowbPrec
, genericShowbList
, genericPrintT
, genericPrintTL
, genericHPrintT
, genericHPrintTL
, genericLiftShowbPrec
, genericShowbPrec1
, GTextShow(..)
, GTextShowCon(..)
, GTextShow1(..)
, GTextShow1Con(..)
, IsNullary(..)
, ConType(..)
) where
import Data.Monoid.Compat ((<>))
import qualified Data.Text as TS (Text)
import qualified Data.Text.IO as TS (putStrLn, hPutStrLn)
import Data.Text.Lazy (toStrict)
import Data.Text.Lazy.Builder (Builder, fromString, singleton, toLazyText)
import qualified Data.Text.Lazy as TL (Text)
import qualified Data.Text.Lazy.IO as TL (putStrLn, hPutStrLn)
import Data.Typeable (Typeable)
import Generics.Deriving.Base
#if __GLASGOW_HASKELL__ < 702
import qualified Generics.Deriving.TH as Generics (deriveAll)
#endif
import GHC.Exts (Char(C#), Double(D#), Float(F#), Int(I#), Word(W#))
import GHC.Show (appPrec, appPrec1)
import Language.Haskell.TH.Lift
import Prelude ()
import Prelude.Compat
import System.IO (Handle)
import TextShow.Classes (TextShow(..), TextShow1(..),
showbListWith, showbParen, showbSpace)
import TextShow.Instances ()
import TextShow.Utils (isInfixTypeCon, isTupleString)
#include "inline.h"
genericShowt :: (Generic a, GTextShow (Rep a)) => a -> TS.Text
genericShowt = toStrict . genericShowtl
genericShowtl :: (Generic a, GTextShow (Rep a)) => a -> TL.Text
genericShowtl = toLazyText . genericShowb
genericShowtPrec :: (Generic a, GTextShow (Rep a)) => Int -> a -> TS.Text
genericShowtPrec p = toStrict . genericShowtlPrec p
genericShowtlPrec :: (Generic a, GTextShow (Rep a)) => Int -> a -> TL.Text
genericShowtlPrec p = toLazyText . genericShowbPrec p
genericShowtList :: (Generic a, GTextShow (Rep a)) => [a] -> TS.Text
genericShowtList = toStrict . genericShowtlList
genericShowtlList :: (Generic a, GTextShow (Rep a)) => [a] -> TL.Text
genericShowtlList = toLazyText . genericShowbList
genericShowb :: (Generic a, GTextShow (Rep a)) => a -> Builder
genericShowb = genericShowbPrec 0
genericShowbPrec :: (Generic a, GTextShow (Rep a)) => Int -> a -> Builder
genericShowbPrec p = gShowbPrec p . from
genericShowbList :: (Generic a, GTextShow (Rep a)) => [a] -> Builder
genericShowbList = showbListWith genericShowb
genericPrintT :: (Generic a, GTextShow (Rep a)) => a -> IO ()
genericPrintT = TS.putStrLn . genericShowt
genericPrintTL :: (Generic a, GTextShow (Rep a)) => a -> IO ()
genericPrintTL = TL.putStrLn . genericShowtl
genericHPrintT :: (Generic a, GTextShow (Rep a)) => Handle -> a -> IO ()
genericHPrintT h = TS.hPutStrLn h . genericShowt
genericHPrintTL :: (Generic a, GTextShow (Rep a)) => Handle -> a -> IO ()
genericHPrintTL h = TL.hPutStrLn h . genericShowtl
genericLiftShowbPrec :: (Generic1 f, GTextShow1 (Rep1 f))
=> (Int -> a -> Builder) -> ([a] -> Builder)
-> Int -> f a -> Builder
genericLiftShowbPrec sp sl p = gLiftShowbPrec sp sl p . from1
genericShowbPrec1 :: (Generic a, Generic1 f, GTextShow (Rep a), GTextShow1 (Rep1 f))
=> Int -> f a -> Builder
genericShowbPrec1 = genericLiftShowbPrec genericShowbPrec genericShowbList
data ConType = Rec | Tup | Pref | Inf String
deriving ( Eq
, Ord
, Read
, Show
, Typeable
#if __GLASGOW_HASKELL__ >= 702
, Generic
#endif
#if __GLASGOW_HASKELL__ >= 800
, Lift
#endif
)
instance TextShow ConType where
showbPrec = genericShowbPrec
INLINE_INST_FUN(showbPrec)
class GTextShow f where
gShowbPrec :: Int -> f a -> Builder
#if __GLASGOW_HASKELL__ >= 708
deriving instance Typeable GTextShow
#endif
instance GTextShow f => GTextShow (D1 d f) where
gShowbPrec p (M1 x) = gShowbPrec p x
instance (GTextShow f, GTextShow g) => GTextShow (f :+: g) where
gShowbPrec p (L1 x) = gShowbPrec p x
gShowbPrec p (R1 x) = gShowbPrec p x
instance (Constructor c, GTextShowCon f, IsNullary f) => GTextShow (C1 c f) where
gShowbPrec = gShowbConstructor gShowbPrecCon
class GTextShowCon f where
gShowbPrecCon :: ConType -> Int -> f a -> Builder
#if __GLASGOW_HASKELL__ >= 708
deriving instance Typeable GTextShowCon
#endif
instance GTextShowCon V1 where
gShowbPrecCon = error "Void showbPrec"
instance GTextShowCon U1 where
gShowbPrecCon _ _ U1 = mempty
instance TextShow c => GTextShowCon (K1 i c) where
gShowbPrecCon _ p (K1 x) = showbPrec p x
instance (Selector s, GTextShowCon f) => GTextShowCon (S1 s f) where
gShowbPrecCon = gShowbSelector gShowbPrecCon
instance (GTextShowCon f, GTextShowCon g) => GTextShowCon (f :*: g) where
gShowbPrecCon = gShowbProduct gShowbPrecCon gShowbPrecCon
instance GTextShowCon UChar where
gShowbPrecCon _ = gShowbUCharPrec
instance GTextShowCon UDouble where
gShowbPrecCon _ = gShowbUDoublePrec
instance GTextShowCon UFloat where
gShowbPrecCon _ = gShowbUFloatPrec
instance GTextShowCon UInt where
gShowbPrecCon _ = gShowbUIntPrec
instance GTextShowCon UWord where
gShowbPrecCon _ = gShowbUWordPrec
class GTextShow1 f where
gLiftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> f a -> Builder
#if __GLASGOW_HASKELL__ >= 708
deriving instance Typeable GTextShow1
#endif
instance GTextShow1 f => GTextShow1 (D1 d f) where
gLiftShowbPrec sp sl p (M1 x) = gLiftShowbPrec sp sl p x
instance GTextShow1 V1 where
gLiftShowbPrec = error "Void showbPrecWith"
instance (GTextShow1 f, GTextShow1 g) => GTextShow1 (f :+: g) where
gLiftShowbPrec sp sl p (L1 x) = gLiftShowbPrec sp sl p x
gLiftShowbPrec sp sl p (R1 x) = gLiftShowbPrec sp sl p x
instance (Constructor c, GTextShow1Con f, IsNullary f) => GTextShow1 (C1 c f) where
gLiftShowbPrec sp sl =
gShowbConstructor (\t' -> gLiftShowbPrecCon t' sp sl)
class GTextShow1Con f where
gLiftShowbPrecCon :: ConType -> (Int -> a -> Builder) -> ([a] -> Builder)
-> Int -> f a -> Builder
#if __GLASGOW_HASKELL__ >= 708
deriving instance Typeable GTextShow1Con
#endif
instance GTextShow1Con U1 where
gLiftShowbPrecCon _ _ _ _ U1 = mempty
instance GTextShow1Con Par1 where
gLiftShowbPrecCon _ sp _ p (Par1 x) = sp p x
instance TextShow c => GTextShow1Con (K1 i c) where
gLiftShowbPrecCon _ _ _ p (K1 x) = showbPrec p x
instance TextShow1 f => GTextShow1Con (Rec1 f) where
gLiftShowbPrecCon _ sp sl p (Rec1 x) = liftShowbPrec sp sl p x
instance (Selector s, GTextShow1Con f) => GTextShow1Con (S1 s f) where
gLiftShowbPrecCon t sp sl =
gShowbSelector (\t' -> gLiftShowbPrecCon t' sp sl) t
instance (GTextShow1Con f, GTextShow1Con g) => GTextShow1Con (f :*: g) where
gLiftShowbPrecCon t sp sl =
gShowbProduct (\t' -> gLiftShowbPrecCon t' sp sl)
(\t' -> gLiftShowbPrecCon t' sp sl) t
instance (TextShow1 f, GTextShow1Con g) => GTextShow1Con (f :.: g) where
gLiftShowbPrecCon t sp sl p (Comp1 x) =
liftShowbPrec (gLiftShowbPrecCon t sp sl)
(showbListWith (gLiftShowbPrecCon t sp sl 0))
p x
instance GTextShow1Con UChar where
gLiftShowbPrecCon _ _ _ = gShowbUCharPrec
instance GTextShow1Con UDouble where
gLiftShowbPrecCon _ _ _ = gShowbUDoublePrec
instance GTextShow1Con UFloat where
gLiftShowbPrecCon _ _ _ = gShowbUFloatPrec
instance GTextShow1Con UInt where
gLiftShowbPrecCon _ _ _ = gShowbUIntPrec
instance GTextShow1Con UWord where
gLiftShowbPrecCon _ _ _ = gShowbUWordPrec
class IsNullary f where
isNullary :: f a -> Bool
instance IsNullary U1 where
isNullary _ = True
instance IsNullary Par1 where
isNullary _ = False
instance IsNullary (K1 i c) where
isNullary _ = False
instance IsNullary f => IsNullary (S1 s f) where
isNullary (M1 x) = isNullary x
instance IsNullary (Rec1 f) where
isNullary _ = False
instance IsNullary (f :*: g) where
isNullary _ = False
instance IsNullary (f :.: g) where
isNullary _ = False
instance IsNullary UChar where
isNullary _ = False
instance IsNullary UDouble where
isNullary _ = False
instance IsNullary UFloat where
isNullary _ = False
instance IsNullary UInt where
isNullary _ = False
instance IsNullary UWord where
isNullary _ = False
gShowbConstructor :: forall c f p.
(Constructor c, IsNullary f)
=> (ConType -> Int -> f p -> Builder)
-> Int -> C1 c f p -> Builder
gShowbConstructor gs p c@(M1 x) = case fixity of
Prefix -> showbParen ( p > appPrec
&& not ( isNullary x
|| conIsTuple c
#if __GLASGOW_HASKELL__ >= 711
|| conIsRecord c
#endif
)
) $
(if conIsTuple c
then mempty
else let cn = conName c
in showbParen (isInfixTypeCon cn) $ fromString cn)
<> (if isNullary x || conIsTuple c
then mempty
else singleton ' ')
<> showbBraces t (gs t appPrec1 x)
Infix _ m -> showbParen (p > m) $ gs t (m+1) x
where
fixity :: Fixity
fixity = conFixity c
t :: ConType
t = if conIsRecord c
then Rec
else case conIsTuple c of
True -> Tup
False -> case fixity of
Prefix -> Pref
Infix _ _ -> Inf $ conName c
showbBraces :: ConType -> Builder -> Builder
showbBraces Rec b = singleton '{' <> b <> singleton '}'
showbBraces Tup b = singleton '(' <> b <> singleton ')'
showbBraces Pref b = b
showbBraces (Inf _) b = b
conIsTuple :: C1 c f p -> Bool
conIsTuple = isTupleString . conName
gShowbSelector :: Selector s
=> (ConType -> Int -> f p -> Builder)
-> ConType -> Int -> S1 s f p -> Builder
gShowbSelector gs t p sel@(M1 x)
| selName sel == "" = gs t p x
| otherwise = fromString (selName sel) <> " = " <> gs t 0 x
gShowbProduct :: (ConType -> Int -> f p -> Builder)
-> (ConType -> Int -> g p -> Builder)
-> ConType -> Int -> ((f :*: g) p) -> Builder
gShowbProduct gsa gsb t@Rec _ (a :*: b) =
gsa t 0 a
<> ", "
<> gsb t 0 b
gShowbProduct gsa gsb t@(Inf o) p (a :*: b) =
gsa t p a
<> showbSpace
<> infixOp
<> showbSpace
<> gsb t p b
where
infixOp :: Builder
infixOp = if isInfixTypeCon o
then fromString o
else singleton '`' <> fromString o <> singleton '`'
gShowbProduct gsa gsb t@Tup _ (a :*: b) =
gsa t 0 a
<> singleton ','
<> gsb t 0 b
gShowbProduct gsa gsb t@Pref p (a :*: b) =
gsa t p a
<> showbSpace
<> gsb t p b
gShowbUCharPrec :: Int -> UChar p -> Builder
gShowbUCharPrec p (UChar c) = showbPrec (hashPrec p) (C# c) <> oneHash
gShowbUDoublePrec :: Int -> UDouble p -> Builder
gShowbUDoublePrec p (UDouble d) = showbPrec (hashPrec p) (D# d) <> twoHash
gShowbUFloatPrec :: Int -> UFloat p -> Builder
gShowbUFloatPrec p (UFloat f) = showbPrec (hashPrec p) (F# f) <> oneHash
gShowbUIntPrec :: Int -> UInt p -> Builder
gShowbUIntPrec p (UInt i) = showbPrec (hashPrec p) (I# i) <> oneHash
gShowbUWordPrec :: Int -> UWord p -> Builder
gShowbUWordPrec p (UWord w) = showbPrec (hashPrec p) (W# w) <> twoHash
oneHash, twoHash :: Builder
hashPrec :: Int -> Int
#if __GLASGOW_HASKELL__ >= 711
oneHash = singleton '#'
twoHash = fromString "##"
hashPrec = const 0
#else
oneHash = mempty
twoHash = mempty
hashPrec = id
#endif
#if __GLASGOW_HASKELL__ < 702
$(Generics.deriveAll ''ConType)
#endif
#if __GLASGOW_HASKELL__ < 800
$(deriveLift ''ConType)
#endif