]> matita.cs.unibo.it Git - helm.git/blob - helm/ocaml/cic_disambiguation/pp.ml
removed dependency on netclient, use http_client module from ocaml-http
[helm.git] / helm / ocaml / cic_disambiguation / pp.ml
1
2 open Ast
3 open Printf
4
5 let pp_binder = function
6   | `Lambda -> "lambda"
7   | `Pi -> "pi"
8   | `Exists -> "exists"
9   | `Forall -> "forall"
10
11 let rec pp_term = function
12   | LocatedTerm ((p_begin, p_end), term) ->
13       sprintf "[%d,%d]%s" p_begin p_end (pp_term term)
14
15   | Appl terms -> sprintf "(%s)" (String.concat " " (List.map pp_term terms))
16   | Binder (kind, var, typ, body) ->
17       sprintf "\\%s %s%s.%s" (pp_binder kind) var
18         (match typ with None -> "" | Some typ -> ": " ^ pp_term typ)
19         (pp_term body)
20   | Case (term, typ, patterns) ->
21       sprintf "%smatch %s with %s"
22         (match typ with None -> "" | Some t -> sprintf "<%s>" (pp_term t))
23         (pp_term term) (pp_patterns patterns)
24   | LetIn (name, t1, t2) ->
25       sprintf "let %s = %s in %s" name (pp_term t1) (pp_term t2)
26   | LetRec (definitions, term) ->
27       sprintf "let rec %s in %s"
28         (String.concat " and "
29           (List.map
30             (fun (name, body, typ, index) ->
31               sprintf "%s%s = %s" name
32                 (match typ with None -> "" | Some typ -> ": " ^ pp_term typ)
33                 (pp_term body))
34             definitions))
35         (pp_term term)
36   | Ident (name, []) -> name
37   | Ident (name, substs) -> sprintf "%s[%s]" name (pp_substs substs)
38   | Meta (name, substs) ->
39       sprintf "%s[%s]" name
40         (String.concat "; "
41           (List.map (function None -> "_" | Some term -> pp_term term) substs))
42   | Int num -> string_of_int num
43
44 and pp_subst (name, term) = sprintf "%s := %s" name (pp_term term)
45 and pp_substs substs = String.concat "; " (List.map pp_subst substs)
46
47 and pp_pattern (names, term) =
48   sprintf "%s -> %s"
49     (match names with
50     | [n] -> n
51     | names -> "(" ^ String.concat " " names ^ ")")
52     (pp_term term)
53
54 and pp_patterns patterns =
55   sprintf "[%s]" (String.concat " | " (List.map pp_pattern patterns))
56