Skip to content

Commit

Permalink
pretty-printer/parser: improve reparsability of the pretty-printer ou…
Browse files Browse the repository at this point in the history
…tput
  • Loading branch information
strub committed Sep 25, 2024
1 parent d181918 commit 5a36b1b
Show file tree
Hide file tree
Showing 4 changed files with 19 additions and 13 deletions.
4 changes: 2 additions & 2 deletions src/ecParser.mly
Original file line number Diff line number Diff line change
Expand Up @@ -1440,10 +1440,10 @@ lvalue_u:
| LPAREN p=plist2(qident, COMMA) RPAREN
{ PLvTuple p }

| x=loc(fident) DLBRACKET ti=tvars_app? e=expr RBRACKET
| x=loc(fident) DLBRACKET ti=tvars_app? es=plist1(expr, COMMA) RBRACKET
{ match lqident_of_fident x.pl_desc with
| None -> parse_error x.pl_loc None
| Some v -> PLvMap (mk_loc x.pl_loc v, ti, e) }
| Some v -> PLvMap (mk_loc x.pl_loc v, ti, es) }

%inline lvalue:
| x=loc(lvalue_u) { x }
Expand Down
2 changes: 1 addition & 1 deletion src/ecParsetree.ml
Original file line number Diff line number Diff line change
Expand Up @@ -96,7 +96,7 @@ and 'a rfield = {
type plvalue_r =
| PLvSymbol of pqsymbol
| PLvTuple of pqsymbol list
| PLvMap of pqsymbol * ptyannot option * pexpr
| PLvMap of pqsymbol * ptyannot option * pexpr list

and plvalue = plvalue_r located

Expand Down
21 changes: 13 additions & 8 deletions src/ecPrinting.ml
Original file line number Diff line number Diff line change
Expand Up @@ -3028,11 +3028,14 @@ let pp_ovdecl ppe fmt ov =
let pp_pvdecl ppe fmt v =
Format.fprintf fmt "%s : %a" v.v_name (pp_type ppe) v.v_type

let pp_funsig ppe fmt fs =
Format.fprintf fmt "@[<hov 2>proc %s(%a) :@ %a@]"
fs.fs_name
(pp_list ", " (pp_ovdecl ppe)) fs.fs_anames
(pp_type ppe) fs.fs_ret
let pp_funsig ?(with_sig = true) ppe fmt fs =
if with_sig then
Format.fprintf fmt "@[<hov 2>proc %s(%a) :@ %a@]"
fs.fs_name
(pp_list ", " (pp_ovdecl ppe)) fs.fs_anames
(pp_type ppe) fs.fs_ret
else
Format.fprintf fmt "@[<hov 2>proc %s@]" fs.fs_name

let pp_sigitem moi_opt ppe fmt (Tys_function fs) =
Format.fprintf fmt "@[<hov 2>%a@ %t@]"
Expand Down Expand Up @@ -3189,6 +3192,10 @@ and pp_moditem ppe fmt (p, i) =
Format.fprintf fmt "@[<hov 2>return@ @[%a@];@]" (pp_expr ppe) e
in

let pp_funsig ppe fmt fun_ =
let with_sig = match fun_.f_def with FBalias _ -> false | _ -> true in
Format.fprintf fmt "%a" (pp_funsig ~with_sig ppe) fun_.f_sig in

let pp_fundef ppe fmt fun_ =
match fun_.f_def with
| (FBdef def) ->
Expand All @@ -3210,9 +3217,7 @@ and pp_moditem ppe fmt (p, i) =
Format.fprintf fmt "?ABSTRACT?"
in

Format.fprintf fmt "@[<v>%a = %a@]"
(pp_funsig ppe) f.f_sig
(pp_fundef ppe) f
Format.fprintf fmt "@[<v>%a = %a@]" (pp_funsig ppe) f (pp_fundef ppe) f

let pp_modexp ppe fmt (mp, me) =
Format.fprintf fmt "%a." (pp_modexp ppe) (mp, me)
Expand Down
5 changes: 3 additions & 2 deletions src/ecTyping.ml
Original file line number Diff line number Diff line change
Expand Up @@ -2709,11 +2709,12 @@ and translvalue ue (env : EcEnv.env) lvalue =
let ty = ttuple (List.map snd xs) in
Lval (LvTuple xs), ty

| PLvMap (x, tvi, e) ->
| PLvMap (x, tvi, es) ->
let tvi = tvi |> omap (transtvi env ue) in
let codomty = UE.fresh ue in
let pv, xty = trans_pv env x in
let e, ety = transexp env `InProc ue e in
let e, ety = List.split (List.map (transexp env `InProc ue) es) in
let e, ety = e_tuple e, ttuple ety in
let name = ([], EcCoreLib.s_set) in
let esig = [xty; ety; codomty] in
let ops = select_exp_op env `InProc None name ue tvi esig in
Expand Down

0 comments on commit 5a36b1b

Please sign in to comment.