-- GENERATED by C->Haskell Compiler, version 0.16.4 Crystal Seed, 24 Jan 2009 (Haskell)
-- Edit the ORIGNAL .chs file instead!


{-# LINE 1 "lib/CPython/Protocols/Mapping.chs" #-}{-# LANGUAGE ForeignFunctionInterface #-}

-- Copyright (C) 2009 John Millikin <jmillikin@gmail.com>
--
-- This program is free software: you can redistribute it and/or modify
-- it under the terms of the GNU General Public License as published by
-- the Free Software Foundation, either version 3 of the License, or
-- any later version.
--
-- This program 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 General Public License for more details.
--
-- You should have received a copy of the GNU General Public License
-- along with this program.  If not, see <http://www.gnu.org/licenses/>.

module CPython.Protocols.Mapping
	( Mapping (..)
	, SomeMapping
	, castToMapping
	, getItem
	, setItem
	, deleteItem
	, size
	, hasKey
	, keys
	, values
	, items
	) where


import           CPython.Internal

instance Mapping Dictionary where
	toMapping = unsafeCastToMapping

castToMapping :: Object a => a -> IO (Maybe SomeMapping)
castToMapping obj =
	withObject obj $ \objPtr -> do
	isMapping <- fmap cToBool $ pyMappingCheck objPtr
	return $ if isMapping
		then Just $ unsafeCastToMapping obj
		else Nothing

getItem :: (Mapping self, Object key) => self -> key -> IO (SomeObject)
getItem a1 a2 =
  withObject a1 $ \a1' -> 
  withObject a2 $ \a2' -> 
  getItem'_ a1' a2' >>= \res ->
  stealObject res >>= \res' ->
  return (res')
{-# LINE 51 "lib/CPython/Protocols/Mapping.chs" #-}

setItem :: (Mapping self, Object key, Object value) => self -> key -> value -> IO (())
setItem a1 a2 a3 =
  withObject a1 $ \a1' -> 
  withObject a2 $ \a2' -> 
  withObject a3 $ \a3' -> 
  setItem'_ a1' a2' a3' >>= \res ->
  checkStatusCode res >>= \res' ->
  return (res')
{-# LINE 58 "lib/CPython/Protocols/Mapping.chs" #-}

deleteItem :: (Mapping self, Object key) => self -> key -> IO (())
deleteItem a1 a2 =
  withObject a1 $ \a1' -> 
  withObject a2 $ \a2' -> 
  deleteItem'_ a1' a2' >>= \res ->
  checkStatusCode res >>= \res' ->
  return (res')
{-# LINE 64 "lib/CPython/Protocols/Mapping.chs" #-}

size :: Mapping self => self -> IO (Integer)
size a1 =
  withObject a1 $ \a1' -> 
  size'_ a1' >>= \res ->
  checkIntReturn res >>= \res' ->
  return (res')
{-# LINE 69 "lib/CPython/Protocols/Mapping.chs" #-}

hasKey :: (Mapping self, Object key) => self -> key -> IO (Bool)
hasKey a1 a2 =
  withObject a1 $ \a1' -> 
  withObject a2 $ \a2' -> 
  hasKey'_ a1' a2' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 75 "lib/CPython/Protocols/Mapping.chs" #-}

keys :: Mapping self => self -> IO (List)
keys a1 =
  withObject a1 $ \a1' -> 
  keys'_ a1' >>= \res ->
  stealObject res >>= \res' ->
  return (res')
{-# LINE 80 "lib/CPython/Protocols/Mapping.chs" #-}

values :: Mapping self => self -> IO (List)
values a1 =
  withObject a1 $ \a1' -> 
  values'_ a1' >>= \res ->
  stealObject res >>= \res' ->
  return (res')
{-# LINE 85 "lib/CPython/Protocols/Mapping.chs" #-}

items :: Mapping self => self -> IO (List)
items a1 =
  withObject a1 $ \a1' -> 
  items'_ a1' >>= \res ->
  stealObject res >>= \res' ->
  return (res')
{-# LINE 90 "lib/CPython/Protocols/Mapping.chs" #-}

foreign import ccall safe "CPython/Protocols/Mapping.chs.h PyMapping_Check"
  pyMappingCheck :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "CPython/Protocols/Mapping.chs.h PyObject_GetItem"
  getItem'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

foreign import ccall safe "CPython/Protocols/Mapping.chs.h PyObject_SetItem"
  setItem'_ :: ((Ptr ()) -> ((Ptr ()) -> ((Ptr ()) -> (IO CInt))))

foreign import ccall safe "CPython/Protocols/Mapping.chs.h PyObject_DelItem"
  deleteItem'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO CInt)))

foreign import ccall safe "CPython/Protocols/Mapping.chs.h PyMapping_Size"
  size'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "CPython/Protocols/Mapping.chs.h PyMapping_HasKey"
  hasKey'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO CInt)))

foreign import ccall safe "CPython/Protocols/Mapping.chs.h PyMapping_Keys"
  keys'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "CPython/Protocols/Mapping.chs.h PyMapping_Values"
  values'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "CPython/Protocols/Mapping.chs.h PyMapping_Items"
  items'_ :: ((Ptr ()) -> (IO (Ptr ())))