~clint-fewbar/ubuntu/precise/erlang/merge-15b

« back to all changes in this revision

Viewing changes to lib/odbc/test/mysql.erl

  • Committer: Package Import Robot
  • Author(s): Sergei Golovan
  • Date: 2011-12-15 19:20:10 UTC
  • mfrom: (1.1.18) (3.5.15 sid)
  • mto: (3.5.16 sid)
  • mto: This revision was merged to the branch mainline in revision 33.
  • Revision ID: package-import@ubuntu.com-20111215192010-jnxcfe3tbrpp0big
Tags: 1:15.b-dfsg-1
* New upstream release.
* Upload to experimental because this release breaks external drivers
  API along with ABI, so several applications are to be fixed.
* Removed SSL patch because the old SSL implementation is removed from
  the upstream distribution.
* Removed never used patch which added native code to erlang beam files.
* Removed the erlang-docbuilder binary package because the docbuilder
  application was dropped by upstream.
* Documented dropping ${erlang-docbuilder:Depends} substvar in
  erlang-depends(1) manpage.
* Made erlang-base and erlang-base-hipe provide virtual package
  erlang-abi-15.b (the number means the first erlang version, which
  provides current ABI).

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%%
 
4
%% Copyright Ericsson AB 2011-2011. All Rights Reserved.
 
5
%%
 
6
%% The contents of this file are subject to the Erlang Public License,
 
7
%% Version 1.1, (the "License"); you may not use this file except in
 
8
%% compliance with the License. You should have received a copy of the
 
9
%% Erlang Public License along with this software. If not, it can be
 
10
%% retrieved online at http://www.erlang.org/.
 
11
%%
 
12
%% Software distributed under the License is distributed on an "AS IS"
 
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
14
%% the License for the specific language governing rights and limitations
 
15
%% under the License.
 
16
%%
 
17
%% %CopyrightEnd%
 
18
%%
 
19
 
 
20
%%
 
21
 
 
22
-module(mysql).
 
23
 
 
24
%% Note: This directive should only be used in test suites.
 
25
-compile(export_all).
 
26
 
 
27
%-------------------------------------------------------------------------
 
28
connection_string() ->
 
29
    case test_server:os_type() of
 
30
        {unix, linux} ->
 
31
            "DSN=MySQL;Database=odbctest;Uid=odbctest;Pwd=gurka;CHARSET=utf8;SSTMT=SET NAMES 'utf8';";
 
32
        {unix, sunos} ->
 
33
            solaris_str();
 
34
        {unix, darwin} ->
 
35
            "DSN=MySQLMac;Database=odbctest;Uid=odbctest;Pwd=gurka;CHARSET=utf8;SSTMT=SET NAMES 'utf8';"
 
36
    end.
 
37
 
 
38
solaris_str() ->
 
39
    case erlang:system_info(system_architecture) of
 
40
        "sparc" ++ _ ->
 
41
            "DSN=MySQLSolaris10;Database=odbctest;Uid=odbctest;Pwd=gurka;CHARSET=utf8;SSTMT=SET NAMES 'utf8';";
 
42
        "i386" ++ _ ->
 
43
            "DSN=MySQLSolaris10i386;Database=odbctest;Uid=odbctest;Pwd=gurka;CHARSET=utf8;SSTMT=SET NAMES 'utf8';"
 
44
    end.
 
45
 
 
46
%-------------------------------------------------------------------------
 
47
insert_result() ->
 
48
    {selected,["ID","DATA"],[{1,"bar"}]}.
 
49
 
 
50
update_result() ->
 
51
    {selected,["ID","DATA"],[{1,"foo"}]}.
 
52
 
 
53
selected_ID(N, next) ->
 
54
    {selected,["ID"],[{N}]};
 
55
 
 
56
selected_ID(_, _) ->
 
57
    {error, driver_does_not_support_function}.
 
58
 
 
59
selected_next_N(1)->
 
60
    {selected,["ID"],
 
61
     [{1},
 
62
      {2},
 
63
      {3}]};
 
64
 
 
65
selected_next_N(2)->
 
66
    {selected,["ID"],
 
67
     [{4},
 
68
      {5}]}.
 
