CURL Extern Type, reproduce CURL low level behaviors

Introduced properties

fun easy_clean

curl :: NativeCurl :: easy_clean

Easy Clean / Release CURL instance
fun easy_getinfo_chars(opt: CURLInfoChars): nullable String

curl :: NativeCurl :: easy_getinfo_chars

Request Chars internal information from the CURL session
fun easy_getinfo_double(opt: CURLInfoDouble): nullable Float

curl :: NativeCurl :: easy_getinfo_double

Request Double internal information from the CURL session
fun easy_getinfo_long(opt: CURLInfoLong): nullable Int

curl :: NativeCurl :: easy_getinfo_long

Request Long internal information from the CURL session
fun easy_getinfo_slist(opt: CURLInfoSList): nullable Array[String]

curl :: NativeCurl :: easy_getinfo_slist

Request SList internal information from the CURL session
init easy_init: NativeCurl

curl :: NativeCurl :: easy_init

Constructor, CURL low level initializer
fun easy_perform: CURLCode

curl :: NativeCurl :: easy_perform

Perform the transfer described by setted options
fun easy_setopt(opt: CURLOption, obj: Object): CURLCode

curl :: NativeCurl :: easy_setopt

Set options to tell CURL how to behave. Obj parameter type can be Int, Bool, String, FileWriter, CURLSList.
fun escape(url: String): String

curl :: NativeCurl :: escape

Convert given string to URL encoded string
fun is_init: Bool

curl :: NativeCurl :: is_init

Check for correct initialization
fun register_callback_body(delegate: NativeCurlCallbacks): CURLCode

curl :: NativeCurl :: register_callback_body

Register delegate to get callbacks about the CURL transfer
fun register_callback_header(delegate: NativeCurlCallbacks): CURLCode

curl :: NativeCurl :: register_callback_header

Register delegate to get callbacks about the CURL transfer
fun register_callback_read(delegate: NativeCurlCallbacks): CURLCode

curl :: NativeCurl :: register_callback_read

Register delegate to get callbacks about the CURL transfer
fun register_callback_stream(delegate: NativeCurlCallbacks): CURLCode

curl :: NativeCurl :: register_callback_stream

Register delegate to get callbacks about the CURL transfer
fun register_read_datas_callback(delegate: NativeCurlCallbacks, datas: String): CURLCode

curl :: NativeCurl :: register_read_datas_callback

Register delegate to read datas from given buffer

Redefined properties

redef type SELF: NativeCurl

curl $ NativeCurl :: SELF

Type of this instance, automatically specialized in every class

All properties

fun !=(other: nullable Object): Bool

core :: Object :: !=

Have self and other different values?
fun ==(other: nullable Object): Bool

core :: Object :: ==

Have self and other the same value?
type CLASS: Class[SELF]

core :: Object :: CLASS

The type of the class of self.
type SELF: Object

core :: Object :: SELF

Type of this instance, automatically specialized in every class
fun address_is_null: Bool

core :: Pointer :: address_is_null

Is the address behind this Object at NULL?
protected fun class_factory(name: String): CLASS

core :: Object :: class_factory

Implementation used by get_class to create the specific class.
fun class_name: String

core :: Object :: class_name

The class name of the object.
fun easy_clean

curl :: NativeCurl :: easy_clean

Easy Clean / Release CURL instance
fun easy_getinfo_chars(opt: CURLInfoChars): nullable String

curl :: NativeCurl :: easy_getinfo_chars

Request Chars internal information from the CURL session
fun easy_getinfo_double(opt: CURLInfoDouble): nullable Float

curl :: NativeCurl :: easy_getinfo_double

Request Double internal information from the CURL session
fun easy_getinfo_long(opt: CURLInfoLong): nullable Int

curl :: NativeCurl :: easy_getinfo_long

Request Long internal information from the CURL session
fun easy_getinfo_slist(opt: CURLInfoSList): nullable Array[String]

