#if MIN_VERSION_base(4,5,0)
#else
#endif
module Text.Show.Text.Foreign.C.Types (
showbCCharPrec
, showbCSCharPrec
, showbCUChar
, showbCShortPrec
, showbCUShort
, showbCIntPrec
, showbCUInt
, showbCLongPrec
, showbCULong
, showbCPtrdiffPrec
, showbCSize
, showbCWcharPrec
, showbCSigAtomicPrec
, showbCLLongPrec
, showbCULLong
, showbCIntPtrPrec
, showbCUIntPtr
, showbCIntMaxPrec
, showbCUIntMax
, showbCClockPrec
, showbCTimePrec
#if MIN_VERSION_base(4,4,0)
, showbCUSeconds
, showbCSUSecondsPrec
#endif
, showbCFloatPrec
, showbCDoublePrec
) where
import Data.Text.Lazy.Builder (Builder)
import Foreign.C.Types
import Prelude hiding (Show)
import Text.Show.Text.Classes (Show(showb, showbPrec))
import Text.Show.Text.Data.Floating ()
import Text.Show.Text.Data.Integral ()
#if !(MIN_VERSION_base(4,5,0))
import GHC.Prim (unsafeCoerce#)
import Text.Show.Text.Data.Floating (showbDoublePrec, showbFloatPrec)
import Text.Show.Text.Data.Integral ( showbInt8Prec
, showbInt16Prec
, showbInt32Prec
, showbInt64Prec
, showbWord8
, showbWord16
, showbWord32
, showbWord64
)
# include "inline.h"
#endif
showbCCharPrec :: Int -> CChar -> Builder
#if MIN_VERSION_base(4,5,0)
showbCCharPrec = showbPrec
#else
showbCCharPrec p c = showbInt8Prec p $ unsafeCoerce# c
#endif
showbCSCharPrec :: Int -> CSChar -> Builder
#if MIN_VERSION_base(4,5,0)
showbCSCharPrec = showbPrec
#else
showbCSCharPrec p c = showbInt8Prec p $ unsafeCoerce# c
#endif
showbCUChar :: CUChar -> Builder
#if MIN_VERSION_base(4,5,0)
showbCUChar = showb
#else
showbCUChar c = showbWord8 $ unsafeCoerce# c
#endif
showbCShortPrec :: Int -> CShort -> Builder
#if MIN_VERSION_base(4,5,0)
showbCShortPrec = showbPrec
#else
showbCShortPrec p c = showbInt16Prec p $ unsafeCoerce# c
#endif
showbCUShort :: CUShort -> Builder
#if MIN_VERSION_base(4,5,0)
showbCUShort = showb
#else
showbCUShort c = showbWord16 $ unsafeCoerce# c
#endif
showbCIntPrec :: Int -> CInt -> Builder
#if MIN_VERSION_base(4,5,0)
showbCIntPrec = showbPrec
#else
showbCIntPrec p c = showbInt32Prec p $ unsafeCoerce# c
#endif
showbCUInt :: CUInt -> Builder
#if MIN_VERSION_base(4,5,0)
showbCUInt = showb
#else
showbCUInt c = showbWord32 $ unsafeCoerce# c
#endif
showbCLongPrec :: Int -> CLong -> Builder
#if MIN_VERSION_base(4,5,0)
showbCLongPrec = showbPrec
#else
showbCLongPrec p c = showbInt32Prec p $ unsafeCoerce# c
#endif
showbCULong :: CULong -> Builder
#if MIN_VERSION_base(4,5,0)
showbCULong = showb
#else
showbCULong c = showbWord32 $ unsafeCoerce# c
#endif
showbCPtrdiffPrec :: Int -> CPtrdiff -> Builder
#if MIN_VERSION_base(4,5,0)
showbCPtrdiffPrec = showbPrec
#else
showbCPtrdiffPrec p c = showbInt32Prec p $ unsafeCoerce# c
#endif
showbCSize :: CSize -> Builder
#if MIN_VERSION_base(4,5,0)
showbCSize = showb
#else
showbCSize c = showbWord32 $ unsafeCoerce# c
#endif
showbCWcharPrec :: Int -> CWchar -> Builder
#if MIN_VERSION_base(4,5,0)
showbCWcharPrec = showbPrec
#else
showbCWcharPrec p c = showbInt32Prec p $ unsafeCoerce# c
#endif
showbCSigAtomicPrec :: Int -> CSigAtomic -> Builder
#if MIN_VERSION_base(4,5,0)
showbCSigAtomicPrec = showbPrec
#else
showbCSigAtomicPrec p c = showbInt32Prec p $ unsafeCoerce# c
#endif
showbCLLongPrec :: Int -> CLLong -> Builder
#if MIN_VERSION_base(4,5,0)
showbCLLongPrec = showbPrec
#else
showbCLLongPrec p c = showbInt64Prec p $ unsafeCoerce# c
#endif
showbCULLong :: CULLong -> Builder
#if MIN_VERSION_base(4,5,0)
showbCULLong = showb
#else
showbCULLong c = showbWord64 $ unsafeCoerce# c
#endif
showbCIntPtrPrec :: Int -> CIntPtr -> Builder
#if MIN_VERSION_base(4,5,0)
showbCIntPtrPrec = showbPrec
#else
showbCIntPtrPrec p c = showbInt32Prec p $ unsafeCoerce# c
#endif
showbCUIntPtr :: CUIntPtr -> Builder
#if MIN_VERSION_base(4,5,0)
showbCUIntPtr = showb
#else
showbCUIntPtr c = showbWord32 $ unsafeCoerce# c
#endif
showbCIntMaxPrec :: Int -> CIntMax -> Builder
#if MIN_VERSION_base(4,5,0)
showbCIntMaxPrec = showbPrec
#else
showbCIntMaxPrec p c = showbInt64Prec p $ unsafeCoerce# c
#endif
showbCUIntMax :: CUIntMax -> Builder
#if MIN_VERSION_base(4,5,0)
showbCUIntMax = showb
#else
showbCUIntMax c = showbWord64 $ unsafeCoerce# c
#endif
showbCClockPrec :: Int -> CClock -> Builder
#if MIN_VERSION_base(4,5,0)
showbCClockPrec = showbPrec
#else
showbCClockPrec p c = showbInt32Prec p $ unsafeCoerce# c
#endif
showbCTimePrec :: Int -> CTime -> Builder
#if MIN_VERSION_base(4,5,0)
showbCTimePrec = showbPrec
#else
showbCTimePrec p c = showbInt32Prec p $ unsafeCoerce# c
#endif
#if MIN_VERSION_base(4,4,0)
showbCUSeconds :: CUSeconds -> Builder
# if MIN_VERSION_base(4,5,0)
showbCUSeconds = showb
# else
showbCUSeconds c = showbWord32 $ unsafeCoerce# c
# endif
showbCSUSecondsPrec :: Int -> CSUSeconds -> Builder
# if MIN_VERSION_base(4,5,0)
showbCSUSecondsPrec = showbPrec
# else
showbCSUSecondsPrec p c = showbInt32Prec p $ unsafeCoerce# c
# endif
#endif
showbCFloatPrec :: Int -> CFloat -> Builder
#if MIN_VERSION_base(4,5,0)
showbCFloatPrec = showbPrec
#else
showbCFloatPrec p c = showbFloatPrec p $ unsafeCoerce# c
#endif
showbCDoublePrec :: Int -> CDouble -> Builder
#if MIN_VERSION_base(4,5,0)
showbCDoublePrec = showbPrec
#else
showbCDoublePrec p c = showbDoublePrec p $ unsafeCoerce# c
#endif
#if MIN_VERSION_base(4,5,0)
deriving instance Show CChar
deriving instance Show CSChar
deriving instance Show CUChar
deriving instance Show CShort
deriving instance Show CUShort
deriving instance Show CInt
deriving instance Show CUInt
deriving instance Show CLong
deriving instance Show CULong
deriving instance Show CPtrdiff
deriving instance Show CSize
deriving instance Show CWchar
deriving instance Show CSigAtomic
deriving instance Show CLLong
deriving instance Show CULLong
deriving instance Show CIntPtr
deriving instance Show CUIntPtr
deriving instance Show CIntMax
deriving instance Show CUIntMax
deriving instance Show CClock
deriving instance Show CTime
# if MIN_VERSION_base(4,4,0)
deriving instance Show CUSeconds
deriving instance Show CSUSeconds
# endif
deriving instance Show CFloat
deriving instance Show CDouble
#else
instance Show CChar where
showbPrec = showbCCharPrec
INLINE_INST_FUN(showbPrec)
instance Show CSChar where
showbPrec = showbCSCharPrec
INLINE_INST_FUN(showbPrec)
instance Show CUChar where
showb = showbCUChar
INLINE_INST_FUN(showb)
instance Show CShort where
showbPrec = showbCShortPrec
INLINE_INST_FUN(showbPrec)
instance Show CUShort where
showb = showbCUShort
INLINE_INST_FUN(showb)
instance Show CInt where
showbPrec = showbCIntPrec
INLINE_INST_FUN(showbPrec)
instance Show CUInt where
showb = showbCUInt
INLINE_INST_FUN(showb)
instance Show CLong where
showbPrec = showbCLongPrec
INLINE_INST_FUN(showbPrec)
instance Show CULong where
showb = showbCULong
INLINE_INST_FUN(showb)
instance Show CPtrdiff where
showbPrec = showbCPtrdiffPrec
INLINE_INST_FUN(showbPrec)
instance Show CSize where
showb = showbCSize
INLINE_INST_FUN(showb)
instance Show CWchar where
showbPrec = showbCWcharPrec
INLINE_INST_FUN(showbPrec)
instance Show CSigAtomic where
showbPrec = showbCSigAtomicPrec
INLINE_INST_FUN(showbPrec)
instance Show CLLong where
showbPrec = showbCLLongPrec
INLINE_INST_FUN(showbPrec)
instance Show CULLong where
showb = showbCULLong
INLINE_INST_FUN(showb)
instance Show CIntPtr where
showbPrec = showbCIntPtrPrec
INLINE_INST_FUN(showbPrec)
instance Show CUIntPtr where
showb = showbCUIntPtr
INLINE_INST_FUN(showb)
instance Show CIntMax where
showbPrec = showbCIntMaxPrec
INLINE_INST_FUN(showbPrec)
instance Show CUIntMax where
showb = showbCUIntMax
INLINE_INST_FUN(showb)
instance Show CClock where
showbPrec = showbCClockPrec
INLINE_INST_FUN(showbPrec)
instance Show CTime where
showbPrec = showbCTimePrec
INLINE_INST_FUN(showbPrec)
# if MIN_VERSION_base(4,4,0)
instance Show CUSeconds where
showb = showbCUSeconds
INLINE_INST_FUN(showb)
instance Show CSUSeconds where
showbPrec = showbCSUSecondsPrec
INLINE_INST_FUN(showbPrec)
# endif
instance Show CFloat where
showbPrec = showbCFloatPrec
INLINE_INST_FUN(showbPrec)
instance Show CDouble where
showbPrec = showbCDoublePrec
INLINE_INST_FUN(showbPrec)
#endif