module TextShow.System.IO (
showbHandle
, showbIOMode
, showbBufferModePrec
, showbHandlePosn
, showbSeekMode
, showbTextEncoding
#if MIN_VERSION_base(4,4,0)
, showbCodingProgress
, showbCodingFailureMode
#endif
, showbNewline
, showbNewlineModePrec
) where
import Data.Monoid.Compat ((<>))
import Data.Text.Lazy.Builder (Builder, fromString, singleton)
import GHC.IO.Encoding.Types (TextEncoding(textEncodingName))
#if MIN_VERSION_base(4,4,0)
import GHC.IO.Encoding.Failure (CodingFailureMode)
import GHC.IO.Encoding.Types (CodingProgress)
#endif
import GHC.IO.Handle (HandlePosn(..))
import GHC.IO.Handle.Types (Handle(..))
import System.IO (BufferMode, IOMode, Newline, NewlineMode, SeekMode)
import TextShow.Classes (TextShow(..))
import TextShow.Data.Integral (showbIntegerPrec)
import TextShow.Data.Maybe ()
import TextShow.TH.Internal (deriveTextShow)
#include "inline.h"
showbHandle :: Handle -> Builder
showbHandle (FileHandle file _) = showbHandleFilePath file
showbHandle (DuplexHandle file _ _) = showbHandleFilePath file
showbHandleFilePath :: FilePath -> Builder
showbHandleFilePath file = "{handle: " <> fromString file <> singleton '}'
showbIOMode :: IOMode -> Builder
showbIOMode = showb
showbBufferModePrec :: Int -> BufferMode -> Builder
showbBufferModePrec = showbPrec
showbHandlePosn :: HandlePosn -> Builder
showbHandlePosn (HandlePosn h pos)
= showbHandle h <> " at position " <> showbIntegerPrec 0 pos
showbSeekMode :: SeekMode -> Builder
showbSeekMode = showb
showbTextEncoding :: TextEncoding -> Builder
showbTextEncoding = fromString . textEncodingName
#if MIN_VERSION_base(4,4,0)
showbCodingProgress :: CodingProgress -> Builder
showbCodingProgress = showb
showbCodingFailureMode :: CodingFailureMode -> Builder
showbCodingFailureMode = showb
#endif
showbNewline :: Newline -> Builder
showbNewline = showb
showbNewlineModePrec :: Int -> NewlineMode -> Builder
showbNewlineModePrec = showbPrec
instance TextShow Handle where
showb = showbHandle
INLINE_INST_FUN(showb)
$(deriveTextShow ''IOMode)
$(deriveTextShow ''BufferMode)
instance TextShow HandlePosn where
showb = showbHandlePosn
INLINE_INST_FUN(showb)
$(deriveTextShow ''SeekMode)
instance TextShow TextEncoding where
showb = showbTextEncoding
INLINE_INST_FUN(showb)
#if MIN_VERSION_base(4,4,0)
$(deriveTextShow ''CodingProgress)
$(deriveTextShow ''CodingFailureMode)
#endif
$(deriveTextShow ''Newline)
$(deriveTextShow ''NewlineMode)