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

{-# LANGUAGE EmptyDataDecls,ForeignFunctionInterface #-}

{-# LINE 1 "src/Graphics/UI/Gtk/WebKit/JavaScriptCore/JSObjectRef.chs" #-}

module Graphics.UI.Gtk.WebKit.JavaScriptCore.JSObjectRef where

import Foreign.C.String
import Foreign.C.Types 
import Foreign.Ptr 
import Foreign.Storable
import Data.Word (Word)

import Graphics.UI.Gtk.WebKit.JavaScriptCore.JSBase
{-# LINE 11 "src/Graphics/UI/Gtk/WebKit/JavaScriptCore/JSObjectRef.chs" #-}

-- {#pointer *JSValueRef as Ptr JSValueRef #}

type JSCSize = (CULong)
{-# LINE 15 "src/Graphics/UI/Gtk/WebKit/JavaScriptCore/JSObjectRef.chs" #-}

type JSPropertyAttributes = (CUInt)
{-# LINE 17 "src/Graphics/UI/Gtk/WebKit/JavaScriptCore/JSObjectRef.chs" #-}

type JSClassAttributes = (CUInt)
{-# LINE 19 "src/Graphics/UI/Gtk/WebKit/JavaScriptCore/JSObjectRef.chs" #-}

type JSObjectInitializeCallback = ((FunPtr ((Ptr OpaqueJSContext) -> ((Ptr OpaqueJSValue) -> (IO ())))))
{-# LINE 21 "src/Graphics/UI/Gtk/WebKit/JavaScriptCore/JSObjectRef.chs" #-}

type JSObjectFinalizeCallback = ((FunPtr ((Ptr OpaqueJSValue) -> (IO ()))))
{-# LINE 23 "src/Graphics/UI/Gtk/WebKit/JavaScriptCore/JSObjectRef.chs" #-}

type JSObjectHasPropertyCallback = ((FunPtr ((Ptr OpaqueJSContext) -> ((Ptr OpaqueJSValue) -> ((Ptr OpaqueJSString) -> (IO CUChar))))))
{-# LINE 25 "src/Graphics/UI/Gtk/WebKit/JavaScriptCore/JSObjectRef.chs" #-}

type JSObjectGetPropertyCallback = ((FunPtr ((Ptr OpaqueJSContext) -> ((Ptr OpaqueJSValue) -> ((Ptr OpaqueJSString) -> ((Ptr JSValueRef) -> (IO (Ptr OpaqueJSValue))))))))
{-# LINE 27 "src/Graphics/UI/Gtk/WebKit/JavaScriptCore/JSObjectRef.chs" #-}

type JSObjectSetPropertyCallback = ((FunPtr ((Ptr OpaqueJSContext) -> ((Ptr OpaqueJSValue) -> ((Ptr OpaqueJSString) -> ((Ptr OpaqueJSValue) -> ((Ptr JSValueRef) -> (IO CUChar))))))))
{-# LINE 29 "src/Graphics/UI/Gtk/WebKit/JavaScriptCore/JSObjectRef.chs" #-}

type JSObjectDeletePropertyCallback = ((FunPtr ((Ptr OpaqueJSContext) -> ((Ptr OpaqueJSValue) -> ((Ptr OpaqueJSString) -> ((Ptr JSValueRef) -> (IO CUChar)))))))
{-# LINE 31 "src/Graphics/UI/Gtk/WebKit/JavaScriptCore/JSObjectRef.chs" #-}

type JSObjectGetPropertyNamesCallback = ((FunPtr ((Ptr OpaqueJSContext) -> ((Ptr OpaqueJSValue) -> ((Ptr OpaqueJSPropertyNameAccumulator) -> (IO ()))))))
{-# LINE 33 "src/Graphics/UI/Gtk/WebKit/JavaScriptCore/JSObjectRef.chs" #-}

type JSObjectCallAsFunctionCallback' =
       JSContextRef
    -> JSObjectRef
    -> JSObjectRef
    -> JSCSize
    -> JSValueRefRef
    -> JSValueRefRef
    -> IO JSValueRef

type JSObjectCallAsFunctionCallback = ((FunPtr ((Ptr OpaqueJSContext) -> ((Ptr OpaqueJSValue) -> ((Ptr OpaqueJSValue) -> (CULong -> ((Ptr JSValueRef) -> ((Ptr JSValueRef) -> (IO (Ptr OpaqueJSValue))))))))))
{-# LINE 44 "src/Graphics/UI/Gtk/WebKit/JavaScriptCore/JSObjectRef.chs" #-}

type JSObjectCallAsConstructorCallback' =
       JSContextRef
    -> JSObjectRef
    -> JSCSize
    -> JSValueRefRef
    -> JSValueRefRef
    -> IO JSValueRef

type JSObjectCallAsConstructorCallback = ((FunPtr ((Ptr OpaqueJSContext) -> ((Ptr OpaqueJSValue) -> (CULong -> ((Ptr JSValueRef) -> ((Ptr JSValueRef) -> (IO (Ptr OpaqueJSValue)))))))))
{-# LINE 54 "src/Graphics/UI/Gtk/WebKit/JavaScriptCore/JSObjectRef.chs" #-}

type JSObjectHasInstanceCallback = ((FunPtr ((Ptr OpaqueJSContext) -> ((Ptr OpaqueJSValue) -> ((Ptr OpaqueJSValue) -> ((Ptr JSValueRef) -> (IO CUChar)))))))
{-# LINE 56 "src/Graphics/UI/Gtk/WebKit/JavaScriptCore/JSObjectRef.chs" #-}

type JSObjectConvertToTypeCallback = ((FunPtr ((Ptr OpaqueJSContext) -> ((Ptr OpaqueJSValue) -> (CInt -> ((Ptr JSValueRef) -> (IO (Ptr OpaqueJSValue))))))))
{-# LINE 58 "src/Graphics/UI/Gtk/WebKit/JavaScriptCore/JSObjectRef.chs" #-}

type JSStaticValueRef = ((Ptr ()))
{-# LINE 60 "src/Graphics/UI/Gtk/WebKit/JavaScriptCore/JSObjectRef.chs" #-}


value_get_name :: JSStaticValueRef -> IO String 
value_get_name t = (\ptr -> do {peekByteOff ptr 0 ::IO (Ptr CChar)}) t >>= peekCString 

value_set_name :: JSStaticValueRef -> String -> IO ()
value_set_name t str = (\ptr val -> do {pokeByteOff ptr 0 (val::(Ptr CChar))}) t =<< newCString str 


value_get_getProperty :: JSStaticValueRef -> IO JSObjectGetPropertyCallback 
value_get_getProperty t = (\ptr -> do {peekByteOff ptr 8 ::IO (FunPtr ((Ptr OpaqueJSContext) -> ((Ptr OpaqueJSValue) -> ((Ptr OpaqueJSString) -> ((Ptr JSValueRef) -> (IO (Ptr OpaqueJSValue)))))))}) t


value_set_getProperty :: JSStaticValueRef -> JSObjectGetPropertyCallback -> IO ()
value_set_getProperty t cbk = (\ptr val -> do {pokeByteOff ptr 8 (val::(FunPtr ((Ptr OpaqueJSContext) -> ((Ptr OpaqueJSValue) -> ((Ptr OpaqueJSString) -> ((Ptr JSValueRef) -> (IO (Ptr OpaqueJSValue))))))))}) t cbk 


value_get_setProperty :: JSStaticValueRef -> IO JSObjectSetPropertyCallback 
value_get_setProperty t = (\ptr -> do {peekByteOff ptr 16 ::IO (FunPtr ((Ptr OpaqueJSContext) -> ((Ptr OpaqueJSValue) -> ((Ptr OpaqueJSString) -> ((Ptr OpaqueJSValue) -> ((Ptr JSValueRef) -> (IO CUChar)))))))}) t

value_set_setProperty :: JSStaticValueRef -> JSObjectSetPropertyCallback -> IO ()
value_set_setProperty t cbk = (\ptr val -> do {pokeByteOff ptr 16 (val::(FunPtr ((Ptr OpaqueJSContext) -> ((Ptr OpaqueJSValue) -> ((Ptr OpaqueJSString) -> ((Ptr OpaqueJSValue) -> ((Ptr JSValueRef) -> (IO CUChar))))))))}) t cbk 

value_get_attributes :: JSStaticValueRef -> IO JSPropertyAttributes 
value_get_attributes t = (\ptr -> do {peekByteOff ptr 24 ::IO CUInt}) t

value_set_attributes :: JSStaticValueRef -> JSPropertyAttributes -> IO ()
value_set_attributes t attr = (\ptr val -> do {pokeByteOff ptr 24 (val::CUInt)}) t attr 


type JSStaticFunctionRef = ((Ptr ()))
{-# LINE 91 "src/Graphics/UI/Gtk/WebKit/JavaScriptCore/JSObjectRef.chs" #-}

func_get_name :: JSStaticFunctionRef -> IO String
func_get_name t = (\ptr -> do {peekByteOff ptr 0 ::IO (Ptr CChar)}) t >>= peekCString 

func_set_name :: JSStaticFunctionRef -> String -> IO ()
func_set_name t str = (\ptr val -> do {pokeByteOff ptr 0 (val::(Ptr CChar))}) t =<< newCString str

func_get_callAsFunction :: JSStaticFunctionRef -> IO JSObjectCallAsFunctionCallback
func_get_callAsFunction t = (\ptr -> do {peekByteOff ptr 8 ::IO (FunPtr ((Ptr OpaqueJSContext) -> ((Ptr OpaqueJSValue) -> ((Ptr OpaqueJSValue) -> (CULong -> ((Ptr JSValueRef) -> ((Ptr JSValueRef) -> (IO (Ptr OpaqueJSValue)))))))))}) t 

func_set_callAsFunction :: JSStaticFunctionRef -> JSObjectCallAsFunctionCallback -> IO ()
func_set_callAsFunction t cbk = (\ptr val -> do {pokeByteOff ptr 8 (val::(FunPtr ((Ptr OpaqueJSContext) -> ((Ptr OpaqueJSValue) -> ((Ptr OpaqueJSValue) -> (CULong -> ((Ptr JSValueRef) -> ((Ptr JSValueRef) -> (IO (Ptr OpaqueJSValue))))))))))}) t cbk 

func_get_attributes :: JSStaticFunctionRef -> IO JSPropertyAttributes 
func_get_attributes t = (\ptr -> do {peekByteOff ptr 16 ::IO CUInt}) t

func_set_attributes :: JSStaticFunctionRef -> JSPropertyAttributes -> IO () 
func_set_attributes t attr = (\ptr val -> do {pokeByteOff ptr 16 (val::CUInt)}) t attr 

type JSClassDefinitionRef = ((Ptr ())) 

class_get_version :: JSClassDefinitionRef -> IO Int 
class_get_version t = (\ptr -> do {peekByteOff ptr 0 ::IO CInt}) t >>= return . fromIntegral

class_set_version :: JSClassDefinitionRef -> Int -> IO ()
class_set_version t n = (\ptr val -> do {pokeByteOff ptr 0 (val::CInt)}) t (fromIntegral n) 

class_get_attributes :: JSClassDefinitionRef -> IO JSClassAttributes
class_get_attributes t = (\ptr -> do {peekByteOff ptr 4 ::IO CUInt}) t

class_set_attributes :: JSClassDefinitionRef -> JSClassAttributes -> IO ()
class_set_attributes t attr = (\ptr val -> do {pokeByteOff ptr 4 (val::CUInt)}) t attr 

class_get_className :: JSClassDefinitionRef -> IO String
class_get_className t = (\ptr -> do {peekByteOff ptr 8 ::IO (Ptr CChar)}) t >>= peekCString

class_set_className :: JSClassDefinitionRef -> String -> IO ()
class_set_className t cname = (\ptr val -> do {pokeByteOff ptr 8 (val::(Ptr CChar))}) t =<< newCString cname

class_get_parentClass :: JSClassDefinitionRef -> IO JSClassRef
class_get_parentClass t = (\ptr -> do {peekByteOff ptr 16 ::IO (Ptr ())}) t >>= return . castPtr

class_set_parentClass :: JSClassDefinitionRef -> JSClassRef -> IO ()
class_set_parentClass t c = (\ptr val -> do {pokeByteOff ptr 16 (val::(Ptr ()))}) t (castPtr c)


class_get_staticValues :: JSClassDefinitionRef -> IO JSStaticValueRef
class_get_staticValues t = (\ptr -> do {peekByteOff ptr 24 ::IO (Ptr ())}) t

class_set_staticValues :: JSClassDefinitionRef -> JSStaticValueRef -> IO ()
class_set_staticValues t v = (\ptr val -> do {pokeByteOff ptr 24 (val::(Ptr ()))}) t v


class_get_staticFunctions :: JSClassDefinitionRef -> IO JSStaticFunctionRef 
class_get_staticFunctions t = (\ptr -> do {peekByteOff ptr 32 ::IO (Ptr ())}) t 


class_set_staticFunctions :: JSClassDefinitionRef -> JSStaticFunctionRef -> IO ()
class_set_staticFunctions t f = (\ptr val -> do {pokeByteOff ptr 32 (val::(Ptr ()))}) t f

class_get_initialize :: JSClassDefinitionRef -> IO JSObjectInitializeCallback 
class_get_initialize t = (\ptr -> do {peekByteOff ptr 40 ::IO (FunPtr ((Ptr OpaqueJSContext) -> ((Ptr OpaqueJSValue) -> (IO ()))))}) t

class_set_initialize :: JSClassDefinitionRef -> JSObjectInitializeCallback -> IO ()
class_set_initialize t cbk = (\ptr val -> do {pokeByteOff ptr 40 (val::(FunPtr ((Ptr OpaqueJSContext) -> ((Ptr OpaqueJSValue) -> (IO ())))))}) t cbk  



class_get_finalize :: JSClassDefinitionRef -> IO JSObjectFinalizeCallback 
class_get_finalize t = (\ptr -> do {peekByteOff ptr 48 ::IO (FunPtr ((Ptr OpaqueJSValue) -> (IO ())))}) t

class_set_finalize :: JSClassDefinitionRef -> JSObjectFinalizeCallback -> IO ()
class_set_finalize t f = (\ptr val -> do {pokeByteOff ptr 48 (val::(FunPtr ((Ptr OpaqueJSValue) -> (IO ()))))}) t f


class_get_hasProperty :: JSClassDefinitionRef -> IO JSObjectHasPropertyCallback 
class_get_hasProperty t = (\ptr -> do {peekByteOff ptr 56 ::IO (FunPtr ((Ptr OpaqueJSContext) -> ((Ptr OpaqueJSValue) -> ((Ptr OpaqueJSString) -> (IO CUChar)))))}) t

class_set_hasProperty :: JSClassDefinitionRef -> JSObjectHasPropertyCallback -> IO ()
class_set_hasProperty t f = (\ptr val -> do {pokeByteOff ptr 56 (val::(FunPtr ((Ptr OpaqueJSContext) -> ((Ptr OpaqueJSValue) -> ((Ptr OpaqueJSString) -> (IO CUChar))))))}) t f

class_get_getProperty :: JSClassDefinitionRef -> IO JSObjectGetPropertyCallback 
class_get_getProperty t = (\ptr -> do {peekByteOff ptr 64 ::IO (FunPtr ((Ptr OpaqueJSContext) -> ((Ptr OpaqueJSValue) -> ((Ptr OpaqueJSString) -> ((Ptr JSValueRef) -> (IO (Ptr OpaqueJSValue)))))))}) t

class_set_getProperty :: JSClassDefinitionRef -> JSObjectGetPropertyCallback -> IO ()
class_set_getProperty t f = (\ptr val -> do {pokeByteOff ptr 64 (val::(FunPtr ((Ptr OpaqueJSContext) -> ((Ptr OpaqueJSValue) -> ((Ptr OpaqueJSString) -> ((Ptr JSValueRef) -> (IO (Ptr OpaqueJSValue))))))))}) t f

class_get_setProperty :: JSClassDefinitionRef -> IO JSObjectSetPropertyCallback 
class_get_setProperty t = (\ptr -> do {peekByteOff ptr 72 ::IO (FunPtr ((Ptr OpaqueJSContext) -> ((Ptr OpaqueJSValue) -> ((Ptr OpaqueJSString) -> ((Ptr OpaqueJSValue) -> ((Ptr JSValueRef) -> (IO CUChar)))))))}) t

class_set_setProperty :: JSClassDefinitionRef -> JSObjectSetPropertyCallback -> IO ()
class_set_setProperty t f = (\ptr val -> do {pokeByteOff ptr 72 (val::(FunPtr ((Ptr OpaqueJSContext) -> ((Ptr OpaqueJSValue) -> ((Ptr OpaqueJSString) -> ((Ptr OpaqueJSValue) -> ((Ptr JSValueRef) -> (IO CUChar))))))))}) t f

class_get_deleteProperty :: JSClassDefinitionRef -> IO JSObjectDeletePropertyCallback 
class_get_deleteProperty t = (\ptr -> do {peekByteOff ptr 80 ::IO (FunPtr ((Ptr OpaqueJSContext) -> ((Ptr OpaqueJSValue) -> ((Ptr OpaqueJSString) -> ((Ptr JSValueRef) -> (IO CUChar))))))}) t

class_set_deleteProperty :: JSClassDefinitionRef -> JSObjectDeletePropertyCallback -> IO ()
class_set_deleteProperty t f = (\ptr val -> do {pokeByteOff ptr 80 (val::(FunPtr ((Ptr OpaqueJSContext) -> ((Ptr OpaqueJSValue) -> ((Ptr OpaqueJSString) -> ((Ptr JSValueRef) -> (IO CUChar)))))))}) t f 

class_get_getPropertyNames :: JSClassDefinitionRef -> IO JSObjectGetPropertyNamesCallback
class_get_getPropertyNames t = (\ptr -> do {peekByteOff ptr 88 ::IO (FunPtr ((Ptr OpaqueJSContext) -> ((Ptr OpaqueJSValue) -> ((Ptr OpaqueJSPropertyNameAccumulator) -> (IO ())))))}) t

class_set_getPropertyNames :: JSClassDefinitionRef -> JSObjectGetPropertyNamesCallback -> IO ()
class_set_getPropertyNames t f = (\ptr val -> do {pokeByteOff ptr 88 (val::(FunPtr ((Ptr OpaqueJSContext) -> ((Ptr OpaqueJSValue) -> ((Ptr OpaqueJSPropertyNameAccumulator) -> (IO ()))))))}) t f 

class_get_callAsFunction  :: JSClassDefinitionRef -> IO JSObjectCallAsFunctionCallback
class_get_callAsFunction t = (\ptr -> do {peekByteOff ptr 96 ::IO (FunPtr ((Ptr OpaqueJSContext) -> ((Ptr OpaqueJSValue) -> ((Ptr OpaqueJSValue) -> (CULong -> ((Ptr JSValueRef) -> ((Ptr JSValueRef) -> (IO (Ptr OpaqueJSValue)))))))))}) t

class_set_callAsFunction :: JSClassDefinitionRef -> JSObjectCallAsFunctionCallback -> IO ()
class_set_callAsFunction t f = (\ptr val -> do {pokeByteOff ptr 96 (val::(FunPtr ((Ptr OpaqueJSContext) -> ((Ptr OpaqueJSValue) -> ((Ptr OpaqueJSValue) -> (CULong -> ((Ptr JSValueRef) -> ((Ptr JSValueRef) -> (IO (Ptr OpaqueJSValue))))))))))}) t f 


class_get_callAsConstructor :: JSClassDefinitionRef -> IO JSObjectCallAsConstructorCallback
class_get_callAsConstructor t = (\ptr -> do {peekByteOff ptr 104 ::IO (FunPtr ((Ptr OpaqueJSContext) -> ((Ptr OpaqueJSValue) -> (CULong -> ((Ptr JSValueRef) -> ((Ptr JSValueRef) -> (IO (Ptr OpaqueJSValue))))))))}) t

class_set_callAsConstructor :: JSClassDefinitionRef -> JSObjectCallAsConstructorCallback -> IO ()
class_set_callAsConstructor t f = (\ptr val -> do {pokeByteOff ptr 104 (val::(FunPtr ((Ptr OpaqueJSContext) -> ((Ptr OpaqueJSValue) -> (CULong -> ((Ptr JSValueRef) -> ((Ptr JSValueRef) -> (IO (Ptr OpaqueJSValue)))))))))}) t f


class_get_hasInstance :: JSClassDefinitionRef -> IO JSObjectHasInstanceCallback 
class_get_hasInstance t = (\ptr -> do {peekByteOff ptr 112 ::IO (FunPtr ((Ptr OpaqueJSContext) -> ((Ptr OpaqueJSValue) -> ((Ptr OpaqueJSValue) -> ((Ptr JSValueRef) -> (IO CUChar))))))}) t

class_set_hasInstance :: JSClassDefinitionRef -> JSObjectHasInstanceCallback -> IO ()
class_set_hasInstance t f = (\ptr val -> do {pokeByteOff ptr 112 (val::(FunPtr ((Ptr OpaqueJSContext) -> ((Ptr OpaqueJSValue) -> ((Ptr OpaqueJSValue) -> ((Ptr JSValueRef) -> (IO CUChar)))))))}) t f 


class_get_convertToType :: JSClassDefinitionRef -> IO JSObjectConvertToTypeCallback 
class_get_convertToType t = (\ptr -> do {peekByteOff ptr 120 ::IO (FunPtr ((Ptr OpaqueJSContext) -> ((Ptr OpaqueJSValue) -> (CInt -> ((Ptr JSValueRef) -> (IO (Ptr OpaqueJSValue)))))))}) t

class_set_convertToType :: JSClassDefinitionRef -> JSObjectConvertToTypeCallback -> IO ()
class_set_convertToType t f = (\ptr val -> do {pokeByteOff ptr 120 (val::(FunPtr ((Ptr OpaqueJSContext) -> ((Ptr OpaqueJSValue) -> (CInt -> ((Ptr JSValueRef) -> (IO (Ptr OpaqueJSValue))))))))}) t f


-- kJSClassDefinitionEmpty

jsclasscreate :: JSClassDefinitionRef -> IO (JSClassRef)
jsclasscreate a1 =
  let {a1' = id a1} in 
  jsclasscreate'_ a1' >>= \res ->
  let {res' = id res} in
  return (res')
{-# LINE 227 "src/Graphics/UI/Gtk/WebKit/JavaScriptCore/JSObjectRef.chs" #-}

jsclassretain :: JSClassRef -> IO (JSClassRef)
jsclassretain a1 =
  let {a1' = id a1} in 
  jsclassretain'_ a1' >>= \res ->
  let {res' = id res} in
  return (res')
{-# LINE 229 "src/Graphics/UI/Gtk/WebKit/JavaScriptCore/JSObjectRef.chs" #-}

jsclassrelease :: JSClassRef -> IO ()
jsclassrelease a1 =
  let {a1' = id a1} in 
  jsclassrelease'_ a1' >>= \res ->
  return ()
{-# LINE 231 "src/Graphics/UI/Gtk/WebKit/JavaScriptCore/JSObjectRef.chs" #-}

jsobjectmake :: JSContextRef -> JSClassRef -> Ptr () -> IO (JSObjectRef)
jsobjectmake a1 a2 a3 =
  let {a1' = id a1} in 
  let {a2' = id a2} in 
  let {a3' = id a3} in 
  jsobjectmake'_ a1' a2' a3' >>= \res ->
  let {res' = id res} in
  return (res')
{-# LINE 233 "src/Graphics/UI/Gtk/WebKit/JavaScriptCore/JSObjectRef.chs" #-}

jsobjectmakefunctionwithcallback :: JSContextRef -> JSStringRef -> JSObjectCallAsFunctionCallback -> IO (JSObjectRef)
jsobjectmakefunctionwithcallback a1 a2 a3 =
  let {a1' = id a1} in 
  let {a2' = id a2} in 
  let {a3' = id a3} in 
  jsobjectmakefunctionwithcallback'_ a1' a2' a3' >>= \res ->
  let {res' = id res} in
  return (res')
{-# LINE 235 "src/Graphics/UI/Gtk/WebKit/JavaScriptCore/JSObjectRef.chs" #-}

jsobjectmakeconstructor :: JSContextRef -> JSClassRef -> JSObjectCallAsConstructorCallback -> IO (JSObjectRef)
jsobjectmakeconstructor a1 a2 a3 =
  let {a1' = id a1} in 
  let {a2' = id a2} in 
  let {a3' = id a3} in 
  jsobjectmakeconstructor'_ a1' a2' a3' >>= \res ->
  let {res' = id res} in
  return (res')
{-# LINE 237 "src/Graphics/UI/Gtk/WebKit/JavaScriptCore/JSObjectRef.chs" #-}

jsobjectmakearray :: JSContextRef -> CSize -> JSValueRefRef -> JSValueRefRef -> IO (JSObjectRef)
jsobjectmakearray a1 a2 a3 a4 =
  let {a1' = id a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = id a3} in 
  let {a4' = id a4} in 
  jsobjectmakearray'_ a1' a2' a3' a4' >>= \res ->
  let {res' = id res} in
  return (res')
{-# LINE 239 "src/Graphics/UI/Gtk/WebKit/JavaScriptCore/JSObjectRef.chs" #-}

jsobjectmakedate :: JSContextRef -> CSize -> JSValueRefRef -> JSValueRefRef -> IO (JSObjectRef)
jsobjectmakedate a1 a2 a3 a4 =
  let {a1' = id a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = id a3} in 
  let {a4' = id a4} in 
  jsobjectmakedate'_ a1' a2' a3' a4' >>= \res ->
  let {res' = id res} in
  return (res')
{-# LINE 241 "src/Graphics/UI/Gtk/WebKit/JavaScriptCore/JSObjectRef.chs" #-}

jsobjectmakeerror :: JSContextRef -> CSize -> JSValueRefRef -> JSValueRefRef -> IO (JSObjectRef)
jsobjectmakeerror a1 a2 a3 a4 =
  let {a1' = id a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = id a3} in 
  let {a4' = id a4} in 
  jsobjectmakeerror'_ a1' a2' a3' a4' >>= \res ->
  let {res' = id res} in
  return (res')
{-# LINE 243 "src/Graphics/UI/Gtk/WebKit/JavaScriptCore/JSObjectRef.chs" #-}

jsobjectmakeregexp :: JSContextRef -> CSize -> JSValueRefRef -> JSValueRefRef -> IO (JSObjectRef)
jsobjectmakeregexp a1 a2 a3 a4 =
  let {a1' = id a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = id a3} in 
  let {a4' = id a4} in 
  jsobjectmakeregexp'_ a1' a2' a3' a4' >>= \res ->
  let {res' = id res} in
  return (res')
{-# LINE 245 "src/Graphics/UI/Gtk/WebKit/JavaScriptCore/JSObjectRef.chs" #-}


jsobjectmakefunction :: JSContextRef -> JSStringRef -> CUInt -> JSStringRefRef -> JSStringRef -> JSStringRef -> Int -> JSValueRefRef -> IO (JSObjectRef)
jsobjectmakefunction a1 a2 a3 a4 a5 a6 a7 a8 =
  let {a1' = id a1} in 
  let {a2' = id a2} in 
  let {a3' = id a3} in 
  let {a4' = id a4} in 
  let {a5' = id a5} in 
  let {a6' = id a6} in 
  let {a7' = fromIntegral a7} in 
  let {a8' = id a8} in 
  jsobjectmakefunction'_ a1' a2' a3' a4' a5' a6' a7' a8' >>= \res ->
  let {res' = id res} in
  return (res')
{-# LINE 248 "src/Graphics/UI/Gtk/WebKit/JavaScriptCore/JSObjectRef.chs" #-}

jsobjectgetprototype :: JSContextRef -> JSObjectRef -> IO (JSValueRef)
jsobjectgetprototype a1 a2 =
  let {a1' = id a1} in 
  let {a2' = id a2} in 
  jsobjectgetprototype'_ a1' a2' >>= \res ->
  let {res' = id res} in
  return (res')
{-# LINE 250 "src/Graphics/UI/Gtk/WebKit/JavaScriptCore/JSObjectRef.chs" #-}

jsobjectsetprototype :: JSContextRef -> JSObjectRef -> JSValueRef -> IO ()
jsobjectsetprototype a1 a2 a3 =
  let {a1' = id a1} in 
  let {a2' = id a2} in 
  let {a3' = id a3} in 
  jsobjectsetprototype'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 252 "src/Graphics/UI/Gtk/WebKit/JavaScriptCore/JSObjectRef.chs" #-}

jsobjecthasproperty :: JSContextRef -> JSObjectRef -> JSStringRef -> IO (Bool)
jsobjecthasproperty a1 a2 a3 =
  let {a1' = id a1} in 
  let {a2' = id a2} in 
  let {a3' = id a3} in 
  jsobjecthasproperty'_ a1' a2' a3' >>= \res ->
  let {res' = getBool res} in
  return (res')
{-# LINE 254 "src/Graphics/UI/Gtk/WebKit/JavaScriptCore/JSObjectRef.chs" #-}

jsobjectgetproperty :: JSContextRef -> JSObjectRef -> JSStringRef -> JSValueRefRef -> IO (JSValueRef)
jsobjectgetproperty a1 a2 a3 a4 =
  let {a1' = id a1} in 
  let {a2' = id a2} in 
  let {a3' = id a3} in 
  let {a4' = id a4} in 
  jsobjectgetproperty'_ a1' a2' a3' a4' >>= \res ->
  let {res' = id res} in
  return (res')
{-# LINE 256 "src/Graphics/UI/Gtk/WebKit/JavaScriptCore/JSObjectRef.chs" #-}

jsobjectsetproperty :: JSContextRef -> JSObjectRef -> JSStringRef -> JSValueRef -> JSPropertyAttributes -> JSValueRefRef -> IO ()
jsobjectsetproperty a1 a2 a3 a4 a5 a6 =
  let {a1' = id a1} in 
  let {a2' = id a2} in 
  let {a3' = id a3} in 
  let {a4' = id a4} in 
  let {a5' = id a5} in 
  let {a6' = id a6} in 
  jsobjectsetproperty'_ a1' a2' a3' a4' a5' a6' >>= \res ->
  return ()
{-# LINE 258 "src/Graphics/UI/Gtk/WebKit/JavaScriptCore/JSObjectRef.chs" #-}

jsobjectdeleteproperty :: JSContextRef -> JSObjectRef -> JSStringRef -> JSValueRefRef -> IO (Bool)
jsobjectdeleteproperty a1 a2 a3 a4 =
  let {a1' = id a1} in 
  let {a2' = id a2} in 
  let {a3' = id a3} in 
  let {a4' = id a4} in 
  jsobjectdeleteproperty'_ a1' a2' a3' a4' >>= \res ->
  let {res' = getBool res} in
  return (res')
{-# LINE 260 "src/Graphics/UI/Gtk/WebKit/JavaScriptCore/JSObjectRef.chs" #-}

jsobjectgetpropertyatindex :: JSContextRef -> JSObjectRef -> CUInt -> JSValueRefRef -> IO (JSValueRef)
jsobjectgetpropertyatindex a1 a2 a3 a4 =
  let {a1' = id a1} in 
  let {a2' = id a2} in 
  let {a3' = id a3} in 
  let {a4' = id a4} in 
  jsobjectgetpropertyatindex'_ a1' a2' a3' a4' >>= \res ->
  let {res' = id res} in
  return (res')
{-# LINE 262 "src/Graphics/UI/Gtk/WebKit/JavaScriptCore/JSObjectRef.chs" #-}

jsobjectsetpropertyatindex :: JSContextRef -> JSObjectRef -> CUInt -> JSValueRef -> JSValueRefRef -> IO ()
jsobjectsetpropertyatindex a1 a2 a3 a4 a5 =
  let {a1' = id a1} in 
  let {a2' = id a2} in 
  let {a3' = id a3} in 
  let {a4' = id a4} in 
  let {a5' = id a5} in 
  jsobjectsetpropertyatindex'_ a1' a2' a3' a4' a5' >>= \res ->
  return ()
{-# LINE 264 "src/Graphics/UI/Gtk/WebKit/JavaScriptCore/JSObjectRef.chs" #-}

jsobjectgetprivate :: JSObjectRef -> IO (Ptr ())
jsobjectgetprivate a1 =
  let {a1' = id a1} in 
  jsobjectgetprivate'_ a1' >>= \res ->
  let {res' = id res} in
  return (res')
{-# LINE 266 "src/Graphics/UI/Gtk/WebKit/JavaScriptCore/JSObjectRef.chs" #-}

jsobjectsetprivate :: JSObjectRef -> Ptr () -> IO (Bool)
jsobjectsetprivate a1 a2 =
  let {a1' = id a1} in 
  let {a2' = id a2} in 
  jsobjectsetprivate'_ a1' a2' >>= \res ->
  let {res' = getBool res} in
  return (res')
{-# LINE 268 "src/Graphics/UI/Gtk/WebKit/JavaScriptCore/JSObjectRef.chs" #-}

jsobjectisfunction :: JSContextRef -> JSObjectRef -> IO (Bool)
jsobjectisfunction a1 a2 =
  let {a1' = id a1} in 
  let {a2' = id a2} in 
  jsobjectisfunction'_ a1' a2' >>= \res ->
  let {res' = getBool res} in
  return (res')
{-# LINE 270 "src/Graphics/UI/Gtk/WebKit/JavaScriptCore/JSObjectRef.chs" #-}

jsobjectcallasfunction :: JSContextRef -> JSObjectRef -> JSObjectRef -> CSize -> JSValueRefRef -> JSValueRefRef -> IO (JSValueRef)
jsobjectcallasfunction a1 a2 a3 a4 a5 a6 =
  let {a1' = id a1} in 
  let {a2' = id a2} in 
  let {a3' = id a3} in 
  let {a4' = fromIntegral a4} in 
  let {a5' = id a5} in 
  let {a6' = id a6} in 
  jsobjectcallasfunction'_ a1' a2' a3' a4' a5' a6' >>= \res ->
  let {res' = id res} in
  return (res')
{-# LINE 272 "src/Graphics/UI/Gtk/WebKit/JavaScriptCore/JSObjectRef.chs" #-}

jsobjectcallasconstructor :: JSContextRef -> JSObjectRef -> CSize -> JSValueRefRef -> JSValueRefRef -> IO (JSObjectRef)
jsobjectcallasconstructor a1 a2 a3 a4 a5 =
  let {a1' = id a1} in 
  let {a2' = id a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = id a4} in 
  let {a5' = id a5} in 
  jsobjectcallasconstructor'_ a1' a2' a3' a4' a5' >>= \res ->
  let {res' = id res} in
  return (res')
{-# LINE 274 "src/Graphics/UI/Gtk/WebKit/JavaScriptCore/JSObjectRef.chs" #-}
 
jsobjectcopypropertynames :: JSContextRef -> JSObjectRef -> IO (JSPropertyNameArrayRef)
jsobjectcopypropertynames a1 a2 =
  let {a1' = id a1} in 
  let {a2' = id a2} in 
  jsobjectcopypropertynames'_ a1' a2' >>= \res ->
  let {res' = id res} in
  return (res')
{-# LINE 276 "src/Graphics/UI/Gtk/WebKit/JavaScriptCore/JSObjectRef.chs" #-}

jspropertynamearrayretain :: JSPropertyNameArrayRef -> IO (JSPropertyNameArrayRef)
jspropertynamearrayretain a1 =
  let {a1' = id a1} in 
  jspropertynamearrayretain'_ a1' >>= \res ->
  let {res' = id res} in
  return (res')
{-# LINE 278 "src/Graphics/UI/Gtk/WebKit/JavaScriptCore/JSObjectRef.chs" #-}

jspropertynamearrayrelease :: JSPropertyNameArrayRef -> IO ()
jspropertynamearrayrelease a1 =
  let {a1' = id a1} in 
  jspropertynamearrayrelease'_ a1' >>= \res ->
  return ()
{-# LINE 280 "src/Graphics/UI/Gtk/WebKit/JavaScriptCore/JSObjectRef.chs" #-}

jspropertynamearraygetcount :: JSPropertyNameArrayRef -> IO (CSize)
jspropertynamearraygetcount a1 =
  let {a1' = id a1} in 
  jspropertynamearraygetcount'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 282 "src/Graphics/UI/Gtk/WebKit/JavaScriptCore/JSObjectRef.chs" #-}

jspropertynamearraygetnameatindex :: JSPropertyNameArrayRef -> CSize -> IO (JSStringRef)
jspropertynamearraygetnameatindex a1 a2 =
  let {a1' = id a1} in 
  let {a2' = fromIntegral a2} in 
  jspropertynamearraygetnameatindex'_ a1' a2' >>= \res ->
  let {res' = id res} in
  return (res')
{-# LINE 284 "src/Graphics/UI/Gtk/WebKit/JavaScriptCore/JSObjectRef.chs" #-}

jspropertynameaccumulatoraddname :: JSPropertyNameAccumulatorRef -> JSStringRef -> IO ()
jspropertynameaccumulatoraddname a1 a2 =
  let {a1' = id a1} in 
  let {a2' = id a2} in 
  jspropertynameaccumulatoraddname'_ a1' a2' >>= \res ->
  return ()
{-# LINE 286 "src/Graphics/UI/Gtk/WebKit/JavaScriptCore/JSObjectRef.chs" #-}








foreign import ccall safe "JSClassCreate"
  jsclasscreate'_ :: ((Ptr ()) -> (IO (Ptr OpaqueJSClass)))

foreign import ccall safe "JSClassRetain"
  jsclassretain'_ :: ((Ptr OpaqueJSClass) -> (IO (Ptr OpaqueJSClass)))

foreign import ccall safe "JSClassRelease"
  jsclassrelease'_ :: ((Ptr OpaqueJSClass) -> (IO ()))

foreign import ccall safe "JSObjectMake"
  jsobjectmake'_ :: ((Ptr OpaqueJSContext) -> ((Ptr OpaqueJSClass) -> ((Ptr ()) -> (IO (Ptr OpaqueJSValue)))))

foreign import ccall safe "JSObjectMakeFunctionWithCallback"
  jsobjectmakefunctionwithcallback'_ :: ((Ptr OpaqueJSContext) -> ((Ptr OpaqueJSString) -> ((FunPtr ((Ptr OpaqueJSContext) -> ((Ptr OpaqueJSValue) -> ((Ptr OpaqueJSValue) -> (CULong -> ((Ptr JSValueRef) -> ((Ptr JSValueRef) -> (IO (Ptr OpaqueJSValue))))))))) -> (IO (Ptr OpaqueJSValue)))))

foreign import ccall safe "JSObjectMakeConstructor"
  jsobjectmakeconstructor'_ :: ((Ptr OpaqueJSContext) -> ((Ptr OpaqueJSClass) -> ((FunPtr ((Ptr OpaqueJSContext) -> ((Ptr OpaqueJSValue) -> (CULong -> ((Ptr JSValueRef) -> ((Ptr JSValueRef) -> (IO (Ptr OpaqueJSValue)))))))) -> (IO (Ptr OpaqueJSValue)))))

foreign import ccall safe "JSObjectMakeArray"
  jsobjectmakearray'_ :: ((Ptr OpaqueJSContext) -> (CULong -> ((Ptr JSValueRef) -> ((Ptr JSValueRef) -> (IO (Ptr OpaqueJSValue))))))

foreign import ccall safe "JSObjectMakeDate"
  jsobjectmakedate'_ :: ((Ptr OpaqueJSContext) -> (CULong -> ((Ptr JSValueRef) -> ((Ptr JSValueRef) -> (IO (Ptr OpaqueJSValue))))))

foreign import ccall safe "JSObjectMakeError"
  jsobjectmakeerror'_ :: ((Ptr OpaqueJSContext) -> (CULong -> ((Ptr JSValueRef) -> ((Ptr JSValueRef) -> (IO (Ptr OpaqueJSValue))))))

foreign import ccall safe "JSObjectMakeRegExp"
  jsobjectmakeregexp'_ :: ((Ptr OpaqueJSContext) -> (CULong -> ((Ptr JSValueRef) -> ((Ptr JSValueRef) -> (IO (Ptr OpaqueJSValue))))))

foreign import ccall safe "JSObjectMakeFunction"
  jsobjectmakefunction'_ :: ((Ptr OpaqueJSContext) -> ((Ptr OpaqueJSString) -> (CUInt -> ((Ptr JSStringRef) -> ((Ptr OpaqueJSString) -> ((Ptr OpaqueJSString) -> (CInt -> ((Ptr JSValueRef) -> (IO (Ptr OpaqueJSValue))))))))))

foreign import ccall safe "JSObjectGetPrototype"
  jsobjectgetprototype'_ :: ((Ptr OpaqueJSContext) -> ((Ptr OpaqueJSValue) -> (IO (Ptr OpaqueJSValue))))

foreign import ccall safe "JSObjectSetPrototype"
  jsobjectsetprototype'_ :: ((Ptr OpaqueJSContext) -> ((Ptr OpaqueJSValue) -> ((Ptr OpaqueJSValue) -> (IO ()))))

foreign import ccall safe "JSObjectHasProperty"
  jsobjecthasproperty'_ :: ((Ptr OpaqueJSContext) -> ((Ptr OpaqueJSValue) -> ((Ptr OpaqueJSString) -> (IO CUChar))))

foreign import ccall safe "JSObjectGetProperty"
  jsobjectgetproperty'_ :: ((Ptr OpaqueJSContext) -> ((Ptr OpaqueJSValue) -> ((Ptr OpaqueJSString) -> ((Ptr JSValueRef) -> (IO (Ptr OpaqueJSValue))))))

foreign import ccall safe "JSObjectSetProperty"
  jsobjectsetproperty'_ :: ((Ptr OpaqueJSContext) -> ((Ptr OpaqueJSValue) -> ((Ptr OpaqueJSString) -> ((Ptr OpaqueJSValue) -> (CUInt -> ((Ptr JSValueRef) -> (IO ())))))))

foreign import ccall safe "JSObjectDeleteProperty"
  jsobjectdeleteproperty'_ :: ((Ptr OpaqueJSContext) -> ((Ptr OpaqueJSValue) -> ((Ptr OpaqueJSString) -> ((Ptr JSValueRef) -> (IO CUChar)))))

foreign import ccall safe "JSObjectGetPropertyAtIndex"
  jsobjectgetpropertyatindex'_ :: ((Ptr OpaqueJSContext) -> ((Ptr OpaqueJSValue) -> (CUInt -> ((Ptr JSValueRef) -> (IO (Ptr OpaqueJSValue))))))

foreign import ccall safe "JSObjectSetPropertyAtIndex"
  jsobjectsetpropertyatindex'_ :: ((Ptr OpaqueJSContext) -> ((Ptr OpaqueJSValue) -> (CUInt -> ((Ptr OpaqueJSValue) -> ((Ptr JSValueRef) -> (IO ()))))))

foreign import ccall safe "JSObjectGetPrivate"
  jsobjectgetprivate'_ :: ((Ptr OpaqueJSValue) -> (IO (Ptr ())))

foreign import ccall safe "JSObjectSetPrivate"
  jsobjectsetprivate'_ :: ((Ptr OpaqueJSValue) -> ((Ptr ()) -> (IO CUChar)))

foreign import ccall safe "JSObjectIsFunction"
  jsobjectisfunction'_ :: ((Ptr OpaqueJSContext) -> ((Ptr OpaqueJSValue) -> (IO CUChar)))

foreign import ccall safe "JSObjectCallAsFunction"
  jsobjectcallasfunction'_ :: ((Ptr OpaqueJSContext) -> ((Ptr OpaqueJSValue) -> ((Ptr OpaqueJSValue) -> (CULong -> ((Ptr JSValueRef) -> ((Ptr JSValueRef) -> (IO (Ptr OpaqueJSValue))))))))

foreign import ccall safe "JSObjectCallAsConstructor"
  jsobjectcallasconstructor'_ :: ((Ptr OpaqueJSContext) -> ((Ptr OpaqueJSValue) -> (CULong -> ((Ptr JSValueRef) -> ((Ptr JSValueRef) -> (IO (Ptr OpaqueJSValue)))))))

foreign import ccall safe "JSObjectCopyPropertyNames"
  jsobjectcopypropertynames'_ :: ((Ptr OpaqueJSContext) -> ((Ptr OpaqueJSValue) -> (IO (Ptr OpaqueJSPropertyNameArray))))

foreign import ccall safe "JSPropertyNameArrayRetain"
  jspropertynamearrayretain'_ :: ((Ptr OpaqueJSPropertyNameArray) -> (IO (Ptr OpaqueJSPropertyNameArray)))

foreign import ccall safe "JSPropertyNameArrayRelease"
  jspropertynamearrayrelease'_ :: ((Ptr OpaqueJSPropertyNameArray) -> (IO ()))

foreign import ccall safe "JSPropertyNameArrayGetCount"
  jspropertynamearraygetcount'_ :: ((Ptr OpaqueJSPropertyNameArray) -> (IO CULong))

foreign import ccall safe "JSPropertyNameArrayGetNameAtIndex"
  jspropertynamearraygetnameatindex'_ :: ((Ptr OpaqueJSPropertyNameArray) -> (CULong -> (IO (Ptr OpaqueJSString))))

foreign import ccall safe "JSPropertyNameAccumulatorAddName"
  jspropertynameaccumulatoraddname'_ :: ((Ptr OpaqueJSPropertyNameAccumulator) -> ((Ptr OpaqueJSString) -> (IO ())))