forked from pool/libguestfs
		
	Accepting request 1281953 from Virtualization
Upstream patches to fix how BTRFS based images (SLES and openSUSE) are handled OBS-URL: https://build.opensuse.org/request/show/1281953 OBS-URL: https://build.opensuse.org/package/show/openSUSE:Factory/libguestfs?expand=0&rev=122
This commit is contained in:
		
							
								
								
									
										132
									
								
								004-Add-more-debugging-to-list_filesystems.patch
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										132
									
								
								004-Add-more-debugging-to-list_filesystems.patch
									
									
									
									
									
										Normal file
									
								
							@@ -0,0 +1,132 @@
 | 
			
		||||
Subject: daemon/listfs.ml: Add more debugging to list_filesystems
 | 
			
		||||
From: Richard W.M. Jones rjones@redhat.com Thu May 22 10:03:32 2025 +0100
 | 
			
		||||
Date: Tue May 27 17:01:09 2025 +0100:
 | 
			
		||||
Git: 7ac190ed20e7a2f8e664a4994e5508f050ed12e8
 | 
			
		||||
 | 
			
		||||
This function is used from other parts of the daemon, especially for
 | 
			
		||||
example with inspection.  However it was difficult to follow exactly
 | 
			
		||||
what filesystems it was returning because of insufficient debugging
 | 
			
		||||
information.
 | 
			
		||||
 | 
			
		||||
diff --git a/daemon/listfs.ml b/daemon/listfs.ml
 | 
			
		||||
index 0139e927d..4c90796ef 100644
 | 
			
		||||
--- a/daemon/listfs.ml
 | 
			
		||||
+++ b/daemon/listfs.ml
 | 
			
		||||
@@ -25,12 +25,17 @@ open Std_utils
 | 
			
		||||
  * contain filesystems, so we filter them out.
 | 
			
		||||
  *)
 | 
			
		||||
 let rec list_filesystems () =
 | 
			
		||||
+  if verbose () then
 | 
			
		||||
+    eprintf "list_filesystems: start\n";
 | 
			
		||||
+
 | 
			
		||||
   let has_lvm2 = Optgroups.lvm2_available () in
 | 
			
		||||
   let has_ldm = Optgroups.ldm_available () in
 | 
			
		||||
 
 | 
			
		||||
-  let ret = ref [] in
 | 
			
		||||
+  let ret : (Mountable.t * string) list ref = ref [] in
 | 
			
		||||
 
 | 
			
		||||
   (* Devices. *)
 | 
			
		||||
+  if verbose () then
 | 
			
		||||
+    eprintf "list_filesystems: checking for whole devices\n";
 | 
			
		||||
   let devices = Devsparts.list_devices () in
 | 
			
		||||
   let devices = List.filter is_not_partitioned_device devices in
 | 
			
		||||
   List.iter (check_with_vfs_type ret) devices;
 | 
			
		||||
@@ -39,32 +44,44 @@ let rec list_filesystems () =
 | 
			
		||||
    * We include these in case any encrypted devices contain
 | 
			
		||||
    * direct filesystems.
 | 
			
		||||
    *)
 | 
			
		||||
+  if verbose () then
 | 
			
		||||
+    eprintf "list_filesystems: checking for device-mapper devices\n";
 | 
			
		||||
   let devices = Lvm_dm.list_dm_devices () in
 | 
			
		||||
   let devices = List.filter is_not_partitioned_device devices in
 | 
			
		||||
   List.iter (check_with_vfs_type ret) devices;
 | 
			
		||||
 
 | 
			
		||||
   (* Partitions. *)
 | 
			
		||||
+  if verbose () then
 | 
			
		||||
+    eprintf "list_filesystems: checking for partitions\n";
 | 
			
		||||
   let partitions = Devsparts.list_partitions () in
 | 
			
		||||
   let partitions = List.filter is_partition_can_hold_filesystem partitions in
 | 
			
		||||
   List.iter (check_with_vfs_type ret) partitions;
 | 
			
		||||
 
 | 
			
		||||
   (* MD. *)
 | 
			
		||||
