package logtk

  1. Overview
  2. Docs
Legend:
Page
Library
Module
Module type
Parameter
Class
Class type
Source

Source file callProver.ml

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

(* This file is free software, part of Logtk. See file "license" for more details. *)

(** {1 Call external provers with TSTP} *)

open Logtk

module A = Ast_tptp
module TT = Trace_tstp
module Err = CCResult
module ST = STerm

type 'a or_error = ('a, string) CCResult.t
type untyped = STerm.t

(** {2 Description of provers} *)

module Prover = struct
  type t = {
    name : string;                (** name of the prover *)
    command : string;             (** command to call prover*)
    unsat : string list;           (** prover returned unsat *)
    sat : string list;             (** prover returned sat *)
  } (** data useful to invoke a prover. The prover must read from
        stdin. The command is interpolated using {! Buffer.add_substitude}, with
        the given patterns:

        - "timeout" is the timeout in seconds *)

  let __table : (string,t) Hashtbl.t = Hashtbl.create 5

  let lookup name = Hashtbl.find __table name

  let list_provers () =
    Hashtbl.fold
      (fun n _ acc -> n :: acc)
      __table []

  let register name prover =
    if Hashtbl.mem __table name
    then invalid_arg ("prover already registered: "^ name)
    else Hashtbl.add __table name prover

  let p_E = {
    name = "E";
    command = "eprover --cpu-limit=${timeout} --auto -l0 --tstp-in --tstp-out";
    unsat = ["SZS status Unsat"; "SZS status Theorem"];
    sat = ["SZS status Satisfiable"; "SZS status CounterTheorem"];
  }

  let p_Eproof =
    { p_E with
      name = "Eproof";
      command = "eproof_ram --cpu-limit=${timeout} -tAuto -xAuto -l0 --tstp-in --tstp-out";
    }

  let p_SPASS = {
    name = "SPASS";
    command = "SPASS -TPTP -TimeLimit=${timeout} -Stdin";
    unsat = ["Proof found"];
    sat = ["Completion found"];
  }

  let p_Zenon = {
    name = "Zenon";
    command = "zenon -itptp -p0 -max-time ${timeout}s -";
    unsat = ["PROOF-FOUND"];
    sat = ["NO-PROOF"];
  }

  let default = [p_E; p_SPASS]
end

let name p = p.Prover.name

(** {2 Run provers} *)

type result =
  | Unsat
  | Sat
  | Unknown
  | Error of string

(* among the strings in [patterns], find if one is a substring of [s] *)
let _find_mem patterns s =
  List.exists
    (fun p -> CCString.find ~sub:p s >= 0)
    patterns

let call_with_out ?(timeout=30) ?(args=[]) ~prover decls =
  (* compute input to give to the prover *)
  let input =
    CCFormat.sprintf "@[<v>%a@]"
      (Util.pp_list ~sep:"" (A.pp ST.pp)) decls in
  (* build command (add arguments to the end) *)
  let buf = Buffer.create 15 in
  Buffer.add_substitute buf
    (function
      | "timeout" -> string_of_int timeout
      | s -> s)
    prover.Prover.command;
  List.iter (fun arg -> Buffer.add_char buf ' '; Buffer.add_string buf arg) args;
  let cmd = Buffer.contents buf in
  Util.debugf 2 "run prover %s" (fun k->k prover.Prover.name);
  Util.debugf 4 "command is: \"%s\"" (fun k->k cmd);
  Util.debugf 4 "obligation is: \"%s\"" (fun k->k input);
  Err.(
    (* run the prover *)
    Util.popen ~cmd ~input
    >>= fun output ->
    Util.debugf 2 "prover %s done" (fun k->k prover.Prover.name);
    Util.debugf 4 "output: \"%s\"" (fun k->k output);
    (* parse output *)
    let result =
      if _find_mem prover.Prover.unsat output
      then Unsat
      else if _find_mem prover.Prover.sat output
      then Sat
      else Unknown
    in
    Err.return (result, output)
  )

let call ?timeout ?args ~prover decls =
  Err.(
    call_with_out ?timeout ?args ~prover decls
    >>= fun (res, _) ->
    return res
  )

