{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PolyKinds         #-}

{-# OPTIONS -Wno-orphans #-}
{-|
Module:      TextShow.Data.Tagged
Copyright:   (C) 2014-2017 Ryan Scott
License:     BSD-style (see the file LICENSE)
Maintainer:  Ryan Scott
Stability:   Provisional
Portability: GHC

'TextShow' instance for 'Tagged'.

/Since: 2/
-}
module TextShow.Data.Tagged () where

import Data.Tagged (Tagged(..))
import TextShow (TextShow(..), TextShow1(..), TextShow2(..),
                 Builder, showbPrec1, showbUnaryWith)

-- | Convert a 'Tagged' value to a 'Builder' with the given show function and precedence.
liftShowbTaggedPrec :: (Int -> b -> Builder) -> Int -> Tagged s b -> Builder
liftShowbTaggedPrec :: forall {k} b (s :: k).
(Int -> b -> Builder) -> Int -> Tagged s b -> Builder
liftShowbTaggedPrec Int -> b -> Builder
sp Int
p (Tagged b
b) = forall a. (Int -> a -> Builder) -> Builder -> Int -> a -> Builder
showbUnaryWith Int -> b -> Builder
sp Builder
"Tagged" Int
p b
b
{-# INLINE liftShowbTaggedPrec #-}

-- | /Since: 2/
instance TextShow b => TextShow (Tagged s b) where
    showbPrec :: Int -> Tagged s b -> Builder
showbPrec = forall (f :: * -> *) a.
(TextShow1 f, TextShow a) =>
Int -> f a -> Builder
showbPrec1
    {-# INLINE showbPrec #-}

-- | /Since: 2/
instance TextShow1 (Tagged s) where
    liftShowbPrec :: forall a.
(Int -> a -> Builder)
-> ([a] -> Builder) -> Int -> Tagged s a -> Builder
liftShowbPrec Int -> a -> Builder
sp [a] -> Builder
_ = forall {k} b (s :: k).
(Int -> b -> Builder) -> Int -> Tagged s b -> Builder
liftShowbTaggedPrec Int -> a -> Builder
sp
    {-# INLINE liftShowbPrec #-}

-- | /Since: 2/
instance TextShow2 Tagged where
    liftShowbPrec2 :: forall a b.
(Int -> a -> Builder)
-> ([a] -> Builder)
-> (Int -> b -> Builder)
-> ([b] -> Builder)
-> Int
-> Tagged a b
-> Builder
liftShowbPrec2 Int -> a -> Builder
_ [a] -> Builder
_ Int -> b -> Builder
sp [b] -> Builder
_ = forall {k} b (s :: k).
(Int -> b -> Builder) -> Int -> Tagged s b -> Builder
liftShowbTaggedPrec Int -> b -> Builder
sp
    {-# INLINE liftShowbPrec2 #-}