module System.Glib.GList (
GList,
readGList,
fromGList,
toGList,
withGList,
GSList,
readGSList,
fromGSList,
fromGSListRev,
toGSList,
withGSList,
) where
import Foreign
import Control.Exception (bracket)
import Control.Monad (foldM)
type GList = Ptr (())
type GSList = Ptr (())
readGList :: GList -> IO [Ptr a]
readGList glist
| glist==nullPtr = return []
| otherwise = do
x <- (\ptr -> do {peekByteOff ptr 0 ::IO (Ptr ())}) glist
glist' <- (\ptr -> do {peekByteOff ptr 4 ::IO (Ptr ())}) glist
xs <- readGList glist'
return (castPtr x:xs)
fromGList :: GList -> IO [Ptr a]
fromGList glist = do
glist' <- g_list_reverse glist
extractList glist' []
where
extractList gl xs
| gl==nullPtr = return xs
| otherwise = do
x <- (\ptr -> do {peekByteOff ptr 0 ::IO (Ptr ())}) gl
gl' <- g_list_delete_link gl gl
extractList gl' (castPtr x:xs)
readGSList :: GSList -> IO [Ptr a]
readGSList gslist
| gslist==nullPtr = return []
| otherwise = do
x <- (\ptr -> do {peekByteOff ptr 0 ::IO (Ptr ())}) gslist
gslist' <- (\ptr -> do {peekByteOff ptr 4 ::IO (Ptr ())}) gslist
xs <- readGSList gslist'
return (castPtr x:xs)
fromGSList :: GSList -> IO [Ptr a]
fromGSList gslist
| gslist==nullPtr = return []
| otherwise = do
x <- (\ptr -> do {peekByteOff ptr 0 ::IO (Ptr ())}) gslist
gslist' <- g_slist_delete_link gslist gslist
xs <- fromGSList gslist'
return (castPtr x:xs)
fromGSListRev :: GSList -> IO [Ptr a]
fromGSListRev gslist =
extractList gslist []
where
extractList gslist xs
| gslist==nullPtr = return xs
| otherwise = do
x <- (\ptr -> do {peekByteOff ptr 0 ::IO (Ptr ())}) gslist
gslist' <- g_slist_delete_link gslist gslist
extractList gslist' (castPtr x:xs)
toGList :: [Ptr a] -> IO GList
toGList = foldM prepend nullPtr . reverse
where
prepend l x = g_list_prepend l (castPtr x)
toGSList :: [Ptr a] -> IO GSList
toGSList = foldM prepend nullPtr . reverse
where
prepend l x = g_slist_prepend l (castPtr x)
withGList :: [Ptr a] -> (GSList -> IO b) -> IO b
withGList xs = bracket (toGList xs) g_list_free
withGSList :: [Ptr a] -> (GSList -> IO b) -> IO b
withGSList xs = bracket (toGSList xs) g_slist_free
foreign import ccall unsafe "g_list_reverse"
g_list_reverse :: ((Ptr ()) -> (IO (Ptr ())))
foreign import ccall unsafe "g_list_delete_link"
g_list_delete_link :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))
foreign import ccall unsafe "g_slist_delete_link"
g_slist_delete_link :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))
foreign import ccall unsafe "g_list_prepend"
g_list_prepend :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))
foreign import ccall unsafe "g_slist_prepend"
g_slist_prepend :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))
foreign import ccall unsafe "g_list_free"
g_list_free :: ((Ptr ()) -> (IO ()))
foreign import ccall unsafe "g_slist_free"
g_slist_free :: ((Ptr ()) -> (IO ()))