Blame src/FileUtil.mli

Packit 9ff65e
(******************************************************************************)
Packit 9ff65e
(*  ocaml-fileutils: files and filenames common operations                    *)
Packit 9ff65e
(*                                                                            *)
Packit 9ff65e
(*  Copyright (C) 2003-2014, Sylvain Le Gall                                  *)
Packit 9ff65e
(*                                                                            *)
Packit 9ff65e
(*  This library is free software; you can redistribute it and/or modify it   *)
Packit 9ff65e
(*  under the terms of the GNU Lesser General Public License as published by  *)
Packit 9ff65e
(*  the Free Software Foundation; either version 2.1 of the License, or (at   *)
Packit 9ff65e
(*  your option) any later version, with the OCaml static compilation         *)
Packit 9ff65e
(*  exception.                                                                *)
Packit 9ff65e
(*                                                                            *)
Packit 9ff65e
(*  This library is distributed in the hope that it will be useful, but       *)
Packit 9ff65e
(*  WITHOUT ANY WARRANTY; without even the implied warranty of                *)
Packit 9ff65e
(*  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the file         *)
Packit 9ff65e
(*  COPYING for more details.                                                 *)
Packit 9ff65e
(*                                                                            *)
Packit 9ff65e
(*  You should have received a copy of the GNU Lesser General Public License  *)
Packit 9ff65e
(*  along with this library; if not, write to the Free Software Foundation,   *)
Packit 9ff65e
(*  Inc., 51 Franklin St, Fifth Floor, Boston, MA  02110-1301 USA             *)
Packit 9ff65e
(******************************************************************************)
Packit 9ff65e
Packit 9ff65e
(** POSIX utilities for files and directories.
Packit 9ff65e
Packit 9ff65e
    A module to provide the core POSIX utilities to manipulate files and
Packit 9ff65e
    directories. All functions try to mimic common POSIX utilities but are
Packit 9ff65e
    written in pure OCaml.
Packit 9ff65e
Packit 9ff65e
    @author Sylvain Le Gall
Packit 9ff65e
  *)
Packit 9ff65e
Packit 9ff65e
open FilePath
Packit 9ff65e
Packit 9ff65e
Packit 9ff65e
(*********************************************************************)
Packit 9ff65e
(**
Packit 9ff65e
Packit 9ff65e
  {2 Types and exceptions }
Packit 9ff65e
Packit 9ff65e
  *)
Packit 9ff65e
Packit 9ff65e
exception FileDoesntExist of filename
Packit 9ff65e
exception RecursiveLink of filename
Packit 9ff65e
Packit 9ff65e
(** Generic error handling functions. Whenever such a function is available it
Packit 9ff65e
    helps report the error and allows to raise an exception. The [string]
Packit 9ff65e
    provided is the human readable version of ['a]. In most cases ['a] is a
Packit 9ff65e
    polymorphic variant.
Packit 9ff65e
  *)
Packit 9ff65e
type 'a error_handler = string -> 'a -> unit
Packit 9ff65e
Packit 9ff65e
(** Exception raised when after an [error_handler] the execution cannot
Packit 9ff65e
    continue. The rest of the workflow logic cannot handle the default case and
Packit 9ff65e
    the whole operation can be in the middle of transformation.
Packit 9ff65e
  *)
Packit 9ff65e
exception Fatal of string
Packit 9ff65e
Packit 9ff65e
(** Policy concerning links which are directories. *)
Packit 9ff65e
type action_link =
Packit 9ff65e
  | Follow
Packit 9ff65e
    (** We consider link as simple directory (it is dangerous) *)
Packit 9ff65e
  | Skip
Packit 9ff65e
    (** Just skip it *)
Packit 9ff65e
  | SkipInform of (filename -> unit)
Packit 9ff65e
    (** Skip and execute an action *)
Packit 9ff65e
  | AskFollow of (filename -> bool)
Packit 9ff65e
    (** Ask and wait for input, false means skip *)
Packit 9ff65e
Packit 9ff65e
(** For certain command, you should need to ask the user wether
Packit 9ff65e
    or not he wants to act.
Packit 9ff65e
  *)
Packit 9ff65e
type interactive =
Packit 9ff65e
  | Force (** Do it anyway *)
Packit 9ff65e
  | Ask of (filename -> bool) (** Promp the user *)
