#if !(MIN_VERSION_base(4,5,0))
#endif
#include "HsBaseConfig.h"
module Text.Show.Text.System.Posix.Types (
showbFdPrec
#if defined(HTYPE_DEV_T)
, showbCDev
#endif
#if defined(HTYPE_INO_T)
, showbCIno
#endif
#if defined(HTYPE_MODE_T)
, showbCMode
#endif
#if defined(HTYPE_OFF_T)
, showbCOffPrec
#endif
#if defined(HTYPE_PID_T)
, showbCPidPrec
#endif
#if defined(HTYPE_SSIZE_T)
, showbCSsizePrec
#endif
#if defined(HTYPE_GID_T)
, showbCGid
#endif
#if defined(HTYPE_NLINK_T)
, showbCNlink
#endif
#if defined(HTYPE_UID_T)
, showbCUid
#endif
#if defined(HTYPE_CC_T)
, showbCCc
#endif
#if defined(HTYPE_SPEED_T)
, showbCSpeed
#endif
#if defined(HTYPE_TCFLAG_T)
, showbCTcflag
#endif
#if defined(HTYPE_RLIM_T)
, showbCRLim
#endif
) where
import Data.Text.Lazy.Builder (Builder)
import Prelude hiding (Show)
import System.Posix.Types
import Text.Show.Text.Classes (Show(showb, showbPrec))
import Text.Show.Text.Data.Integral ()
import Text.Show.Text.Foreign.C.Types ()
#if !(MIN_VERSION_base(4,5,0))
import GHC.Prim (unsafeCoerce#)
import Text.Show.Text.Data.Integral ( showbInt32Prec
, showbInt64Prec
, showbWord8
, showbWord32
, showbWord64
)
# include "inline.h"
#endif
#if defined(HTYPE_DEV_T)
showbCDev :: CDev -> Builder
# if MIN_VERSION_base(4,5,0)
showbCDev = showb
# else
showbCDev c = showbWord64 $ unsafeCoerce# c
# endif
#endif
#if defined(HTYPE_INO_T)
showbCIno :: CIno -> Builder
# if MIN_VERSION_base(4,5,0)
showbCIno = showb
# else
showbCIno c = showbWord64 $ unsafeCoerce# c
# endif
#endif
#if defined(HTYPE_MODE_T)
showbCMode :: CMode -> Builder
# if MIN_VERSION_base(4,5,0)
showbCMode = showb
# else
showbCMode c = showbWord32 $ unsafeCoerce# c
# endif
#endif
#if defined(HTYPE_OFF_T)
showbCOffPrec :: Int -> COff -> Builder
# if MIN_VERSION_base(4,5,0)
showbCOffPrec = showbPrec
# else
showbCOffPrec p c = showbInt64Prec p $ unsafeCoerce# c
# endif
#endif
#if defined(HTYPE_PID_T)
showbCPidPrec :: Int -> CPid -> Builder
# if MIN_VERSION_base(4,5,0)
showbCPidPrec = showbPrec
# else
showbCPidPrec p c = showbInt32Prec p $ unsafeCoerce# c
# endif
#endif
#if defined(HTYPE_SSIZE_T)
showbCSsizePrec :: Int -> CSsize -> Builder
# if MIN_VERSION_base(4,5,0)
showbCSsizePrec = showbPrec
# else
showbCSsizePrec p c = showbInt32Prec p $ unsafeCoerce# c
# endif
#endif
#if defined(HTYPE_GID_T)
showbCGid :: CGid -> Builder
# if MIN_VERSION_base(4,5,0)
showbCGid = showb
# else
showbCGid c = showbWord32 $ unsafeCoerce# c
# endif
#endif
#if defined(HTYPE_NLINK_T)
showbCNlink :: CNlink -> Builder
# if MIN_VERSION_base(4,5,0)
showbCNlink = showb
# else
showbCNlink c = showbWord32 $ unsafeCoerce# c
# endif
#endif
#if defined(HTYPE_UID_T)
showbCUid :: CUid -> Builder
# if MIN_VERSION_base(4,5,0)
showbCUid = showb
# else
showbCUid c = showbWord32 $ unsafeCoerce# c
# endif
#endif
#if defined(HTYPE_CC_T)
showbCCc :: CCc -> Builder
# if MIN_VERSION_base(4,5,0)
showbCCc = showb
# else
showbCCc c = showbWord8 $ unsafeCoerce# c
# endif
#endif
#if defined(HTYPE_SPEED_T)
showbCSpeed :: CSpeed -> Builder
# if MIN_VERSION_base(4,5,0)
showbCSpeed = showb
# else
showbCSpeed c = showbWord32 $ unsafeCoerce# c
# endif
#endif
#if defined(HTYPE_TCFLAG_T)
showbCTcflag :: CTcflag -> Builder
# if MIN_VERSION_base(4,5,0)
showbCTcflag = showb
# else
showbCTcflag c = showbWord32 $ unsafeCoerce# c
# endif
#endif
#if defined(HTYPE_RLIM_T)
showbCRLim :: CRLim -> Builder
# if MIN_VERSION_base(4,5,0)
showbCRLim = showb
# else
showbCRLim c = showbWord64 $ unsafeCoerce# c
# endif
#endif
showbFdPrec :: Int -> Fd -> Builder
showbFdPrec = showbPrec
#if MIN_VERSION_base(4,5,0)
# if defined(HTYPE_DEV_T)
deriving instance Show CDev
# endif
# if defined(HTYPE_INO_T)
deriving instance Show CIno
# endif
# if defined(HTYPE_MODE_T)
deriving instance Show CMode
# endif
# if defined(HTYPE_OFF_T)
deriving instance Show COff
# endif
# if defined(HTYPE_PID_T)
deriving instance Show CPid
# endif
# if defined(HTYPE_SSIZE_T)
deriving instance Show CSsize
# endif
# if defined(HTYPE_GID_T)
deriving instance Show CGid
# endif
# if defined(HTYPE_NLINK_T)
deriving instance Show CNlink
# endif
# if defined(HTYPE_UID_T)
deriving instance Show CUid
# endif
# if defined(HTYPE_CC_T)
deriving instance Show CCc
# endif
# if defined(HTYPE_SPEED_T)
deriving instance Show CSpeed
# endif
# if defined(HTYPE_TCFLAG_T)
deriving instance Show CTcflag
# endif
# if defined(HTYPE_RLIM_T)
deriving instance Show CRLim
# endif
#else
# if defined(HTYPE_DEV_T)
instance Show CDev where
showb = showbCDev
INLINE_INST_FUN(showb)
# endif
# if defined(HTYPE_INO_T)
instance Show CIno where
showb = showbCIno
INLINE_INST_FUN(showb)
# endif
# if defined(HTYPE_MODE_T)
instance Show CMode where
showb = showbCMode
INLINE_INST_FUN(showb)
# endif
# if defined(HTYPE_OFF_T)
instance Show COff where
showbPrec = showbCOffPrec
INLINE_INST_FUN(showbPrec)
# endif
# if defined(HTYPE_PID_T)
instance Show CPid where
showbPrec = showbCPidPrec
INLINE_INST_FUN(showbPrec)
# endif
# if defined(HTYPE_SSIZE_T)
instance Show CSsize where
showbPrec = showbCSsizePrec
INLINE_INST_FUN(showbPrec)
# endif
# if defined(HTYPE_GID_T)
instance Show CGid where
showb = showbCGid
INLINE_INST_FUN(showb)
# endif
# if defined(HTYPE_NLINK_T)
instance Show CNlink where
showb = showbCNlink
INLINE_INST_FUN(showb)
# endif
# if defined(HTYPE_UID_T)
instance Show CUid where
showb = showbCUid
INLINE_INST_FUN(showb)
# endif
# if defined(HTYPE_CC_T)
instance Show CCc where
showb = showbCCc
INLINE_INST_FUN(showb)
# endif
# if defined(HTYPE_SPEED_T)
instance Show CSpeed where
showb = showbCSpeed
INLINE_INST_FUN(showb)
# endif
# if defined(HTYPE_TCFLAG_T)
instance Show CTcflag where
showb = showbCTcflag
INLINE_INST_FUN(showb)
# endif
# if defined(HTYPE_RLIM_T)
instance Show CRLim where
showb = showbCRLim
INLINE_INST_FUN(showb)
# endif
#endif
deriving instance Show Fd