Initial commit of OpenSPARC T2 architecture model.
[OpenSPARC-T2-SAM] / sam-t2 / devtools / amd64 / share / swig / 1.3.26 / ocaml / std_string.i
CommitLineData
920dae64
AT
1// -*- C++ -*-
2// SWIG typemaps for std::string
3// Art Yerkes
4// Modified from: Luigi Ballabio
5// Apr 8, 2002
6//
7// Ocaml implementation
8
9// ------------------------------------------------------------------------
10// std::string is typemapped by value
11// This can prevent exporting methods which return a string
12// in order for the user to modify it.
13// However, I think I'll wait until someone asks for it...
14// ------------------------------------------------------------------------
15
16%include exception.i
17
18%{
19#include <string>
20#include <vector>
21 using std::string;
22 using std::vector;
23%}
24
25%include std_vector.i
26
27namespace std {
28 template <class charT> class basic_string {
29 public:
30 typedef charT *pointer;
31 typedef charT &reference;
32 typedef const charT &const_reference;
33 typedef size_t size_type;
34 typedef ptrdiff_t difference_type;
35 basic_string();
36 basic_string( charT *str );
37 size_t size();
38 charT operator []( int pos ) const;
39 charT *c_str() const;
40 basic_string<charT> &operator = ( const basic_string &ws );
41 basic_string<charT> &operator = ( const charT *str );
42 basic_string<charT> &append( const basic_string<charT> &other );
43 basic_string<charT> &append( const charT *str );
44 void push_back( charT c );
45 void clear();
46 void reserve( size_type t );
47 void resize( size_type n, charT c = charT() );
48 int compare( const basic_string<charT> &other ) const;
49 int compare( const charT *str ) const;
50 basic_string<charT> &insert( size_type pos,
51 const basic_string<charT> &str );
52 size_type find( const basic_string<charT> &other, int pos = 0 ) const;
53 size_type find( charT c, int pos = 0 ) const;
54 %extend {
55 bool operator == ( const basic_string<charT> &other ) const {
56 return self->compare( other ) == 0;
57 }
58 bool operator != ( const basic_string<charT> &other ) const {
59 return self->compare( other ) != 0;
60 }
61 bool operator < ( const basic_string<charT> &other ) const {
62 return self->compare( other ) == -1;
63 }
64 bool operator > ( const basic_string<charT> &other ) const {
65 return self->compare( other ) == 1;
66 }
67 bool operator <= ( const basic_string<charT> &other ) const {
68 return self->compare( other ) != 1;
69 }
70 bool operator >= ( const basic_string<charT> &other ) const {
71 return self->compare( other ) != -1;
72 }
73 }
74 };
75
76 %template(string) basic_string<char>;
77 %template(wstring) basic_string<wchar_t>;
78 typedef basic_string<char> string;
79 typedef basic_string<wchar_t> wstring;
80
81 /* Overloading check */
82 %typemap(in) string {
83 if (caml_ptr_check($input))
84 $1 = std::string((char *)caml_ptr_val($input,0),
85 caml_string_len($input));
86 else
87 SWIG_exception(SWIG_TypeError, "string expected");
88 }
89
90 %typemap(in) const string & (std::string temp) {
91 if (caml_ptr_check($input)) {
92 temp = std::string((char *)caml_ptr_val($input,0),
93 caml_string_len($input));
94 $1 = &temp;
95 } else {
96 SWIG_exception(SWIG_TypeError, "string expected");
97 }
98 }
99
100 %typemap(in) string & (std::string temp) {
101 if (caml_ptr_check($input)) {
102 temp = std::string((char *)caml_ptr_val($input,0),
103 caml_string_len($input));
104 $1 = &temp;
105 } else {
106 SWIG_exception(SWIG_TypeError, "string expected");
107 }
108 }
109
110 %typemap(in) string * (std::string *temp) {
111 if (caml_ptr_check($input)) {
112 temp = new std::string((char *)caml_ptr_val($input,0),
113 caml_string_len($input));
114 $1 = temp;
115 } else {
116 SWIG_exception(SWIG_TypeError, "string expected");
117 }
118 }
119
120 %typemap(free) string * (std::string *temp) {
121 delete temp;
122 }
123
124 %typemap(argout) string & {
125 caml_list_append(swig_result,caml_val_string_len((*$1).c_str(),
126 (*$1).size()));
127 }
128
129 %typemap(directorout) string {
130 $result = std::string((char *)caml_ptr_val($input,0),
131 caml_string_len($input));
132 }
133
134 %typemap(out) string {
135 $result = caml_val_string_len($1.c_str(),$1.size());
136 }
137
138 %typemap(out) string * {
139 $result = caml_val_string_len((*$1).c_str(),(*$1).size());
140 }
141}
142
143#ifdef ENABLE_CHARPTR_ARRAY
144char **c_charptr_array( const std::vector <string > &str_v );
145
146%{
147 SWIGEXT char **c_charptr_array( const std::vector <string > &str_v ) {
148 char **out = new char *[str_v.size() + 1];
149 out[str_v.size()] = 0;
150 for( int i = 0; i < str_v.size(); i++ ) {
151 out[i] = (char *)str_v[i].c_str();
152 }
153 return out;
154 }
155%}
156#endif
157
158#ifdef ENABLE_STRING_VECTOR
159%template (StringVector) std::vector<string >;
160
161%insert(ml) %{
162 (* Some STL convenience items *)
163
164 let string_array_to_vector sa =
165 let nv = _new_StringVector C_void in
166 array_to_vector nv (fun x -> C_string x) sa ; nv
167
168 let c_string_array ar =
169 _c_charptr_array (string_array_to_vector ar)
170%}
171
172%insert(mli) %{
173 val c_string_array: string array -> c_obj
174%}
175#endif