ocaml/camlp4/etc/q_phony.ml

48 lines
1.6 KiB
OCaml

(* camlp4r pa_extend.cmo q_MLast.cmo *)
(***********************************************************************)
(* *)
(* Camlp4 *)
(* *)
(* Daniel de Rauglaudre, projet Cristal, INRIA Rocquencourt *)
(* *)
(* Copyright 2001 Institut National de Recherche en Informatique et *)
(* Automatique. Distributed only by permission. *)
(* *)
(***********************************************************************)
(* $Id$ *)
open Pcaml;
value t = ref "";
Quotation.add ""
(Quotation.ExAst
(fun s ->
let t =
if t.val = "" then "<<" ^ s ^ ">>"
else "<:" ^ t.val ^ "<" ^ s ^ ">>"
in
let loc = (0, 0) in
<:expr< $uid:t$ >>,
fun s ->
let t =
if t.val = "" then "<<" ^ s ^ ">>"
else "<:" ^ t.val ^ "<" ^ s ^ ">>"
in
let loc = (0, 0) in
<:patt< $uid:t$ >>))
;
Quotation.default.val := "";
Quotation.translate.val := fun s -> do { t.val := s; "" };
EXTEND
expr: LEVEL "top"
[ [ "ifdef"; c = UIDENT; "then"; e1 = expr; "else"; e2 = expr ->
<:expr< if def $uid:c$ then $e1$ else $e2$ >>
| "ifndef"; c = UIDENT; "then"; e1 = expr; "else"; e2 = expr ->
<:expr< if ndef $uid:c$ then $e1$ else $e2$ >> ] ]
;
END;