+  if verbose () then
 | 
			
		||||
+    eprintf "list_filesystems: checking for MD devices\n";
 | 
			
		||||
   let mds = Md.list_md_devices () in
 | 
			
		||||
   let mds = List.filter is_not_partitioned_device mds in
 | 
			
		||||
   List.iter (check_with_vfs_type ret) mds;
 | 
			
		||||
 
 | 
			
		||||
   (* LVM. *)
 | 
			
		||||
   if has_lvm2 then (
 | 
			
		||||
+    if verbose () then
 | 
			
		||||
+      eprintf "list_filesystems: checking for logical volumes\n";
 | 
			
		||||
     let lvs = Lvm.lvs () in
 | 
			
		||||
     List.iter (check_with_vfs_type ret) lvs
 | 
			
		||||
   );
 | 
			
		||||
 
 | 
			
		||||
   (* LDM. *)
 | 
			
		||||
   if has_ldm then (
 | 
			
		||||
+    if verbose () then
 | 
			
		||||
+      eprintf "list_filesystems: checking for LDM volumes\n";
 | 
			
		||||
     let ldmvols = Ldm.list_ldm_volumes () in
 | 
			
		||||
     List.iter (check_with_vfs_type ret) ldmvols
 | 
			
		||||
   );
 | 
			
		||||
 
 | 
			
		||||
+  if verbose () then
 | 
			
		||||
