-- GENERATED by C->Haskell Compiler, version 0.13.13 (gtk2hs branch) "Bin IO", 27 May 2012 (Haskell)
-- Edit the ORIGNAL .chs file instead!


{-# LINE 1 "./System/Glib/GList.chs" #-}
-- -*-haskell-*-
--  GIMP Toolkit (GTK)
--
--  Author : Axel Simon
--
--  Created: 19 March 2002
--
--  Copyright (C) 2002 Axel Simon
--
--  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.
--
-- |
-- Maintainer  : gtk2hs-users@lists.sourceforge.net
-- Stability   : provisional
-- Portability : portable (depends on GHC)
--
-- Defines functions to extract data from a GList and to produce a GList from
-- a list of pointers.
--
-- * The same for GSList.
--
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)


{-# LINE 49 "./System/Glib/GList.chs" #-}

type GList = Ptr (())
{-# LINE 51 "./System/Glib/GList.chs" #-}
type GSList = Ptr (())
{-# LINE 52 "./System/Glib/GList.chs" #-}

-- methods

-- Turn a GList into a list of pointers but don't destroy the list.
--
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 8 ::IO (Ptr ())}) glist
    xs <- readGList glist'
    return (castPtr x:xs)

-- Turn a GList into a list of pointers (freeing the GList in the process).
--
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)

-- Turn a GSList into a list of pointers but don't destroy the list.
--
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 8 ::IO (Ptr ())}) gslist
    xs <- readGSList gslist'
    return (castPtr x:xs)

-- Turn a GSList into a list of pointers (freeing the GSList in the process).
--
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)

-- Turn a GSList into a list of pointers and reverse it.
--
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)

-- Turn a list of something into a GList.
--
toGList :: [Ptr a] -> IO GList
toGList = foldM prepend nullPtr . reverse
  where
    -- prepend :: GList -> Ptr a -> IO GList
    prepend l x = g_list_prepend l (castPtr x)

-- Turn a list of something into a GSList.
--
toGSList :: [Ptr a] -> IO GSList
toGSList = foldM prepend nullPtr . reverse
  where
    -- prepend :: GSList -> Ptr a -> IO GList
    prepend l x = g_slist_prepend l (castPtr x)

-- Temporarily allocate a list of something
--
withGList :: [Ptr a] -> (GSList -> IO b) -> IO b
withGList xs = bracket (toGList xs) g_list_free
{-# LINE 135 "./System/Glib/GList.chs" #-}

-- Temporarily allocate a list of something
--
withGSList :: [Ptr a] -> (GSList -> IO b) -> IO b
withGSList xs = bracket (toGSList xs) g_slist_free
{-# LINE 140 "./System/Glib/GList.chs" #-}


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 ()))