Packit 9ff65e
Packit 9ff65e
Packit 9ff65e
(*********************************************************************)
Packit 9ff65e
(**
Packit 9ff65e
Packit 9ff65e
   {2 Permission }
Packit 9ff65e
Packit 9ff65e
  *)
Packit 9ff65e
Packit 9ff65e
(** Base permission. This is the permission corresponding to one user or group.
Packit 9ff65e
  *)
Packit 9ff65e
type base_permission =
Packit 9ff65e
  {
Packit 9ff65e
    sticky: bool;
Packit 9ff65e
    exec: bool;
Packit 9ff65e
    write: bool;
Packit 9ff65e
    read: bool;
Packit 9ff65e
  }
Packit 9ff65e
Packit 9ff65e
(** Full permission. All the base permissions of a file.
Packit 9ff65e
  *)
Packit 9ff65e
type permission =
Packit 9ff65e
  {
Packit 9ff65e
    user: base_permission;
Packit 9ff65e
    group: base_permission;
Packit 9ff65e
    other: base_permission;
Packit 9ff65e
  }
Packit 9ff65e
Packit 9ff65e
(** Translate POSIX integer permission. *)
Packit 9ff65e
val permission_of_int: int -> permission
Packit 9ff65e
Packit 9ff65e
(** Return the POSIX integer permission *)
Packit 9ff65e
val int_of_permission: permission -> int
Packit 9ff65e
Packit 9ff65e
(** Permission symbolic mode. *)
Packit 9ff65e
module Mode:
Packit 9ff65e
sig
Packit 9ff65e
  type who = [`User | `Group | `Other | `All]
Packit 9ff65e
  type wholist = [ who | `List of who list ]
Packit 9ff65e
  type permcopy = [`User | `Group | `Other]
Packit 9ff65e
  type perm = [ `Read | `Write | `Exec | `ExecX | `Sticky | `StickyO ]
Packit 9ff65e
  type permlist = [ perm | `List of perm list ]
Packit 9ff65e
  type actionarg = [ permlist | permcopy ]
Packit 9ff65e
  type action = [ `Set of actionarg | `Add of actionarg | `Remove of actionarg]
Packit 9ff65e
  type actionlist = [ action | `List of action list ]
Packit 9ff65e
  type clause = [ `User of actionlist | `Group of actionlist
Packit 9ff65e
                | `Other of actionlist | `All of actionlist
Packit 9ff65e
                | `None of actionlist ]
