[Haskell-cafe] bindings to the xmms_remote API, GList and something more

Andrea Rossato mailing_list at istitutocolli.org
Fri Sep 21 05:44:38 EDT 2007


On Fri, Sep 21, 2007 at 09:08:13AM +0200, Andrea Rossato wrote:
> Hi,
> I think there's a huge flaw in the Haskell design:


I don't know if this is a feature, the fact that most of the times you
can find a solution to your problems by yourself, but only after
polluting the haskell-cafe mailing list with your question...

> Basically there are two C types I'm having problem with:
> 
> 1. GList: even though I read the gtk2hs code I do not exactly
>    understand how to create a GList to feed to this function:
> 
>     void xmms_remote_playlist_add(gint session, GList * list);
> 
>     As far as I understand this function takes a session number and a
>     list of files' names. Still I seem not to be able to create a
>     wrapper function around the imported one.

Well I used gtk2hs more carefully and that's the wrapper:

foreign import ccall unsafe "beepctrl.h xmms_remote_playlist_add"
    c_xmms_remote_playlist_add :: CInt -> GList -> IO ()

xmms_remote_playlist_add :: Session -> [String] -> IO ()
xmms_remote_playlist_add s fns = do
  l <- mapM newCString fns >>= toGList
  c_xmms_remote_playlist_add (fromIntegral s) l

-- stolen from gtk2hs 
#include <glib.h>
{# context lib="glib" prefix="g" #}
{#pointer * GList#}

toGList :: [Ptr a] -> IO GList
toGList pl = makeList nullPtr pl
  where
    makeList :: GList -> [Ptr a] -> IO GList
    makeList current (x:xs) = do
      newHead <- {#call unsafe list_prepend#} current (castPtr x)
      makeList newHead xs
    makeList current [] = return current


> 2. what a "gchar ** list" is? As far as my C goes, it should be an array
>    of strings, right? What should I use on the Haskell side, newArray?
>    void xmms_remote_playlist(gint session, gchar ** list, gint num,
> 	                           gboolean enqueue);

yes, indeed:
foreign import ccall unsafe "beepctrl.h xmms_remote_playlist"
    c_xmms_remote_playlist :: CInt -> Ptr CString -> CInt -> {# type gboolean #}  -> IO ()

xmms_remote_playlist :: Session -> [String] -> Bool -> IO ()
xmms_remote_playlist s l b = do
  la <- newArray =<< mapM newCString l
  c_xmms_remote_playlist (fromIntegral s) la (fromIntegral $ length l) (fromBool b)

The next two question are still waiting for an answer though...;-)

> 3. c2hs v. hsc2hs? Which should I prefer? In c2hs I write {#pointer *
>    GList#}. What is the equivalent in hsc2hs?
> 
> 4. As I said, I solved my personal problem: I imported enough
>    functions to create the client I needed. Releasing the library is
>    just something I would like to do, to give something back to the
>    Haskell community. So this is something useful if I can provide
>    robust and well designed code. This is a name space question: what
>    is the name of the exported module? Sound.XMMS, Sound.XmmsRemote?
>    Is the some kind of convention I should be referring to?


I apologize for the noise. The auto-replay is for documentation (who
knows, maybe others searching the list archives may find this info
useful).

Andrea



More information about the Haskell-Cafe mailing list