File: count.ml

package info (click to toggle)
numerix 0.22-3
  • links: PTS
  • area: main
  • in suites: etch, etch-m68k
  • size: 4,380 kB
  • ctags: 4,165
  • sloc: asm: 26,210; ansic: 12,168; ml: 4,912; sh: 3,899; pascal: 414; makefile: 179
file content (410 lines) | stat: -rw-r--r-- 16,029 bytes parent folder | download | duplicates (2)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
366
367
368
369
370
371
372
373
374
375
376
377
378
379
380
381
382
383
384
385
386
387
388
389
390
391
392
393
394
395
396
397
398
399
400
401
402
403
404
405
406
407
408
409
410
(* file kernel/ocaml/ml/count.ml: count operations
 +-----------------------------------------------------------------------+
 |  Copyright 2005-2006, Michel Quercia (michel.quercia@prepas.org)      |
 |                                                                       |
 |  This file is part of Numerix. Numerix is free software; you can      |
 |  redistribute it and/or modify it under the terms of the GNU Lesser   |
 |  General Public License as published by the Free Software Foundation; |
 |  either version 2.1 of the License, or (at your option) any later     |
 |  version.                                                             |
 |                                                                       |
 |  The Numerix Library is distributed in the hope that it will be       |
 |  useful, but WITHOUT ANY WARRANTY; without even the implied warranty  |
 |  of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU  |
 |  Lesser General Public License for more details.                      |
 |                                                                       |
 |  You should have received a copy of the GNU Lesser General Public     |
 |  License along with the GNU MP Library; see the file COPYING. If not, |
 |  write to the Free Software Foundation, Inc., 59 Temple Place -       |
 |  Suite 330, Boston, MA 02111-1307, USA.                               |
 +-----------------------------------------------------------------------+
 |                                                                       |
 |                              Statistiques                             |
 |                                                                       |
 +-----------------------------------------------------------------------*)

                           (* +----------------+
                              |  Statistiques  |
                              +----------------+ *)