let decls_of_string ~source str =
  let lexbuf = Lexing.from_string str in
  ParseLocation.set_file lexbuf source;
  Util_tptp.parse_lexbuf lexbuf

(* try to parse a proof. Returns a proof option *)
let proof_of_decls decls =
  let res = Trace_tstp.of_decls decls in
  match res with
  | Err.Error _ -> None
  | Err.Ok proof -> Some proof

let call_proof ?timeout ?args ~prover decls =
  Err.(
    call_with_out ?timeout ?args ~prover decls
    >>= fun (res, output) ->
    decls_of_string ~source:("output of prover "^ prover.Prover.name) output
    >>= Trace_tstp.of_decls
    >>= fun proof ->
    return (res, proof)
  )

module Eprover = struct
  type result = {
    answer : szs_answer;
    output : string;
    decls : untyped Ast_tptp.t Iter.t option;
    proof : Trace_tstp.t option;
  }
  and szs_answer =
    | Theorem
    | CounterSatisfiable
    | Unknown

  let string_of_answer = function
    | Theorem -> "Theorem"
    | CounterSatisfiable -> "CounterSatisfiable"
    | Unknown -> "Unknown"

  (* parse SZS answer *)
  let parse_answer output =
    if CCString.mem ~sub:"SZS status Theorem" output
    then Theorem
    else if CCString.mem ~sub:"SZS status CounterSatisfiable" output
    then CounterSatisfiable
    else Unknown

  (* run eproof_ram on the given input. returns a result *)
  let _run_either ?(opts=[]) ?(level=1) ~prover ~steps ~input () =
    let level' = Printf.sprintf "-l%d" level in
    let command =
      [ prover; "--tstp-in"; "--tstp-out"; level'; "-C"
      ; string_of_int steps; "-xAuto"; "-tAuto" ] @ opts
    in
    let cmd = String.concat " " command in
    Err.(
      Util.popen ~cmd ~input
      >>= fun output ->
      (* parse answer *)
      let answer = parse_answer output in
      (* read its output *)
      let decls, proof =
        match decls_of_string ~source:"E" output with
        | Err.Error _ -> None, None
        | Err.Ok s ->
          (* try to parse proof, if it's a theorem *)
          let proof =
            if answer = Theorem
            then proof_of_decls s
            else None
          in
          Some s, proof
      in
      Err.return { answer; output; decls; proof }
    )

  (* run eproof_ram on the given input. returns a result *)
  let run_eproof ~steps ~input =
    _run_either ~prover:"eproof_ram" ~steps ~input ()

  (* run eprover on the given input. returns a result Lwt *)
  let run_eprover ?opts ?level ~steps ~input () =
    _run_either ~prover:"eprover" ?opts ?level ~steps ~input ()

  (* explore the surrounding of this list of formulas, returning a
     list of terms (clausal form) *)
  let discover ?(opts=[]) ~steps decls =
    let command = [ "eprover"; "--tstp-in"; "--tstp-out";
                    "-S"; "--restrict-literal-comparisons";
                    "-C"; string_of_int steps ] @ opts in
    let cmd = String.concat " " command in
    (* build stdin *)
    let input =
      CCFormat.sprintf "@[%a@]"
        (Util.pp_iter ~sep:"" (A.pp ST.pp)) decls
    in
    Err.(
      (* call E *)
      Util.popen ~cmd ~input
      >>= fun output ->
      (* read its output *)
      decls_of_string ~source:"E" output
    )

  let cnf ?(opts=[]) decls =
    let command = [ "eprover"; "--tstp-in"; "--tstp-out"; "--cnf" ] @ opts in
    let cmd = String.concat " " command in
    (* build stdin *)
    let input =
      CCFormat.sprintf "@[%a@]"
        (Util.pp_iter ~sep:"" (A.pp ST.pp)) decls
    in
    Err.(
      (* call E *)
      Util.popen ~cmd ~input
      >>= fun output ->
      (* read its output *)
      decls_of_string ~source:"E" output
    )
end
OCaml

Innovation. Community. Security.