curl :: NativeCurl :: easy_getinfo_slist

Request SList internal information from the CURL session
init easy_init: NativeCurl

curl :: NativeCurl :: easy_init

Constructor, CURL low level initializer
fun easy_perform: CURLCode

curl :: NativeCurl :: easy_perform

Perform the transfer described by setted options
fun easy_setopt(opt: CURLOption, obj: Object): CURLCode

curl :: NativeCurl :: easy_setopt

Set options to tell CURL how to behave. Obj parameter type can be Int, Bool, String, FileWriter, CURLSList.
fun escape(url: String): String

curl :: NativeCurl :: escape

Convert given string to URL encoded string
fun free

core :: Pointer :: free

Free the memory pointed by this pointer
fun get_class: CLASS

core :: Object :: get_class

The meta-object representing the dynamic type of self.
fun hash: Int

core :: Object :: hash

The hash code of the object.
init init

core :: Object :: init

fun inspect: String

core :: Object :: inspect

Developer readable representation of self.
protected fun inspect_head: String

core :: Object :: inspect_head

Return "CLASSNAME:#OBJECTID".
fun is_init: Bool

curl :: NativeCurl :: is_init

Check for correct initialization
intern fun is_same_instance(other: nullable Object): Bool

core :: Object :: is_same_instance

Return true if self and other are the same instance (i.e. same identity).
fun is_same_serialized(other: nullable Object): Bool

core :: Object :: is_same_serialized

Is self the same as other in a serialization context?
intern fun is_same_type(other: Object): Bool

core :: Object :: is_same_type

Return true if self and other have the same dynamic type.
init nul: Pointer

core :: Pointer :: nul

C NULL pointer
intern fun object_id: Int

core :: Object :: object_id

An internal hash code for the object based on its identity.
fun output

core :: Object :: output

Display self on stdout (debug only).
intern fun output_class_name

core :: Object :: output_class_name

Display class name on stdout (debug only).
fun register_callback_body(delegate: NativeCurlCallbacks): CURLCode

curl :: NativeCurl :: register_callback_body

Register delegate to get callbacks about the CURL transfer
fun register_callback_header(delegate: NativeCurlCallbacks): CURLCode

curl :: NativeCurl :: register_callback_header

Register delegate to get callbacks about the CURL transfer
fun register_callback_read(delegate: NativeCurlCallbacks): CURLCode

curl :: NativeCurl :: register_callback_read

Register delegate to get callbacks about the CURL transfer
fun register_callback_stream(delegate: NativeCurlCallbacks): CURLCode

curl :: NativeCurl :: register_callback_stream

Register delegate to get callbacks about the CURL transfer
fun register_read_datas_callback(delegate: NativeCurlCallbacks, datas: String): CURLCode

curl :: NativeCurl :: register_read_datas_callback

Register delegate to read datas from given buffer
fun serialization_hash: Int

core :: Object :: serialization_hash

Hash value use for serialization
intern fun sys: Sys

core :: Object :: sys

Return the global sys object, the only instance of the Sys class.
abstract fun to_jvalue(env: JniEnv): JValue

core :: Object :: to_jvalue

fun to_s: String

core :: Object :: to_s

User readable representation of self.
package_diagram curl::NativeCurl NativeCurl core::Pointer Pointer curl::NativeCurl->core::Pointer core::Object Object core::Pointer->core::Object ...core::Object ... ...core::Object->core::Object

Ancestors

interface Object

core :: Object

The root of the class hierarchy.

Parents

extern class Pointer

core :: Pointer

Pointer classes are used to manipulate extern C structures.

Class definitions

