File: start.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 (103 lines) | stat: -rw-r--r-- 5,794 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
(* file kernel/ocaml/ml/start.ml: Run-time selection of a module
 +-----------------------------------------------------------------------+
 |  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.                               |
 +-----------------------------------------------------------------------+
 |                                                                       |
 |                 Slection d'un module  l'excution                   |
 |                                                                       |
 +-----------------------------------------------------------------------*)

                      (* +---------------------------+
                         |  Slection  l'excution  |
                         +---------------------------+ *)

module type Main_type = sig
  val main : string list -> unit
end

module Start(Main : functor(E:Int_type) -> Main_type) = struct
  open Printf

  let module_list =
  (* "clong" :: *)
  (* "dlong" :: *)
  (* "slong" :: *)
  (* "big"   :: *)
  (* "gmp"   :: *)
  []

  let error msg  =
    printf "%s\n" msg;
    printf "available modules :";
    List.iter (fun x -> printf " %s" x) module_list;
    printf "\n";
    flush   stdout;
    exit(1)

  (* analyse la ligne de commande et retire les options -e xxx et -count *)
  let rec parse mlist count opts = function
    | "-count"::s-> parse mlist true opts s
    | "-e"::e::s -> parse (e::mlist) count opts s
    | "-e"::_    -> error "unspecified integers"
    | o::s       -> parse mlist count (o::opts) s
    | []         -> mlist,count,(List.rev opts)

  (* lancement d'un module Main(Cmp(X,Y)) ou Main(Count(Cmp(X,Y))) *)
  module Select(A:Int_type) = struct
    let start mlist count opts = match count,mlist with
    | _,    []         -> failwith "this can't happen"
  (*| false,"clong"::_ -> let module M = Main(Cmp(Clong)(A))  in M.main opts *)
  (*| false,"dlong"::_ -> let module M = Main(Cmp(Dlong)(A))  in M.main opts *)
  (*| false,"slong"::_ -> let module M = Main(Cmp(Slong)(A))  in M.main opts *)
  (*| false,"big"  ::_ -> let module M = Main(Cmp(Big)(A))    in M.main opts *)
  (*| false,"gmp"  ::_ -> let module M = Main(Cmp(Gmp)(A))    in M.main opts *)
  (*| true, "clong"::_ -> let module M = Count(Cmp(Clong)(A)) in let module N = Main(M) in N.main opts; M.print_stats() *)
  (*| true, "dlong"::_ -> let module M = Count(Cmp(Dlong)(A)) in let module N = Main(M) in N.main opts; M.print_stats() *)
  (*| true, "slong"::_ -> let module M = Count(Cmp(Slong)(A)) in let module N = Main(M) in N.main opts; M.print_stats() *)
  (*| true, "big"  ::_ -> let module M = Count(Cmp(Big)(A))   in let module N = Main(M) in N.main opts; M.print_stats() *)
  (*| true, "gmp"  ::_ -> let module M = Count(Cmp(Gmp)(A))   in let module N = Main(M) in N.main opts; M.print_stats() *)
    | _,    m::_       -> error ("unknown integers: " ^ m)
  end

  let start() =
    let mlist,count,opts = parse [] false [] (Array.to_list Sys.argv) in
    let mlist = match mlist,module_list with
      | [],(m::_) -> [m]
      | _         -> mlist
    in
    match count,mlist with
      | _,    []         -> failwith "this can't happen"
    (*| false,["clong"]  -> let module M = Main(Clong)   in M.main opts *)
    (*| false,["dlong"]  -> let module M = Main(Dlong)   in M.main opts *)
    (*| false,["slong"]  -> let module M = Main(Slong)   in M.main opts *)
    (*| false,["big"  ]  -> let module M = Main(Big)     in M.main opts *)
    (*| false,["gmp"  ]  -> let module M = Main(Gmp)     in M.main opts *)
    (*| true, ["clong"]  -> let module M = Count(Clong)  in let module N = Main(M) in N.main opts; M.print_stats() *)
    (*| true, ["dlong"]  -> let module M = Count(Dlong)  in let module N = Main(M) in N.main opts; M.print_stats() *)
    (*| true, ["slong"]  -> let module M = Count(Slong)  in let module N = Main(M) in N.main opts; M.print_stats() *)
    (*| true, ["big"  ]  -> let module M = Count(Big)    in let module N = Main(M) in N.main opts; M.print_stats() *)
    (*| true, ["gmp"  ]  -> let module M = Count(Gmp)    in let module N = Main(M) in N.main opts; M.print_stats() *)
    (*| _,    "clong"::t -> let module M = Select(Clong) in M.start t count opts *)
    (*| _,    "dlong"::t -> let module M = Select(Dlong) in M.start t count opts *)
    (*| _,    "slong"::t -> let module M = Select(Slong) in M.start t count opts *)
    (*| _,    "big"  ::t -> let module M = Select(Big)   in M.start t count opts *)
    (*| _,    "gmp"  ::t -> let module M = Select(Gmp)   in M.start t count opts *)
      | _,    m::_       -> error ("unknown integers: " ^ m)

end