+    eprintf "list_filesystems: finished\n%!";
 | 
			
		||||
   !ret
 | 
			
		||||
 
 | 
			
		||||
 (* Look to see if device can directly contain filesystem (RHBZ#590167).
 | 
			
		||||
@@ -146,12 +163,15 @@ and check_with_vfs_type ret device =
 | 
			
		||||
     try Blkid.vfs_type mountable
 | 
			
		||||
     with exn ->
 | 
			
		||||
        if verbose () then
 | 
			
		||||
-         eprintf "check_with_vfs_type: %s: %s\n"
 | 
			
		||||
+         eprintf "list_filesystems: check_with_vfs_type: %s: %s\n"
 | 
			
		||||
                  device (Printexc.to_string exn);
 | 
			
		||||
        "" in
 | 
			
		||||
 
 | 
			
		||||
-  if vfs_type = "" then
 | 
			
		||||
-    List.push_back ret (mountable, "unknown")
 | 
			
		||||
+  if vfs_type = "" then (
 | 
			
		||||
+    let fs = mountable, "unknown" in
 | 
			
		||||
+    debug_one_fs fs;
 | 
			
		||||
+    List.push_back ret fs
 | 
			
		||||
+  )
 | 
			
		||||
 
 | 
			
		||||
   (* Ignore all "*_member" strings.  In libblkid these are returned
 | 
			
		||||
    * for things which are members of some RAID or LVM set, most
 | 
			
		||||
@@ -179,17 +199,30 @@ and check_with_vfs_type ret device =
 | 
			
		||||
       ) vols in
 | 
			
		||||
 
 | 
			
		||||
     (* whole device = default volume *)
 | 
			
		||||
-    List.push_back ret (mountable, vfs_type);
 | 
			
		||||
+    let fs = mountable, vfs_type in
 | 
			
		||||
+    debug_one_fs fs;
 | 
			
		||||
+    List.push_back ret fs;
 | 
			
		||||
 
 | 
			
		||||
     (* subvolumes *)
 | 
			
		||||
     List.push_back_list ret (
 | 
			
		||||
       List.map (
 | 
			
		||||
         fun { Structs.btrfssubvolume_path = path } ->
 | 
			
		||||
           let mountable = Mountable.of_btrfsvol device path in
 | 
			
		||||
-          (mountable, "btrfs")
 | 
			
		||||
+          let fs = mountable, "btrfs" in
 | 
			
		||||
+          debug_one_fs fs;
 | 
			
		||||
+          fs
 | 
			
		||||
       ) vols
 | 
			
		||||
     )
 | 
			
		||||
   )
 | 
			
		||||
 
 | 
			
		||||
-  else
 | 
			
		||||
-    List.push_back ret (mountable, vfs_type)
 | 
			
		||||
+  (* Otherwise it's some other VFS type. *)
 | 
			
		||||
+  else (
 | 
			
		||||
+    let fs = mountable, vfs_type in
 | 
			
		||||
+    debug_one_fs fs;
 | 
			
		||||
+    List.push_back ret fs
 | 
			
		||||
+  )
 | 
			
		||||
+
 | 
			
		||||
+and debug_one_fs (mountable, vfs_type) =
 | 
			
		||||
+  if verbose () then
 | 
			
		||||
+    eprintf "list_filesystems: adding %S, %S\n"
 | 
			
		||||
+      (Mountable.to_string mountable) vfs_type
 | 
			
		||||
							
								
								
									
										122
									
								
								005-Pipeline-style-when-mapping-and-filtering-filesystems.patch
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										122
									
								
								005-Pipeline-style-when-mapping-and-filtering-filesystems.patch
									
									
									
									
									
										Normal file
									
								
							@@ -0,0 +1,122 @@
 | 
			
		||||
Subject: daemon/inspect.ml: Pipeline style when mapping and filtering filesystems
 | 
			
		||||
From: Richard W.M. Jones rjones@redhat.com Sun May 25 09:29:18 2025 +0100
 | 
			
		||||
Date: Tue May 27 17:01:09 2025 +0100:
 | 
			
		||||
Git: b2ec671abd026fbe9fff94d48f51282df555b71d
 | 
			
		||||
 | 
			
		||||
No actual change in the functionality, just make it clear that this is
 | 
			
		||||
a pipeline of transformations on the list of filesystems.
 | 
			
		||||
 | 
			
		||||
diff --git a/daemon/inspect.ml b/daemon/inspect.ml
 | 
			
		||||
index 2c027b7c5..03174ef23 100644
 | 
			
		||||
--- a/daemon/inspect.ml
 | 
			
		||||
+++ b/daemon/inspect.ml
 | 
			
		||||
@@ -29,40 +29,43 @@ let re_primary_partition = PCRE.compile "^/dev/(?:h|s|v)d.[1234]$"
 | 
			
		||||
 let rec inspect_os () =
 | 
			
		||||
   Mount_utils.umount_all ();
 | 
			
		||||
 
 | 
			
		||||
-  (* Iterate over all detected filesystems.  Inspect each one in turn. *)
 | 
			
		||||
-  let fses = Listfs.list_filesystems () in
 | 
			
		||||
+  (* Start with the full list of filesystems, and inspect each one
 | 
			
		||||
+   * in turn to determine its possible role (root, /usr, homedir, etc.)
 | 
			
		||||
+   * Then we filter out duplicates and merge some filesystems into
 | 
			
		||||
+   * others.
 | 
			
		||||
+   *)
 | 
			
		||||
 
 | 
			
		||||
   let fses =
 | 
			
		||||
+    Listfs.list_filesystems () |>
 | 
			
		||||
+
 | 
			
		||||
+    (* Filter out those filesystems which are mountable, and inspect
 | 
			
		||||
+     * each one to find its possible role.  Converts the list to
 | 
			
		||||
+     * type: {!Inspect_types.fs} list.
 | 
			
		||||
+     *)
 | 
			
		||||
     List.filter_map (
 | 
			
		||||
       fun (mountable, vfs_type) ->
 | 
			
		||||
         Inspect_fs.check_for_filesystem_on mountable vfs_type
 | 
			
		||||
-  ) fses in
 | 
			
		||||
-  if verbose () then (
 | 
			
		||||
-    eprintf "inspect_os: fses:\n";
 | 
			
		||||
-    List.iter (fun fs -> eprintf "%s" (string_of_fs fs)) fses;
 | 
			
		||||
-    flush stderr
 | 
			
		||||
-  );
 | 
			
		||||
+    ) |>
 | 
			
		||||
 
 | 
			
		||||
-  (* The OS inspection information for CoreOS are gathered by inspecting
 | 
			
		||||
-   * multiple filesystems. Gather all the inspected information in the
 | 
			
		||||
-   * inspect_fs struct of the root filesystem.
 | 
			
		||||
-   *)
 | 
			
		||||
-  eprintf "inspect_os: collect_coreos_inspection_info\n%!";
 | 
			
		||||
-  let fses = collect_coreos_inspection_info fses in
 | 
			
		||||
+    debug_list_of_filesystems |>
 | 
			
		||||
 
 | 
			
		||||
-  (* Check if the same filesystem was listed twice as root in fses.
 | 
			
		||||
-   * This may happen for the *BSD root partition where an MBR partition
 | 
			
		||||
-   * is a shadow of the real root partition probably /dev/sda5
 | 
			
		||||
-   *)
 | 
			
		||||
-  eprintf "inspect_os: check_for_duplicated_bsd_root\n%!";
 | 
			
		||||
-  let fses = check_for_duplicated_bsd_root fses in
 | 
			
		||||
+    (* The OS inspection information for CoreOS are gathered by inspecting
 | 
			
		||||
+     * multiple filesystems. Gather all the inspected information in the
 | 
			
		||||
+     * inspect_fs struct of the root filesystem.
 | 
			
		||||
+     *)
 | 
			
		||||
+    collect_coreos_inspection_info |>
 | 
			
		||||
 
 | 
			
		||||
-  (* For Linux guests with a separate /usr filesystem, merge some of the
 | 
			
		||||
-   * inspected information in that partition to the inspect_fs struct
 | 
			
		||||
-   * of the root filesystem.
 | 
			
		||||
-   *)
 | 
			
		||||
-  eprintf "inspect_os: collect_linux_inspection_info\n%!";
 | 
			
		||||
-  let fses = collect_linux_inspection_info fses in
 | 
			
		||||
+    (* Check if the same filesystem was listed twice as root in fses.
 | 
			
		||||
+     * This may happen for the *BSD root partition where an MBR partition
 | 
			
		||||
+     * is a shadow of the real root partition probably /dev/sda5
 | 
			
		||||
+     *)
 | 
			
		||||
+    check_for_duplicated_bsd_root |>
 | 
			
		||||
+
 | 
			
		||||
+    (* For Linux guests with a separate /usr filesystem, merge some of the
 | 
			
		||||
+     * inspected information in that partition to the inspect_fs struct
 | 
			
		||||
+     * of the root filesystem.
 | 
			
		||||
+     *)
 | 
			
		||||
+    collect_linux_inspection_info in
 | 
			
		||||
 
 | 
			
		||||
   (* Save what we found in a global variable. *)
 | 
			
		||||
   Inspect_types.inspect_fses := fses;
 | 
			
		||||
@@ -75,11 +78,21 @@ let rec inspect_os () =
 | 
			
		||||
    *)
 | 
			
		||||
   inspect_get_roots ()
 | 
			
		||||
 
 | 
			
		||||