Packit 9ff65e
Packit 9ff65e
  (** Typical symbolic mode:
Packit 9ff65e
   - g+r -> [`Group (`Add `Read)]
Packit 9ff65e
   - u=rw,g+rw,o-rwx ->
Packit 9ff65e
     [`User (`Set (`List [`Read; `Write]));
Packit 9ff65e
      `Group (`Add (`List [`Read; `Write]));
Packit 9ff65e
      `Other (`Remove (`List [`Read; `Write; `Exec]))]
Packit 9ff65e
   *)
Packit 9ff65e
  type t = clause list
Packit 9ff65e
end
Packit 9ff65e
Packit 9ff65e
(*********************************************************************)
Packit 9ff65e
(**
Packit 9ff65e
Packit 9ff65e
   {2 Size operation}
Packit 9ff65e
 
Packit 9ff65e
  *)
Packit 9ff65e
Packit 9ff65e
(** File size
Packit 9ff65e
  *)
Packit 9ff65e
type size =
Packit 9ff65e
    TB of int64 (** Tera bytes *)
Packit 9ff65e
  | GB of int64 (** Giga bytes *)
Packit 9ff65e
  | MB of int64 (** Mega bytes *)
Packit 9ff65e
  | KB of int64 (** Kilo bytes *)
Packit 9ff65e
  | B  of int64 (** Bytes *)
Packit 9ff65e
Packit 9ff65e
(** Convert size to bytes. *)
Packit 9ff65e
val byte_of_size: size -> int64
Packit 9ff65e
Packit 9ff65e
(** Add two sizes. *)
Packit 9ff65e
val size_add: size -> size -> size
Packit 9ff65e
Packit 9ff65e
(** Compare two sizes, using the classical compare function. If fuzzy is set to
Packit 9ff65e
    true, the comparison is done on the most significant size unit of both
Packit 9ff65e
    value.
Packit 9ff65e
  *)
Packit 9ff65e
val size_compare: ?fuzzy:bool -> size -> size -> int
Packit 9ff65e
Packit 9ff65e
(** Convert a value to a string representation. If fuzzy is set to true, only
Packit 9ff65e
    consider the most significant unit
Packit 9ff65e
  *)
Packit 9ff65e
val string_of_size: ?fuzzy:bool -> size -> string
Packit 9ff65e
Packit 9ff65e
(*********************************************************************)
Packit 9ff65e
(**
Packit 9ff65e
Packit 9ff65e
   {2 stat }
Packit 9ff65e
Packit 9ff65e
  *)
Packit 9ff65e
Packit 9ff65e
(** Kind of file. This set is a combination of all POSIX file, some of them
Packit 9ff65e
    doesn't exist at all on certain file system or OS.
Packit 9ff65e
  *)
Packit 9ff65e
type kind =
Packit 9ff65e
    Dir
Packit 9ff65e
  | File
Packit 9ff65e
  | Dev_char
Packit 9ff65e
  | Dev_block
Packit 9ff65e
  | Fifo
Packit 9ff65e
  | Socket
Packit 9ff65e
  | Symlink (** @since 0.4.6 *)
Packit 9ff65e
Packit 9ff65e
Packit 9ff65e
(** Information about a file. This type is derived from Unix.stat
Packit 9ff65e
  *)
Packit 9ff65e
type stat =
Packit 9ff65e
  {
Packit 9ff65e
    kind: kind;
Packit 9ff65e
    is_link: bool;
Packit 9ff65e
    permission: permission;
Packit 9ff65e
    size: size;
Packit 9ff65e
    owner: int;
Packit 9ff65e
    group_owner: int;
Packit 9ff65e
    access_time: float;
Packit 9ff65e
    modification_time: float;
Packit 9ff65e
    creation_time: float;
Packit 9ff65e
    device: int;
Packit 9ff65e
    inode: int;
Packit 9ff65e
  }
Packit 9ff65e
Packit 9ff65e
Packit 9ff65e
(** [stat fln] Return information about the file (like Unix.stat)
Packit 9ff65e
    Non POSIX command.
Packit 9ff65e
  *)
Packit 9ff65e
val stat: ?dereference:bool -> filename -> stat
Packit 9ff65e
Packit 9ff65e
(*********************************************************************)
Packit 9ff65e
(**
Packit 9ff65e
 
Packit 9ff65e
  {2 umask }
Packit 9ff65e
   
Packit 9ff65e
  *)
Packit 9ff65e
Packit 9ff65e
exception UmaskError of string
Packit 9ff65e
Packit 9ff65e
(** Possible umask errors. *)
Packit 9ff65e
type umask_error = [ `Exc of exn | `NoStickyBit of int ]
Packit 9ff65e
Packit 9ff65e
(** Get or set the file mode creation mask.
Packit 9ff65e
    See {{:http://pubs.opengroup.org/onlinepubs/007904875/utilities/umask.html}POSIX documentation}.
Packit 9ff65e
  *)
Packit 9ff65e
val umask:
Packit 9ff65e
  ?error:(umask_error error_handler) ->
Packit 9ff65e
  ?mode:[< `Octal of int | `Symbolic of Mode.t ] ->
Packit 9ff65e
  [< `Octal of int -> 'a | `Symbolic of Mode.t -> 'a] ->
Packit 9ff65e
  'a
Packit 9ff65e
Packit 9ff65e
(** Apply umask to a given file permission.
Packit 9ff65e
  *)
Packit 9ff65e
val umask_apply: int -> int
Packit 9ff65e
Packit 9ff65e
(*********************************************************************)
Packit 9ff65e
(**
Packit 9ff65e
Packit 9ff65e
  {2 test }
Packit 9ff65e
Packit 9ff65e
  *)
Packit 9ff65e
Packit 9ff65e
(** Pattern you can use to test file. If the file doesn't exist the result is
Packit 9ff65e
    always false.
Packit 9ff65e
  *)
Packit 9ff65e
type test_file =
Packit 9ff65e
  | Is_dev_block                 (** FILE is block special *)
Packit 9ff65e
  | Is_dev_char                  (** FILE is character special *)
Packit 9ff65e
  | Is_dir                       (** FILE is a directory *)
Packit 9ff65e
  | Exists                       (** FILE exists *)
Packit 9ff65e
  | Is_file                      (** FILE is a regular file *)
Packit 9ff65e
  | Is_set_group_ID              (** FILE is set-group-ID *)
Packit 9ff65e
  | Has_sticky_bit               (** FILE has its sticky bit set *)
Packit 9ff65e
  | Is_link                      (** FILE is a symbolic link *)
Packit 9ff65e
  | Is_pipe                      (** FILE is a named pipe *)
Packit 9ff65e
  | Is_readable                  (** FILE is readable *)
Packit 9ff65e
  | Is_writeable                 (** FILE is writeable *)
Packit 9ff65e
  | Size_not_null                (** FILE has a size greater than zero *)
Packit 9ff65e
  | Size_bigger_than of size     (** FILE has a size greater than given size *)
Packit 9ff65e
  | Size_smaller_than of size    (** FILE has a size smaller than given size *)
Packit 9ff65e
  | Size_equal_to of size        (** FILE has the same size as given size *)
Packit 9ff65e
  | Size_fuzzy_equal_to of size  (** FILE has approximatively the same size as
Packit 9ff65e
                                     given size *)
Packit 9ff65e
  | Is_socket                    (** FILE is a socket *)
Packit 9ff65e
  | Has_set_user_ID              (** FILE its set-user-ID bit is set *)
Packit 9ff65e
  | Is_exec                      (** FILE is executable *)
Packit 9ff65e
  | Is_owned_by_user_ID          (** FILE is owned by the effective user ID *)
Packit 9ff65e
  | Is_owned_by_group_ID         (** FILE is owned by the effective group ID *)
Packit 9ff65e
  | Is_newer_than of filename    (** FILE1 is newer (modification date) than
Packit 9ff65e
                                     FILE2 *)
Packit 9ff65e
  | Is_older_than of filename    (** FILE1 is older than FILE2 *)
Packit 9ff65e
  | Is_newer_than_date of float  (** FILE is newer than given date *)
Packit 9ff65e
  | Is_older_than_date of float  (** FILE is older than given date *)
Packit 9ff65e
  | And of test_file * test_file (** Result of TEST1 and TEST2 *)
Packit 9ff65e
  | Or of test_file * test_file  (** Result of TEST1 or TEST2 *)
Packit 9ff65e
  | Not of test_file             (** Result of not TEST *)
Packit 9ff65e
  | Match of string              (** Compilable match (Str or PCRE or ...) *)
Packit 9ff65e
  | True                         (** Always true *)
Packit 9ff65e
  | False                        (** Always false *)
Packit 9ff65e
  | Has_extension of extension   (** Check extension *)
Packit 9ff65e
  | Has_no_extension             (** Check absence of extension *)
Packit 9ff65e
  | Is_parent_dir                (** Basename is the parent dir *)
Packit 9ff65e
  | Is_current_dir               (** Basename is the current dir *)
Packit 9ff65e
  | Basename_is of filename      (** Check the basename *)
Packit 9ff65e
  | Dirname_is of filename       (** Check the dirname *)
Packit 9ff65e
  | Custom of (filename -> bool) (** Custom operation on filename *)
Packit 9ff65e
Packit 9ff65e
Packit 9ff65e
(** Test a file.
Packit 9ff65e
    See {{:http://pubs.opengroup.org/onlinepubs/007904875/utilities/test.html}POSIX documentation}.
Packit 9ff65e
  *)
Packit 9ff65e
val test:
Packit 9ff65e
  ?match_compile:(filename -> filename -> bool) ->
Packit 9ff65e
  test_file -> filename -> bool
Packit 9ff65e
Packit 9ff65e
(*********************************************************************)
Packit 9ff65e
(**
Packit 9ff65e
Packit 9ff65e
  {2 chmod }
Packit 9ff65e
Packit 9ff65e
  *)
Packit 9ff65e
Packit 9ff65e
exception ChmodError of string
Packit 9ff65e
Packit 9ff65e
(** Possible chmod errors. *)
Packit 9ff65e
type chmod_error = [`Exc of exn]
Packit 9ff65e
Packit 9ff65e
(** Change permissions of files.
Packit 9ff65e
    See {{:http://pubs.opengroup.org/onlinepubs/007904875/utilities/chmod.html}POSIX documentation}.
Packit 9ff65e
  *)
Packit 9ff65e
val chmod:
Packit 9ff65e
  ?error:(chmod_error error_handler) ->
Packit 9ff65e
  ?recurse:bool ->
Packit 9ff65e
  [< `Octal of Unix.file_perm | `Symbolic of Mode.t ] ->
Packit 9ff65e
  filename list -> unit
Packit 9ff65e
Packit 9ff65e
(*********************************************************************)
Packit 9ff65e
(**
Packit 9ff65e
Packit 9ff65e
  {2 mkdir }
Packit 9ff65e
Packit 9ff65e
  *)
Packit 9ff65e
Packit 9ff65e
exception MkdirError of string
Packit 9ff65e
Packit 9ff65e
(** Possible mkdir errors. *)
Packit 9ff65e
type mkdir_error =
Packit 9ff65e
  [ `DirnameAlreadyUsed of filename
Packit 9ff65e
  | `Exc of exn
Packit 9ff65e
  | `MissingComponentPath of filename
Packit 9ff65e
  | `MkdirChmod of filename * Unix.file_perm * string * chmod_error ]
Packit 9ff65e
Packit 9ff65e
(** Create the directory which name is provided. Set [~parent] to true
Packit 9ff65e
    if you also want to create every directory of the path. Use mode to
Packit 9ff65e
    provide some specific right.
Packit 9ff65e
    See {{:http://pubs.opengroup.org/onlinepubs/007904875/utilities/mkdir.html}POSIX documentation}.
Packit 9ff65e
  *)
Packit 9ff65e
val mkdir:
Packit 9ff65e
  ?error:(mkdir_error error_handler) ->
Packit 9ff65e
  ?parent:bool ->
Packit 9ff65e
  ?mode:[< `Octal of Unix.file_perm | `Symbolic of FileUtilMode.t ] ->
Packit 9ff65e
  filename -> unit
Packit 9ff65e
Packit 9ff65e
(*********************************************************************)
Packit 9ff65e
(**
Packit 9ff65e
Packit 9ff65e
    {2 rm }
Packit 9ff65e
Packit 9ff65e
  *)
Packit 9ff65e
Packit 9ff65e
exception RmError of string
Packit 9ff65e
Packit 9ff65e
(** Possible rm errors. *)
Packit 9ff65e
type rm_error =
Packit 9ff65e
  [ `DirNotEmpty of filename
Packit 9ff65e
  | `Exc of exn
Packit 9ff65e
  | `NoRecurse of filename ]
Packit 9ff65e
Packit 9ff65e
(** Remove the filename provided. Set [~recurse] to true in order to
Packit 9ff65e
    completely delete a directory.
Packit 9ff65e
    See {{:http://pubs.opengroup.org/onlinepubs/007904875/utilities/rm.html}POSIX documentation}.
Packit 9ff65e
  *)
Packit 9ff65e
val rm:
Packit 9ff65e
  ?error:(rm_error error_handler) ->
Packit 9ff65e
  ?force:interactive -> ?recurse:bool -> filename list -> unit
Packit 9ff65e
Packit 9ff65e
(*********************************************************************)
Packit 9ff65e
(**
Packit 9ff65e
Packit 9ff65e
    {2 cp }
Packit 9ff65e
Packit 9ff65e
  *)
Packit 9ff65e
Packit 9ff65e
exception CpError of string
Packit 9ff65e
Packit 9ff65e
(** Possible cp errors. *)
Packit 9ff65e
type cp_error =
Packit 9ff65e
  [ `CannotChmodDstDir of filename * exn
Packit 9ff65e
  | `CannotCopyDir of filename
Packit 9ff65e
  | `CannotCopyFilesToFile of filename list * filename
Packit 9ff65e
  | `CannotCreateDir of filename * exn
Packit 9ff65e
  | `CannotListSrcDir of filename * exn
Packit 9ff65e
  | `CannotOpenDstFile of filename * exn
Packit 9ff65e
  | `CannotOpenSrcFile of filename * exn
Packit 9ff65e
  | `CannotRemoveDstFile of filename * exn
Packit 9ff65e
  | `DstDirNotDir of filename
Packit 9ff65e
  | `ErrorRead of filename * exn
Packit 9ff65e
  | `ErrorWrite of filename * exn
Packit 9ff65e
  | `Exc of exn
Packit 9ff65e
  | `NoSourceFile of filename
Packit 9ff65e
  | `PartialWrite of filename * int * int
Packit 9ff65e
  | `SameFile of filename * filename
Packit 9ff65e
  | `UnhandledType of filename * kind ]
Packit 9ff65e
Packit 9ff65e
(** Copy the hierarchy of files/directory to another destination.
Packit 9ff65e
    See {{:http://pubs.opengroup.org/onlinepubs/007904875/utilities/cp.html}POSIX documentation}.
Packit 9ff65e
  *)
Packit 9ff65e
val cp:
Packit 9ff65e
  ?follow:action_link ->
Packit 9ff65e
  ?force:interactive ->
Packit 9ff65e
  ?recurse:bool ->
Packit 9ff65e
  ?preserve:bool ->
Packit 9ff65e
  ?error:(cp_error error_handler) ->
Packit 9ff65e
  filename list -> filename -> unit
Packit 9ff65e
Packit 9ff65e
(*********************************************************************)
Packit 9ff65e
(**
Packit 9ff65e
Packit 9ff65e
    {2 mv }
Packit 9ff65e
Packit 9ff65e
  *)
Packit 9ff65e
Packit 9ff65e
exception MvError of string
Packit 9ff65e
Packit 9ff65e
(** Possible mv errors. *)
Packit 9ff65e
type mv_error =
Packit 9ff65e
  [ `Exc of exn
Packit 9ff65e
  | `MvCp of filename * filename * string * cp_error
Packit 9ff65e
  | `MvRm of  filename * string * rm_error
Packit 9ff65e
  | `NoSourceFile ]
Packit 9ff65e
Packit 9ff65e
(** Move files/directories to another destination.
Packit 9ff65e
    See {{:http://pubs.opengroup.org/onlinepubs/007904875/utilities/mv.html}POSIX documentation}.
Packit 9ff65e
  *)
Packit 9ff65e
val mv:
Packit 9ff65e
  ?error:(mv_error error_handler) ->
Packit 9ff65e
  ?force:interactive -> filename -> filename -> unit
Packit 9ff65e
Packit 9ff65e
Packit 9ff65e
(*********************************************************************)
Packit 9ff65e
(**
Packit 9ff65e
Packit 9ff65e
   {2 touch }
Packit 9ff65e
Packit 9ff65e
  *)
Packit 9ff65e
Packit 9ff65e
(** Time for file *)
Packit 9ff65e
type touch_time_t =
Packit 9ff65e
  | Touch_now                   (** Use Unix.gettimeofday *)
Packit 9ff65e
  | Touch_file_time of filename (** Get mtime of file *)
Packit 9ff65e
  | Touch_timestamp of float    (** Use GMT timestamp *)
Packit 9ff65e
Packit 9ff65e
Packit 9ff65e
(** Modify the timestamp of the given filename.
Packit 9ff65e
    See {{:http://pubs.opengroup.org/onlinepubs/007904875/utilities/touch.html}POSIX documentation}.
Packit 9ff65e
    If atime and mtime are not specified, they are both considered true. If only
Packit 9ff65e
    atime or mtime is sepcified, the other is false.
Packit 9ff65e
    @param atime  modify access time.
Packit 9ff65e
    @param mtime  modify modification time.
Packit 9ff65e
    @param create if file doesn't exist, create it, default true
Packit 9ff65e
    @param time   what time to set, default Touch_now
Packit 9ff65e
  *)
Packit 9ff65e
val touch:
Packit 9ff65e
  ?atime:bool ->
Packit 9ff65e
  ?mtime:bool ->
Packit 9ff65e
  ?create:bool -> ?time:touch_time_t -> filename -> unit
Packit 9ff65e
Packit 9ff65e
(*********************************************************************)
Packit 9ff65e
(**
Packit 9ff65e
Packit 9ff65e
   {2 ls }
Packit 9ff65e
Packit 9ff65e
  *)
Packit 9ff65e
Packit 9ff65e
(** Apply a filtering pattern to a filename.
Packit 9ff65e
  *)
Packit 9ff65e
val filter: test_file -> filename list -> filename list
Packit 9ff65e
Packit 9ff65e
(** List the content of a directory.
Packit 9ff65e
    See {{:http://pubs.opengroup.org/onlinepubs/007904875/utilities/ls.html}POSIX documentation}.
Packit 9ff65e
  *)
Packit 9ff65e
val ls: filename -> filename list
Packit 9ff65e
Packit 9ff65e
(*********************************************************************)
Packit 9ff65e
(**
Packit 9ff65e
Packit 9ff65e
  {2 Misc operations }
Packit 9ff65e
Packit 9ff65e
  *)
Packit 9ff65e
Packit 9ff65e
(** Return the current dir.
Packit 9ff65e
    See {{:http://pubs.opengroup.org/onlinepubs/007904875/utilities/pwd.html}POSIX documentation}.
Packit 9ff65e
  *)
Packit 9ff65e
val pwd: unit -> filename
Packit 9ff65e
Packit 9ff65e
(** Resolve to the real filename removing symlink.
Packit 9ff65e
    Non POSIX command.
Packit 9ff65e
  *)
Packit 9ff65e
val readlink: filename -> filename
Packit 9ff65e
Packit 9ff65e
(** Try to find the executable in the PATH. Use environement variable
Packit 9ff65e
    PATH if none is provided.
Packit 9ff65e
    Non POSIX command.
Packit 9ff65e
  *)
Packit 9ff65e
val which:
Packit 9ff65e
  ?path:filename list -> filename -> filename
Packit 9ff65e
Packit 9ff65e
(** [cmp skip1 fln1 skip2 fln2] Compare files [fln1] and [fln2] starting at pos
Packit 9ff65e
    [skip1] [skip2] and returning the first octect where a difference occurs.
Packit 9ff65e
    Returns [Some -1] if one of the file is not readable or if it is not a
Packit 9ff65e
    file.
Packit 9ff65e
    See {{:http://pubs.opengroup.org/onlinepubs/007904875/utilities/cmp.html}POSIX documentation}.
Packit 9ff65e
  *)
Packit 9ff65e
val cmp:
Packit 9ff65e
  ?skip1:int ->
Packit 9ff65e
  filename -> ?skip2:int -> filename -> int option
Packit 9ff65e
Packit 9ff65e
(** [du fln_lst] Return the amount of space of all the file
Packit 9ff65e
    which are subdir of fln_lst. Also return details for each
Packit 9ff65e
    file scanned.
Packit 9ff65e
    See {{:http://pubs.opengroup.org/onlinepubs/007904875/utilities/du.html}POSIX documentation}.
Packit 9ff65e
  *)
Packit 9ff65e
val du: filename list -> size * (filename * size) list
Packit 9ff65e
Packit 9ff65e
(** [find ~follow:fol tst fln exec accu] Descend the directory tree starting
Packit 9ff65e
    from the given filename and using the test provided. You cannot match
Packit 9ff65e
    [current_dir] and [parent_dir]. For every file found, the action [exec] is
Packit 9ff65e
    done, using the [accu] to start. For a simple file listing, you can use
Packit 9ff65e
    [find True "." (fun x y -> y :: x) []]
Packit 9ff65e
    See {{:http://pubs.opengroup.org/onlinepubs/007904875/utilities/find.html}POSIX documentation}.
Packit 9ff65e
  *)
Packit 9ff65e
val find:
Packit 9ff65e
  ?follow:action_link ->
Packit 9ff65e
  ?match_compile:(filename -> filename -> bool) ->
Packit 9ff65e
  test_file ->
Packit 9ff65e
  filename -> ('a -> filename -> 'a) -> 'a -> 'a
Packit 9ff65e
Packit 9ff65e
(** For future release:
Packit 9ff65e
- [val pathchk: filename -> boolean * string], check whether file names are
Packit 9ff65e
  valid or portable
Packit 9ff65e
- [val setfacl: filename -> permission -> unit], set file access control
Packit 9ff65e
  lists (UNIX + extended attribute)
Packit 9ff65e
- [val getfacl: filename -> permission], get file access control lists
Packit 9ff65e
Packit 9ff65e
ACL related function will be handled through a plugin system to handle at
Packit 9ff65e
runtime which attribute can be read/write (i.e. Win32 ACL, NFS acl, Linux ACL --
Packit 9ff65e
or none).
Packit 9ff65e
*)