module Count(A:Int_type) = struct
  open Printf

  type statelt = {
    mutable n:float;  (* nombre d''appels,   number of calls      *)
    mutable s:float;  (* somme des tailles,  sum of operand sizes *)
    mutable m:int     (* taille maximale,    max operand size     *)
  }

  let cadd  = {n=0.0; s=0.0; m=0} (* add      sub                              *)
  let cmul  = {n=0.0; s=0.0; m=0} (* mul      sqr                              *)
  let cquo  = {n=0.0; s=0.0; m=0} (* quo      modulo       quomod              *)
  let cpow  = {n=0.0; s=0.0; m=0} (* pow      powmod       fact                *)
  let croot = {n=0.0; s=0.0; m=0} (* sqrt     root                             *)
  let cgcd  = {n=0.0; s=0.0; m=0} (* gcd      gcd_ex       cfrac       isprime *)
  let cbin  = {n=0.0; s=0.0; m=0} (* shr      shl          split       join    *)
                                  (* nbits    lowbits      highbits    nth_bit *)
                                  (* nth_word random                           *)
  let cmisc = {n=0.0; s=0.0; m=0} (* abs      neg          make_ref    copy_in *)
                                  (* copy_out comparaisons conversions         *)

  let clear_stats() =
    cadd.n  <- 0.0;  cadd.s  <- 0.0;  cadd.m  <- 0;
    cmul.n  <- 0.0;  cmul.s  <- 0.0;  cmul.m  <- 0;
    cquo.n  <- 0.0;  cquo.s  <- 0.0;  cquo.m  <- 0;
    cpow.n  <- 0.0;  cpow.s  <- 0.0;  cpow.m  <- 0;
    croot.n <- 0.0;  croot.s <- 0.0;  croot.m <- 0;
    cgcd.n  <- 0.0;  cgcd.s  <- 0.0;  cgcd.m  <- 0;
    cbin.n  <- 0.0;  cbin.s  <- 0.0;  cbin.m  <- 0;
    cmisc.n <- 0.0;  cmisc.s <- 0.0;  cmisc.m <- 0
    
  let print_stat nom c =
    if c.n = 0.0
    then printf "%5s %10d %10s %10s\n" nom 0 "-" "-"
    else printf "%5s %10d %10d %10d\n" nom (truncate c.n)
                                           (truncate(c.s/.c.n)) c.m
  let print_stats() =
    printf "%5s %10s %10s %10s\n" "op" "count" "avg.size" "max.size";
    print_stat "add"  cadd;
    print_stat "mul"  cmul;
    print_stat "quo"  cquo;
    print_stat "pow"  cpow;
    print_stat "root" croot;
    print_stat "gcd"  cgcd;
    print_stat "bin"  cbin;
    print_stat "misc" cmisc;
    flush stdout

  (*
    fonctions de comptage : signature fonction compteur
    abrviations pour les types des arguments
    tref       = r
    t          = t
    int        = i
    unit       = u
    round_mode = m
    string     = s
    bool       = b
    tristate   = c
  *)

  let i f c = fun i1 ->
    c.n <- c.n +. 1.0;
    f i1

  let i_i f c = fun i1 i2 ->
    c.n <- c.n +. 1.0;
    f i1 i2

  let m_r_r_t_t f c = fun m r1 r2 t1 t2 ->
    let n1 = A.nbits(t1) and n2 = A.nbits(t2) in
    c.n <- c.n +. 1.0;
    c.s <- c.s +. float(n1+n2)/.2.0;
    c.m <- max c.m (max n1 n2);
    f m r1 r2 t1 t2 

  let m_r_t f c = fun m r1 t1 ->
    let n1 = A.nbits(t1) in
    c.n <- c.n +. 1.0;
    c.s <- c.s +. float(n1);
    c.m <- max c.m n1;
    f m r1 t1

  let m_r_t_i f c = fun m r1 t1 i1 ->
    let n1 = A.nbits(t1) in
    c.n <- c.n +. 1.0;
    c.s <- c.s +. float(n1);
    c.m <- max c.m n1;
    f m r1 t1 i1

  let m_r_t_t f c = fun m r1 t1 t2 ->
    let n1 = A.nbits(t1) and n2 = A.nbits(t2) in
    c.n <- c.n +. 1.0;
    c.s <- c.s +. float(n1+n2)/.2.0;
    c.m <- max c.m (max n1 n2);
    f m r1 t1 t2 

  let m_r_t_t_t f c = fun m r1 t1 t2 t3 ->
    let n1 = A.nbits(t1) and n2 = A.nbits(t2) and n3 = A.nbits(t3) in
    c.n <- c.n +. 1.0;
    c.s <- c.s +. float(n1+n2+n3)/.3.0;
    c.m <- max c.m (max n1 (max n2 n3));
    f m r1 t1 t2 t3

  let m_t f c = fun m t1 ->
    let n1 = A.nbits(t1) in
    c.n <- c.n +. 1.0;
    c.s <- c.s +. float(n1);
    c.m <- max c.m n1;
    f m t1

  let m_t_i f c = fun m t1 i1 ->
    let n1 = A.nbits(t1) in
    c.n <- c.n +. 1.0;
    c.s <- c.s +. float(n1);
    c.m <- max c.m n1;
    f m t1 i1

  let m_t_t f c = fun m t1 t2 ->
    let n1 = A.nbits(t1) and n2 = A.nbits(t2) in
    c.n <- c.n +. 1.0;
    c.s <- c.s +. float(n1+n2)/.2.0;
    c.m <- max c.m (max n1 n2);
    f m t1 t2

  let m_t_t_t f c = fun m t1 t2 t3 ->
    let n1 = A.nbits(t1) and n2 = A.nbits(t2) and n3 = A.nbits(t3) in
    c.n <- c.n +. 1.0;
    c.s <- c.s +. float(n1+n2+n3)/.3.0;
    c.m <- max c.m (max n1 (max n2 n3));
    f m t1 t2 t3

  let r f c = fun r1 ->
    c.n <- c.n +. 1.0;
    f r1

  let r_i f c = fun r1 i1 ->
    c.n <- c.n +. 1.0;
    f r1 i1

  let r_i_i f c = fun r1 i1 i2 ->
    c.n <- c.n +. 1.0;
    f r1 i1 i2

  let r_r_r_r_r_t_t f c = fun r1 r2 r3 r4 r5 t1 t2 ->
    let n1 = A.nbits(t1) and n2 = A.nbits(t2) in
    c.n <- c.n +. 1.0;
    c.s <- c.s +. float(n1+n2)/.2.0;
    c.m <- max c.m (max n1 n2);
    f r1 r2 r3 r4 r5 t1 t2

  let r_r_r_t_t f c = fun r1 r2 r3 t1 t2 ->
    let n1 = A.nbits(t1) and n2 = A.nbits(t2) in
    c.n <- c.n +. 1.0;
    c.s <- c.s +. float(n1+n2)/.2.0;
    c.m <- max c.m (max n1 n2);
    f r1 r2 r3 t1 t2

  let r_r_t_i f c = fun r1 r2 t1 i1 ->
    let n1 = A.nbits(t1) in
    c.n <- c.n +. 1.0;
    c.s <- c.s +. float(n1);
    c.m <- max c.m n1;
    f r1 r2 t1 i1

  let r_r_t_t f c = fun r1 r2 t1 t2 ->
    let n1 = A.nbits(t1) and n2 = A.nbits(t2) in
    c.n <- c.n +. 1.0;
    c.s <- c.s +. float(n1+n2)/.2.0;
    c.m <- max c.m (max n1 n2);
    f r1 r2 t1 t2

  let r_s f c = fun r1 s1 ->
    c.n <- c.n +. 1.0;
    f r1 s1

  let r_t f c = fun r1 t1 ->
    let n1 = A.nbits(t1) in
    c.n <- c.n +. 1.0;
    c.s <- c.s +. float(n1);
    c.m <- max c.m n1;
    f r1 t1

  let r_t_i f c = fun r1 t1 i1 ->
    let n1 = A.nbits(t1) in
    c.n <- c.n +. 1.0;
    c.s <- c.s +. float(n1);
    c.m <- max c.m n1;
    f r1 t1 i1

  let r_t_t f c = fun r1 t1 t2 ->
    let n1 = A.nbits(t1) and n2 = A.nbits(t2) in
    c.n <- c.n +. 1.0;
    c.s <- c.s +. float(n1+n2)/.2.0;
    c.m <- max c.m (max n1 n2);
    f r1 t1 t2

  let r_t_t_i f c = fun r1 t1 t2 i2 ->
    let n1 = A.nbits(t1) and n2 = A.nbits(t2) in
    c.n <- c.n +. 1.0;
    c.s <- c.s +. float(n1+n2)/.2.0;
    c.m <- max c.m (max n1 n2);
    f r1 t1 t2 i2

  let r_t_t_t f c = fun r1 t1 t2 t3 ->
    let n1 = A.nbits(t1) and n2 = A.nbits(t2) and n3 = A.nbits(t3) in
    c.n <- c.n +. 1.0;
    c.s <- c.s +. float(n1+n2+n3)/.3.0;
    c.m <- max c.m (max n1 (max n2 n3));
    f r1 t1 t2 t3

  let s f c = fun s1 ->
    c.n <- c.n +. 1.0;
    f s1

  let t f c = fun t1 ->
    let n1 = A.nbits(t1) in
    c.n <- c.n +. 1.0;
    c.s <- c.s +. float(n1);
    c.m <- max c.m n1;
    f t1

  let t_i f c = fun t1 i1 ->
    let n1 = A.nbits(t1) in
    c.n <- c.n +. 1.0;
    c.s <- c.s +. float(n1);
    c.m <- max c.m n1;
    f t1 i1

  let t_t f c = fun t1 t2 ->
    let n1 = A.nbits(t1) and n2 = A.nbits(t2) in
    c.n <- c.n +. 1.0;
    c.s <- c.s +. float(n1+n2)/.2.0;
    c.m <- max c.m (max n1 n2);
    f t1 t2

  let t_t_i f c = fun t1 t2 i1 ->
    let n1 = A.nbits(t1) and n2 = A.nbits(t2) in
    c.n <- c.n +. 1.0;
    c.s <- c.s +. float(n1+n2)/.2.0;
    c.m <- max c.m (max n1 n2);
    f t1 t2 i1

  let t_t_t f c = fun t1 t2 t3 ->
    let n1 = A.nbits(t1) and n2 = A.nbits(t2) and n3 = A.nbits(t3) in
    c.n <- c.n +. 1.0;
    c.s <- c.s +. float(n1+n2+n3)/.3.0;
    c.m <- max c.m (max n1 (max n2 n3));
    f t1 t2 t3

  (* oprations  implmenter *)
  type t     = A.t
  type tref  = A.tref
  let name() = sprintf "Count(%s)" (A.name())
  let zero   = A.zero
  let one    = A.one
  exception Error of string

  let make_ref    = t               A.make_ref     cmisc
  let copy_in     = r_t             A.copy_in      cmisc
  let copy_out    = r               A.copy_out     cmisc