+and debug_list_of_filesystems fses =
 | 
			
		||||
+  if verbose () then (
 | 
			
		||||
+    eprintf "inspect_os: fses:\n";
 | 
			
		||||
+    List.iter (fun fs -> eprintf "%s" (string_of_fs fs)) fses;
 | 
			
		||||
+    flush stderr
 | 
			
		||||
+  );
 | 
			
		||||
+  fses
 | 
			
		||||
+
 | 
			
		||||
 (* Traverse through the filesystem list and find out if it contains
 | 
			
		||||
  * the [/] and [/usr] filesystems of a CoreOS image. If this is the
 | 
			
		||||
  * case, sum up all the collected information on the root fs.
 | 
			
		||||
  *)
 | 
			
		||||
 and collect_coreos_inspection_info fses =
 | 
			
		||||
+  eprintf "inspect_os: collect_coreos_inspection_info\n%!";
 | 
			
		||||
+
 | 
			
		||||
   (* Split the list into CoreOS root(s), CoreOS usr(s), and
 | 
			
		||||
    * everything else.
 | 
			
		||||
    *)
 | 
			
		||||
@@ -137,6 +150,8 @@ and collect_coreos_inspection_info fses =
 | 
			
		||||
  * [http://www.freebsd.org/doc/handbook/disk-organization.html])
 | 
			
		||||
  *)
 | 
			
		||||
 and check_for_duplicated_bsd_root fses =
 | 
			
		||||
