module Text.Show.Text.Control.Applicative.Trans (
showbBackwardsPrecWith
, showbLiftPrecWith
) where
import Control.Applicative.Backwards (Backwards(..))
import Control.Applicative.Lift (Lift(..))
import Prelude hiding (Show)
import Text.Show.Text (Show(showbPrec), Show1(..), Builder,
showbPrec1, showbUnaryWith)
#include "inline.h"
showbBackwardsPrecWith :: Show1 f
=> (Int -> a -> Builder)
-> Int -> Backwards f a -> Builder
showbBackwardsPrecWith sp p (Backwards x)
= showbUnaryWith (showbPrecWith sp) "Backwards" p x
showbLiftPrecWith :: Show1 f
=> (Int -> a -> Builder)
-> Int -> Lift f a -> Builder
showbLiftPrecWith sp p (Pure x) = showbUnaryWith sp "Pure" p x
showbLiftPrecWith sp p (Other y) = showbUnaryWith (showbPrecWith sp) "Other" p y
instance (Show1 f, Show a) => Show (Backwards f a) where
showbPrec = showbPrec1
INLINE_INST_FUN(showbPrec)
instance Show1 f => Show1 (Backwards f) where
showbPrecWith = showbBackwardsPrecWith
INLINE_INST_FUN(showbPrecWith)
instance (Show1 f, Show a) => Show (Lift f a) where
showbPrec = showbPrec1
INLINE_INST_FUN(showbPrec)
instance Show1 f => Show1 (Lift f) where
showbPrecWith = showbLiftPrecWith
INLINE_INST_FUN(showbPrecWith)