Strating to remove Core

This commit is contained in:
Anthony Scemama 2017-08-18 19:43:52 +02:00
parent 8523096a90
commit 3764b2b45d
16 changed files with 160 additions and 120 deletions

View File

@ -1,4 +1,3 @@
open Core
module Tcp : sig module Tcp : sig
type t type t
@ -8,7 +7,7 @@ module Tcp : sig
end = struct end = struct
type t = string type t = string
let of_string x = let of_string x =
if not (String.is_prefix ~prefix:"tcp://" x) then if not (String_ext.is_prefix ~prefix:"tcp://" x) then
invalid_arg "Address Invalid" invalid_arg "Address Invalid"
; ;
x x
@ -26,7 +25,7 @@ module Ipc : sig
end = struct end = struct
type t = string type t = string
let of_string x = let of_string x =
assert (String.is_prefix ~prefix:"ipc://" x); assert (String_ext.is_prefix ~prefix:"ipc://" x);
x x
let create name = let create name =
Printf.sprintf "ipc://%s" name Printf.sprintf "ipc://%s" name
@ -41,7 +40,7 @@ module Inproc : sig
end = struct end = struct
type t = string type t = string
let of_string x = let of_string x =
assert (String.is_prefix ~prefix:"inproc://" x); assert (String_ext.is_prefix ~prefix:"inproc://" x);
x x
let create name = let create name =
Printf.sprintf "inproc://%s" name Printf.sprintf "inproc://%s" name

View File

@ -1,4 +1,4 @@
open Core open Sexplib.Std
open Qptypes open Qptypes
type t = (Gto.t * Nucl_number.t) list [@@deriving sexp] type t = (Gto.t * Nucl_number.t) list [@@deriving sexp]
@ -16,7 +16,7 @@ let read in_channel at_number =
(** Find an element in the basis set file *) (** Find an element in the basis set file *)
let find in_channel element = let find in_channel element =
In_channel.seek in_channel 0L; seek_in in_channel 0;
let element_read = ref Element.X in let element_read = ref Element.X in
while !element_read <> element while !element_read <> element
do do
@ -56,13 +56,13 @@ let to_string_general ~fmt ~atom_sep ?ele_array b =
do_work ((Gto.to_string ~fmt g)::accu) n tail do_work ((Gto.to_string ~fmt g)::accu) n tail
in in
do_work [new_nucleus 1] 1 b do_work [new_nucleus 1] 1 b
|> String.concat ~sep:"\n" |> String.concat "\n"
let to_string_gamess ?ele_array = let to_string_gamess ?ele_array =
to_string_general ?ele_array ~fmt:Gto.Gamess ~atom_sep:"" to_string_general ?ele_array ~fmt:Gto.Gamess ~atom_sep:""
let to_string_gaussian ?ele_array b = let to_string_gaussian ?ele_array b =
String.concat ~sep:"\n" String.concat "\n"
[ to_string_general ?ele_array ~fmt:Gto.Gaussian ~atom_sep:"****" b ; "****" ] [ to_string_general ?ele_array ~fmt:Gto.Gaussian ~atom_sep:"****" b ; "****" ]
let to_string ?(fmt=Gto.Gamess) = let to_string ?(fmt=Gto.Gamess) =

View File

@ -1,5 +1,5 @@
open Core;; open Qptypes
open Qptypes;; open Sexplib.Std
type t = int64 array [@@deriving sexp] type t = int64 array [@@deriving sexp]
@ -9,8 +9,8 @@ let to_int64_array (x:t) = (x:int64 array)
let to_alpha_beta x = let to_alpha_beta x =
let x = to_int64_array x in let x = to_int64_array x in
let n_int = (Array.length x)/2 in let n_int = (Array.length x)/2 in
( Array.init n_int ~f:(fun i -> x.(i)) , ( Array.init n_int (fun i -> x.(i)) ,
Array.init n_int ~f:(fun i -> x.(i+n_int)) ) Array.init n_int (fun i -> x.(i+n_int)) )
let to_bitlist_couple x = let to_bitlist_couple x =
@ -28,12 +28,14 @@ let bitlist_to_string ~mo_tot_num x =
let len = let len =
MO_number.to_int mo_tot_num MO_number.to_int mo_tot_num
in in
List.map x ~f:(function let s =
| Bit.Zero -> "-" List.map (function
| Bit.One -> "+" | Bit.Zero -> "-"
) | Bit.One -> "+"
|> String.concat ) x
|> String.sub ~pos:0 ~len |> String.concat ""
in
String.sub s 0 len
@ -77,6 +79,6 @@ let to_string ~mo_tot_num x =
let (xa,xb) = to_bitlist_couple x in let (xa,xb) = to_bitlist_couple x in
[ " " ; bitlist_to_string ~mo_tot_num xa ; "\n" ; [ " " ; bitlist_to_string ~mo_tot_num xa ; "\n" ;
" " ; bitlist_to_string ~mo_tot_num xb ] " " ; bitlist_to_string ~mo_tot_num xb ]
|> String.concat |> String.concat ""