69
 
 
70
selected_relative_N(_)->
 
71
    {error, driver_does_not_support_function}.
 
72
 
 
73
selected_absolute_N(_)->
 
74
    {error, driver_does_not_support_function}.
 
75
 
 
76
selected_list_rows() ->
 
77
    {selected,["ID", "DATA"],[[1, "bar"],[2,"foo"]]}.
 
78
 
 
79
first_list_rows() ->
 
80
    {error, driver_does_not_support_function}.
 
81
last_list_rows() ->
 
82
    {error, driver_does_not_support_function}.
 
83
prev_list_rows() ->
 
84
    {error, driver_does_not_support_function}.
 
85
next_list_rows() ->
 
86
    {selected,["ID","DATA"],[[1,"bar"]]}.
 
87
 
 
88
multiple_select()->
 
89
    [{selected,["ID", "DATA"],[{1, "bar"},{2, "foo"}]},
 
90
     {selected,["ID"],[{"foo"}]}].
 
91
 
 
92
multiple_mix()->
 
93
    [{updated, 1},{updated, 1},
 
94
     {selected,["ID", "DATA"],[{1, "foobar"},{2, "foo"}]},
 
95
     {updated, 1}, {selected,["DATA"],[{"foo"}]}].
 
96
 
 
97
%-------------------------------------------------------------------------
 
98
var_char_min() ->
 
99
    0.
 
100
var_char_max() ->
 
101
    65535.
 
102
 
 
103
create_var_char_table(Size) ->
 
104
    " (FIELD varchar(" ++ integer_to_list(Size) ++ "))".
 
105
 
 
106
%-------------------------------------------------------------------------
 
107
text_min() ->
 
108
    1.
 
109
text_max() ->
 
110
   2147483646. % 2147483647. %% 2^31 - 1
 
111
 
 
112
create_text_table() ->
 
113
    " (FIELD text)".
 
114
 
 
115
%-------------------------------------------------------------------------
 
116
create_timestamp_table() ->
 
117
    " (FIELD TIMESTAMP)".
 
118
 
 
119
%-------------------------------------------------------------------------
 
120
tiny_int_min() ->
 
121
    -128.
 
122
tiny_int_max() ->
 
123
    127.
 
124
 
 
125
create_tiny_int_table() ->
 
126
     " (FIELD tinyint)".
 
127
 
 
128
tiny_int_min_selected() ->
 
129
    {selected,["FIELD"],[{tiny_int_min()}]}.
 
130
 
 
131
tiny_int_max_selected() ->
 
132
    {selected,["FIELD"], [{tiny_int_max()}]}.
 
133
 
 
134
%-------------------------------------------------------------------------
 
135
small_int_min() ->
 
136
    -32768.
 
137
small_int_max() ->
 
138
    32767.
 
139
 
 
140
create_small_int_table() ->
 
141
     " (FIELD smallint)".
 
142
 
 
143
small_int_min_selected() ->
 
144
    {selected,["FIELD"],[{-32768}]}.
 
145
 
 
146
small_int_max_selected() ->
 
147
    {selected,["FIELD"], [{32767}]}.
 
148
 
 
149
%-------------------------------------------------------------------------
 
150
int_min() ->
 
151
   -2147483648.
 
152
int_max() ->
 
153
    2147483647.
 
154
 
 
155
create_int_table() ->
 
156
     " (FIELD int)".
 
157
 
 
158
int_min_selected() ->
 
159
    {selected,["FIELD"],[{-2147483648}]}.
 
160
 
 
161
int_max_selected() ->
 
162
    {selected,["FIELD"], [{2147483647}]}.
 
163
 
 
164
%-------------------------------------------------------------------------
 
165
big_int_min() ->
 
166
    -9223372036854775808.
 
167
 
 
168
big_int_max() ->
 
169
    9223372036854775807.
 
170
 
 
171
create_big_int_table() ->
 
172
     " (FIELD bigint )".
 
173
 
 
174
big_int_min_selected() ->
 
175
    {selected,["FIELD"], [{"-9223372036854775808"}]}.
 
