Home | History | Annotate | Download | only in ocaml
      1 /* -----------------------------------------------------------------------------
      2  * std_vector.i
      3  *
      4  * SWIG typemaps for std::vector types
      5  * ----------------------------------------------------------------------------- */
      6 
      7 %include <std_common.i>
      8 
      9 // ------------------------------------------------------------------------
     10 // std::vector
     11 //
     12 // The aim of all that follows would be to integrate std::vector with
     13 // Python as much as possible, namely, to allow the user to pass and
     14 // be returned Python tuples or lists.
     15 // const declarations are used to guess the intent of the function being
     16 // exported; therefore, the following rationale is applied:
     17 //
     18 //   -- f(std::vector<T>), f(const std::vector<T>&), f(const std::vector<T>*):
     19 //      the parameter being read-only, either a Python sequence or a
     20 //      previously wrapped std::vector<T> can be passed.
     21 //   -- f(std::vector<T>&), f(std::vector<T>*):
     22 //      the parameter must be modified; therefore, only a wrapped std::vector
     23 //      can be passed.
     24 //   -- std::vector<T> f():
     25 //      the vector is returned by copy; therefore, a Python sequence of T:s
     26 //      is returned which is most easily used in other Python functions
     27 //   -- std::vector<T>& f(), std::vector<T>* f(), const std::vector<T>& f(),
     28 //      const std::vector<T>* f():
     29 //      the vector is returned by reference; therefore, a wrapped std::vector
     30 //      is returned
     31 // ------------------------------------------------------------------------
     32 
     33 %{
     34 #include <vector>
     35 #include <algorithm>
     36 #include <stdexcept>
     37 %}
     38 
     39 // exported class
     40 
     41 namespace std {
     42     template <class T> class vector {
     43     public:
     44         vector(unsigned int size = 0);
     45         vector(unsigned int size, const T& value);
     46         vector(const vector<T>&);
     47         unsigned int size() const;
     48         bool empty() const;
     49         void clear();
     50         void push_back(const T& x);
     51 	T operator [] ( int f );
     52 	vector <T> &operator = ( vector <T> &other );
     53 	%extend {
     54 	    void set( int i, const T &x ) {
     55 		self->resize(i+1);
     56 		(*self)[i] = x;
     57 	    }
     58 	};
     59 	%extend {
     60 	    T *to_array() {
     61 		T *array = new T[self->size() + 1];
     62 		for( int i = 0; i < self->size(); i++ )
     63 		    array[i] = (*self)[i];
     64 		return array;
     65 	    }
     66 	};
     67     };
     68 };
     69 
     70 %insert(ml) %{
     71 
     72   let array_to_vector v argcons array =
     73     for i = 0 to (Array.length array) - 1 do
     74 	(invoke v) "set" (C_list [ C_int i ; (argcons array.(i)) ])
     75     done ;
     76     v
     77 
     78   let vector_to_array v argcons array =
     79     for i = 0; to (get_int ((invoke v) "size" C_void)) - 1 do
     80 	array.(i) <- argcons ((invoke v) "[]" (C_int i))
     81     done ;
     82     v
     83 
     84 %}
     85 
     86 %insert(mli) %{
     87     val array_to_vector : c_obj -> ('a -> c_obj) -> 'a array -> c_obj
     88     val vector_to_array : c_obj -> (c_obj -> 'a) -> 'a array -> c_obj
     89 %}
     90