View File

@ -1,5 +1,5 @@
open Core
open Qptypes open Qptypes
open Sexplib.Std
exception GTO_Read_Failure of string exception GTO_Read_Failure of string
exception End_Of_Basis exception End_Of_Basis
@ -15,7 +15,7 @@ type t =
let of_prim_coef_list pc = let of_prim_coef_list pc =
let (p,c) = List.hd_exn pc in let (p,c) = List.hd pc in
let sym = p.GaussianPrimitive.sym in let sym = p.GaussianPrimitive.sym in
let rec check = function let rec check = function
| [] -> `OK | [] -> `OK
@ -37,12 +37,12 @@ let of_prim_coef_list pc =
let read_one in_channel = let read_one in_channel =
(* Fetch number of lines to read on first line *) (* Fetch number of lines to read on first line *)
let buffer = input_line in_channel in let buffer = input_line in_channel in
if ( (String.strip buffer) = "" ) then if ( (String_ext.strip buffer) = "" ) then
raise End_Of_Basis; raise End_Of_Basis;
let sym_str = String.sub buffer 0 2 in let sym_str = String.sub buffer 0 2 in
let n_str = String.sub buffer 2 ((String.length buffer)-2) in let n_str = String.sub buffer 2 ((String.length buffer)-2) in
let sym = Symmetry.of_string (String.strip sym_str) in let sym = Symmetry.of_string (String_ext.strip sym_str) in
let n = Int.of_string (String.strip n_str) in let n = int_of_string (String_ext.strip n_str) in
(* Read all the primitives *) (* Read all the primitives *)
let rec read_lines result = function let rec read_lines result = function
| 0 -> result | 0 -> result
@ -50,18 +50,19 @@ let read_one in_channel =
begin begin
let line_buffer = input_line in_channel in let line_buffer = input_line in_channel in
let buffer = line_buffer let buffer = line_buffer
|> String.split ~on:' ' |> String_ext.split ~on:' '
|> List.filter ~f:(fun x -> x <> "") |> List.filter (fun x -> x <> "")
in in
match buffer with match buffer with
| [ j ; expo ; coef ] -> | [ j ; expo ; coef ] ->
begin begin
let coef = String.tr ~target:'D' ~replacement:'e' coef let coef =
Str.global_replace (Str.regexp "D") "e" coef
in in
let p = let p =
GaussianPrimitive.of_sym_expo sym GaussianPrimitive.of_sym_expo sym
(AO_expo.of_float (Float.of_string expo) ) (AO_expo.of_float (float_of_string expo) )
and c = AO_coef.of_float (Float.of_string coef) in and c = AO_coef.of_float (float_of_string coef) in
read_lines ( (p,c)::result) (i-1) read_lines ( (p,c)::result) (i-1)
end end
| _ -> raise (GTO_Read_Failure line_buffer) | _ -> raise (GTO_Read_Failure line_buffer)
@ -89,7 +90,7 @@ let to_string_gamess { sym = sym ; lc = lc } =
do_work (result::accu) (i+1) tail do_work (result::accu) (i+1) tail
in in
(do_work [result] 1 lc) (do_work [result] 1 lc)
|> String.concat ~sep:"\n" |> String.concat "\n"
(** Write the GTO in Gaussian format *) (** Write the GTO in Gaussian format *)
@ -109,7 +110,7 @@ let to_string_gaussian { sym = sym ; lc = lc } =
do_work (result::accu) (i+1) tail do_work (result::accu) (i+1) tail
in in
(do_work [result] 1 lc) (do_work [result] 1 lc)
|> String.concat ~sep:"\n" |> String.concat "\n"
(** Transform the gto to a string *) (** Transform the gto to a string *)

View File