176
 
 
177
big_int_max_selected() ->
 
178
    {selected,["FIELD"], [{"9223372036854775807"}]}.
 
179
 
 
180
%-------------------------------------------------------------------------
 
181
bit_false() ->
 
182
    0.
 
183
bit_true() ->
 
184
    1.
 
185
 
 
186
create_bit_table() ->
 
187
     " (FIELD bit)".
 
188
 
 
189
bit_false_selected() ->
 
190
    {selected,["FIELD"],[{"0"}]}.
 
191
 
 
192
bit_true_selected() ->
 
193
    {selected,["FIELD"], [{"1"}]}.
 
194
 
 
195
%-------------------------------------------------------------------------
 
196
 
 
197
%% Do not test float min/max as value is only theoretical defined in
 
198
%% mysql and may vary depending on hardware.
 
199
 
 
200
create_float_table() ->
 
201
    " (FIELD float)".
 
202
 
 
203
float_zero_selected() ->
 
204
    {selected,["FIELD"],[{0.00000e+0}]}.
 
205
 
 
206
%-------------------------------------------------------------------------
 
207
real_min() ->
 
208
    -3.40e+38.
 
209
real_max() ->
 
210
    3.40e+38.
 
211
 
 
212
real_underflow() ->
 
213
    "-3.41e+38".
 
214
 
 
215
real_overflow() ->
 
216
    "3.41e+38".
 
217
 
 
218
create_real_table() ->
 
219
    " (FIELD real)".
 
220
 
 
221
real_zero_selected() ->
 
222
    {selected,["FIELD"],[{0.00000e+0}]}.
 
223
 
 
224
%-------------------------------------------------------------------------
 
225
param_select_small_int() ->
 
226
    {selected,["FIELD"],[{1}, {2}]}.
 
227
 
 
228
param_select_int() ->
 
229
    Int = small_int_max() + 1,
 
230
    {selected,["FIELD"],[{1}, {Int}]}.
 
231
 
 
232
param_select_decimal() ->
 
233
    {selected,["FIELD"],[{1},{2}]}.
 
234
 
 
235
param_select_numeric() ->
 
236
    {selected,["FIELD"],[{1},{2}]}.
 
237
 
 
238
param_select_float() ->
 
239
    {selected,["FIELD"],[{1.30000},{1.20000}]}.
 
240
 
 
241
param_select_real() ->
 
242
    {selected,["FIELD"],[{1.30000},{1.20000}]}.
 
243
 
 
244
param_select_double() ->
 
245
    {selected,["FIELD"],[{1.30000},{1.20000}]}.
 
246
 
 
247
param_select_mix() ->
 
248
    {selected,["ID","DATA"],[{1, "foo"}, {2, "bar"}]}.
 
249
 
 
250
param_update() ->
 
251
    {selected,["ID","DATA"],[{1, "foobar"}, {2, "foobar"}, {3, "baz"}]}.
 
252
 
 
253
param_delete() ->
 
254
    {selected,["ID","DATA"],[{3, "baz"}]}.
 
255
 
 
256
param_select() ->
 
257
    {selected,["ID","DATA"],[{1, "foo"},{3, "foo"}]}.
 
258
 
 
259
%-------------------------------------------------------------------------
 
260
describe_integer() ->
 
261
    {ok,[{"myint1",sql_smallint},
 
262
         {"myint2",sql_integer},
 
263
         {"myint3",sql_integer}]}.
 
264
 
 
265
describe_string() ->
 
266
    {ok,[{"str1",{sql_char,10}},
 
267
         {"str2",{sql_char,10}},
 
268
         {"str3",{sql_varchar,10}},
 
269
         {"str4",{sql_varchar,10}}]}.
 
270
 
 
271
describe_floating() ->
 
272
     {ok,[{"f",sql_real},{"r",sql_double},{"d",sql_double}]}.
 
273
describe_dec_num() ->
 
274
    {ok,[{"mydec",{sql_decimal,9,3}},{"mynum",{sql_decimal,9,2}}]}.
 
275
 
 
276
describe_timestamp() ->
 
277
    {ok, [{"FIELD", sql_timestamp}]}.