summaryrefslogtreecommitdiffstats
path: root/stdlib/pervasives.ml
diff options
context:
space:
mode:
authorXavier Leroy <xavier.leroy@inria.fr>2003-07-05 11:13:24 +0000
committerXavier Leroy <xavier.leroy@inria.fr>2003-07-05 11:13:24 +0000
commit1a4be860d079fa8902a25ede9df61bfe57407129 (patch)
tree155a789214729baf0c2a608ee58232f3ff4c0c5d /stdlib/pervasives.ml
parent62e030d764506fc1c76d0e459f2e86f6eb7ef139 (diff)
Renommage type format -> format4 et reintroduction type format a 3 arguments pour compatibilite arriere
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@5658 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'stdlib/pervasives.ml')
-rw-r--r--stdlib/pervasives.ml11
1 files changed, 6 insertions, 5 deletions
diff --git a/stdlib/pervasives.ml b/stdlib/pervasives.ml
index 8a7381999..99d9ceaa2 100644
--- a/stdlib/pervasives.ml
+++ b/stdlib/pervasives.ml
@@ -401,13 +401,14 @@ external incr: int ref -> unit = "%incr"
external decr: int ref -> unit = "%decr"
(* Formats *)
+type ('a, 'b, 'c) format = ('a, 'b, 'c, 'c) format4
external format_of_string :
- ('a, 'b, 'c, 'd) format -> ('a, 'b, 'c, 'd) format = "%identity"
-external string_of_format : ('a, 'b, 'c, 'd) format -> string = "%identity"
+ ('a, 'b, 'c, 'd) format4 -> ('a, 'b, 'c, 'd) format4 = "%identity"
+external string_of_format : ('a, 'b, 'c, 'd) format4 -> string = "%identity"
-external string_to_format : string -> ('a, 'b, 'c, 'd) format = "%identity"
-let (( ^^ ) : ('a, 'b, 'c, 'd) format -> ('d, 'b, 'c, 'e) format ->
- ('a, 'b, 'c, 'e) format) = fun fmt1 fmt2 ->
+external string_to_format : string -> ('a, 'b, 'c, 'd) format4 = "%identity"
+let (( ^^ ) : ('a, 'b, 'c, 'd) format4 -> ('d, 'b, 'c, 'e) format4 ->
+ ('a, 'b, 'c, 'e) format4) = fun fmt1 fmt2 ->
string_to_format (string_of_format fmt1 ^ string_of_format fmt2);;
(* Miscellaneous *)