summaryrefslogtreecommitdiffstats
path: root/erlang/examples
diff options
context:
space:
mode:
authorRichard W.M. Jones <rjones@redhat.com>2011-09-20 18:03:58 +0100
committerRichard W.M. Jones <rjones@redhat.com>2011-09-21 15:21:58 +0100
commit84763d7fca3668c62ee3fe53d0e00a5a672f687b (patch)
tree823b91a69e995438e4af670099408d3285a02176 /erlang/examples
parent917f947590c92318fee2545ba88245d0de012e31 (diff)
downloadlibguestfs-84763d7fca3668c62ee3fe53d0e00a5a672f687b.tar.gz
libguestfs-84763d7fca3668c62ee3fe53d0e00a5a672f687b.tar.xz
libguestfs-84763d7fca3668c62ee3fe53d0e00a5a672f687b.zip
Add Erlang bindings.
Diffstat (limited to 'erlang/examples')
-rw-r--r--erlang/examples/LICENSE2
-rw-r--r--erlang/examples/Makefile.am39
-rwxr-xr-xerlang/examples/create_disk.erl65
-rw-r--r--erlang/examples/guestfs-erlang.pod133
-rwxr-xr-xerlang/examples/inspect_vm.erl79
5 files changed, 318 insertions, 0 deletions
diff --git a/erlang/examples/LICENSE b/erlang/examples/LICENSE
new file mode 100644
index 00000000..555f04d2
--- /dev/null
+++ b/erlang/examples/LICENSE
@@ -0,0 +1,2 @@
+All the examples in the erlang/examples/ subdirectory may be freely
+copied without any restrictions.
diff --git a/erlang/examples/Makefile.am b/erlang/examples/Makefile.am
new file mode 100644
index 00000000..9fa82bb3
--- /dev/null
+++ b/erlang/examples/Makefile.am
@@ -0,0 +1,39 @@
+# libguestfs Erlang examples
+# Copyright (C) 2011 Red Hat Inc.
+#
+# This program is free software; you can redistribute it and/or modify
+# it under the terms of the GNU General Public License as published by
+# the Free Software Foundation; either version 2 of the License, or
+# (at your option) any later version.
+#
+# This program is distributed in the hope that it will be useful,
+# but WITHOUT ANY WARRANTY; without even the implied warranty of
+# MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
+# GNU General Public License for more details.
+#
+# You should have received a copy of the GNU General Public License
+# along with this program; if not, write to the Free Software
+# Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA.
+
+EXTRA_DIST = \
+ LICENSE \
+ create_disk.erl \
+ inspect_vm.erl \
+ guestfs-erlang.pod
+
+CLEANFILES = stamp-guestfs-erlang.pod
+
+man_MANS = guestfs-erlang.3
+noinst_DATA = $(top_builddir)/html/guestfs-erlang.3.html
+
+guestfs-erlang.3 $(top_builddir)/html/guestfs-erlang.3.html: stamp-guestfs-erlang.pod
+
+stamp-guestfs-erlang.pod: guestfs-erlang.pod create_disk.erl inspect_vm.erl
+ $(top_builddir)/podwrapper.sh \
+ --section 3 \
+ --man guestfs-erlang.3 \
+ --html $(top_builddir)/html/guestfs-erlang.3.html \
+ --verbatim $(srcdir)/create_disk.erl:@EXAMPLE1@ \
+ --verbatim $(srcdir)/inspect_vm.erl:@EXAMPLE2@ \
+ $<
+ touch $@
diff --git a/erlang/examples/create_disk.erl b/erlang/examples/create_disk.erl
new file mode 100755
index 00000000..231c3989
--- /dev/null
+++ b/erlang/examples/create_disk.erl
@@ -0,0 +1,65 @@
+#!/usr/bin/env escript
+%%! -smp enable -sname create_disk debug verbose
+% Example showing how to create a disk image.
+
+main(_) ->
+ Output = "disk.img",
+
+ {ok, G} = guestfs:create(),
+
+ % Create a raw-format sparse disk image, 512 MB in size.
+ {ok, File} = file:open(Output, [raw, write, binary]),
+ {ok, _} = file:position(File, 512 * 1024 * 1024 - 1),
+ ok = file:write(File, " "),
+ ok = file:close(File),
+
+ % Set the trace flag so that we can see each libguestfs call.
+ ok = guestfs:set_trace(G, true),
+
+ % Set the autosync flag so that the disk will be synchronized
+ % automatically when the libguestfs handle is closed.
+ ok = guestfs:set_autosync(G, true),
+
+ % Attach the disk image to libguestfs.
+ ok = guestfs:add_drive_opts(G, Output,
+ [{format, "raw"}, {readonly, false}]),
+
+ % Run the libguestfs back-end.
+ ok = guestfs:launch(G),
+
+ % Get the list of devices. Because we only added one drive
+ % above, we expect that this list should contain a single
+ % element.
+ [Device] = guestfs:list_devices(G),
+
+ % Partition the disk as one single MBR partition.
+ ok = guestfs:part_disk(G, Device, "mbr"),
+
+ % Get the list of partitions. We expect a single element, which
+ % is the partition we have just created.
+ [Partition] = guestfs:list_partitions(G),
+
+ % Create a filesystem on the partition.
+ ok = guestfs:mkfs(G, "ext4", Partition),
+
+ % Now mount the filesystem so that we can add files. *)
+ ok = guestfs:mount_options(G, "", Partition, "/"),
+
+ % Create some files and directories. *)
+ ok = guestfs:touch(G, "/empty"),
+ Message = "Hello, world\n",
+ ok = guestfs:write(G, "/hello", Message),
+ ok = guestfs:mkdir(G, "/foo"),
+
+ % This one uploads the local file /etc/resolv.conf into
+ % the disk image.
+ ok = guestfs:upload(G, "/etc/resolv.conf", "/foo/resolv.conf"),
+
+ % Because 'autosync' was set (above) we can just close the handle
+ % and the disk contents will be synchronized. You can also do
+ % this manually by calling guestfs:umount_all and guestfs:sync.
+ %
+ % Note also that handles are automatically closed if they are
+ % reaped by the garbage collector. You only need to call close
+ % if you want to close the handle right away.
+ ok = guestfs:close(G).
diff --git a/erlang/examples/guestfs-erlang.pod b/erlang/examples/guestfs-erlang.pod
new file mode 100644
index 00000000..8721318b
--- /dev/null
+++ b/erlang/examples/guestfs-erlang.pod
@@ -0,0 +1,133 @@
+=encoding utf8
+
+=head1 NAME
+
+guestfs-erlang - How to use libguestfs from Erlang
+
+=head1 SYNOPSIS
+
+ {ok, G} = guestfs:create(),
+ ok = guestfs:add_drive_opts(G, Disk,
+ [{format, "raw"}, {readonly, true}]),
+ ok = guestfs:launch(G),
+ [Device] = guestfs:list_devices(G),
+ ok = guestfs:close(G).
+
+=head1 DESCRIPTION
+
+This manual page documents how to call libguestfs from the Erlang
+programming language. This page just documents the differences from
+the C API and gives some examples. If you are not familiar with using
+libguestfs, you also need to read L<guestfs(3)>.
+
+=head2 OPENING AND CLOSING THE HANDLE
+
+The Erlang bindings are implemented using an external program called
+C<erl-guestfs>. This program must be on the current PATH, or else you
+should specify the full path to the program:
+
+ {ok, G} = guestfs:create().
+
+ {ok, G} = guestfs:create("/path/to/erl-guestfs").
+
+C<G> is the libguestfs handle which you should pass to other
+functions.
+
+To close the handle:
+
+ ok = guestfs:close(G).
+
+=head2 FUNCTIONS WITH OPTIONAL ARGUMENTS
+
+For functions that take optional arguments, the first arguments are
+the non-optional ones. The last argument is a list of tuples
+supplying the remaining optional arguments.
+
+ ok = guestfs:add_drive_opts(G, Disk,
+ [{format, "raw"}, {readonly, true}]).
+
+If the last argument would be an empty list, you can also omit it:
+
+ ok = guestfs:add_drive_opts(G, Disk).
+
+=head2 RETURN VALUES AND ERRORS
+
+On success, most functions return a C<Result> term (which could be a
+list, string, tuple etc.). If there is nothing for the function to
+return, then the atom C<ok> is returned.
+
+On error, you would see one of the following tuples:
+
+=over 4
+
+=item C<{error, Msg, Errno}>
+
+This indicates an ordinary error from the function.
+
+C<Msg> is the error message (string) and C<Errno> is the Unix error
+(integer).
+
+C<Errno> can be zero. See L<guestfs(3)/guestfs_last_errno>.
+
+=item C<{unknown, Function}>
+
+This indicates that the function you called is not known. Generally
+this means you are mixing C<erl-guestfs> from another version of
+libguestfs, which you should not do.
+
+C<Function> is the name of the unknown function.
+
+=item C<{unknownarg, Arg}>
+
+This indicates that you called a function with optional arguments,
+with an unknown argument name.
+
+C<Arg> is the name of the unknown argument.
+
+=back
+
+=head1 EXAMPLE 1: CREATE A DISK IMAGE
+
+@EXAMPLE1@
+
+=head1 EXAMPLE 2: INSPECT A VIRTUAL MACHINE DISK IMAGE
+
+@EXAMPLE2@
+
+=head1 SEE ALSO
+
+L<guestfs(3)>,
+L<guestfs-examples(3)>,
+L<guestfs-java(3)>,
+L<guestfs-ocaml(3)>,
+L<guestfs-perl(3)>,
+L<guestfs-python(3)>,
+L<guestfs-recipes(1)>,
+L<guestfs-ruby(3)>,
+L<http://www.erlang.org/>.
+L<http://libguestfs.org/>.
+
+=head1 AUTHORS
+
+Richard W.M. Jones (C<rjones at redhat dot com>)
+
+=head1 COPYRIGHT
+
+Copyright (C) 2011 Red Hat Inc. L<http://libguestfs.org/>
+
+The examples in this manual page may be freely copied, modified and
+distributed without any restrictions.
+
+This library is free software; you can redistribute it and/or
+modify it under the terms of the GNU Lesser General Public
+License as published by the Free Software Foundation; either
+version 2 of the License, or (at your option) any later version.
+
+This library is distributed in the hope that it will be useful,
+but WITHOUT ANY WARRANTY; without even the implied warranty of
+MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
+Lesser General Public License for more details.
+
+You should have received a copy of the GNU Lesser General Public
+License along with this library; if not, write to the Free Software
+Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA
diff --git a/erlang/examples/inspect_vm.erl b/erlang/examples/inspect_vm.erl
new file mode 100755
index 00000000..87d751ca
--- /dev/null
+++ b/erlang/examples/inspect_vm.erl
@@ -0,0 +1,79 @@
+#!/usr/bin/env escript
+%%! -smp enable -sname inspect_vm debug verbose
+% Example showing how to inspect a virtual machine disk.
+
+main([Disk]) ->
+ {ok, G} = guestfs:create(),
+
+ % Attach the disk image read-only to libguestfs.
+ ok = guestfs:add_drive_opts(G, Disk, [{readonly, true}]),
+
+ % Run the libguestfs back-end.
+ ok = guestfs:launch(G),
+
+ % Ask libguestfs to inspect for operating systems.
+ case guestfs:inspect_os(G) of
+ [] ->
+ io:fwrite("inspect_vm: no operating systems found~n"),
+ exit(no_operating_system);
+ Roots ->
+ list_os(G, Roots)
+ end.
+
+list_os(_, []) ->
+ ok;
+list_os(G, [Root|Roots]) ->
+ io:fwrite("Root device: ~s~n", [Root]),
+
+ % Print basic information about the operating system.
+ Product_name = guestfs:inspect_get_product_name(G, Root),
+ io:fwrite(" Product name: ~s~n", [Product_name]),
+ Major = guestfs:inspect_get_major_version(G, Root),
+ Minor = guestfs:inspect_get_minor_version(G, Root),
+ io:fwrite(" Version: ~w.~w~n", [Major, Minor]),
+ Type = guestfs:inspect_get_type(G, Root),
+ io:fwrite(" Type: ~s~n", [Type]),
+ Distro = guestfs:inspect_get_distro(G, Root),
+ io:fwrite(" Distro: ~s~n", [Distro]),
+
+ % Mount up the disks, like guestfish -i.
+ Mps = sort_mps(guestfs:inspect_get_mountpoints(G, Root)),
+ mount_mps(G, Mps),
+
+ % If /etc/issue.net file exists, print up to 3 lines. *)
+ Filename = "/etc/issue.net",
+ Is_file = guestfs:is_file(G, Filename),
+ if Is_file ->
+ io:fwrite("--- ~s ---~n", [Filename]),
+ Lines = guestfs:head_n(G, 3, Filename),
+ write_lines(Lines);
+ true -> ok
+ end,
+
+ % Unmount everything.
+ ok = guestfs:umount_all(G),
+
+ list_os(G, Roots).
+
+% Sort keys by length, shortest first, so that we end up
+% mounting the filesystems in the correct order.
+sort_mps(Mps) ->
+ Cmp = fun ({A,_}, {B,_}) ->
+ length(A) =< length(B) end,
+ lists:sort(Cmp, Mps).
+
+mount_mps(_, []) ->
+ ok;
+mount_mps(G, [{Mp, Dev}|Mps]) ->
+ case guestfs:mount_ro(G, Dev, Mp) of
+ ok -> ok;
+ { error, Msg, _ } ->
+ io:fwrite("~s (ignored)~n", [Msg])
+ end,
+ mount_mps(G, Mps).
+
+write_lines([]) ->
+ ok;
+write_lines([Line|Lines]) ->
+ io:fwrite("~s~n", [Line]),
+ write_lines(Lines).