module Bindings.APU.Version where
import Foreign.Ptr (Ptr,FunPtr,plusPtr)
import Foreign.Ptr (wordPtrToPtr,castPtrToFunPtr)
import Foreign.Storable
import Foreign.C.Types
import Foreign.C.String (CString,CStringLen,CWString,CWStringLen)
import Foreign.Marshal.Alloc (alloca)
import Foreign.Marshal.Array (peekArray,pokeArray)
import Data.Int
import Data.Word
import Bindings.APR.Version
c'APU_MAJOR_VERSION = 1
c'APU_MAJOR_VERSION :: (Num a) => a
c'APU_MINOR_VERSION = 3
c'APU_MINOR_VERSION :: (Num a) => a
c'APU_PATCH_VERSION = 9
c'APU_PATCH_VERSION :: (Num a) => a
foreign import ccall "array_APU_VERSION_STRING" c'APU_VERSION_STRING
:: Ptr (CChar)
foreign import ccall "apu_version" c'apu_version
:: Ptr C'apr_version_t -> IO ()
foreign import ccall "&apu_version" p'apu_version
:: FunPtr (Ptr C'apr_version_t -> IO ())
foreign import ccall "apu_version_string" c'apu_version_string
:: IO (Ptr CChar)
foreign import ccall "&apu_version_string" p'apu_version_string
:: FunPtr (IO (Ptr CChar))