{-# LANGUAGE ForeignFunctionInterface #-}

-- Copyright 2010 Evgeniy Vodolazskiy (waterlaz@gmail.com)
--
-- This library is free software; you can redistribute it and/or
-- modify it under the terms of the GNU Lesser General Public
-- License as published by the Free Software Foundation; either
-- version 2.1 of the License, or (at your option) any later version.
--
-- This library is distributed in the hope that it will be useful,
-- but WITHOUT ANY WARRANTY; without even the implied warranty of
-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
-- Lesser General Public License for more details.

module Network.XMMS.Result where

import Foreign
import Foreign.Ptr
import Foreign.C.Types
import Foreign.C.String
import Foreign.ForeignPtr
import Foreign.Marshal.Alloc

import Network.XMMS.Constants
import Network.XMMS.Types
import Network.XMMS.Value
import Network.XMMS.Utilities



--Get the class of the result (default, signal, broadcast).
--xmmsc_result_type_t 	xmmsc_result_get_class (xmmsc_result_t *res)


--void 	xmmsc_result_disconnect (xmmsc_result_t *res)
foreign import ccall unsafe "xmmsclient/xmmsclient.h xmmsc_result_disconnect" 
    xmmsc_result_disconnect :: Ptr C_xmmsc_result -> IO ()
-- |Disconnect a signal or a broadcast.
resultDisconnect :: Result -> IO ()
resultDisconnect result = withForeignPtr result xmmsc_result_disconnect



--return the cookie of a resultset.
--uint32_t xmmsc_result_cookie_get (xmmsc_result_t *res)
 	
--void 	xmmsc_result_visc_set (xmmsc_result_t *res, xmmsc_visualization_t *visc)

--xmmsc_visualization_t * 	xmmsc_result_visc_get (xmmsc_result_t *res)

--xmmsv_t *value, void *userdata
foreign import ccall "wrapper"
  wrapper :: (Ptr C_xmmsc_value -> Ptr () -> IO CInt) -> IO (FunPtr (Ptr C_xmmsc_value -> Ptr () -> IO CInt))
    
xmmsCallback :: (XMMSCV -> IO Bool) -> IO (FunPtr (Ptr C_xmmsc_value -> Ptr () -> IO CInt))
xmmsCallback f = do
    let c_f valuePtr ptr = do
          value <- convertValueCtoHs valuePtr
          --result <- newForeignPtr xmmsc_result_unref resultPtr
          keepAlive <- f value
          if keepAlive then return 1 else return 0
    wrapper c_f
    
            
            

--void xmmsc_result_notifier_set (xmmsc_result_t *res, xmmsc_result_notifier_t func, void *user_data)
-- |Set up a callback for the result retrival. This callback Will be called when the answers arrives. 
foreign import ccall safe "xmmsclient/xmmsclient.h xmmsc_result_notifier_set" 
    xmmsc_result_notifier_set :: Ptr C_xmmsc_result -> FunPtr (Ptr C_xmmsc_value -> Ptr () -> IO CInt) -> Ptr () -> IO ()
resultNotifierSet :: Result -> (XMMSCV -> IO Bool) -> IO ()
resultNotifierSet result f = do
    xmmsF <- xmmsCallback f
    withForeignPtr result (\ptr -> xmmsc_result_notifier_set ptr xmmsF nullPtr)


--Set up a callback for the result retrieval.
--void 	xmmsc_result_notifier_set_full (xmmsc_result_t *res, xmmsc_result_notifier_t func, void *user_data, xmmsc_user_data_free_func_t free_func)
 	
 
--void xmmsc_result_wait (xmmsc_result_t *res)
foreign import ccall unsafe "xmmsclient/xmmsclient.h xmmsc_result_wait" 
    xmmsc_result_wait :: Ptr C_xmmsc_result -> IO ()
-- |Block for the reply.
resultWait :: Result -> IO ()
resultWait result = withForeignPtr result xmmsc_result_wait


--xmmsc_connection_t * 	xmmsc_result_get_connection (xmmsc_result_t *res)
foreign import ccall unsafe "xmmsclient/xmmsclient.h xmmsc_result_get_connection" 
    xmmsc_result_get_connection :: Ptr C_xmmsc_result -> IO (Ptr C_xmmsc_connection)
resultGetConnection :: Result -> IO (Connection)
resultGetConnection result = do
    conPtr <- withForeignPtr result xmmsc_result_get_connection
    xmmsc_ref conPtr
    newForeignPtr xmmsc_unref conPtr
        


--Get the value from a result. 
--xmmsv_t * xmmsc_result_get_value  (xmmsc_result_t  *res)
--This function is not used here and gets imported elsewhere