Module Opendal.Operator

OpenDAL OCaml Bindings

Apache OpenDAL™ OCaml binding provides a unified data access layer that allows users to easily and efficiently retrieve data from various storage services.

Basic Usage

  (* Create an operator for local filesystem *)
  let op =
    Operator.new_operator "fs" [ ("root", "/tmp") ] |> Result.get_ok
  in

  (* Write data to a file *)
  let _ = Operator.write op "hello.txt" (Bytes.of_string "Hello, World!") in

  (* Read data back *)
  let content = Operator.read op "hello.txt" |> Result.get_ok in
  print_endline (String.of_bytes content)

Core Operations

val new_operator : string -> (string * string) list -> (Opendal_core.Operator.operator, string) Stdlib.result

new_operator scheme config_map creates a new blocking operator from given scheme and configuration.

  • parameter scheme

    The storage service scheme. Supported services include:

    • "fs" for local filesystem
    • "s3" for Amazon S3
    • "gcs" for Google Cloud Storage
    • "azblob" for Azure Blob Storage
    • And many more. See the full list.
  • parameter config_map

    Configuration key-value pairs required by the target service. For example, for S3: ("bucket", "my-bucket"); ("region", "us-east-1")

  • returns

    A blocking operator wrapped in Result.

@example

  (* Local filesystem *)
  let fs_op = new_operator "fs" [("root", "/tmp")] in
  
  (* S3 storage *)
  let s3_op = new_operator "s3" [
    ("bucket", "my-bucket");
    ("region", "us-east-1");
    ("access_key_id", "...");
    ("secret_access_key", "...")
  ] in
val list : Opendal_core.Operator.operator -> string -> (Opendal_core.Operator.entry array, string) Stdlib.result

list operator path lists all entries in the given directory path.

  • parameter operator

    The blocking operator

  • parameter path

    Directory path to list (should end with "/")

  • returns

    Array of directory entries

Note: This loads all entries into memory. For large directories, consider using lister for streaming access.

@example

  match list op "data/" with
  | Ok entries -> 
      Array.iter (fun entry -> 
        printf "Found: %s\n" (Entry.name entry)
      ) entries
  | Error err -> printf "Error: %s\n" err
val lister : Opendal_core.Operator.operator -> string -> (Opendal_core.Operator.lister, string) Stdlib.result

lister operator path creates a streaming lister for the given directory.

  • parameter operator

    The blocking operator

  • parameter path

    Directory path to list (should end with "/")

  • returns

    A lister for streaming access to entries

Use Lister.next to iterate through entries one by one. This is memory-efficient for large directories.

@example

  match lister op "data/" with
  | Ok lst ->
      let rec iter () =
        match Lister.next lst with
        | Ok (Some entry) -> 
            printf "Found: %s\n" (Entry.name entry);
            iter ()
        | Ok None -> () (* End of listing *)
        | Error err -> printf "Error: %s\n" err
      in iter ()
  | Error err -> printf "Error: %s\n" err
val stat : Opendal_core.Operator.operator -> string -> (Opendal_core.Operator.metadata, string) Stdlib.result

stat operator path gets metadata for the given path.

  • parameter operator

    The blocking operator

  • parameter path

    Path to get metadata for

  • returns

    Metadata for the path

@example

  match stat op "file.txt" with
  | Ok meta ->
      printf "Size: %Ld bytes\n" (Metadata.content_length meta);
      printf "Is file: %b\n" (Metadata.is_file meta)
  | Error err -> printf "Error: %s\n" err
val is_exist : Opendal_core.Operator.operator -> string -> (bool, string) Stdlib.result

is_exist operator path checks if the given path exists.

  • parameter operator

    The blocking operator

  • parameter path

    Path to check

  • returns

    true if path exists, false otherwise

@example

  match is_exist op "file.txt" with
  | Ok true -> print_endline "File exists"
  | Ok false -> print_endline "File does not exist"  
  | Error err -> printf "Error: %s\n" err
val create_dir : Opendal_core.Operator.operator -> string -> (bool, string) Stdlib.result

create_dir operator path creates a directory at the given path.

  • parameter operator

    The blocking operator

  • parameter path

    Directory path to create (must end with "/")

Notes:

  • Creating existing directories succeeds
  • Creates parent directories recursively (like "mkdir -p")
  • Path must end with "/" to indicate it's a directory

@example

  match create_dir op "data/subdir/" with
  | Ok () -> print_endline "Directory created"
  | Error err -> printf "Error: %s\n" err
val read : Opendal_core.Operator.operator -> string -> (char array, string) Stdlib.result

read operator path reads the entire file content into memory.

  • parameter operator

    The blocking operator

  • parameter path

    File path to read

  • returns

    File content as a char array

For large files or streaming access, consider using reader.

@example

  match read op "file.txt" with
  | Ok content -> 
      let bytes = Array.to_seq content |> Bytes.of_seq in
      print_endline (Bytes.to_string bytes)
  | Error err -> printf "Error: %s\n" err
val reader : Opendal_core.Operator.operator -> string -> (Opendal_core.Operator.reader, string) Stdlib.result

