{-# 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.Utilities 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 ------------------ --Help Functions safePeekCString cstring = if cstring == nullPtr then return "" else peekCString cstring withString :: String -> (CString -> IO (a)) -> IO (a) withString s action |s == "" = action nullPtr |otherwise = do c_s <- newCString s res <- action c_s free c_s return res ---------------------- wrapCallResult :: (Ptr C_xmmsc_connection -> IO (Ptr C_xmmsc_result)) -> (Connection -> IO Result) wrapCallResult c_function = flip withForeignPtr ( \ptrCon -> do result <- c_function ptrCon newForeignPtr xmmsc_result_unref result) --Decreases the references for the xmmsc_result_t When the number of references reaches 0 it will be freed. --void xmmsc_result_unref (xmmsc_result_t *res) foreign import ccall "xmmsclient/xmmsclient.h &xmmsc_result_unref" xmmsc_result_unref :: FunPtr (Ptr C_xmmsc_result -> IO ()) --References the xmmsc_result_t. --xmmsc_result_t *xmmsc_result_ref (xmmsc_result_t *res) foreign import ccall "xmmsclient/xmmsclient.h xmmsc_result_ref" xmmsc_result_ref :: Ptr C_xmmsc_result -> IO () --References the xmmsc_connection_t. --xmmsc_connection_t * xmmsc_ref (xmmsc_connection_t *c) foreign import ccall unsafe "xmmsclient/xmmsclient.h xmmsc_ref" xmmsc_ref :: Ptr C_xmmsc_connection -> IO (Ptr C_xmmsc_connection) --void xmmsc_unref (xmmsc_connection_t *connection) foreign import ccall "xmmsclient/xmmsclient.h &xmmsc_unref" xmmsc_unref :: FunPtr (Ptr C_xmmsc_connection -> IO ())