+  eprintf "inspect_os: check_for_duplicated_bsd_root\n%!";
 | 
			
		||||
+
 | 
			
		||||
   try
 | 
			
		||||
     let is_primary_partition = function
 | 
			
		||||
       | { m_type = (MountablePath | MountableBtrfsVol _) } -> false
 | 
			
		||||
@@ -183,6 +198,8 @@ and check_for_duplicated_bsd_root fses =
 | 
			
		||||
  * root fs from the respective [/usr] filesystems.
 | 
			
		||||
  *)
 | 
			
		||||
 and collect_linux_inspection_info fses =
 | 
			
		||||
+  eprintf "inspect_os: collect_linux_inspection_info\n%!";
 | 
			
		||||
+
 | 
			
		||||
   List.map (
 | 
			
		||||
     function
 | 
			
		||||
     | { role = RoleRoot { distro = Some DISTRO_COREOS } } as root -> root
 | 
			
		||||
							
								
								
									
										92
									
								
								007-inspection-Ignore-btrfs-snapshots-of-roots.patch
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										92
									
								
								007-inspection-Ignore-btrfs-snapshots-of-roots.patch
									
									
									
									
									
										Normal file
									
								
							@@ -0,0 +1,92 @@
 | 
			
		||||
Subject: inspection: Ignore btrfs snapshots of roots
 | 
			
		||||
From: Richard W.M. Jones rjones@redhat.com Thu May 22 11:32:11 2025 +0100
 | 
			
		||||
Date: Tue May 27 17:01:09 2025 +0100:
 | 
			
		||||
Git: 8f5e4f07ba92d42506072520260d96ce77d58e21
 | 
			
		||||
 | 
			
		||||
In SLES guests in particular, btrfs snapshots seem to be used to allow
 | 
			
		||||
rollback of changes made to the filesystem.  Dozens of snapshots may
 | 
			
		||||
be present.  Technically therefore these are multi-boot guests.  The
 | 
			
		||||
libguestfs concept of "root" of an operating system does not map well
 | 
			
		||||
to this, causing problems in virt-inspector and virt-v2v.
 | 
			
		||||
 | 
			
		||||
In this commit we ignore these duplicates.  The test is quite narrow
 | 
			
		||||
to avoid false positives: We only remove a duplicate if it is a member
 | 
			
		||||
of a parent device, both are btrfs, both the snapshot and parent have
 | 
			
		||||
a root role, and the roles are otherwise very similar.
 | 
			
		||||
 | 
			
		||||
There may be a case for reporting this information separately in
 | 
			
		||||
future, although it's also easy to find this out now.  For example,
 | 
			
		||||
when you see a btrfs root device returned by inspect_os, you could
 | 
			
		||||
call btrfs_subvolume_list on the root device to list the snapshots.
 | 
			
		||||
 | 
			
		||||
Fixes: https://issues.redhat.com/browse/RHEL-93109
 | 
			
		||||
 | 
			
		||||
diff --git a/daemon/inspect.ml b/daemon/inspect.ml
 | 
			
		||||
index 5c6be3193..84571f582 100644
 | 
			
		||||
--- a/daemon/inspect.ml
 | 
			
		||||
+++ b/daemon/inspect.ml
 | 
			
		||||
@@ -61,6 +61,11 @@ let rec inspect_os () =
 | 
			
		||||
      *)
 | 
			
		||||
     check_for_duplicated_bsd_root |>
 | 
			
		||||
 
 | 
			
		||||
