module Bindings.SVM 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
foreign import ccall "&libsvm_version" p'libsvm_version
:: Ptr (CInt)
data C'svm_node = C'svm_node{
c'svm_node'index :: CInt
,
c'svm_node'value :: CDouble
} deriving (Eq,Show)
instance Storable C'svm_node where
sizeOf _ = 12
alignment = sizeOf
peek p = do
v0 <- peekByteOff p 0
v1 <- peekByteOff p 4
return $ C'svm_node v0 v1
poke p (C'svm_node v0 v1) = do
pokeByteOff p 0 v0
pokeByteOff p 4 v1
return ()
data C'svm_problem = C'svm_problem{
c'svm_problem'l :: CInt
,
c'svm_problem'y :: Ptr CDouble
,
c'svm_problem'x :: Ptr (Ptr C'svm_node)
} deriving (Eq,Show)
instance Storable C'svm_problem where
sizeOf _ = 12
alignment = sizeOf
peek p = do
v0 <- peekByteOff p 0
v1 <- peekByteOff p 4
v2 <- peekByteOff p 8
return $ C'svm_problem v0 v1 v2
poke p (C'svm_problem v0 v1 v2) = do
pokeByteOff p 0 v0
pokeByteOff p 4 v1
pokeByteOff p 8 v2
return ()
c'C_SVC = 0
c'C_SVC :: (Num a) => a
c'NU_SVC = 1
c'NU_SVC :: (Num a) => a
c'ONE_CLASS = 2
c'ONE_CLASS :: (Num a) => a
c'EPSILON_SVR = 3
c'EPSILON_SVR :: (Num a) => a
c'NU_SVR = 4
c'NU_SVR :: (Num a) => a
c'LINEAR = 0
c'LINEAR :: (Num a) => a
c'POLY = 1
c'POLY :: (Num a) => a
c'RBF = 2
c'RBF :: (Num a) => a
c'SIGMOID = 3
c'SIGMOID :: (Num a) => a
c'PRECOMPUTED = 4
c'PRECOMPUTED :: (Num a) => a
data C'svm_parameter = C'svm_parameter{
c'svm_parameter'svm_type :: CInt
,
c'svm_parameter'kernel_type :: CInt
,
c'svm_parameter'degree :: CInt
,
c'svm_parameter'gamma :: CDouble
,
c'svm_parameter'coef0 :: CDouble
,
c'svm_parameter'cache_size :: CDouble
,
c'svm_parameter'eps :: CDouble
,
c'svm_parameter'C :: CDouble
,
c'svm_parameter'nr_weight :: CInt
,
c'svm_parameter'weight_label :: Ptr CInt
,
c'svm_parameter'weight :: Ptr CDouble
,
c'svm_parameter'nu :: CDouble
,
c'svm_parameter'p :: CDouble
,
c'svm_parameter'shrinking :: CInt
,
c'svm_parameter'probability :: CInt
} deriving (Eq,Show)
instance Storable C'svm_parameter where
sizeOf _ = 88
alignment = sizeOf
peek p = do
v0 <- peekByteOff p 0
v1 <- peekByteOff p 4
v2 <- peekByteOff p 8
v3 <- peekByteOff p 12
v4 <- peekByteOff p 20
v5 <- peekByteOff p 28
v6 <- peekByteOff p 36
v7 <- peekByteOff p 44
v8 <- peekByteOff p 52
v9 <- peekByteOff p 56
v10 <- peekByteOff p 60
v11 <- peekByteOff p 64
v12 <- peekByteOff p 72
v13 <- peekByteOff p 80
v14 <- peekByteOff p 84
return $ C'svm_parameter v0 v1 v2 v3 v4 v5 v6 v7 v8 v9 v10 v11 v12 v13 v14
poke p (C'svm_parameter v0 v1 v2 v3 v4 v5 v6 v7 v8 v9 v10 v11 v12 v13 v14) = do
pokeByteOff p 0 v0
pokeByteOff p 4 v1
pokeByteOff p 8 v2
pokeByteOff p 12 v3
pokeByteOff p 20 v4
pokeByteOff p 28 v5
pokeByteOff p 36 v6
pokeByteOff p 44 v7
pokeByteOff p 52 v8
pokeByteOff p 56 v9
pokeByteOff p 60 v10
pokeByteOff p 64 v11
pokeByteOff p 72 v12
pokeByteOff p 80 v13
pokeByteOff p 84 v14
return ()
data C'svm_model = C'svm_model
foreign import ccall "svm_train" c'svm_train
:: Ptr C'svm_problem -> Ptr C'svm_parameter -> IO (Ptr C'svm_model)
foreign import ccall "&svm_train" p'svm_train
:: FunPtr (Ptr C'svm_problem -> Ptr C'svm_parameter -> IO (Ptr C'svm_model))
foreign import ccall "svm_cross_validation" c'svm_cross_validation
:: Ptr C'svm_problem -> Ptr C'svm_parameter -> CInt -> Ptr CDouble -> IO ()
foreign import ccall "&svm_cross_validation" p'svm_cross_validation
:: FunPtr (Ptr C'svm_problem -> Ptr C'svm_parameter -> CInt -> Ptr CDouble -> IO ())
foreign import ccall "svm_save_model" c'svm_save_model
:: CString -> Ptr C'svm_model -> IO ()
foreign import ccall "&svm_save_model" p'svm_save_model
:: FunPtr (CString -> Ptr C'svm_model -> IO ())
foreign import ccall "svm_load_model" c'svm_load_model
:: CString -> IO (Ptr C'svm_model)
foreign import ccall "&svm_load_model" p'svm_load_model
:: FunPtr (CString -> IO (Ptr C'svm_model))
foreign import ccall "svm_get_svm_type" c'svm_get_svm_type
:: Ptr C'svm_model -> IO CInt
foreign import ccall "&svm_get_svm_type" p'svm_get_svm_type
:: FunPtr (Ptr C'svm_model -> IO CInt)
foreign import ccall "svm_get_nr_class" c'svm_get_nr_class
:: Ptr C'svm_model -> IO CInt
foreign import ccall "&svm_get_nr_class" p'svm_get_nr_class
:: FunPtr (Ptr C'svm_model -> IO CInt)
foreign import ccall "svm_get_labels" c'svm_get_labels
:: Ptr C'svm_model -> Ptr CInt -> IO ()
foreign import ccall "&svm_get_labels" p'svm_get_labels
:: FunPtr (Ptr C'svm_model -> Ptr CInt -> IO ())
foreign import ccall "svm_get_svr_probability" c'svm_get_svr_probability
:: Ptr C'svm_model -> IO CDouble
foreign import ccall "&svm_get_svr_probability" p'svm_get_svr_probability
:: FunPtr (Ptr C'svm_model -> IO CDouble)
foreign import ccall "svm_predict_values" c'svm_predict_values
:: Ptr C'svm_model -> Ptr C'svm_node -> Ptr CDouble -> IO ()
foreign import ccall "&svm_predict_values" p'svm_predict_values
:: FunPtr (Ptr C'svm_model -> Ptr C'svm_node -> Ptr CDouble -> IO ())
foreign import ccall "svm_predict" c'svm_predict
:: Ptr C'svm_model -> Ptr C'svm_node -> IO CDouble
foreign import ccall "&svm_predict" p'svm_predict
:: FunPtr (Ptr C'svm_model -> Ptr C'svm_node -> IO CDouble)
foreign import ccall "svm_predict_probability" c'svm_predict_probability
:: Ptr C'svm_model -> Ptr C'svm_node -> Ptr CDouble -> IO CDouble
foreign import ccall "&svm_predict_probability" p'svm_predict_probability
:: FunPtr (Ptr C'svm_model -> Ptr C'svm_node -> Ptr CDouble -> IO CDouble)
foreign import ccall "svm_free_model_content" c'svm_free_model_content
:: Ptr C'svm_model -> IO ()
foreign import ccall "&svm_free_model_content" p'svm_free_model_content
:: FunPtr (Ptr C'svm_model -> IO ())
foreign import ccall "svm_free_and_destroy_model" c'svm_free_and_destroy_model
:: Ptr (Ptr C'svm_model) -> IO ()
foreign import ccall "&svm_free_and_destroy_model" p'svm_free_and_destroy_model
:: FunPtr (Ptr (Ptr C'svm_model) -> IO ())
foreign import ccall "svm_destroy_param" c'svm_destroy_param
:: Ptr C'svm_parameter -> IO ()
foreign import ccall "&svm_destroy_param" p'svm_destroy_param
:: FunPtr (Ptr C'svm_parameter -> IO ())
foreign import ccall "svm_check_parameter" c'svm_check_parameter
:: Ptr C'svm_problem -> Ptr C'svm_parameter -> IO CString
foreign import ccall "&svm_check_parameter" p'svm_check_parameter
:: FunPtr (Ptr C'svm_problem -> Ptr C'svm_parameter -> IO CString)
foreign import ccall "svm_check_probability_model" c'svm_check_probability_model
:: Ptr C'svm_model -> IO CInt
foreign import ccall "&svm_check_probability_model" p'svm_check_probability_model
:: FunPtr (Ptr C'svm_model -> IO CInt)
foreign import ccall "svm_set_print_string_function" c'svm_set_print_string_function
:: FunPtr (CString -> IO ()) -> IO ()
foreign import ccall "&svm_set_print_string_function" p'svm_set_print_string_function
:: FunPtr (FunPtr (CString -> IO ()) -> IO ())