@ -1,5 +1,5 @@
open Core;; open Qptypes
open Qptypes;; open Sexplib.Std
type t = (Symmetry.Xyz.t * Gto.t * Nucl_number.t ) list [@@deriving sexp] type t = (Symmetry.Xyz.t * Gto.t * Nucl_number.t ) list [@@deriving sexp]
@ -10,14 +10,14 @@ let of_basis b =
begin begin
let new_accu = let new_accu =
Symmetry.Xyz.of_symmetry g.Gto.sym Symmetry.Xyz.of_symmetry g.Gto.sym
|> List.rev_map ~f:(fun x-> (x,g,n)) |> List.rev_map (fun x-> (x,g,n))
in in
do_work (new_accu@accu) tail do_work (new_accu@accu) tail
end end
in in
do_work [] b do_work [] b
|> List.rev |> List.rev
;;
let to_basis b = let to_basis b =
let rec do_work accu = function let rec do_work accu = function
@ -25,7 +25,7 @@ let to_basis b =
| (s,g,n)::tail -> | (s,g,n)::tail ->
let first_sym = let first_sym =
Symmetry.Xyz.of_symmetry g.Gto.sym Symmetry.Xyz.of_symmetry g.Gto.sym
|> List.hd_exn |> List.hd
in in
let new_accu = let new_accu =
if ( s = first_sym ) then if ( s = first_sym ) then
@ -36,19 +36,19 @@ let to_basis b =
do_work new_accu tail do_work new_accu tail
in in
do_work [] b do_work [] b
;;
let to_string b = let to_string b =
let middle = List.map ~f:(fun (x,y,z) -> let middle = List.map (fun (x,y,z) ->
"( "^((Int.to_string (Nucl_number.to_int z)))^", "^ "( "^((string_of_int (Nucl_number.to_int z)))^", "^
(Symmetry.Xyz.to_string x)^", "^(Gto.to_string y) (Symmetry.Xyz.to_string x)^", "^(Gto.to_string y)
^" )" ^" )"
) b ) b
|> String.concat ~sep:",\n" |> String.concat ",\n"
in "("^middle^")" in "("^middle^")"
;;
include To_md5;;
include To_md5
let to_md5 = to_md5 sexp_of_t let to_md5 = to_md5 sexp_of_t
;;

View File

