{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell   #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
{-|
Module:      TextShow.System.IO
Copyright:   (C) 2014-2017 Ryan Scott
License:     BSD-style (see the file LICENSE)
Maintainer:  Ryan Scott
Stability:   Provisional
Portability: GHC

'TextShow' instances for 'IO'-related data types.

/Since: 2/
-}
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)

-- | /Since: 2/
instance TextShow Handle where
    showb :: Handle -> Builder
showb (FileHandle   FilePath
file MVar Handle__
_)   = FilePath -> Builder
showbHandleFilePath FilePath
file
    showb (DuplexHandle FilePath
file MVar Handle__
_ MVar Handle__
_) = FilePath -> Builder
showbHandleFilePath FilePath
file
    {-# INLINE showb #-}

-- | Convert a 'Handle`'s 'FilePath' to a 'Builder'.
showbHandleFilePath :: FilePath -> Builder
showbHandleFilePath :: FilePath -> Builder
showbHandleFilePath FilePath
file = Builder
"{handle: " forall a. Semigroup a => a -> a -> a
<> FilePath -> Builder
fromString FilePath
file forall a. Semigroup a => a -> a -> a
<> Char -> Builder
singleton Char
'}'
{-# INLINE showbHandleFilePath #-}

-- | /Since: 2/
$(deriveTextShow ''IOMode)
-- | /Since: 2/
$(deriveTextShow ''BufferMode)

-- | /Since: 2/
instance TextShow HandlePosn where
    showb :: HandlePosn -> Builder
showb (HandlePosn Handle
h HandlePosition
pos) = forall a. TextShow a => a -> Builder
showb Handle
h forall a. Semigroup a => a -> a -> a
<> Builder
" at position " forall a. Semigroup a => a -> a -> a
<> forall a. TextShow a => Int -> a -> Builder
showbPrec Int
0 HandlePosition
pos
    {-# INLINE showb #-}

-- | /Since: 2/
$(deriveTextShow ''SeekMode)

-- | /Since: 2/
instance TextShow TextEncoding where
    showb :: TextEncoding -> Builder
showb = FilePath -> Builder
fromString forall b c a. (b -> c) -> (a -> b) -> a -> c
. TextEncoding -> FilePath
textEncodingName
    {-# INLINE showb #-}

-- | /Since: 2/
$(deriveTextShow ''CodingProgress)
-- | /Since: 2/
$(deriveTextShow ''CodingFailureMode)
-- | /Since: 2/
$(deriveTextShow ''Newline)
-- | /Since: 2/
$(deriveTextShow ''NewlineMode)