curl $ NativeCurl
# CURL Extern Type, reproduce CURL low level behaviors
extern class NativeCurl `{ CURL * `}
	# Constructor, CURL low level initializer
	new easy_init `{ return curl_easy_init(); `}

	# Check for correct initialization
	fun is_init: Bool `{ return (self != NULL); `}

	# Easy Clean / Release CURL instance
	fun easy_clean `{ curl_easy_cleanup( self ); `}

	# Perform the transfer described by setted options
	fun easy_perform: CURLCode `{ return curl_easy_perform( self ); `}

	# Set options to tell CURL how to behave. Obj parameter type can be Int, Bool, String, FileWriter, CURLSList.
	fun easy_setopt(opt: CURLOption, obj: Object): CURLCode
	do
		if obj isa Int then return native_setopt_int(opt, obj)
		if obj == true then return native_setopt_int(opt, 1)
		if obj == false then return native_setopt_int(opt, 0)
		if obj isa String then return native_setopt_string(opt, obj.to_cstring)
		if obj isa FileWriter then return native_setopt_file(opt, obj._file.as(not null))
		if obj isa CURLSList then return native_setopt_slist(opt, obj)
		return once new CURLCode.unknown_option
	end

	# Internal method to set options to CURL using NativeFile parameter.
	private fun native_setopt_file(opt: CURLOption, file: NativeFile): CURLCode `{
		return curl_easy_setopt( self, opt, file);
	`}

	# Internal method to set options to CURL using Int parameter.
	private fun native_setopt_int(opt: CURLOption, num: Int): CURLCode `{ return curl_easy_setopt( self, opt, num); `}

	# Internal method to set options to CURL using CURLSList parameter.
	private fun native_setopt_slist(opt: CURLOption, list: CURLSList): CURLCode `{ return curl_easy_setopt( self, opt, list); `}

	# Internal method to set options to CURL using String parameter.
	private fun native_setopt_string(opt: CURLOption, str: CString): CURLCode `{
		return curl_easy_setopt( self, opt, str);
	`}

	# Request Chars internal information from the CURL session
	fun easy_getinfo_chars(opt: CURLInfoChars): nullable String
	do
		 var answ = new Ref[CString]("".to_cstring)
		 if not native_getinfo_chars(opt, answ).is_ok then return null
		 if answ.item.address_is_null then return null
		 return answ.item.to_s
	end

	# Internal method used to get String object information initially known as C Chars type
	private fun native_getinfo_chars(opt: CURLInfoChars, res: Ref[CString]): CURLCode
	import Ref[CString].item= `{
		char *r;
		CURLcode c = curl_easy_getinfo( self, opt, &r);
		if (c == CURLE_OK) Ref_of_CString_item__assign(res, r);
		return c;
	`}

	# Request Long internal information from the CURL session
	fun easy_getinfo_long(opt: CURLInfoLong): nullable Int
	do
		 var answ = new Ref[Int](0)
		 if not native_getinfo_long(opt, answ).is_ok then return null
		 return answ.item
	end

	# Internal method used to get Int object information initially knowns as C Long type
	private fun native_getinfo_long(opt: CURLInfoLong, res: Ref[Int]): CURLCode
	import Ref[Int].item= `{
		long r;
		CURLcode c = curl_easy_getinfo( self, opt, &r);
		if (c == CURLE_OK) Ref_of_Int_item__assign(res, r);
		return c;
	`}

	# Request Double internal information from the CURL session
	fun easy_getinfo_double(opt: CURLInfoDouble): nullable Float
	do
		 var answ = new Ref[Float](0.0)
		 if not native_getinfo_double(opt, answ).is_ok then return null
		 return answ.item
	end

	# Internal method used to get Int object information initially knowns as C Double type
	private fun native_getinfo_double(opt: CURLInfoDouble, res: Ref[Float]): CURLCode
	import Ref[Float].item= `{
		double r;
		CURLcode c = curl_easy_getinfo(self, opt, &r);
		if (c == CURLE_OK) Ref_of_Float_item__assign(res, r);
		return c;
	`}

	# Request SList internal information from the CURL session
	fun easy_getinfo_slist(opt: CURLInfoSList): nullable Array[String]
	do
		var answ = new Ref[CURLSList](new CURLSList)
		if not native_getinfo_slist(opt, answ).is_ok then return null

		var native = answ.item
		var nity = native.to_a
		native.destroy
		return nity
	end

	# Internal method used to get Array[String] object information initially knowns as C SList type
	private fun native_getinfo_slist(opt: CURLInfoSList, res: Ref[CURLSList]): CURLCode
	import Ref[CURLSList].item= `{
		struct curl_slist* csl;
		CURLcode c = curl_easy_getinfo(self, opt, &csl);
		if (c == CURLE_OK) Ref_of_CURLSList_item__assign(res, csl);
		return c;
	`}

	# Register delegate to read datas from given buffer
	fun register_read_datas_callback(delegate: NativeCurlCallbacks, datas: String): CURLCode
	do
		if datas.length > 0 then return native_register_read_datas_callback(delegate, datas, datas.length)
		return once new CURLCode.unknown_option
	end

	# Internal method used to configure read callback
	private fun native_register_read_datas_callback(delegate: NativeCurlCallbacks, datas: String, size: Int): CURLCode import String.to_cstring `{
		CURLCallbackReadDatas *d = NULL;
		d = malloc(sizeof(CURLCallbackReadDatas));
		d->data = (char*)String_to_cstring(datas);
		d->len = size;
		d->pos = 0;
		return curl_easy_setopt( self, CURLOPT_READDATA, d);
	`}

	# Register `delegate` to get callbacks about the CURL transfer
	fun register_callback_header(delegate: NativeCurlCallbacks): CURLCode
	import CString.native_callback_header `{
		CURLcode e;
		NativeCurlCallbacks_incr_ref(delegate); // FIXME deallocated these when download completes?

		e = curl_easy_setopt(self, CURLOPT_HEADERFUNCTION, (curl_write_callback)&CString_native_callback_header);
		if(e != CURLE_OK) return e;

		e = curl_easy_setopt(self, CURLOPT_WRITEHEADER, delegate);
		return e;
	`}

	# Register `delegate` to get callbacks about the CURL transfer
	fun register_callback_body(delegate: NativeCurlCallbacks): CURLCode
	import CString.native_callback_body `{
		CURLcode e;
		NativeCurlCallbacks_incr_ref(delegate);

		e = curl_easy_setopt(self, CURLOPT_WRITEFUNCTION, (curl_write_callback)&CString_native_callback_body);
		if(e != CURLE_OK) return e;

		e = curl_easy_setopt(self, CURLOPT_WRITEDATA, delegate);
		return e;
	`}

	# Register `delegate` to get callbacks about the CURL transfer
	fun register_callback_stream(delegate: NativeCurlCallbacks): CURLCode
	import CString.native_callback_stream `{
		CURLcode e;
		NativeCurlCallbacks_incr_ref(delegate);

		e = curl_easy_setopt(self, CURLOPT_WRITEFUNCTION, (curl_write_callback)&CString_native_callback_stream);
		if(e != CURLE_OK) return e;

		e = curl_easy_setopt(self, CURLOPT_WRITEDATA, delegate);
		return e;
	`}

	# Register `delegate` to get callbacks about the CURL transfer
	fun register_callback_read(delegate: NativeCurlCallbacks): CURLCode
	import CString.native_callback_stream `{
		NativeCurlCallbacks_incr_ref(delegate);

		return curl_easy_setopt(self, CURLOPT_READFUNCTION, (curl_write_callback)&nit_curl_callback_read_func);
	`}

	# Convert given string to URL encoded string
	fun escape(url: String): String import String.to_cstring, CString.to_s `{
		char *orig_url, *encoded_url = NULL;
		orig_url = String_to_cstring(url);
		encoded_url = curl_easy_escape( self, orig_url, strlen(orig_url));
		String b_url = CString_to_s(encoded_url);
		curl_free(encoded_url);
		return b_url;
	`}
end
lib/curl/native_curl.nit:72,1--260,3