~ubuntu-branches/debian/sid/ocaml/sid

« back to all changes in this revision

Viewing changes to otherlibs/num/test/test_nums.ml

  • Committer: Bazaar Package Importer
  • Author(s): Stéphane Glondu
  • Date: 2011-04-21 21:35:08 UTC
  • mfrom: (1.1.11 upstream) (12.1.14 sid)
  • Revision ID: james.westby@ubuntu.com-20110421213508-kg34453aqmb0moha
* Fixes related to -output-obj with g++ (in debian/patches):
  - add Declare-primitive-name-table-as-const-char
  - add Avoid-multiple-declarations-in-generated-.c-files-in
  - fix Embed-bytecode-in-C-object-when-using-custom: the closing
    brace for extern "C" { ... } was missing in some cases

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
 
open Test;;
2
 
open Nat;;
3
 
open Big_int;;
4
 
open Ratio;;
5
 
open Int_misc;;
6
 
open Num;;
7
 
open Arith_status;;
8
 
 
9
 
testing_function "add_num";;
10
 
 
11
 
test 1
12
 
eq_num (add_num (Int 1) (Int 3), Int 4);;
13
 
test 2
14
 
eq_num (add_num (Int 1) (Big_int (big_int_of_int 3)), Int 4);;
15
 
test 3
16
 
eq_num (add_num (Int 1) (Ratio (ratio_of_string "3/4")), 
17
 
        Ratio (ratio_of_string "7/4"));;
18
 
test 4
19
 
eq_num (add_num (Big_int (big_int_of_int 1)) (Ratio (ratio_of_string "3/4")), 
20
 
        Ratio (ratio_of_string "7/4"));;
21
 
test 5
22
 
eq_num (add_num (Big_int (big_int_of_int 1)) (Big_int (big_int_of_int 3)),
23
 
        Int 4);;
24
 
test 6
25
 
eq_num (add_num (Big_int (big_int_of_int 1)) (Ratio (ratio_of_string "3/4")),
26
 
        Ratio (ratio_of_string "7/4"));;
27
 
test 7
28
 
eq_num (add_num (Ratio (ratio_of_string "2/3")) (Ratio (ratio_of_string "3/4")),
29
 
        Ratio (ratio_of_string "17/12"));;
30
 
test 8
31
 
eq_num (add_num (Int least_int) (Int 1), 
32
 
        Int (- (pred biggest_int)));;
33
 
test 9
34
 
eq_num (add_num (Int biggest_int) (Int 1), 
35
 
        Big_int (minus_big_int (pred_big_int (big_int_of_int least_int))));;
36
 
 
37
 
testing_function "sub_num";;
38
 
 
39
 
test 1
40
 
eq_num (sub_num (Int 1) (Int 3), Int (-2));;
41
 
test 2
42
 
eq_num (sub_num (Int 1) (Big_int (big_int_of_int 3)), Int (-2));;
43
 
test 3
44
 
eq_num (sub_num (Int 1) (Ratio (ratio_of_string "3/4")), 
45
 
        Ratio (ratio_of_string "1/4"));;
46
 
test 4
47
 
eq_num (sub_num (Big_int (big_int_of_int 1)) (Ratio (ratio_of_string "3/4")), 
48
 
        Ratio (ratio_of_string "1/4"));;
49
 
test 5
50
 
eq_num (sub_num (Big_int (big_int_of_int 1)) (Big_int (big_int_of_int 3)),
51
 
        Int (-2));;
52
 
test 7
53
 
eq_num (sub_num (Big_int (big_int_of_int 1)) (Ratio (ratio_of_string "3/4")),
54
 
        Ratio (ratio_of_string "1/4"));;
55
 
test 8
56
 
eq_num (sub_num (Ratio (ratio_of_string "2/3")) (Ratio (ratio_of_string "3/4")),
57
 
        Ratio (ratio_of_string "-1/12"));;
58
 
