{-# INCLUDE <bindings.macros.h> #-}
{-# INCLUDE <stdio.h> #-}
{-# LINE 1 "src/Bindings/C/Stdio.hsc" #-}

{-# LINE 2 "src/Bindings/C/Stdio.hsc" #-}

{-# LINE 3 "src/Bindings/C/Stdio.hsc" #-}

-- | <http://www.opengroup.org/onlinepubs/9699919799/basedefs/stdio.h.html>

module Bindings.C.Stdio where
import Foreign
import Foreign.C

c'BUFSIZ = 8192 ; c'BUFSIZ :: (Num a) => a

{-# LINE 11 "src/Bindings/C/Stdio.hsc" #-}
c'L_tmpnam = 20 ; c'L_tmpnam :: (Num a) => a

{-# LINE 12 "src/Bindings/C/Stdio.hsc" #-}
c'_IOFBF = 0 ; c'_IOFBF :: (Num a) => a

{-# LINE 13 "src/Bindings/C/Stdio.hsc" #-}
c'_IOLBF = 1 ; c'_IOLBF :: (Num a) => a

{-# LINE 14 "src/Bindings/C/Stdio.hsc" #-}
c'_IONBF = 2 ; c'_IONBF :: (Num a) => a

{-# LINE 15 "src/Bindings/C/Stdio.hsc" #-}
c'SEEK_CUR = 1 ; c'SEEK_CUR :: (Num a) => a

{-# LINE 16 "src/Bindings/C/Stdio.hsc" #-}
c'SEEK_END = 2 ; c'SEEK_END :: (Num a) => a

{-# LINE 17 "src/Bindings/C/Stdio.hsc" #-}
c'SEEK_SET = 0 ; c'SEEK_SET :: (Num a) => a

{-# LINE 18 "src/Bindings/C/Stdio.hsc" #-}
c'FILENAME_MAX = 4096 ; c'FILENAME_MAX :: (Num a) => a

{-# LINE 19 "src/Bindings/C/Stdio.hsc" #-}
c'FOPEN_MAX = 16 ; c'FOPEN_MAX :: (Num a) => a

{-# LINE 20 "src/Bindings/C/Stdio.hsc" #-}
c'TMP_MAX = 238328 ; c'TMP_MAX :: (Num a) => a

{-# LINE 21 "src/Bindings/C/Stdio.hsc" #-}
c'EOF = -1 ; c'EOF :: (Num a) => a

{-# LINE 22 "src/Bindings/C/Stdio.hsc" #-}

foreign import ccall "clearerr" c'clearerr :: Ptr CFile -> IO ()
foreign import ccall "&clearerr" p'clearerr :: FunPtr (Ptr CFile -> IO ())

{-# LINE 24 "src/Bindings/C/Stdio.hsc" #-}
foreign import ccall "fclose" c'fclose :: Ptr CFile -> IO CInt
foreign import ccall "&fclose" p'fclose :: FunPtr (Ptr CFile -> IO CInt)

{-# LINE 25 "src/Bindings/C/Stdio.hsc" #-}
foreign import ccall "feof" c'feof :: Ptr CFile -> IO CInt
foreign import ccall "&feof" p'feof :: FunPtr (Ptr CFile -> IO CInt)

{-# LINE 26 "src/Bindings/C/Stdio.hsc" #-}
foreign import ccall "ferror" c'ferror :: Ptr CFile -> IO CInt
foreign import ccall "&ferror" p'ferror :: FunPtr (Ptr CFile -> IO CInt)

{-# LINE 27 "src/Bindings/C/Stdio.hsc" #-}
foreign import ccall "fflush" c'fflush :: Ptr CFile -> IO CInt
foreign import ccall "&fflush" p'fflush :: FunPtr (Ptr CFile -> IO CInt)

{-# LINE 28 "src/Bindings/C/Stdio.hsc" #-}
foreign import ccall "fgetc" c'fgetc :: Ptr CFile -> IO CInt
foreign import ccall "&fgetc" p'fgetc :: FunPtr (Ptr CFile -> IO CInt)

{-# LINE 29 "src/Bindings/C/Stdio.hsc" #-}
foreign import ccall "fgetpos" c'fgetpos :: Ptr CFile -> Ptr CFpos -> IO CInt
foreign import ccall "&fgetpos" p'fgetpos :: FunPtr (Ptr CFile -> Ptr CFpos -> IO CInt)

{-# LINE 30 "src/Bindings/C/Stdio.hsc" #-}
foreign import ccall "fgets" c'fgets :: CString -> CInt -> Ptr CFile -> IO CString
foreign import ccall "&fgets" p'fgets :: FunPtr (CString -> CInt -> Ptr CFile -> IO CString)

{-# LINE 31 "src/Bindings/C/Stdio.hsc" #-}
foreign import ccall "fopen" c'fopen :: CString -> CString -> IO (Ptr CFile)
foreign import ccall "&fopen" p'fopen :: FunPtr (CString -> CString -> IO (Ptr CFile))

{-# LINE 32 "src/Bindings/C/Stdio.hsc" #-}
foreign import ccall "fputc" c'fputc :: CInt -> Ptr CFile -> IO CInt
foreign import ccall "&fputc" p'fputc :: FunPtr (CInt -> Ptr CFile -> IO CInt)

{-# LINE 33 "src/Bindings/C/Stdio.hsc" #-}
foreign import ccall "fputs" c'fputs :: CString -> Ptr CFile -> IO CInt
foreign import ccall "&fputs" p'fputs :: FunPtr (CString -> Ptr CFile -> IO CInt)

{-# LINE 34 "src/Bindings/C/Stdio.hsc" #-}
foreign import ccall "fread" c'fread :: Ptr () -> CSize -> CSize -> Ptr CFile -> IO CSize
foreign import ccall "&fread" p'fread :: FunPtr (Ptr () -> CSize -> CSize -> Ptr CFile -> IO CSize)

{-# LINE 35 "src/Bindings/C/Stdio.hsc" #-}
foreign import ccall "freopen" c'freopen :: CString -> CString -> Ptr CFile -> IO (Ptr CFile)
foreign import ccall "&freopen" p'freopen :: FunPtr (CString -> CString -> Ptr CFile -> IO (Ptr CFile))

{-# LINE 36 "src/Bindings/C/Stdio.hsc" #-}
foreign import ccall "fseek" c'fseek :: Ptr CFile -> CLong -> CInt -> IO CInt
foreign import ccall "&fseek" p'fseek :: FunPtr (Ptr CFile -> CLong -> CInt -> IO CInt)

{-# LINE 37 "src/Bindings/C/Stdio.hsc" #-}
foreign import ccall "fsetpos" c'fsetpos :: Ptr CFile -> Ptr CFpos -> IO CInt
foreign import ccall "&fsetpos" p'fsetpos :: FunPtr (Ptr CFile -> Ptr CFpos -> IO CInt)

{-# LINE 38 "src/Bindings/C/Stdio.hsc" #-}
foreign import ccall "ftell" c'ftell :: Ptr CFile -> IO CLong
foreign import ccall "&ftell" p'ftell :: FunPtr (Ptr CFile -> IO CLong)

{-# LINE 39 "src/Bindings/C/Stdio.hsc" #-}
foreign import ccall "fwrite" c'fwrite :: Ptr () -> CSize -> CSize -> Ptr CFile -> IO CSize
foreign import ccall "&fwrite" p'fwrite :: FunPtr (Ptr () -> CSize -> CSize -> Ptr CFile -> IO CSize)

{-# LINE 40 "src/Bindings/C/Stdio.hsc" #-}
foreign import ccall "getc" c'getc :: Ptr CFile -> IO CInt
foreign import ccall "&getc" p'getc :: FunPtr (Ptr CFile -> IO CInt)

{-# LINE 41 "src/Bindings/C/Stdio.hsc" #-}
foreign import ccall "getchar" c'getchar :: IO CInt
foreign import ccall "&getchar" p'getchar :: FunPtr (IO CInt)

{-# LINE 42 "src/Bindings/C/Stdio.hsc" #-}
foreign import ccall "perror" c'perror :: CString -> IO ()
foreign import ccall "&perror" p'perror :: FunPtr (CString -> IO ())

{-# LINE 43 "src/Bindings/C/Stdio.hsc" #-}
foreign import ccall "putc" c'putc :: CInt -> Ptr CFile -> IO CInt
foreign import ccall "&putc" p'putc :: FunPtr (CInt -> Ptr CFile -> IO CInt)

{-# LINE 44 "src/Bindings/C/Stdio.hsc" #-}
foreign import ccall "putchar" c'putchar :: CInt -> IO CInt
foreign import ccall "&putchar" p'putchar :: FunPtr (CInt -> IO CInt)

{-# LINE 45 "src/Bindings/C/Stdio.hsc" #-}
foreign import ccall "puts" c'puts :: CString -> IO CInt
foreign import ccall "&puts" p'puts :: FunPtr (CString -> IO CInt)

{-# LINE 46 "src/Bindings/C/Stdio.hsc" #-}
foreign import ccall "remove" c'remove :: CString -> IO CInt
foreign import ccall "&remove" p'remove :: FunPtr (CString -> IO CInt)

{-# LINE 47 "src/Bindings/C/Stdio.hsc" #-}
foreign import ccall "rename" c'rename :: CString -> CString -> IO CInt
foreign import ccall "&rename" p'rename :: FunPtr (CString -> CString -> IO CInt)

{-# LINE 48 "src/Bindings/C/Stdio.hsc" #-}
foreign import ccall "rewind" c'rewind :: Ptr CFile -> IO ()
foreign import ccall "&rewind" p'rewind :: FunPtr (Ptr CFile -> IO ())

{-# LINE 49 "src/Bindings/C/Stdio.hsc" #-}
foreign import ccall "setbuf" c'setbuf :: Ptr CFile -> CString -> IO ()
foreign import ccall "&setbuf" p'setbuf :: FunPtr (Ptr CFile -> CString -> IO ())

{-# LINE 50 "src/Bindings/C/Stdio.hsc" #-}
foreign import ccall "setvbuf" c'setvbuf :: Ptr CFile -> CString -> CInt -> CSize -> IO CInt
foreign import ccall "&setvbuf" p'setvbuf :: FunPtr (Ptr CFile -> CString -> CInt -> CSize -> IO CInt)

{-# LINE 51 "src/Bindings/C/Stdio.hsc" #-}
foreign import ccall "tmpfile" c'tmpfile :: IO (Ptr CFile)
foreign import ccall "&tmpfile" p'tmpfile :: FunPtr (IO (Ptr CFile))

{-# LINE 52 "src/Bindings/C/Stdio.hsc" #-}
foreign import ccall "ungetc" c'ungetc :: CInt -> Ptr CFile -> IO CInt
foreign import ccall "&ungetc" p'ungetc :: FunPtr (CInt -> Ptr CFile -> IO CInt)

{-# LINE 53 "src/Bindings/C/Stdio.hsc" #-}