reader operator path creates a reader for streaming file access.

  • parameter operator

    The blocking operator

  • parameter path

    File path to read

  • returns

    A reader for streaming access

Use Reader.pread to read data from specific positions.

@example

  match reader op "file.txt" with
  | Ok r ->
      let buf = Bytes.create 1024 in
      (match Reader.pread r buf 0L with
       | Ok bytes_read -> printf "Read %d bytes\n" bytes_read
       | Error err -> printf "Error: %s\n" err)
  | Error err -> printf "Error: %s\n" err
val write : Opendal_core.Operator.operator -> string -> bytes -> (unit, string) Stdlib.result

write operator path data writes data to the given path.

  • parameter operator

    The blocking operator

  • parameter path

    File path to write to

  • parameter data

    Data to write

Notes:

  • Overwrites existing files
  • Creates parent directories if needed
  • Ensures all data is written atomically

@example

  let data = Bytes.of_string "Hello, World!" in
  match write op "hello.txt" data with
  | Ok () -> print_endline "File written"
  | Error err -> printf "Error: %s\n" err
val writer : Opendal_core.Operator.operator -> string -> (Opendal_core.Operator.writer, string) Stdlib.result

writer operator path creates a writer for streaming file writes.

  • parameter operator

    The blocking operator

  • parameter path

    File path to write to

  • returns

    A writer for streaming writes

Use Writer.write to write data chunks and Writer.close to finalize.

@example

  match writer op "large_file.txt" with
  | Ok w ->
      let _ = Writer.write w (Bytes.of_string "chunk1") in
      let _ = Writer.write w (Bytes.of_string "chunk2") in
      Writer.close w
  | Error err -> printf "Error: %s\n" err
val copy : Opendal_core.Operator.operator -> string -> string -> (unit, string) Stdlib.result

copy operator from to copies a file from source to destination.

  • parameter operator

    The blocking operator

  • parameter from

    Source file path

  • parameter to

    Destination file path

Notes:

  • Overwrites destination if it exists
  • Creates parent directories if needed
  • Both paths must be files (not directories)

@example

  match copy op "source.txt" "backup.txt" with
  | Ok () -> print_endline "File copied"
  | Error err -> printf "Error: %s\n" err
val rename : Opendal_core.Operator.operator -> string -> string -> (unit, string) Stdlib.result

rename operator from to renames/moves a file from source to destination.

  • parameter operator

    The blocking operator

  • parameter from

    Source file path

  • parameter to

    Destination file path

Notes:

  • Overwrites destination if it exists
  • Creates parent directories if needed
  • Source file is removed after successful operation

@example

  match rename op "old_name.txt" "new_name.txt" with
  | Ok () -> print_endline "File renamed"
  | Error err -> printf "Error: %s\n" err
val delete : Opendal_core.Operator.operator -> string -> (unit, string) Stdlib.result

delete operator path deletes the file at the given path.

  • parameter operator

    The blocking operator

  • parameter path

    File path to delete

Notes:

  • Succeeds even if file doesn't exist (idempotent)
  • Cannot be used to delete directories (use remove_all instead)

@example

  match delete op "unwanted.txt" with
  | Ok () -> print_endline "File deleted"
  | Error err -> printf "Error: %s\n" err
val remove : Opendal_core.Operator.operator -> string array -> (unit, string) Stdlib.result

remove operator paths deletes multiple files in a batch operation.

  • parameter operator

    The blocking operator

  • parameter paths

    Array of file paths to delete

This is more efficient than calling delete multiple times for services that support batch deletion.

@example

  let files = [|"file1.txt"; "file2.txt"; "file3.txt"|] in
  match remove op files with
  | Ok () -> print_endline "Files deleted"
  | Error err -> printf "Error: %s\n" err
val remove_all : Opendal_core.Operator.operator -> string -> (unit, string) Stdlib.result

remove_all operator path recursively deletes the directory and all its contents.

  • parameter operator

    The blocking operator

  • parameter path

    Directory path to delete (should end with "/")

⚠️ WARNING: This operation permanently deletes all files and subdirectories. Use with extreme caution!

@example

  match remove_all op "temp_data/" with
  | Ok () -> print_endline "Directory deleted"
  | Error err -> printf "Error: %s\n" err
val check : Opendal_core.Operator.operator -> (unit, string) Stdlib.result

check operator performs a health check on the storage service.

  • parameter operator

    The blocking operator

This verifies that the operator can connect to and access the configured storage service.

@example

  match check op with
  | Ok () -> print_endline "Storage service is accessible"
  | Error err -> printf "Error: %s\n" err

info operator returns information about the operator.

  • parameter operator

    The blocking operator

  • returns

    Operator information (name, scheme, root path, capabilities)

@example

  let info = info op in
  printf "Service: %s\n" (OperatorInfo.name info);
  printf "Scheme: %s\n" (OperatorInfo.scheme info);
  printf "Root: %s\n" (OperatorInfo.root info)
module Reader : sig ... end
module Writer : sig ... end
module Lister : sig ... end
module Metadata : sig ... end
module Entry : sig ... end
module OperatorInfo : sig ... end
module Capability : sig ... end