test 9
59
 
eq_num (sub_num (Int least_int) (Int (-1)), 
60
 
        Int (- (pred biggest_int)));;
61
 
test 10
62
 
eq_num (sub_num (Int (-1)) (Int biggest_int), pred_num (Int least_int));;
63
 
 
64
 
testing_function "mult_num";;
65
 
 
66
 
test 1
67
 
eq_num (mult_num (Int 2) (Int 3), Int 6);;
68
 
test 2
69
 
eq_num (mult_num (Int 127) (Int (int_of_string "257")),
70
 
                  Int (int_of_string "32639"));;
71
 
test 3
72
 
eq_num (mult_num (Int 257) (Int (int_of_string "260")), 
73
 
        Big_int (big_int_of_string "66820"));;
74
 
test 4
75
 
eq_num (mult_num (Int 2) (Big_int (big_int_of_int 3)), Int 6);;
76
 
test 5
77
 
eq_num (mult_num (Int 10) (Ratio (ratio_of_string "3/4")), 
78
 
        Ratio (ratio_of_string "15/2"));;
79
 
test 6
80
 
eq_num (mult_num (Big_int (big_int_of_int 10)) (Ratio (ratio_of_string "3/4")),
81
 
        Ratio (ratio_of_string "15/2"));;
82
 
test 7
83
 
eq_num (mult_num (Big_int (big_int_of_int 2)) (Big_int (big_int_of_int 3)),
84
 
        Int 6);;
85
 
test 8
86
 
eq_num (mult_num (Big_int (big_int_of_int 10)) (Ratio (ratio_of_string "3/4")),
87
 
        Ratio (ratio_of_string "15/2"));;
88
 
test 9
89
 
eq_num (mult_num (Ratio (ratio_of_string "2/3")) (Ratio (ratio_of_string "3/4"))
90
 
               , Ratio (ratio_of_string "1/2"));;
91
 
 
92
 
testing_function "div_num";;
93
 
 
94
 
test 1
95
 
eq_num (div_num (Int 6) (Int 3), Int 2);;
96
 
test 2
97
 
eq_num (div_num (Int (int_of_string "32639")) 
98
 
                 (Int (int_of_string "257")), Int 127);;
99
 
test 3
100
 
eq_num (div_num (Big_int (big_int_of_string "66820")) 
101
 
                 (Int (int_of_string "257")), 
102
 
        Int 260);;
103
 
test 4
104
 
eq_num (div_num (Int 6) (Big_int (big_int_of_int 3)), Int 2);;
105
 
test 5
106
 
eq_num (div_num (Ratio (ratio_of_string "15/2")) 
107
 
                 (Int 10),
108
 
        Ratio (ratio_of_string "3/4"));; 
109
 
test 6
110
 
eq_num (div_num (Big_int (big_int_of_int 6)) (Big_int (big_int_of_int 3)),
111
 
        Int 2);;
112
 
test 7 
113
 
eq_num (div_num (Ratio (ratio_of_string "15/2")) 
114
 
                 (Big_int (big_int_of_int 10)),
115
 
        Ratio (ratio_of_string "3/4"));;
116
 
test 8
117
 
eq_num (div_num (Ratio (ratio_of_string "15/2")) 
118
 
                 (Ratio (ratio_of_string "3/4")),
119
 
        Big_int (big_int_of_int 10));;
120
 
test 9
121
 
eq_num (div_num (Ratio (ratio_of_string "1/2")) 
122
 
                 (Ratio (ratio_of_string "3/4")),
123
 
        Ratio (ratio_of_string "2/3"));;
124
 
 
125
 
testing_function "is_integer_num";;
126
 
 
127
 
test 1
128
 
eq (is_integer_num (Int 3),true);;
129
 
test 2
130
 
eq (is_integer_num (Big_int (big_int_of_string "1234567890")),true);;
131
 
test 3
132
 