@ -1,4 +1,4 @@
open Core open Sexplib
(* (*
let rec transpose = function let rec transpose = function
@ -14,12 +14,12 @@ let rec transpose = function
let input_to_sexp s = let input_to_sexp s =
let result = let result =
String.split_lines s String_ext.split ~on:'\n' s
|> List.filter ~f:(fun x-> |> List.filter (fun x-> (String_ext.strip x) <> "")
(String.strip x) <> "") |> List.map (fun x-> "("^
|> List.map ~f:(fun x-> (Str.global_replace (Str.regexp "=") " " x)
"("^(String.tr '=' ' ' x)^")") ^")")
|> String.concat |> String.concat ""
in in
print_endline ("("^result^")"); print_endline ("("^result^")");
"("^result^")" "("^result^")"
@ -29,10 +29,10 @@ let rmdir dirname =
let rec remove_one dir = let rec remove_one dir =
Sys.chdir dir; Sys.chdir dir;
Sys.readdir "." Sys.readdir "."
|> Array.iter ~f:(fun x -> |> Array.iter (fun x ->
match (Sys.is_directory x, Sys.is_file x) with match (Sys.is_directory x, Sys.file_exists x) with
| (`Yes, _) -> remove_one x | (true, _) -> remove_one x
| (_, `Yes) -> Sys.remove x | (_, true) -> Sys.remove x
| _ -> failwith ("Unable to remove file "^x^".") | _ -> failwith ("Unable to remove file "^x^".")
); );
Sys.chdir ".."; Sys.chdir "..";

View File

@ -1,4 +1,4 @@
open Core;; open Sexplib.Std
(* A range is a string of the type: (* A range is a string of the type:
* *
@ -12,14 +12,14 @@ open Core;;
*) *)
type t = int list [@@deriving sexp] type t = int list [@@deriving sexp]
let expand_range r = let expand_range r =
match String.lsplit2 ~on:'-' r with match String_ext.lsplit2 ~on:'-' r with
| Some (s, f) -> | Some (s, f) ->
begin begin
let start = Int.of_string s let start = int_of_string s
and finish = Int.of_string f and finish = int_of_string f
in in
assert (start <= finish) ; assert (start <= finish) ;
let rec do_work = function let rec do_work = function
@ -31,9 +31,9 @@ let expand_range r =
begin begin
match r with match r with
| "" -> [] | "" -> []
| _ -> [Int.of_string r] | _ -> [int_of_string r]
end end
;;
let of_string s = let of_string s =
match s.[0] with match s.[0] with
@ -43,36 +43,37 @@ let of_string s =
assert (s.[0] = '[') ; assert (s.[0] = '[') ;
assert (s.[(String.length s)-1] = ']') ; assert (s.[(String.length s)-1] = ']') ;
let s = String.sub s 1 ((String.length s) - 2) in let s = String.sub s 1 ((String.length s) - 2) in
let l = String.split ~on:',' s in let l = String_ext.split ~on:',' s in
let l = List.map ~f:expand_range l in let l = List.map expand_range l in
List.concat l |> List.dedup ~compare:Int.compare |> List.sort ~cmp:Int.compare List.concat l
;; |> List.sort_uniq compare
let to_string l = let to_string l =
let rec do_work buf symbol = function let rec do_work buf symbol = function
| [] -> buf | [] -> buf
| a::([] as t) -> | a::([] as t) ->
do_work (buf^symbol^(Int.to_string a)) "" t do_work (buf^symbol^(string_of_int a)) "" t
| a::(b::q as t) -> | a::(b::q as t) ->
if (b-a = 1) then if (b-a = 1) then
do_work buf "-" t do_work buf "-" t
else else
do_work (buf^symbol^(Int.to_string a)^","^(Int.to_string b)) "" t do_work (buf^symbol^(string_of_int a)^","^(string_of_int b)) "" t
in in
let result = let result =
match l with match l with
| [] -> | [] ->
"[]" "[]"
| h::t -> | h::t ->
do_work ("["^(Int.to_string h)) "" l in do_work ("["^(string_of_int h)) "" l in
(String.sub result 0 ((String.length result)))^"]" (String.sub result 0 ((String.length result)))^"]"
;;
let test_module () = let test_module () =
let s = "[72-107,36-53,126-131]" in let s = "[72-107,36-53,126-131]" in
let l = of_string s in let l = of_string s in
print_string s ; Out_channel.newline stdout ; print_string s ; print_newline () ;
List.iter ~f:(fun x -> Printf.printf "%d, " x) l ; Out_channel.newline stdout ; List.iter (fun x -> Printf.printf "%d, " x) l ; print_newline () ;
to_string l |> print_string ; Out_channel.newline stdout to_string l |> print_string ; print_newline ();
;;

View File

@ -1,4 +1,4 @@
type t = int list [@@deriving sexp] type t = int list [@@deriving sexp]
(** A range is a sorted list of ints in an interval. (** A range is a sorted list of ints in an interval.
It is created using a string : It is created using a string :

View File

@ -2,6 +2,8 @@ include String
(** Split a string on a given character *) (** Split a string on a given character *)
let split ?(on=' ') str = let split ?(on=' ') str =
split_on_char on str
(*
let rec do_work ?(accu=[]) ?(left="") = function let rec do_work ?(accu=[]) ?(left="") = function
| "" -> List.rev (left::accu) | "" -> List.rev (left::accu)
| s -> | s ->
@ -21,6 +23,7 @@ let split ?(on=' ') str =
do_work ~accu ~left:new_left new_s do_work ~accu ~left:new_left new_s
in in
do_work str do_work str
*)
(** Strip blanks on the left of a string *) (** Strip blanks on the left of a string *)
@ -101,12 +104,39 @@ let rsplit2_exn ?(on=' ') s =
do_work length do_work length
let lsplit2 ?(on=' ') s =
try
Some (lsplit2_exn ~on s)
with
| Not_found -> None
let rsplit2 ?(on=' ') s =
try
Some (rsplit2_exn ~on s)
with
| Not_found -> None
let to_list s = let to_list s =
Array.init (String.length s) (fun i -> s.[i]) Array.init (String.length s) (fun i -> s.[i])
|> Array.to_list |> Array.to_list
let fold ~init ~f s = let fold ~init ~f s =
to_list s to_list s
|> List.fold_left f init |> List.fold_left f init
let is_prefix ~prefix s =
let len =
String.length prefix
in
if len > String.length s then
false
else
prefix = String.sub s 0 len
let of_char c =
String.make 1 c

View File

@ -1,5 +1,5 @@
open Qptypes open Qptypes
open Core open Sexplib.Std
type t = S|P|D|F|G|H|I|J|K|L [@@deriving sexp] type t = S|P|D|F|G|H|I|J|K|L [@@deriving sexp]
@ -86,7 +86,7 @@ module Xyz = struct
let flush state accu number = let flush state accu number =
let n = let n =
if (number = "") then 1 if (number = "") then 1
else (Int.of_string number) else (int_of_string number)
in in
match state with match state with
| X -> { x= Positive_int.(of_int ( (to_int accu.x) +n)); | X -> { x= Positive_int.(of_int ( (to_int accu.x) +n));
@ -111,10 +111,9 @@ module Xyz = struct
| 'Z'::rest | 'z'::rest -> | 'Z'::rest | 'z'::rest ->
let new_accu = flush state accu number in let new_accu = flush state accu number in
do_work Z new_accu "" rest do_work Z new_accu "" rest
| c::rest -> do_work state accu (number^(String.of_char c)) rest | c::rest -> do_work state accu (number^(String_ext.of_char c)) rest
in in
String.to_list_rev s String_ext.to_list s
|> List.rev
|> do_work Null |> do_work Null
{ x=Positive_int.of_int 0 ; { x=Positive_int.of_int 0 ;
y=Positive_int.of_int 0 ; y=Positive_int.of_int 0 ;

View File

@ -1,5 +1,5 @@
open Core;; open Qptypes
open Qptypes;; open Sexplib
let to_md5 sexp_of_t t = let to_md5 sexp_of_t t =
sexp_of_t t sexp_of_t t

View File

@ -1,4 +1,10 @@
open Core;; let global_replace x =
x
|> Str.global_replace (Str.regexp "Float.to_string") "string_of_float"
|> Str.global_replace (Str.regexp "Float.of_string") "float_of_string"
|> Str.global_replace (Str.regexp "Int.to_string") "string_of_int"
|> Str.global_replace (Str.regexp "Int.of_string") "int_of_string"
|> Str.global_replace (Str.regexp "String.\(to\|of\)_string") ""
let input_data = " let input_data = "
* Positive_float : float * Positive_float : float
@ -118,8 +124,12 @@ let input_data = "
* MD5 : string * MD5 : string
assert ((String.length x) = 32); assert ((String.length x) = 32);
assert (String.fold x ~init:true ~f:(fun accu x -> assert (
accu && (x < 'g'))); let a =
Array.init (String.length x) (fun i -> x.[i])
in
Array.fold_left (fun accu x -> accu && (x < 'g')) true a
);
* Rst_string : string * Rst_string : string
@ -127,7 +137,7 @@ let input_data = "
assert (x <> \"\") ; assert (x <> \"\") ;
" "
;;
let input_ezfio = " let input_ezfio = "
* MO_number : int * MO_number : int
@ -156,7 +166,7 @@ let input_ezfio = "
More than 10 billion of determinants More than 10 billion of determinants
" "
;;
let untouched = " let untouched = "
module MO_guess : sig module MO_guess : sig
@ -206,7 +216,7 @@ end = struct
end end
" "
;;
let template = format_of_string " let template = format_of_string "
module %s : sig module %s : sig
@ -222,35 +232,36 @@ end = struct
end end
" "
;;
let parse_input input= let parse_input input=
print_string "open Core;;\nlet warning = print_string;;\n" ; print_string "open Sexplib.Std\nlet warning = print_string\n" ;
let rec parse result = function let rec parse result = function
| [] -> result | [] -> result
| ( "" , "" )::tail -> parse result tail | ( "" , "" )::tail -> parse result tail
| ( t , text )::tail -> | ( t , text )::tail ->
let name,typ,params,params_val = let name,typ,params,params_val =
match String.split ~on:':' t with match String_ext.split ~on:':' t with
| [name;typ] -> (name,typ,"","") | [name;typ] -> (name,typ,"","")
| name::typ::params::params_val -> (name,typ,params, | name::typ::params::params_val -> (name,typ,params,
(String.concat params_val ~sep:":") ) (String.concat ":" params_val) )
| _ -> assert false | _ -> assert false
in in
let typ = String.strip typ let typ = String_ext.strip typ
and name = String.strip name in and name = String_ext.strip name in
let typ_cap = String.capitalize typ in let typ_cap = String.capitalize typ in
let newstring = Printf.sprintf template name typ typ typ params_val typ typ let newstring = Printf.sprintf template name typ typ typ params_val typ typ
typ typ params ( String.strip text ) typ_cap typ typ params ( String_ext.strip text ) typ_cap
in in
List.rev (parse (newstring::result) tail ) List.rev (parse (newstring::result) tail )
in in
String.split ~on:'*' input String_ext.split ~on:'*' input
|> List.map ~f:(String.lsplit2_exn ~on:'\n') |> List.map (String_ext.lsplit2_exn ~on:'\n')
|> parse [] |> parse []
|> String.concat |> String.concat ""
|> global_replace
|> print_string |> print_string
;;
let ezfio_template = format_of_string " let ezfio_template = format_of_string "
@ -287,24 +298,24 @@ end = struct
end end
end end
" "
;;
let parse_input_ezfio input= let parse_input_ezfio input=
let parse s = let parse s =
match ( match (
String.split s ~on:'\n' String_ext.split s ~on:'\n'
|> List.filter ~f:(fun x -> (String.strip x) <> "") |> List.filter (fun x -> (String_ext.strip x) <> "")
) with ) with
| [] -> "" | [] -> ""
| a :: b :: c :: d :: [] -> | a :: b :: c :: d :: [] ->
begin begin
let (name,typ) = String.lsplit2_exn ~on:':' a let (name,typ) = String_ext.lsplit2_exn ~on:':' a
and ezfio_func = b and ezfio_func = b
and (min, max) = String.lsplit2_exn ~on:':' c and (min, max) = String_ext.lsplit2_exn ~on:':' c
and msg = d and msg = d
in in
let (name, typ, ezfio_func, min, max, msg) = let (name, typ, ezfio_func, min, max, msg) =
match (List.map [ name ; typ ; ezfio_func ; min ; max ; msg ] ~f:String.strip) with match List.map String_ext.strip [ name ; typ ; ezfio_func ; min ; max ; msg ] with
| [ name ; typ ; ezfio_func ; min ; max ; msg ] -> (name, typ, ezfio_func, min, max, msg) | [ name ; typ ; ezfio_func ; min ; max ; msg ] -> (name, typ, ezfio_func, min, max, msg)
| _ -> assert false | _ -> assert false
in in
@ -314,16 +325,17 @@ let parse_input_ezfio input=
end end
| _ -> failwith "Error in input_ezfio" | _ -> failwith "Error in input_ezfio"
in in
String.split ~on:'*' input String_ext.split ~on:'*' input
|> List.map ~f:parse |> List.map parse
|> String.concat |> String.concat ""
|> global_replace
|> print_string |> print_string
;;
let () = let () =
parse_input input_data ; parse_input input_data ;
parse_input_ezfio input_ezfio; parse_input_ezfio input_ezfio;
print_endline untouched; print_endline untouched

View File

@ -1,15 +1,13 @@
open Core
open Qputils open Qputils
open Qptypes open Qptypes
open Symmetry open Symmetry
let () = let () =
"SPDFGHIJKL" "SPDFGHIJKL"
|> String.to_list_rev |> String_ext.to_list
|> List.rev |> List.map of_char
|> List.map ~f:of_char |> List.map Xyz.of_symmetry
|> List.map ~f:Xyz.of_symmetry |> List.iter (fun x -> List.iter (fun y -> Xyz.to_string y |> print_endline) x ;
|> List.iter ~f:(fun x -> List.iter x ~f:(fun y -> Xyz.to_string y |> print_endline) ;
print_newline ();) print_newline ();)

View File

@ -1,5 +1,3 @@
open Core
let () = let () =
TaskServer.run 12345 TaskServer.run 12345

View File

@ -170,7 +170,7 @@ class EZFIO_ocaml(object):
else: else:
l_template += [" {0:<30} : {1};".format(p, t.ocaml)] l_template += [" {0:<30} : {1};".format(p, t.ocaml)]
l_template += [" } with sexp", l_template += [" } [@@deriving sexp]",
";;"] ";;"]
# ~#~#~#~#~#~ # # ~#~#~#~#~#~ #

View File

@ -4,7 +4,7 @@
open Qputils open Qputils
open Qptypes open Qptypes
open Core.Std open Core
(** Interactive editing of the input. (** Interactive editing of the input.