{-# LANGUAGE OverloadedStrings #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module TextShow.Control.Monad.ST () where
import Control.Monad.ST (ST)
import TextShow.Classes (TextShow(..), TextShow1(..), TextShow2(..))
instance TextShow (ST s a) where
showb :: ST s a -> Builder
showb = (Int -> a -> Builder)
-> ([a] -> Builder) -> Int -> ST s a -> Builder
forall (f :: * -> *) a.
TextShow1 f =>
(Int -> a -> Builder) -> ([a] -> Builder) -> Int -> f a -> Builder
liftShowbPrec Int -> a -> Builder
forall a. HasCallStack => a
undefined [a] -> Builder
forall a. HasCallStack => a
undefined Int
0
{-# INLINE showb #-}
instance TextShow1 (ST s) where
liftShowbPrec :: (Int -> a -> Builder)
-> ([a] -> Builder) -> Int -> ST s a -> Builder
liftShowbPrec = (Int -> s -> Builder)
-> ([s] -> Builder)
-> (Int -> a -> Builder)
-> ([a] -> Builder)
-> Int
-> ST s a
-> Builder
forall (f :: * -> * -> *) a b.
TextShow2 f =>
(Int -> a -> Builder)
-> ([a] -> Builder)
-> (Int -> b -> Builder)
-> ([b] -> Builder)
-> Int
-> f a b
-> Builder
liftShowbPrec2 Int -> s -> Builder
forall a. HasCallStack => a
undefined [s] -> Builder
forall a. HasCallStack => a
undefined
{-# INLINE liftShowbPrec #-}
instance TextShow2 ST where
liftShowbPrec2 :: (Int -> a -> Builder)
-> ([a] -> Builder)
-> (Int -> b -> Builder)
-> ([b] -> Builder)
-> Int
-> ST a b
-> Builder
liftShowbPrec2 Int -> a -> Builder
_ [a] -> Builder
_ Int -> b -> Builder
_ [b] -> Builder
_ Int
_ ST a b
_ = Builder
"<<ST action>>"
{-# INLINE liftShowbPrec2 #-}