如何将这样的lisp函数转换为ocaml?

如何将这样的lisp函数转换为ocaml?,ocaml,Ocaml,函数“good red”用于从文件ssqHitNum.txt计算18个最高频率的数字 (defun good-red () (let ((tab (make-hash-table)) (res '()) (nums) (sort-res)) (dotimes (i 33) (setf (gethash (+ i 1) tab) 0)) (with-open-file (stream "ssqHitNum.txt") (loop :for line = (read-

函数“good red”用于从文件ssqHitNum.txt计算18个最高频率的数字

(defun good-red ()
(let ((tab (make-hash-table)) (res '()) (nums) (sort-res))
    (dotimes (i 33) (setf (gethash (+ i 1) tab) 0))
    (with-open-file (stream "ssqHitNum.txt")
        (loop :for line = (read-line stream nil)
             :until (null line)
             :do
                (setq nums (butlast (str2lst (subseq line 6))))
                (dolist (n nums) (incf (gethash n tab)))
                ))
    (maphash #'(lambda (k v) (push (cons k v) res)) tab)
    (setq sort-res (sort res #'> :key #'cdr))
    ;(print sort-res)
    (subseq (mapcar #'car sort-res) 0 18)))
$head ssqHitNum.txt

10000 7 12 18 19 22 28 4
10000 16 17 23 26 31 32 11
10000 3 4 18 22 24 29 11
10000 4 9 10 18 29 32 8
10000 5 7 10 14 17 25 11
数字介于1和33之间。我是否使用
hashtab
并像ocaml中的公共Lisp代码那样逐行扫描文件?还是有更优雅的方式使用ocaml


任何建议都将不胜感激

我不确定你想解决什么问题。(为什么所有输入行都以
10000
开头?)

如果您只想找到第18个最高频率的数字,您不需要逐行读取(在Lisp、C、Ocaml中都是这样),Ocaml的
Scanf.Scanf“%d”(fun x->…)
可以进行输入


在Ocaml中使用
Hashtbl.t
是合理的。

从类似的高级角度来看,使用:

要测试,请从顶层执行以下操作:

#use "topfind";;
#require "batteries";;
#use "/tmp/test.ml";;
test "/tmp/test.txt" 18;;

正如z_axis所要求的,这里是另一个只使用OCaml编译器分发的基本库的解决方案。由于缺少一些方便的函数,它有点冗长

let freq file best_n =
  let table = Hashtbl.create 100 in
  let freq_num num =
    Hashtbl.replace table num
      (1 + try Hashtbl.find table num with Not_found -> 0) in
  begin
    let input = open_in file in
    try while true do
        let line = input_line input in
        let nums = List.tl (Str.split (Str.regexp " +") line) in
        List.iter freq_num nums
    done with End_of_file -> close_in input
  end;
  let sorted =
    let cmp (_,freq1) (_,freq2) = (* decreasing *) compare freq2 freq1 in
    List.sort cmp (Hashtbl.fold (fun k x li -> (k,x)::li) table []) in
  (* take not tail-rec, not a problem for small n such as n=18 *)
  let rec take n = function
    | li when n = 0 -> []
    | [] -> []
    | hd::tl -> hd :: take (n - 1) tl in
  take best_n sorted

默认情况下,regexp模块没有链接,即使它位于默认搜索路径中,因此您必须使用
str.cma
(对于
ocamlc
)或
str.cmxa
(对于
ocamlopt
)显式编译程序。在顶层,使用“topfind”然后
#需要“str”就可以了。

对于一组固定的小整数,使用数组可能更简单:

   let good_red () =
      let a = Array.make 33 0 in
      let bump i = a.(i-1) <- a.(i-1) + 1 in
      let rec iter_lines fh =
         try
            let words = Str.split (Str.regexp " +") (input_line fh) in
            List.iter bump (List.map int_of_string (List.tl words));
            iter_lines fh
         with End_of_file -> () in
      let fh = open_in "ssqHitNum.txt" in
      iter_lines fh;
      close_in fh;
      let b = Array.mapi (fun i freq -> (i+1,freq)) a in
      Array.sort (fun (i1,f1) (i2,f2) -> compare f2 f1) b;
      Array.sub b 0 18;;

   try
   Array.iter (fun (i,freq) -> Printf.printf "%2d %2d\n" freq i) (good_red ())
   with Invalid_argument _ -> print_endline "bad input"
let good_red()=
设a=Array.make 33 0英寸
让i=a(i-1)在
让fh=open_在中的“ssqHitNum.txt”中
iter_线fh;
在fh中关闭_;
设b=Array.mapi(fun i freq->(i+1,freq))a在
Array.sort(fun(i1,f1)(i2,f2)->比较f2 f1)b;
数组.sub 0 18;;
尝试
Array.iter(fun(i,freq)->Printf.Printf“%2d%2d\n”freq i)(good_red())
使用无效参数->打印\结束行“错误输入”
正如gasche提到的,您需要使用str.cma或str.cmxa进行编译。

FWIW,在F#3.0中,您可以这样编写:

System.IO.File.ReadLines @"ssqHitNum.txt"
|> Seq.collect (fun s -> s.Split ' ' |> Seq.skip 1)
|> Seq.countBy id
|> Seq.sortBy (fun (_, p) -> -p)
|> Seq.take 18
在OCaml中,我将从头开始编写这些有用的库函数:

let readAllLines file =
  let lines = ref [] in
  let input = open_in file in
  begin
    try
      while true do
        lines := input_line input :: !lines
      done
    with
    | End_of_file ->
        close_in input
  end;
  List.rev !lines

let collect f xs =
  List.concat (List.map f xs)

let countBy f xs =
  let counts = Hashtbl.create 100 in
  let find key = try Hashtbl.find counts (f key) with Not_found -> 0 in
  let add key = Hashtbl.replace counts (f key) (1 + find key) in
  List.iter add xs;
  Hashtbl.fold (fun k n kns -> (k, n)::kns) table []

let sortBy f xs =
  List.sort (fun x y -> compare (f x) (f y)) xs

let rec truncate n xs =
  match n, xs with
  | 0, _ | _, [] -> []
  | n, x::xs -> x::truncate (n-1) xs

let rec skip n xs =
  match n, xs with
  | 0, xs -> xs
  | n, [] -> []
  | n, _::xs -> skip (n-1) xs

let (|>) x f = f x

let id x = x
然后用同样的方法写:

readAllLines "ssqHitNum.txt"
|> collect (fun s -> split ' ' s |> skip 1)
|> countBy id
|> sortBy (fun (_, p) -> -p)
|> truncate 18

F#更好,因为行是按需读取的,而我的OCaml则提前将所有内容读取到内存中。

10000是应该跳过的周期号。当然可以;我使用电池是因为它在OCaml编译器分发的相当简洁的库上提供了一些方便的函数——就像您使用的是通用的富含Lisp的标准库一样。您的意思是电池是OCaml的标准库。如果是这样,为什么我在freebsd盒中安装OCaml时没有安装它?据我所知,电池的想法是它应该是标准的,但不是OCaml发行版的一部分。这可能与Haskell平台的情况类似(尽管HP的范围似乎更广)。你不想过分贬低你的核心发行版,这只会让从事这项工作的真正聪明的人更加困难。同时,其他真正聪明的人可以更灵活地支持图书馆。杰弗里:你的描述很准确。我相当谨慎地不主张电池应该是OCaml的标准库,因为存在一个很好的替代品,Jane Street library,而其他OCaml用户——通常出于历史原因——开发了自己的库。对于新用户来说,这是一个合理的选择,它的优点是与编译器分发的库兼容,因此教材不需要更改。如果所有数字都在1到33之间,则哈希表似乎比仅使用数组要慢一些。但哈希表在某些数字超出范围(或者如果格式在将来扩展)时更健壮。是的,数组应该比哈希表更快。
readAllLines "ssqHitNum.txt"
|> collect (fun s -> split ' ' s |> skip 1)
|> countBy id
|> sortBy (fun (_, p) -> -p)
|> truncate 18