#if MIN_VERSION_base(4,5,0)
#endif
module TextShow.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 TextShow.Classes (TextShow(..))
import TextShow.Data.Floating ()
import TextShow.Data.Integral ()
#if !(MIN_VERSION_base(4,5,0))
import Data.Int
import Data.Word
import Unsafe.Coerce (unsafeCoerce)
# include "HsBaseConfig.h"
# include "inline.h"
#endif
showbCCharPrec :: Int -> CChar -> Builder
#if MIN_VERSION_base(4,5,0)
showbCCharPrec = showbPrec
#else
showbCCharPrec = unsafeCoerce (showbPrec :: Int -> HTYPE_CHAR -> Builder)
#endif
showbCSCharPrec :: Int -> CSChar -> Builder
#if MIN_VERSION_base(4,5,0)
showbCSCharPrec = showbPrec
#else
showbCSCharPrec = unsafeCoerce (showbPrec :: Int -> HTYPE_SIGNED_CHAR -> Builder)
#endif
showbCUChar :: CUChar -> Builder
#if MIN_VERSION_base(4,5,0)
showbCUChar = showb
#else
showbCUChar = unsafeCoerce (showb :: HTYPE_UNSIGNED_CHAR -> Builder)
#endif
showbCShortPrec :: Int -> CShort -> Builder
#if MIN_VERSION_base(4,5,0)
showbCShortPrec = showbPrec
#else
showbCShortPrec = unsafeCoerce (showbPrec :: Int -> HTYPE_SHORT -> Builder)
#endif
showbCUShort :: CUShort -> Builder
#if MIN_VERSION_base(4,5,0)
showbCUShort = showb
#else
showbCUShort = unsafeCoerce (showb :: HTYPE_UNSIGNED_SHORT -> Builder)
#endif
showbCIntPrec :: Int -> CInt -> Builder
#if MIN_VERSION_base(4,5,0)
showbCIntPrec = showbPrec
#else
showbCIntPrec = unsafeCoerce (showbPrec :: Int -> HTYPE_INT -> Builder)
#endif
showbCUInt :: CUInt -> Builder
#if MIN_VERSION_base(4,5,0)
showbCUInt = showb
#else
showbCUInt = unsafeCoerce (showb :: HTYPE_UNSIGNED_INT -> Builder)
#endif
showbCLongPrec :: Int -> CLong -> Builder
#if MIN_VERSION_base(4,5,0)
showbCLongPrec = showbPrec
#else
showbCLongPrec = unsafeCoerce (showbPrec :: Int -> HTYPE_LONG -> Builder)
#endif
showbCULong :: CULong -> Builder
#if MIN_VERSION_base(4,5,0)
showbCULong = showb
#else
showbCULong = unsafeCoerce (showb :: HTYPE_UNSIGNED_LONG -> Builder)
#endif
showbCPtrdiffPrec :: Int -> CPtrdiff -> Builder
#if MIN_VERSION_base(4,5,0)
showbCPtrdiffPrec = showbPrec
#else
showbCPtrdiffPrec = unsafeCoerce (showbPrec :: Int -> HTYPE_PTRDIFF_T -> Builder)
#endif
showbCSize :: CSize -> Builder
#if MIN_VERSION_base(4,5,0)
showbCSize = showb
#else
showbCSize = unsafeCoerce (showb :: HTYPE_SIZE_T -> Builder)
#endif
showbCWcharPrec :: Int -> CWchar -> Builder
#if MIN_VERSION_base(4,5,0)
showbCWcharPrec = showbPrec
#else
showbCWcharPrec = unsafeCoerce (showbPrec :: Int -> HTYPE_WCHAR_T -> Builder)
#endif
showbCSigAtomicPrec :: Int -> CSigAtomic -> Builder
#if MIN_VERSION_base(4,5,0)
showbCSigAtomicPrec = showbPrec
#else
showbCSigAtomicPrec = unsafeCoerce (showbPrec :: Int -> HTYPE_SIG_ATOMIC_T -> Builder)
#endif
showbCLLongPrec :: Int -> CLLong -> Builder
#if MIN_VERSION_base(4,5,0)
showbCLLongPrec = showbPrec
#else
showbCLLongPrec = unsafeCoerce (showbPrec :: Int -> HTYPE_LONG_LONG -> Builder)
#endif
showbCULLong :: CULLong -> Builder
#if MIN_VERSION_base(4,5,0)
showbCULLong = showb
#else
showbCULLong = unsafeCoerce (showb :: HTYPE_UNSIGNED_LONG_LONG -> Builder)
#endif
showbCIntPtrPrec :: Int -> CIntPtr -> Builder
#if MIN_VERSION_base(4,5,0)
showbCIntPtrPrec = showbPrec
#else
showbCIntPtrPrec = unsafeCoerce (showbPrec :: Int -> HTYPE_INTPTR_T -> Builder)
#endif
showbCUIntPtr :: CUIntPtr -> Builder
#if MIN_VERSION_base(4,5,0)
showbCUIntPtr = showb
#else
showbCUIntPtr = unsafeCoerce (showb :: HTYPE_UINTPTR_T -> Builder)
#endif
showbCIntMaxPrec :: Int -> CIntMax -> Builder
#if MIN_VERSION_base(4,5,0)
showbCIntMaxPrec = showbPrec
#else
showbCIntMaxPrec = unsafeCoerce (showbPrec :: Int -> HTYPE_INTMAX_T -> Builder)
#endif
showbCUIntMax :: CUIntMax -> Builder
#if MIN_VERSION_base(4,5,0)
showbCUIntMax = showb
#else
showbCUIntMax = unsafeCoerce (showb :: HTYPE_UINTMAX_T -> Builder)
#endif
showbCClockPrec :: Int -> CClock -> Builder
#if MIN_VERSION_base(4,5,0)
showbCClockPrec = showbPrec
#else
showbCClockPrec = unsafeCoerce (showbPrec :: Int -> HTYPE_CLOCK_T -> Builder)
#endif
showbCTimePrec :: Int -> CTime -> Builder
#if MIN_VERSION_base(4,5,0)
showbCTimePrec = showbPrec
#else
showbCTimePrec = unsafeCoerce (showbPrec :: Int -> HTYPE_TIME_T -> Builder)
#endif
#if MIN_VERSION_base(4,4,0)
showbCUSeconds :: CUSeconds -> Builder
# if MIN_VERSION_base(4,5,0)
showbCUSeconds = showb
# else
showbCUSeconds = unsafeCoerce (showb :: HTYPE_USECONDS_T -> Builder)
# endif
showbCSUSecondsPrec :: Int -> CSUSeconds -> Builder
# if MIN_VERSION_base(4,5,0)
showbCSUSecondsPrec = showbPrec
# else
showbCSUSecondsPrec = unsafeCoerce (showbPrec :: Int -> HTYPE_SUSECONDS_T -> Builder)
# endif
#endif
showbCFloatPrec :: Int -> CFloat -> Builder
#if MIN_VERSION_base(4,5,0)
showbCFloatPrec = showbPrec
#else
showbCFloatPrec = unsafeCoerce (showbPrec :: Int -> HTYPE_FLOAT -> Builder)
#endif
showbCDoublePrec :: Int -> CDouble -> Builder
#if MIN_VERSION_base(4,5,0)
showbCDoublePrec = showbPrec
#else
showbCDoublePrec = unsafeCoerce (showbPrec :: Int -> HTYPE_DOUBLE -> Builder)
#endif
#if MIN_VERSION_base(4,5,0)
deriving instance TextShow CChar
deriving instance TextShow CSChar
deriving instance TextShow CUChar
deriving instance TextShow CShort
deriving instance TextShow CUShort
deriving instance TextShow CInt
deriving instance TextShow CUInt
deriving instance TextShow CLong
deriving instance TextShow CULong
deriving instance TextShow CPtrdiff
deriving instance TextShow CSize
deriving instance TextShow CWchar
deriving instance TextShow CSigAtomic
deriving instance TextShow CLLong
deriving instance TextShow CULLong
deriving instance TextShow CIntPtr
deriving instance TextShow CUIntPtr
deriving instance TextShow CIntMax
deriving instance TextShow CUIntMax
deriving instance TextShow CClock
deriving instance TextShow CTime
# if MIN_VERSION_base(4,4,0)
deriving instance TextShow CUSeconds
deriving instance TextShow CSUSeconds
# endif
deriving instance TextShow CFloat
deriving instance TextShow CDouble
#else
instance TextShow CChar where
showbPrec = showbCCharPrec
INLINE_INST_FUN(showbPrec)
instance TextShow CSChar where
showbPrec = showbCSCharPrec
INLINE_INST_FUN(showbPrec)
instance TextShow CUChar where
showb = showbCUChar
INLINE_INST_FUN(showb)
instance TextShow CShort where
showbPrec = showbCShortPrec
INLINE_INST_FUN(showbPrec)
instance TextShow CUShort where
showb = showbCUShort
INLINE_INST_FUN(showb)
instance TextShow CInt where
showbPrec = showbCIntPrec
INLINE_INST_FUN(showbPrec)
instance TextShow CUInt where
showb = showbCUInt
INLINE_INST_FUN(showb)
instance TextShow CLong where
showbPrec = showbCLongPrec
INLINE_INST_FUN(showbPrec)
instance TextShow CULong where
showb = showbCULong
INLINE_INST_FUN(showb)
instance TextShow CPtrdiff where
showbPrec = showbCPtrdiffPrec
INLINE_INST_FUN(showbPrec)
instance TextShow CSize where
showb = showbCSize
INLINE_INST_FUN(showb)
instance TextShow CWchar where
showbPrec = showbCWcharPrec
INLINE_INST_FUN(showbPrec)
instance TextShow CSigAtomic where
showbPrec = showbCSigAtomicPrec
INLINE_INST_FUN(showbPrec)
instance TextShow CLLong where
showbPrec = showbCLLongPrec
INLINE_INST_FUN(showbPrec)
instance TextShow CULLong where
showb = showbCULLong
INLINE_INST_FUN(showb)
instance TextShow CIntPtr where
showbPrec = showbCIntPtrPrec
INLINE_INST_FUN(showbPrec)
instance TextShow CUIntPtr where
showb = showbCUIntPtr
INLINE_INST_FUN(showb)
instance TextShow CIntMax where
showbPrec = showbCIntMaxPrec
INLINE_INST_FUN(showbPrec)
instance TextShow CUIntMax where
showb = showbCUIntMax
INLINE_INST_FUN(showb)
instance TextShow CClock where
showbPrec = showbCClockPrec
INLINE_INST_FUN(showbPrec)
instance TextShow CTime where
showbPrec = showbCTimePrec
INLINE_INST_FUN(showbPrec)
# if MIN_VERSION_base(4,4,0)
instance TextShow CUSeconds where
showb = showbCUSeconds
INLINE_INST_FUN(showb)
instance TextShow CSUSeconds where
showbPrec = showbCSUSecondsPrec
INLINE_INST_FUN(showbPrec)
# endif
instance TextShow CFloat where
showbPrec = showbCFloatPrec
INLINE_INST_FUN(showbPrec)
instance TextShow CDouble where
showbPrec = showbCDoublePrec
INLINE_INST_FUN(showbPrec)
#endif