Paresseux.

git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@1716 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Damien Doligez 1997-10-14 13:17:48 +00:00
parent cbb5232b7b
commit c194d39545
13 changed files with 26 additions and 12 deletions

View File

@ -88,7 +88,7 @@ EXPUNGEOBJS=utils/misc.cmo utils/tbl.cmo \
PERVASIVES=arg array callback char digest filename format gc hashtbl \
lexing list map obj parsing pervasives printexc printf queue random \
set sort stack string stream sys oo genlex topdirs toploop weak
set sort stack string stream sys oo genlex topdirs toploop weak lazy
# Recompile the system using the bootstrap compiler
all: runtime ocamlc ocamllex ocamlyacc ocamltools library ocaml \

View File

@ -55,6 +55,7 @@ let keyword_table =
"in", IN;
"include", INCLUDE;
"inherit", INHERIT;
"lazy", LAZY;
"let", LET;
"match", MATCH;
"method", METHOD;

View File

@ -57,6 +57,12 @@ let mkassert e =
else mkexp (Pexp_ifthenelse (e, un, Some raiser))
;;
let mklazy e =
let f = mkexp (Pexp_ident (Ldot (Lident "Lazy", "_lazy"))) in
let void_pat = mkpat (Ppat_construct (Lident "()", None, false)) in
mkexp (Pexp_apply (f, [mkexp (Pexp_function ([void_pat, e]))]))
;;
let mkinfix arg1 name arg2 =
mkexp(Pexp_apply(mkoperator name 2, [arg1; arg2]))
@ -152,6 +158,7 @@ let unclosed opening_name opening_num closing_name closing_num =
%token <string> INFIXOP4
%token INHERIT
%token <int> INT
%token LAZY
%token LBRACE
%token LBRACELESS
%token LBRACKET
@ -487,6 +494,8 @@ expr:
{ mkexp(Pexp_setinstvar($1, $3)) }
| ASSERT simple_expr %prec prec_appl
{ mkassert $2 }
| LAZY simple_expr %prec prec_appl
{ mklazy $2 }
;
simple_expr:
val_longident

View File

@ -110,10 +110,10 @@ let cparser (bpo, pc) =
(* streams *)
let lazy e = mkexp (Pexp_function [(mkpat Ppat_any, e)])
let clazy e = mkexp (Pexp_function [(mkpat Ppat_any, e)])
let rec cstream =
function
[] -> eval "sempty"
| Sexp_term e :: secl -> afun "lcons" [lazy e; cstream secl]
| Sexp_nterm e :: secl -> afun "lapp" [lazy e; cstream secl]
| Sexp_term e :: secl -> afun "lcons" [clazy e; cstream secl]
| Sexp_nterm e :: secl -> afun "lapp" [clazy e; cstream secl]

View File

@ -20,6 +20,8 @@ genlex.cmo: char.cmi hashtbl.cmi list.cmi stream.cmi string.cmi genlex.cmi
genlex.cmx: char.cmx hashtbl.cmx list.cmx stream.cmx string.cmx genlex.cmi
hashtbl.cmo: array.cmi hashtbl.cmi
hashtbl.cmx: array.cmx hashtbl.cmi
lazy.cmo: lazy.cmi
lazy.cmx: lazy.cmi
lexing.cmo: string.cmi lexing.cmi
lexing.cmx: string.cmx lexing.cmi
list.cmo: list.cmi

View File

@ -13,7 +13,8 @@ OBJS=pervasives.cmo list.cmo char.cmo string.cmo array.cmo sys.cmo \
hashtbl.cmo sort.cmo filename.cmo obj.cmo lexing.cmo parsing.cmo \
set.cmo map.cmo stack.cmo queue.cmo stream.cmo \
printf.cmo format.cmo arg.cmo printexc.cmo gc.cmo \
digest.cmo random.cmo oo.cmo genlex.cmo callback.cmo weak.cmo marshal.cmo
digest.cmo random.cmo oo.cmo genlex.cmo callback.cmo weak.cmo marshal.cmo \
lazy.cmo
all: stdlib.cma std_exit.cmo camlheader

View File

@ -7,7 +7,7 @@ OBJS = pervasives.cmo list.cmo char.cmo string.cmo array.cmo sys.cmo
hashtbl.cmo sort.cmo filename.cmo obj.cmo lexing.cmo parsing.cmo ¶
set.cmo map.cmo stack.cmo queue.cmo stream.cmo ¶
printf.cmo format.cmo arg.cmo printexc.cmo gc.cmo ¶
digest.cmo random.cmo oo.cmo genlex.cmo weak.cmo marshal.cmo
digest.cmo random.cmo oo.cmo genlex.cmo weak.cmo marshal.cmo lazy.cmo
all Ä stdlib.cma std_exit.cmo camlheader

View File

@ -11,7 +11,8 @@ OBJS=pervasives.cmo list.cmo char.cmo string.cmo array.cmo sys.cmo \
hashtbl.cmo sort.cmo filename.cmo obj.cmo lexing.cmo parsing.cmo \
set.cmo map.cmo stack.cmo queue.cmo stream.cmo \
printf.cmo format.cmo arg.cmo printexc.cmo gc.cmo \
digest.cmo random.cmo oo.cmo genlex.cmo callback.cmo weak.cmo marshal.cmo
digest.cmo random.cmo oo.cmo genlex.cmo callback.cmo weak.cmo marshal.cmo \
lazy.cmo
all: stdlib.cma std_exit.cmo camlheader

View File

@ -2,7 +2,7 @@
(* *)
(* Objective Caml *)
(* *)
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
(* Damien Doligez, projet Para, INRIA Rocquencourt *)
(* *)
(* Copyright 1996 Institut National de Recherche en Informatique et *)
(* Automatique. Distributed only by permission. *)

View File

@ -2,7 +2,7 @@
(* *)
(* Objective Caml *)
(* *)
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
(* Damien Doligez, projet Para, INRIA Rocquencourt *)
(* *)
(* Copyright 1996 Institut National de Recherche en Informatique et *)
(* Automatique. Distributed only by permission. *)

View File

@ -155,7 +155,7 @@ let lcons f s = {count = 0; data = Slazy (fun _ -> Scons (f (), s.data))};;
let lsing f = {count = 0; data = Slazy (fun _ -> Scons (f (), Sempty))};;
let sempty = {count = 0; data = Sempty};;
let lazy f = {count = 0; data = Slazy (fun _ -> (f ()).data)};;
let slazy f = {count = 0; data = Slazy (fun _ -> (f ()).data)};;
(* For debugging use *)

View File

@ -86,6 +86,6 @@ val lcons : (unit -> 'a) -> 'a t -> 'a t;;
val lsing : (unit -> 'a) -> 'a t;;
val sempty : 'a t;;
val lazy : (unit -> 'a t) -> 'a t;;
val slazy : (unit -> 'a t) -> 'a t;;
val dump : ('a -> unit) -> 'a t -> unit;;

View File

@ -11,7 +11,7 @@
(* $Id$ *)
let version = "1.06-1/14"
let version = "1.06-1/15"
let standard_library =
try