{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module TextShow.System.IO () where
import Data.Text.Lazy.Builder (Builder, fromString, singleton)
import GHC.IO.Encoding.Failure (CodingFailureMode)
import GHC.IO.Encoding.Types (CodingProgress, TextEncoding(textEncodingName))
import GHC.IO.Handle (HandlePosn(..))
import GHC.IO.Handle.Types (Handle(..))
import Prelude ()
import Prelude.Compat
import System.IO (BufferMode, IOMode, Newline, NewlineMode, SeekMode)
import TextShow.Classes (TextShow(..))
import TextShow.Data.Integral ()
import TextShow.Data.Maybe ()
import TextShow.TH.Internal (deriveTextShow)
instance TextShow Handle where
showb (FileHandle file _) = showbHandleFilePath file
showb (DuplexHandle file _ _) = showbHandleFilePath file
{-# INLINE showb #-}
showbHandleFilePath :: FilePath -> Builder
showbHandleFilePath file = "{handle: " <> fromString file <> singleton '}'
{-# INLINE showbHandleFilePath #-}
$(deriveTextShow ''IOMode)
$(deriveTextShow ''BufferMode)
instance TextShow HandlePosn where
showb (HandlePosn h pos) = showb h <> " at position " <> showbPrec 0 pos
{-# INLINE showb #-}
$(deriveTextShow ''SeekMode)
instance TextShow TextEncoding where
showb = fromString . textEncodingName
{-# INLINE showb #-}
$(deriveTextShow ''CodingProgress)
$(deriveTextShow ''CodingFailureMode)
$(deriveTextShow ''Newline)
$(deriveTextShow ''NewlineMode)