eq (not (is_integer_num (Ratio (ratio_of_string "1/2"))),true);;
133
 
test 4
134
 
eq (is_integer_num (Ratio (ratio_of_string "1073774590/32770")),true);;
135
 
 
136
 
testing_function "num_of_ratio";;
137
 
 
138
 
test 1
139
 
eq_num (num_of_ratio (ratio_of_string "4/2"), Int 2);;
140
 
test 2
141
 
eq_num (num_of_ratio (ratio_of_string "11811160075/11"), 
142
 
        Big_int (big_int_of_string "1073741825"));;
143
 
test 3
144
 
eq_num (num_of_ratio (ratio_of_string "123456789012/1234"),
145
 
        Ratio (ratio_of_string "61728394506/617"));;
146
 
 
147
 
testing_function "num_of_string";;
148
 
 
149
 
test 1
150
 
eq_num (num_of_string "123/3456", Ratio (ratio_of_string "123/3456"));;
151
 
(*********
152
 
test 2
153
 
eq_num (num_of_string "12.3/34.56", Ratio (ratio_of_string "1230/3456"));;
154
 
test 3
155
 
eq_num (num_of_string "1.23/325.6", Ratio (ratio_of_string "123/32560"));;
156
 
test 4
157
 
eq_num (num_of_string "12.3/345.6", Ratio (ratio_of_string "123/3456"));;
158
 
set_error_when_null_denominator false;;
159
 
test 5
160
 
eq_num (num_of_string "12.3/0.0", Ratio (ratio_of_string "123/0"));;
161
 
test 6
162
 
eq_num (num_of_string "0/0", Ratio (ratio_of_string "0/0"));;
163
 
set_error_when_null_denominator true;;
164
 
*********)
165
 
test 7
166
 
eq_num (num_of_string "1234567890",
167
 
        Big_int (big_int_of_string "1234567890"));;
168
 
test 8
169
 
eq_num (num_of_string "12345", Int (int_of_string "12345"));;
170
 
(*********
171
 
test 9
172
 
eq_num (num_of_string "0.23", Ratio (ratio_of_string "23/100"));;
173
 
test 10
174
 
eq_num (num_of_string "0.23", Ratio (ratio_of_string "0.23/1"));;
175
 
********)
176
 
 
177
 
failwith_test 11
178
 
num_of_string ("frlshjkurty") (Failure "num_of_string");;
179
 
 
180
 
(*******
181
 
 
182
 
testing_function "immediate numbers";;
183
 
 
184
 
standard arith false;;
185
 
 
186
 
let x = (1/2) in
187
 
test 0 eq_string (string_of_num x, "1/2");;
188
 
 
189
 
let y = 12345678901 in
190
 
test 1 eq_string (string_of_num y, "12345678901");;
191
 
testing_function "immediate numbers";;
192
 
 
193
 
let x = (1/2) in
194
 
test 0 eq_string (string_of_num x, "1/2");;
195
 
 
196
 
let y = 12345678901 in
197
 
test 1 eq_string (string_of_num y, "12345678901");;
198
 
 
199
 
testing_function "pattern_matching on nums";;
200
 
 
201
 
let f1 = function 0 -> true | _  -> false;;
202
 
 
203
 
test 1 eq (f1 0, true);;
204
 
 
205
 
test 2 eq (f1 1, false);;
206
 
 
207
 
test 3 eq (f1 (0/1), true);;
208
 
 
209
 
test 4 eq (f1 (let n = num_of_string "2000000000000000000000000" in n-n) , 
210
 
            true);;
211
 
 
212
 
test 5 eq (f1 (let n = num_of_string "2000000000000000000000000" in n/n-1) , 
213
 
            true);;
214
 
 
215
 
test 6 eq (f1 (let n = num_of_string "2000000000000000000000000" in n+1) , 
216
 
            false);;
217
 
 
218
 
test 7 eq (f1 (1/2), false);;
219
 
 
220
 
**************)