+    (* Check if the root filesystems are duplicated by btrfs snapshots.
 | 
			
		||||
+     * This happens especially for SLES guests.
 | 
			
		||||
+     *)
 | 
			
		||||
+    check_for_duplicated_btrfs_snapshots_of_root |>
 | 
			
		||||
+
 | 
			
		||||
     (* For Linux guests with a separate /usr filesystem, merge some of the
 | 
			
		||||
      * inspected information in that partition to the inspect_fs struct
 | 
			
		||||
      * of the root filesystem.
 | 
			
		||||
@@ -190,6 +195,52 @@ and check_for_duplicated_bsd_root fses =
 | 
			
		||||
   with
 | 
			
		||||
     Not_found -> fses
 | 
			
		||||
 
 | 
			
		||||
+(* Check for the case where the root filesystem gets duplicated by
 | 
			
		||||
+ * btrfs snapshots.  Ignore the snapshots in this case (RHEL-93109).
 | 
			
		||||
+ *)
 | 
			
		||||
+and check_for_duplicated_btrfs_snapshots_of_root fses =
 | 
			
		||||
+  eprintf "inspect_os: check_for_duplicated_btrfs_snapshots_of_root\n%!";
 | 
			
		||||
+
 | 
			
		||||
+  let fs_is_btrfs_snapshot_of_root = function
 | 
			
		||||
+    (* Is this filesystem a btrfs snapshot of root? *)
 | 
			
		||||
+    | { fs_location =
 | 
			
		||||
+          { mountable = { m_type = MountableBtrfsVol _; m_device = dev1 };
 | 
			
		||||
+            vfs_type = "btrfs" };
 | 
			
		||||
+        role = RoleRoot inspection_data1 } as fs1 ->
 | 
			
		||||
+       (* Return true if it duplicates the parent device which has
 | 
			
		||||
+        * a root role.
 | 
			
		||||
+        *)
 | 
			
		||||
+       List.exists (function
 | 
			
		||||
+         | { fs_location =
 | 
			
		||||
+               { mountable = { m_type = MountableDevice; m_device = dev2 };
 | 
			
		||||
+                 vfs_type = "btrfs" };
 | 
			
		||||
+             role = RoleRoot inspection_data2 }
 | 
			
		||||
+              when dev1 = dev2 ->
 | 
			
		||||
+            (* Check the roles are similar enough.  In my test I saw
 | 
			
		||||
+             * that /etc/fstab was slightly different in the parent
 | 
			
		||||
+             * and snapshot.  It's possible this is because the snapshot
 | 
			
		||||
+             * was created during installation, but it's not clear.
 | 
			
		||||
+             *)
 | 
			
		||||
+            let similar =
 | 
			
		||||
+              inspection_data1.os_type = inspection_data2.os_type &&
 | 
			
		||||
+              inspection_data1.distro = inspection_data2.distro &&
 | 
			
		||||
+              inspection_data1.product_name = inspection_data2.product_name &&
 | 
			
		||||
+              inspection_data1.version = inspection_data2.version in
 | 
			
		||||
+            if verbose () && similar then
 | 
			
		||||
+              eprintf "check_for_duplicated_btrfs_snapshots_of_root: \
 | 
			
		||||
+                       dropping duplicate btrfs snapshot:\n%s\n"
 | 
			
		||||
+                (string_of_fs fs1);
 | 
			
		||||
+            similar
 | 
			
		||||
+         | _ -> false
 | 
			
		||||
+       ) fses
 | 
			
		||||
+
 | 
			
		||||
+    (* Anything else is not a snapshot. *)
 | 
			
		||||
+    | _ -> false
 | 
			
		||||
+  in
 | 
			
		||||
+
 | 
			
		||||
+  (* Filter out the duplicates. *)
 | 
			
		||||
+  List.filter (Fun.negate fs_is_btrfs_snapshot_of_root) fses
 | 
			
		||||
+
 | 
			
		||||
 (* Traverse through the filesystem list and find out if it contains
 | 
			
		||||
  * the [/] and [/usr] filesystems of a Linux image (but not CoreOS,
 | 
			
		||||
  * for which there is a separate [collect_coreos_inspection_info]).
 | 
			
		||||
@@ -1,3 +1,13 @@
 | 
			
		||||
-------------------------------------------------------------------
 | 
			
		||||
Wed May 28 09:50:06 MDT 2025 - carnold@suse.com
 | 
			
		||||
 | 
			
		||||
- Upstream bug fix for BTRFS based images (SLES and openSUSE)
 | 
			
		||||
  004-Add-more-debugging-to-list_filesystems.patch
 | 
			
		||||
  005-Pipeline-style-when-mapping-and-filtering-filesystems.patch
 | 
			
		||||
  007-inspection-Ignore-btrfs-snapshots-of-roots.patch
 | 
			
		||||
- Adjustment to use fusermount3 when fuse3 is required by distro.
 | 
			
		||||
  use-fuse3-for-build.patch
 | 
			
		||||
 | 
			
		||||
-------------------------------------------------------------------
 | 
			
		||||
Tue May 27 08:43:54 MDT 2025 - carnold@suse.com
 | 
			
		||||
 | 
			
		||||
 
 | 
			
		||||
@@ -33,6 +33,9 @@ Source101:      README
 | 
			
		||||
 | 
			
		||||
# Patches
 | 
			
		||||
Patch1:         use-rtc-driftfix-slew-for-x86-only.patch
 | 
			
		||||
Patch2:         004-Add-more-debugging-to-list_filesystems.patch
 | 
			
		||||
Patch3:         005-Pipeline-style-when-mapping-and-filtering-filesystems.patch
 | 
			
		||||
Patch4:         007-inspection-Ignore-btrfs-snapshots-of-roots.patch
 | 
			
		||||
Patch100:       use-fuse3-for-build.patch
 | 
			
		||||
 | 
			
		||||
BuildRequires:  bison
 | 
			
		||||
 
 | 
			
		||||
@@ -2,10 +2,10 @@ References: bsc#1242082 - libguestfs: migration to fuse 3 and
 | 
			
		||||
            deprecation of fuse (1)
 | 
			
		||||
See also spec file changes to use fuse3
 | 
			
		||||
 | 
			
		||||
Index: libguestfs-1.55.10/m4/guestfs-fuse.m4
 | 
			
		||||
Index: libguestfs-1.55.13/m4/guestfs-fuse.m4
 | 
			
		||||
===================================================================
 | 
			
		||||
--- libguestfs-1.55.10.orig/m4/guestfs-fuse.m4
 | 
			
		||||
+++ libguestfs-1.55.10/m4/guestfs-fuse.m4
 | 
			
		||||
--- libguestfs-1.55.13.orig/m4/guestfs-fuse.m4
 | 
			
		||||
+++ libguestfs-1.55.13/m4/guestfs-fuse.m4
 | 
			
		||||
@@ -21,7 +21,7 @@ AC_ARG_ENABLE([fuse],
 | 
			
		||||
     [],
 | 
			
		||||
     [enable_fuse=yes])
 | 
			
		||||
@@ -15,10 +15,10 @@ Index: libguestfs-1.55.10/m4/guestfs-fuse.m4
 | 
			
		||||
         AC_SUBST([FUSE_CFLAGS])
 | 
			
		||||
         AC_SUBST([FUSE_LIBS])
 | 
			
		||||
         AC_DEFINE([HAVE_FUSE],[1],[Define to 1 if you have FUSE.])
 | 
			
		||||
Index: libguestfs-1.55.10/lib/fuse.c
 | 
			
		||||
Index: libguestfs-1.55.13/lib/fuse.c
 | 
			
		||||
===================================================================
 | 
			
		||||
--- libguestfs-1.55.10.orig/lib/fuse.c
 | 
			
		||||
+++ libguestfs-1.55.10/lib/fuse.c
 | 
			
		||||
--- libguestfs-1.55.13.orig/lib/fuse.c
 | 
			
		||||
+++ libguestfs-1.55.13/lib/fuse.c
 | 
			
		||||
@@ -40,7 +40,7 @@
 | 
			
		||||
 #define ENOATTR ENODATA
 | 
			
		||||
 #endif
 | 
			
		||||
@@ -163,10 +163,10 @@ Index: libguestfs-1.55.10/lib/fuse.c
 | 
			
		||||
     fuse_opt_free_args (&args);
 | 
			
		||||
     guestfs_int_free_fuse (g);
 | 
			
		||||
     return -1;
 | 
			
		||||
Index: libguestfs-1.55.10/fuse/guestmount.c
 | 
			
		||||
Index: libguestfs-1.55.13/fuse/guestmount.c
 | 
			
		||||
===================================================================
 | 
			
		||||
--- libguestfs-1.55.10.orig/fuse/guestmount.c
 | 
			
		||||
+++ libguestfs-1.55.10/fuse/guestmount.c
 | 
			
		||||
--- libguestfs-1.55.13.orig/fuse/guestmount.c
 | 
			
		||||
+++ libguestfs-1.55.13/fuse/guestmount.c
 | 
			
		||||
@@ -16,7 +16,7 @@
 | 
			
		||||
  * Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
 | 
			
		||||
  */
 | 
			
		||||
@@ -176,3 +176,34 @@ Index: libguestfs-1.55.10/fuse/guestmount.c
 | 
			
		||||
 
 | 
			
		||||
 #include <config.h>
 | 
			
		||||
 
 | 
			
		||||
Index: libguestfs-1.55.13/fuse/guestunmount.c
 | 
			
		||||
===================================================================
 | 
			
		||||
--- libguestfs-1.55.13.orig/fuse/guestunmount.c
 | 
			
		||||
+++ libguestfs-1.55.13/fuse/guestunmount.c
 | 
			
		||||
@@ -241,7 +241,7 @@ do_fusermount (const char *mountpoint, c
 | 
			
		||||
     error (EXIT_FAILURE, errno, "pipe");
 | 
			
		||||
 
 | 
			
		||||
   if (verbose)
 | 
			
		||||
-    fprintf (stderr, "%s: running: fusermount -u %s\n",
 | 
			
		||||
+    fprintf (stderr, "%s: running: fusermount3 -u %s\n",
 | 
			
		||||
              getprogname (), mountpoint);
 | 
			
		||||
 
 | 
			
		||||
   pid = fork ();
 | 
			
		||||
@@ -258,7 +258,7 @@ do_fusermount (const char *mountpoint, c
 | 
			
		||||
     setenv ("LC_ALL", "C", 1);
 | 
			
		||||
 
 | 
			
		||||
 #ifdef __linux__
 | 
			
		||||
-    execlp ("fusermount", "fusermount", "-u", mountpoint, NULL);
 | 
			
		||||
+    execlp ("fusermount3", "fusermount3", "-u", mountpoint, NULL);
 | 
			
		||||
 #else
 | 
			
		||||
     /* use umount where fusermount is not available */
 | 
			
		||||
     execlp ("umount", "umount", mountpoint, NULL);
 | 
			
		||||
@@ -316,7 +316,7 @@ do_fusermount (const char *mountpoint, c
 | 
			
		||||
   }
 | 
			
		||||
 
 | 
			
		||||
   if (verbose)
 | 
			
		||||
-    fprintf (stderr, "%s: fusermount successful\n",
 | 
			
		||||
+    fprintf (stderr, "%s: fusermount3 successful\n",
 | 
			
		||||
              getprogname ());
 | 
			
		||||
 
 | 
			
		||||
   free (buf);
 | 
			
		||||
 
 | 
			
		||||
		Reference in New Issue
	
	Block a user