module Text.Show.HT where
{-# INLINE showsInfixPrec #-}
showsInfixPrec ::
(Show a, Show b) =>
String -> Int -> Int -> a -> b -> ShowS
showsInfixPrec :: forall a b.
(Show a, Show b) =>
String -> Int -> Int -> a -> b -> ShowS
showsInfixPrec String
opStr Int
opPrec Int
prec a
x b
y =
Bool -> ShowS -> ShowS
showParen
(Int
prec forall a. Ord a => a -> a -> Bool
>= Int
opPrec)
(forall a. Show a => Int -> a -> ShowS
showsPrec Int
opPrec a
x forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
" " forall b c a. (b -> c) -> (a -> b) -> a -> c
.
String -> ShowS
showString String
opStr forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
" " forall b c a. (b -> c) -> (a -> b) -> a -> c
.
forall a. Show a => Int -> a -> ShowS
showsPrec Int
opPrec b
y)
concatS :: [ShowS] -> ShowS
concatS :: [ShowS] -> ShowS
concatS = forall a b c. (a -> b -> c) -> b -> a -> c
flip (forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr forall a b. (a -> b) -> a -> b
($))