module Bindings.StandardC where import Bindings.Utilities import Foreign import Foreign.C import qualified Data.Int import qualified Data.Word -- * @ctype.h@ foreign import ccall "isalnum" isalnum :: CInt -> IO CInt foreign import ccall "isalpha" isalpha :: CInt -> IO CInt foreign import ccall "isblank" isblank :: CInt -> IO CInt foreign import ccall "iscntrl" iscntrl :: CInt -> IO CInt foreign import ccall "isdigit" isdigit :: CInt -> IO CInt foreign import ccall "isgraph" isgraph :: CInt -> IO CInt foreign import ccall "islower" islower :: CInt -> IO CInt foreign import ccall "isprint" isprint :: CInt -> IO CInt foreign import ccall "ispunct" ispunct :: CInt -> IO CInt foreign import ccall "isspace" isspace :: CInt -> IO CInt foreign import ccall "isupper" isupper :: CInt -> IO CInt foreign import ccall "isxdigit" isxdigit :: CInt -> IO CInt foreign import ccall "tolower" tolower :: CInt -> IO CInt foreign import ccall "toupper" toupper :: CInt -> IO CInt foreign import ccall "bindings_sc_CHAR_BIT" _CHAR_BIT :: CInt foreign import ccall "bindings_sc_MB_LEN_MAX" _MB_LEN_MAX :: CInt -- * @locale.h@ foreign import ccall "bindings_sc_LC_ALL" _LC_ALL :: CInt foreign import ccall "bindings_sc_LC_COLLATE" _LC_COLLATE :: CInt foreign import ccall "bindings_sc_LC_CTYPE" _LC_CTYPE :: CInt foreign import ccall "bindings_sc_LC_MONETARY" _LC_MONETARY :: CInt foreign import ccall "bindings_sc_LC_NUMERIC" _LC_NUMERIC :: CInt foreign import ccall "bindings_sc_LC_TIME" _LC_TIME :: CInt foreign import ccall "setlocale" setlocale :: CInt -> CString -> IO CString -- * @math.h@ foreign import ccall "acos" acos :: CDouble -> IO CDouble foreign import ccall "acosf" acosf :: CFloat -> IO CFloat foreign import ccall "acosl" acosl :: CLDouble -> IO CLDouble foreign import ccall "asin" asin :: CDouble -> IO CDouble foreign import ccall "asinf" asinf :: CFloat -> IO CFloat foreign import ccall "asinl" asinl :: CLDouble -> IO CLDouble foreign import ccall "atan" atan :: CDouble -> IO CDouble foreign import ccall "atanf" atanf :: CFloat -> IO CFloat foreign import ccall "atanl" atanl :: CLDouble -> IO CLDouble foreign import ccall "atan2" atan2 :: CDouble -> CDouble -> IO CDouble foreign import ccall "atan2f" atan2f :: CFloat -> CFloat -> IO CFloat foreign import ccall "atan2l" atan2l :: CLDouble -> CLDouble -> IO CLDouble foreign import ccall "cos" cos :: CDouble -> IO CDouble foreign import ccall "cosf" cosf :: CFloat -> IO CFloat foreign import ccall "cosl" cosl :: CLDouble -> IO CLDouble foreign import ccall "sin" sin :: CDouble -> IO CDouble foreign import ccall "sinf" sinf :: CFloat -> IO CFloat foreign import ccall "sinl" sinl :: CLDouble -> IO CLDouble foreign import ccall "tan" tan :: CDouble -> IO CDouble foreign import ccall "tanf" tanf :: CFloat -> IO CFloat foreign import ccall "tanl" tanl :: CLDouble -> IO CLDouble foreign import ccall "acosh" acosh :: CDouble -> IO CDouble foreign import ccall "acoshf" acoshf :: CFloat -> IO CFloat foreign import ccall "acoshl" acoshl :: CLDouble -> IO CLDouble foreign import ccall "asinh" asinh :: CDouble -> IO CDouble foreign import ccall "asinhf" asinhf :: CFloat -> IO CFloat foreign import ccall "asinhl" asinhl :: CLDouble -> IO CLDouble foreign import ccall "atanh" atanh :: CDouble -> IO CDouble foreign import ccall "atanhf" atanhf :: CFloat -> IO CFloat foreign import ccall "atanhl" atanhl :: CLDouble -> IO CLDouble foreign import ccall "cosh" cosh :: CDouble -> IO CDouble foreign import ccall "coshf" coshf :: CFloat -> IO CFloat foreign import ccall "coshl" coshl :: CLDouble -> IO CLDouble foreign import ccall "sinh" sinh :: CDouble -> IO CDouble foreign import ccall "sinhf" sinhf :: CFloat -> IO CFloat foreign import ccall "sinhl" sinhl :: CLDouble -> IO CLDouble foreign import ccall "tanh" tanh :: CDouble -> IO CDouble foreign import ccall "tanhf" tanhf :: CFloat -> IO CFloat foreign import ccall "tanhl" tanhl :: CLDouble -> IO CLDouble foreign import ccall "exp" exp :: CDouble -> IO CDouble foreign import ccall "expf" expf :: CFloat -> IO CFloat foreign import ccall "expl" expl :: CLDouble -> IO CLDouble foreign import ccall "exp2" exp2 :: CDouble -> IO CDouble foreign import ccall "exp2f" exp2f :: CFloat -> IO CFloat foreign import ccall "exp2l" exp2l :: CLDouble -> IO CLDouble foreign import ccall "expm1" expm1 :: CDouble -> IO CDouble foreign import ccall "expm1f" expm1f :: CFloat -> IO CFloat foreign import ccall "expm1l" expm1l :: CLDouble -> IO CLDouble foreign import ccall "frexp" frexp :: CDouble -> Ptr CInt -> IO CDouble foreign import ccall "frexpf" frexpf :: CFloat -> Ptr CInt -> IO CFloat foreign import ccall "frexpl" frexpl :: CLDouble -> Ptr CInt -> IO CLDouble foreign import ccall "ilogb" ilogb :: CDouble -> IO CInt foreign import ccall "ilogbf" ilogbf :: CFloat -> IO CFloat foreign import ccall "ilogbl" ilogbl :: CLDouble -> IO CLDouble foreign import ccall "ldexp" ldexp :: CDouble -> CInt -> IO CDouble foreign import ccall "ldexpf" ldexpf :: CFloat -> CInt -> IO CFloat foreign import ccall "ldexpl" ldexpl :: CLDouble -> CInt -> IO CLDouble foreign import ccall "log" log :: CDouble -> IO CDouble foreign import ccall "logf" logf :: CFloat -> IO CFloat foreign import ccall "logl" logl :: CLDouble -> IO CLDouble foreign import ccall "log10" log10 :: CDouble -> IO CDouble foreign import ccall "log10f" log10f :: CFloat -> IO CFloat foreign import ccall "log10l" log10l :: CLDouble -> IO CLDouble foreign import ccall "log1p" log1p :: CDouble -> IO CDouble foreign import ccall "log1pf" log1pf :: CFloat -> IO CFloat foreign import ccall "log1pl" log1pl :: CLDouble -> IO CLDouble foreign import ccall "log2" log2 :: CDouble -> IO CDouble foreign import ccall "log2f" log2f :: CFloat -> IO CFloat foreign import ccall "log2l" log2l :: CLDouble -> IO CLDouble foreign import ccall "logb" logb :: CDouble -> IO CDouble foreign import ccall "logbf" logbf :: CFloat -> IO CFloat foreign import ccall "logbl" logbl :: CLDouble -> IO CLDouble foreign import ccall "modf" modf :: CDouble -> Ptr CDouble -> IO CDouble foreign import ccall "modff" modff :: CFloat -> Ptr CFloat -> IO CFloat foreign import ccall "modfl" modfl :: CLDouble -> Ptr CLDouble -> IO CLDouble foreign import ccall "scalbn" scalbn :: CDouble -> CInt -> IO CDouble foreign import ccall "scalbnf" scalbnf :: CFloat -> CInt -> IO CFloat foreign import ccall "scalbnl" scalbnl :: CLDouble -> CInt -> IO CLDouble foreign import ccall "scalbln" scalbln :: CDouble -> CLong -> IO CDouble foreign import ccall "scalblnf" scalblnf :: CFloat -> CLong -> IO CFloat foreign import ccall "scalblnl" scalblnl :: CLDouble -> CLong -> IO CLDouble foreign import ccall "cbrt" cbrt :: CDouble -> IO CDouble foreign import ccall "cbrtf" cbrtf :: CFloat -> IO CFloat foreign import ccall "cbrtl" cbrtl :: CLDouble -> IO CLDouble foreign import ccall "fabs" fabs :: CDouble -> IO CDouble foreign import ccall "fabsf" fabsf :: CFloat -> IO CFloat foreign import ccall "fabsl" fabsl :: CLDouble -> IO CLDouble foreign import ccall "hypot" hypot :: CDouble -> CDouble -> IO CDouble foreign import ccall "hypotf" hypotf :: CFloat -> CFloat -> IO CFloat foreign import ccall "hypotl" hypotl :: CLDouble -> CLDouble -> IO CLDouble foreign import ccall "pow" pow :: CDouble -> CDouble -> IO CDouble foreign import ccall "powf" powf :: CFloat -> CFloat -> IO CFloat foreign import ccall "powl" powl :: CLDouble -> CLDouble -> IO CLDouble foreign import ccall "sqrt" sqrt :: CDouble -> IO CDouble foreign import ccall "sqrtf" sqrtf :: CFloat -> IO CFloat foreign import ccall "sqrtl" sqrtl :: CLDouble -> IO CLDouble foreign import ccall "erf" erf :: CDouble -> IO CDouble foreign import ccall "erff" erff :: CFloat -> IO CFloat foreign import ccall "erfl" erfl :: CLDouble -> IO CLDouble foreign import ccall "erfc" erfc :: CDouble -> IO CDouble foreign import ccall "erfcf" erfcf :: CFloat -> IO CFloat foreign import ccall "erfcl" erfcl :: CLDouble -> IO CLDouble foreign import ccall "lgamma" lgamma :: CDouble -> IO CDouble foreign import ccall "lgammaf" lgammaf :: CFloat -> IO CFloat foreign import ccall "lgammal" lgammal :: CLDouble -> IO CLDouble foreign import ccall "tgamma" tgamma :: CDouble -> IO CDouble foreign import ccall "tgammaf" tgammaf :: CFloat -> IO CFloat foreign import ccall "tgammal" tgammal :: CLDouble -> IO CLDouble foreign import ccall "ceil" ceil :: CDouble -> IO CDouble foreign import ccall "ceilf" ceilf :: CFloat -> IO CFloat foreign import ccall "ceill" ceill :: CLDouble -> IO CLDouble foreign import ccall "floor" floor :: CDouble -> IO CDouble foreign import ccall "floorf" floorf :: CFloat -> IO CFloat foreign import ccall "floorl" floorl :: CLDouble -> IO CLDouble foreign import ccall "nearbyint" nearbyint :: CDouble -> IO CDouble foreign import ccall "nearbyintf" nearbyintf :: CFloat -> IO CFloat foreign import ccall "nearbyintl" nearbyintl :: CLDouble -> IO CLDouble foreign import ccall "rint" rint :: CDouble -> IO CDouble foreign import ccall "rintf" rintf :: CFloat -> IO CFloat foreign import ccall "rintl" rintl :: CLDouble -> IO CLDouble foreign import ccall "lrint" lrint :: CDouble -> IO CLong foreign import ccall "lrintf" lrintf :: CFloat -> IO CLong foreign import ccall "lrintl" lrintl :: CLDouble -> IO CLong foreign import ccall "llrint" llrint :: CDouble -> IO CLLong foreign import ccall "llrintf" llrintf :: CFloat -> IO CLLong foreign import ccall "llrintl" llrintl :: CLDouble -> IO CLLong foreign import ccall "round" round :: CDouble -> IO CDouble foreign import ccall "roundf" roundf :: CFloat -> IO CFloat foreign import ccall "roundl" roundl :: CLDouble -> IO CLDouble foreign import ccall "lround" lround :: CDouble -> IO CLong foreign import ccall "lroundf" lroundf :: CFloat -> IO CLong foreign import ccall "lroundl" lroundl :: CLDouble -> IO CLDouble foreign import ccall "llround" llround :: CDouble -> IO CLLong foreign import ccall "llroundf" llroundf :: CFloat -> IO CLLong foreign import ccall "llroundl" llroundl :: CLDouble -> IO CLLong foreign import ccall "trunc" trunc :: CDouble -> IO CDouble foreign import ccall "truncf" truncf :: CFloat -> IO CFloat foreign import ccall "truncl" truncl :: CLDouble -> IO CLDouble foreign import ccall "fmod" fmod :: CDouble -> CDouble -> IO CDouble foreign import ccall "fmodf" fmodf :: CFloat -> CFloat -> IO CFloat foreign import ccall "fmodl" fmodl :: CLDouble -> CLDouble -> IO CLDouble foreign import ccall "remainder" remainder :: CDouble -> CDouble -> IO CDouble foreign import ccall "remainderf" remainderf :: CFloat -> CFloat -> IO CFloat foreign import ccall "remainderl" remainderl :: CLDouble -> CLDouble -> IO CLDouble foreign import ccall "remquo" remquo :: CDouble -> CDouble -> Ptr CInt -> IO CDouble foreign import ccall "remquof" remquof :: CFloat -> CFloat -> Ptr CInt -> IO CFloat foreign import ccall "remquol" remquol :: CLDouble -> CLDouble -> Ptr CInt -> IO CLDouble foreign import ccall "nan" nan :: CString -> IO CDouble foreign import ccall "nanf" nanf :: CString -> IO CFloat foreign import ccall "nanl" nanl :: CString -> IO CLDouble foreign import ccall "nextafter" nextafter :: CDouble -> CDouble -> IO CDouble foreign import ccall "nextafterf" nextafterf :: CFloat -> CFloat -> IO CFloat foreign import ccall "nextafterl" nextafterl :: CLDouble -> CLDouble -> IO CLDouble foreign import ccall "nexttoward" nexttoward :: CDouble -> CLDouble -> IO CDouble foreign import ccall "nexttowardf" nexttowardf :: CFloat -> CLDouble -> IO CFloat foreign import ccall "nexttowardl" nexttowardl :: CLDouble -> CLDouble -> IO CLDouble foreign import ccall "fdim" fdim :: CDouble -> CDouble -> IO CDouble foreign import ccall "fdimf" fdimf :: CFloat -> CFloat -> IO CFloat foreign import ccall "fdiml" fdiml :: CLDouble -> CLDouble -> IO CLDouble foreign import ccall "fmax" fmax :: CDouble -> CDouble -> IO CDouble foreign import ccall "fmaxf" fmaxf :: CFloat -> CFloat -> IO CFloat foreign import ccall "fmaxl" fmaxl :: CLDouble -> CLDouble -> IO CLDouble foreign import ccall "fmin" fmin :: CDouble -> CDouble -> IO CDouble foreign import ccall "fminf" fminf :: CFloat -> CFloat -> IO CFloat foreign import ccall "fminl" fminl :: CLDouble -> CLDouble -> IO CLDouble foreign import ccall "fma" fma :: CDouble -> CDouble -> CDouble -> IO CDouble foreign import ccall "fmaf" fmaf :: CFloat -> CFloat -> CFloat -> IO CFloat foreign import ccall "fmal" fmal :: CLDouble -> CLDouble -> CLDouble -> IO CLDouble -- * @signal.h@ foreign import ccall "bindings_cs_SIG_DFL" _SIG_DFL :: Ptr _SignalCallback foreign import ccall "bindings_cs_SIG_ERR" _SIG_ERR :: Ptr _SignalCallback foreign import ccall "bindings_cs_SIG_IGN" _SIG_IGN :: Ptr _SignalCallback foreign import ccall "bindings_cs_SIGABRT" _SIGABRT :: CInt foreign import ccall "bindings_cs_SIGFPE" _SIGFPE :: CInt foreign import ccall "bindings_cs_SIGILL" _SIGILL :: CInt foreign import ccall "bindings_cs_SIGINT" _SIGINT :: CInt foreign import ccall "bindings_cs_SIGSEGV" _SIGSEGV :: CInt foreign import ccall "bindings_cs_SIGTERM" _SIGTERM :: CInt foreign import ccall "signal" signal :: CInt -> Ptr CB000B -> IO () foreign import ccall "raise" raise :: CInt -> IO CInt -- * @stdint.h@ type CInt8 = Data.Int.Int8 type CInt16 = Data.Int.Int16 type CInt32 = Data.Int.Int32 type CInt64 = Data.Int.Int64 type CUInt8 = Data.Word.Word8 type CUInt16 = Data.Word.Word16 type CUInt32 = Data.Word.Word32 type CUInt64 = Data.Word.Word64 -- * @stdio.h@ foreign import ccall "bindings_cs_IOFBF" _IOFBF :: CInt foreign import ccall "bindings_cs_IOLBF" _IOLBF :: CInt foreign import ccall "bindings_cs_IONBF" _IONBF :: CInt foreign import ccall "bindings_cs_BUFSIZ" _BUFSIZ :: CInt foreign import ccall "bindings_cs_EOF" _EOF :: CInt foreign import ccall "bindings_cs_FOPEN_MAX" _FOPEN_MAX :: CInt foreign import ccall "bindings_cs_FILENAME_MAX" _FILENAME_MAX :: CInt foreign import ccall "bindings_cs_L_tmpnam" _L_tmpnam :: CInt foreign import ccall "bindings_cs_SEEK_CUR" _SEEK_CUR :: CInt foreign import ccall "bindings_cs_SEEK_END" _SEEK_END :: CInt foreign import ccall "bindings_cs_SEEK_SET" _SEEK_SET :: CInt foreign import ccall "bindings_cs_TMP_MAX" _TMP_MAX :: CInt foreign import ccall "bindings_cs_stderr" stderr :: Ptr CFile foreign import ccall "bindings_cs_stdin" stdin :: Ptr CFile foreign import ccall "bindings_cs_stdout" stdout :: Ptr CFile foreign import ccall "remove" remove :: CString -> IO CInt foreign import ccall "rename" rename :: CString -> CString -> IO CInt foreign import ccall "tmpfile" tmpfile :: IO (Ptr CFile) foreign import ccall "fclose" fclose :: Ptr CFile -> IO CInt foreign import ccall "fflush" fflush :: Ptr CFile -> IO CInt foreign import ccall "fopen" fopen :: CString -> CString -> IO (Ptr CFile) foreign import ccall "freopen" freopen :: CString -> CString -> Ptr CFile -> IO (Ptr CFile) foreign import ccall "setbuf" setbuf :: Ptr CFile -> CString -> IO () foreign import ccall "setvbuf" setvbuf :: Ptr CFile -> CString -> CInt -> CSize -> IO CInt foreign import ccall "fgetc" fgetc :: Ptr CFile -> IO CInt foreign import ccall "fgets" fgets :: CString -> CInt -> Ptr CFile -> IO CString foreign import ccall "fputc" fputc :: CInt -> Ptr CFile -> IO CInt foreign import ccall "fputs" fputs :: CString -> Ptr CFile -> IO CInt foreign import ccall "getc" getc :: Ptr CFile -> IO CInt foreign import ccall "getchar" getchar :: IO CInt foreign import ccall "putchar" putchar :: CInt -> IO CInt foreign import ccall "puts" puts :: CString -> IO CInt foreign import ccall "ungetc" ungetc :: CInt -> Ptr CFile -> IO CInt foreign import ccall "fread" fread :: Ptr () -> CSize -> CSize -> Ptr CFile -> IO CSize foreign import ccall "fwrite" fwrite :: Ptr () -> CSize -> CSize -> Ptr CFile -> IO CSize foreign import ccall "fgetpos" fgetpos :: Ptr CFile -> Ptr CFpos -> IO CInt foreign import ccall "fseek" fseek :: Ptr CFile -> CLong -> CInt -> IO CInt foreign import ccall "fsetpos" fsetpos :: Ptr CFile -> Ptr CFpos -> IO CInt foreign import ccall "ftell" ftell :: Ptr CFile -> IO CLong foreign import ccall "rewind" rewind :: Ptr CFile -> IO () foreign import ccall "clearerr" clearerr :: Ptr CFile -> IO () foreign import ccall "feof" feof :: Ptr CFile -> IO CInt foreign import ccall "ferror" ferror :: Ptr CFile -> IO CInt foreign import ccall "perror" perror :: CString -> IO () -- * @stdlib.h@ foreign import ccall "bindings_cs_EXIT_FAILURE" _EXIT_FAILURE :: CInt foreign import ccall "bindings_cs_EXIT_SUCCESS" _EXIT_SUCCESS :: CInt foreign import ccall "bindings_cs_RAND_MAX" _RAND_MAX :: CInt foreign import ccall "bindings_cs_MB_CUR_MAX" _MB_CUR_MAX :: IO CSize foreign import ccall "atof" atof :: CString -> IO CDouble foreign import ccall "atoi" atoi :: CString -> IO CInt foreign import ccall "atol" atol :: CString -> IO CLong foreign import ccall "atoll" atoll :: CString -> IO CLLong foreign import ccall "strtod" strtod :: CString -> Ptr CString -> IO CDouble foreign import ccall "strtof" strtof :: CString -> Ptr CString -> IO CFloat foreign import ccall "strtold" strtold :: CString -> Ptr CString -> IO CLDouble foreign import ccall "strtol" strtol :: CString -> Ptr CString -> CInt -> IO CLong foreign import ccall "strtoll" strtoll :: CString -> Ptr CString -> CInt -> IO CLLong foreign import ccall "strtoul" strtoul :: CString -> Ptr CString -> CInt -> IO CULong foreign import ccall "strtoull" strtoull :: CString -> Ptr CString -> CInt -> IO CULLong foreign import ccall "rand" rand :: IO CInt foreign import ccall "srand" srand :: CUInt -> IO () foreign import ccall "calloc" calloc :: CSize -> CSize -> Ptr () foreign import ccall "free" free :: Ptr () -> IO () foreign import ccall "malloc" malloc :: CSize -> IO (Ptr ()) foreign import ccall "realloc" realloc :: Ptr () -> CSize -> IO (Ptr ()) foreign import ccall "abort" abort :: IO () foreign import ccall "atexit" atexit :: FunPtr CB000C -> IO CInt foreign import ccall "exit" exit :: CInt -> IO () foreign import ccall "_Exit" _Exit :: CInt -> IO () foreign import ccall "getenv" getenv :: CString -> IO CString foreign import ccall "system" system :: CString -> IO CInt foreign import ccall "bsearch" bsearch :: Ptr () -> Ptr () -> CSize -> CSize -> FunPtr CB0002 -> IO (Ptr ()) foreign import ccall "qsort" qsort :: Ptr () -> CSize -> CSize -> FunPtr CB0002 -> IO () foreign import ccall "abs" abs :: CInt -> IO CInt foreign import ccall "labs" labs :: CLong -> IO CLong foreign import ccall "llabs" llabs :: CLLong -> IO CLLong foreign import ccall "mblen" mblen :: CString -> CSize -> IO CInt foreign import ccall "mbtowc" mbtowc :: CWString -> CString -> CSize -> IO CInt foreign import ccall "wctomb" wctomb :: CString -> CWchar -> IO CInt foreign import ccall "mbstowcs" mbstowcs :: CWString -> CString -> CSize -> IO CSize foreign import ccall "wcstombs" wcstombs :: CString -> CWString -> CSize -> IO CSize -- * @string.h@ foreign import ccall "memcpy" memcpy :: Ptr () -> Ptr () -> CSize -> IO (Ptr ()) foreign import ccall "memmove" memmove :: Ptr () -> Ptr () -> CSize -> IO (Ptr ()) foreign import ccall "strcpy" strcpy :: CString -> CString -> IO CString foreign import ccall "strncpy" strncpy :: CString -> CString -> CSize -> IO CString foreign import ccall "strcat" strcat :: CString -> CString -> IO CString foreign import ccall "strncat" strncat :: CString -> CString -> CSize -> IO CString foreign import ccall "memcmp" memcmp :: Ptr () -> Ptr () -> CSize -> IO CInt foreign import ccall "strcmp" strcmp :: CString -> CString -> IO CInt foreign import ccall "strcoll" strcoll :: CString -> CString -> IO CInt foreign import ccall "strncmp" strncmp :: CString -> CString -> CSize -> IO CInt foreign import ccall "strxfrm" strxfrm :: CString -> CString -> CSize -> IO CSize foreign import ccall "memchr" memchr :: Ptr () -> CInt -> CSize -> IO (Ptr ()) foreign import ccall "strchr" strchr :: CString -> CInt -> IO CString foreign import ccall "strcspn" strcspn :: CString -> CString -> IO CSize foreign import ccall "strpbrk" strpbrk :: CString -> CString -> IO CString foreign import ccall "strrchr" strrchr :: CString -> CInt -> IO CString foreign import ccall "strspn" strspn :: CString -> CString -> IO CSize foreign import ccall "strstr" strstr :: CString -> CString -> IO CString foreign import ccall "strtok" strtok :: CString -> CString -> IO CString foreign import ccall "memset" memset :: Ptr () -> CInt -> CSize -> IO (Ptr ()) foreign import ccall "strerror" strerror :: CInt -> IO CString foreign import ccall "strlen" strlen :: CString -> IO CSize -- * @time.h@ foreign import ccall "bindings_cs_CLOCKS_PER_SEC" _CLOCKS_PER_SEC :: CClock foreign import ccall "clock" clock :: IO CClock foreign import ccall "difftime" difftime :: CTime -> CTime -> IO CDouble foreign import ccall "time" time :: Ptr CTime -> IO CTime foreign import ccall "ctime" ctime :: Ptr CTime -> IO CString -- * @wchar.h@ foreign import ccall "fgetws" fgetws :: CWString -> CInt -> Ptr CFile -> IO CWString foreign import ccall "fputws" fputws :: CWString -> Ptr CFile -> IO CInt foreign import ccall "fwide" fwide :: Ptr CFile -> CInt -> IO CInt foreign import ccall "wcstod" wcstod :: CWString -> Ptr CString -> IO CDouble foreign import ccall "wcstof" wcstof :: CWString -> Ptr CString -> IO CFloat foreign import ccall "wcstold" wcstold :: CWString -> Ptr CString -> IO CLDouble foreign import ccall "wcstol" wcstol :: CWString -> Ptr CWString -> CInt -> IO CLong foreign import ccall "wcstoll" wcstoll :: CWString -> Ptr CWString -> CInt -> IO CLLong foreign import ccall "wcstoul" wcstoul :: CWString -> Ptr CWString -> CInt -> IO CULong foreign import ccall "wcstoull" wcstoull :: CWString -> Ptr CWString -> CInt -> IO CULLong foreign import ccall "wcscpy" wcscpy :: CWString -> CWString -> IO CWString foreign import ccall "wcsncpy" wcsncpy :: CWString -> CWString -> CSize -> IO CWString foreign import ccall "wmemcpy" wmemcpy :: CWString -> CWString -> CSize -> IO CWString foreign import ccall "wmemmove" wmemmove :: CWString -> CWString -> CSize -> IO CWString foreign import ccall "wcscat" wcscat :: CWString -> CWString -> IO CWString foreign import ccall "wcsncat" wcsncat :: CWString -> CWString -> CSize -> IO CWString foreign import ccall "wcscmp" wcscmp :: CWString -> CWString -> IO CInt foreign import ccall "wcscoll" wcscoll :: CWString -> CWString -> IO CInt foreign import ccall "wcsncmp" wcsncmp :: CWString -> CWString -> CSize -> IO CInt foreign import ccall "wcsxfrm" wcsxfrm :: CWString -> CWString -> CSize -> IO CSize foreign import ccall "wmemcmp" wmemcmp :: CWString -> CWString -> CSize -> IO CInt foreign import ccall "wcschr" wcschr :: CWString -> CWchar -> IO CWchar foreign import ccall "wcscspn" wcscspn :: CWString -> CWString -> IO CSize foreign import ccall "wcspbrk" wcspbrk :: CWString -> CWString -> IO CWString foreign import ccall "wcsrchr" wcsrchr :: CWString -> CWchar -> IO CWString foreign import ccall "wcsspn" wcsspn :: CWString -> CWString -> IO CSize foreign import ccall "wcsstr" wcsstr :: CWString -> CWString -> IO CWString foreign import ccall "wcstok" wcstok :: CWString -> CWString -> CWString -> IO CWString foreign import ccall "wmemchr" wmemchr :: CWString -> CWchar -> CSize -> IO CWString foreign import ccall "wcslen" wcslen :: CWString -> IO CSize foreign import ccall "wmemset" wmemset :: CWString -> CWchar -> CSize -> IO CWString