summaryrefslogtreecommitdiffstats
path: root/stdlib/filename.mli
diff options
context:
space:
mode:
authorXavier Leroy <xavier.leroy@inria.fr>1995-10-24 15:38:03 +0000
committerXavier Leroy <xavier.leroy@inria.fr>1995-10-24 15:38:03 +0000
commitcec6b5e0badd2be95eee5ceb6b89d3def666a31e (patch)
treeb0574c1e8c83f1ef8fb12164b0e8ea63368985d0 /stdlib/filename.mli
parent0dd6dfcaa701420e846559ea53fe51561a30fdfd (diff)
Ajout du module Profiling.
Ajout de Filename.chop_extension. git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@355 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'stdlib/filename.mli')
-rw-r--r--stdlib/filename.mli5
1 files changed, 5 insertions, 0 deletions
diff --git a/stdlib/filename.mli b/stdlib/filename.mli
index 39b19bc16..d78e0a7d9 100644
--- a/stdlib/filename.mli
+++ b/stdlib/filename.mli
@@ -30,6 +30,11 @@ val chop_suffix : string -> string -> string
(* [chop_suffix name suff] removes the suffix [suff] from
the filename [name]. The behavior is undefined if [name] does not
end with the suffix [suff]. *)
+val chop_extension : string -> string
+ (* Return the given file name without its extension. An extension
+ is a suffix starting with a period, [.xyz] for instance.
+ Raise [Invalid_argument] if the given name does not contain
+ a period. *)
val basename : string -> string
val dirname : string -> string
(* Split a file name into directory name / base file name.