(*let look        = r               A.look                *)
  let add         = t_t             A.add          cadd
  let add_1       = t_i             A.add_1        cadd
  let add_in      = r_t_t           A.add_in       cadd
  let add_1_in    = r_t_i           A.add_1_in     cadd
  let sub         = t_t             A.sub          cadd
  let sub_1       = t_i             A.sub_1        cadd
  let sub_in      = r_t_t           A.sub_in       cadd
  let sub_1_in    = r_t_i           A.sub_1_in     cadd
  let mul         = t_t             A.mul          cmul
  let mul_1       = t_i             A.mul_1        cmul
  let mul_in      = r_t_t           A.mul_in       cmul
  let mul_1_in    = r_t_i           A.mul_1_in     cmul
  let quomod      = t_t             A.quomod       cquo
  let quo         = t_t             A.quo          cquo
  let modulo      = t_t             A.modulo       cquo
  let gquomod     = m_t_t           A.gquomod      cquo
  let gquo        = m_t_t           A.gquo         cquo
  let gmod        = m_t_t           A.gmod         cquo
  let quomod_in   = r_r_t_t         A.quomod_in    cquo
  let quo_in      = r_t_t           A.quo_in       cquo
  let mod_in      = r_t_t           A.mod_in       cquo
  let gquomod_in  = m_r_r_t_t       A.gquomod_in   cquo
  let gquo_in     = m_r_t_t         A.gquo_in      cquo
  let gmod_in     = m_r_t_t         A.gmod_in      cquo
  let quomod_1    = t_i             A.quomod_1     cquo
  let quo_1       = t_i             A.quo_1        cquo
  let mod_1       = t_i             A.mod_1        cquo
  let gquomod_1   = m_t_i           A.gquomod_1    cquo
  let gquo_1      = m_t_i           A.gquo_1       cquo
  let gmod_1      = m_t_i           A.gmod_1       cquo
  let quomod_1_in = r_t_i           A.quomod_1_in  cquo
  let quo_1_in    = r_t_i           A.quo_1_in     cquo
  let gquomod_1_in= m_r_t_i         A.gquomod_1_in cquo
  let gquo_1_in   = m_r_t_i         A.gquo_1_in    cquo
  let abs         = t               A.abs          cmisc
  let abs_in      = r_t             A.abs_in       cmisc
  let neg         = t               A.neg          cmisc
  let neg_in      = r_t             A.neg_in       cmisc
  let sqr         = t               A.sqr          cmul
  let pow         = t_i             A.pow          cpow
  let pow_1       = i_i             A.pow_1        cpow
  let powmod      = t_t_t           A.powmod       cpow
  let gpowmod     = m_t_t_t         A.gpowmod      cpow
  let sqr_in      = r_t             A.sqr_in       cmul
  let pow_in      = r_t_i           A.pow_in       cpow
  let pow_1_in    = r_i_i           A.pow_1_in     cpow
  let powmod_in   = r_t_t_t         A.powmod_in    cpow
  let gpowmod_in  = m_r_t_t_t       A.gpowmod_in   cpow
  let sqrt        = t               A.sqrt         croot
  let root        = t_i             A.root         croot
  let gsqrt       = m_t             A.gsqrt        croot
  let groot       = m_t_i           A.groot        croot
  let sqrt_in     = r_t             A.sqrt_in      croot
  let root_in     = r_t_i           A.root_in      croot
  let gsqrt_in    = m_r_t           A.gsqrt_in     croot
  let groot_in    = m_r_t_i         A.groot_in     croot
  let fact        = i               A.fact         cpow
  let fact_in     = r_i             A.fact_in      cpow
  let gcd         = t_t             A.gcd          cgcd
  let gcd_ex      = t_t             A.gcd_ex       cgcd
  let cfrac       = t_t             A.cfrac        cgcd
  let gcd_in      = r_t_t           A.gcd_in       cgcd
  let gcd_ex_in   = r_r_r_t_t       A.gcd_ex_in    cgcd
  let cfrac_in    = r_r_r_r_r_t_t   A.cfrac_in     cgcd
  let isprime     = t               A.isprime      cgcd
  let isprime_1   = i               A.isprime_1    cgcd
  let sgn         = t               A.sgn          cmisc
  let cmp         = t_t             A.cmp          cmisc
  let cmp_1       = t_i             A.cmp_1        cmisc
  let eq          = t_t             A.eq           cmisc
  let eq_1        = t_i             A.eq_1         cmisc
  let neq         = t_t             A.neq          cmisc
  let neq_1       = t_i             A.neq_1        cmisc
  let inf         = t_t             A.inf          cmisc
  let inf_1       = t_i             A.inf_1        cmisc
  let infeq       = t_t             A.infeq        cmisc
  let infeq_1     = t_i             A.infeq_1      cmisc
  let sup         = t_t             A.sup          cmisc
  let sup_1       = t_i             A.sup_1        cmisc
  let supeq       = t_t             A.supeq        cmisc
  let supeq_1     = t_i             A.supeq_1      cmisc
  let of_int      = i               A.of_int       cmisc
  let of_string   = s               A.of_string    cmisc
  let of_int_in   = r_i             A.of_int_in    cmisc
  let of_string_in= r_s             A.of_string_in cmisc
  let int_of      = t               A.int_of       cmisc
  let string_of   = t               A.string_of    cmisc
  let bstring_of  = t               A.bstring_of   cmisc
  let hstring_of  = t               A.hstring_of   cmisc
  let ostring_of  = t               A.ostring_of   cmisc
  let nrandom     = i               A.nrandom      cbin
  let zrandom     = i               A.zrandom      cbin
  let nrandom1    = i               A.nrandom1     cbin
  let zrandom1    = i               A.zrandom1     cbin
  let nrandom_in  = r_i             A.nrandom_in   cbin
  let zrandom_in  = r_i             A.zrandom_in   cbin
  let nrandom1_in = r_i             A.nrandom1_in  cbin
  let zrandom1_in = r_i             A.zrandom1_in  cbin
(*let random_init = i               A.random_init         *)
  let nbits       = t               A.nbits        cbin
  let lowbits     = t               A.lowbits      cbin
  let highbits    = t               A.highbits     cbin
  let nth_word    = t_i             A.nth_word     cbin
  let nth_bit     = t_i             A.nth_bit      cbin
  let shl         = t_i             A.shl          cbin
  let shr         = t_i             A.shr          cbin
  let split       = t_i             A.split        cbin
  let join        = t_t_i           A.join         cbin
  let shl_in      = r_t_i           A.shl_in       cbin
  let shr_in      = r_t_i           A.shr_in       cbin
  let split_in    = r_r_t_i         A.split_in     cbin
  let join_in     = r_t_t_i         A.join_in      cbin

  (* oprations non comptabilises *)
  let look                = A.look
  let random_init         = A.random_init       
  let toplevel_print      = A.toplevel_print
  let toplevel_print_tref = A.toplevel_print_tref
end