Add .gitignore file for git.
[virt-df.git] / lib / diskimage_lvm2.ml
index f8ce5ec..7e58cc9 100644 (file)
@@ -3,19 +3,20 @@
    (C) Copyright 2007 Richard W.M. Jones, Red Hat Inc.
    http://libvirt.org/
 
-   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 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,
+   with the OCaml linking exception described in ../COPYING.LIB.
 
-   This program is distributed in the hope that it will be useful,
+   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 General Public License for more details.
+   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 General Public License
-   along with this program; if not, write to the Free Software
-   Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA.
+   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
 
    Support for LVM2 PVs.
 *)
 open Printf
 open ExtList
 
-open Diskimage_utils
+open Diskimage_impl
 open Diskimage_lvm2_metadata
 
-let plugin_name = "LVM2"
+open Int63.Operators
 
-let sector_size = 512
-let sector_size64 = 512L
+let id = "LVM2"
+
+let sector_size_int = 512
+let sector_size = ~^sector_size_int
+
+(*let attach_private_data, get_private_data =
+  private_data_functions (fun {lvm_cb = {lvm_cb_uq = u}} -> u)*)
 
 (*----------------------------------------------------------------------*)
 (* Block device which can do linear maps, same as the kernel dm-linear.c *)
@@ -48,52 +54,64 @@ class linear_map_device name extent_size segments =
    * satisfy any read request up to the full size.
    *)
   let size_in_extents =
-    List.fold_left max 0L
+    List.fold_left max ~^0
       (List.map (fun (_, end_extent, _, _) -> end_extent) segments) in
   let size = size_in_extents *^ extent_size in
-object
+object (self)
   inherit device
   method name = name
   method size = size
 
-  (* Read method checks which segment the request lies inside and
-   * maps it to the underlying device.  If there is no mapping then
-   * we have to return an error.
-   *
-   * The request must lie inside a single extent, otherwise this is
-   * also an error (XXX - should lift this restriction, however default
-   * extent size is 4 MB so we probably won't hit this very often).
+  (* The natural blocksize for LVM devices is the extent size.
+   * NB. Throws a runtime exception if the extent size is bigger
+   * than an int (only likely to matter on 32 bit).
    *)
-  method read offset len =
-    let offset_in_extents = offset /^ extent_size in
-
-    (* Check we don't cross an extent boundary. *)
-    if (offset +^ Int64.of_int (len-1)) /^ extent_size <> offset_in_extents
-    then invalid_arg "linear_map_device: request crosses extent boundary";
+  method blocksize = extent_size
 
-    if offset_in_extents < 0L || offset_in_extents >= size_in_extents then
+  method private map i =
+    if i < ~^0 || i >= size_in_extents then
       invalid_arg "linear_map_device: read outside device";
 
     let rec loop = function
       | [] ->
-         invalid_arg "linear_map_device: offset not mapped"
+         None
       | (start_extent, end_extent, dev, pvoffset) :: rest ->
-         if start_extent <= offset_in_extents &&
-            offset_in_extents < end_extent
-         then dev#read (offset +^ pvoffset *^ extent_size) len
-         else loop rest
+         if start_extent <= i && i < end_extent then (
+           let dev_offset = (pvoffset +^ i) *^ extent_size in
+           Some (start_extent, end_extent, dev, dev_offset, pvoffset)
+         ) else
+           loop rest
     in
     loop segments
+
+  (* Map block (extent) i to the underlying device. *)
+  method map_block i =
+    match self#map i with
+    | Some (_, _, dev, dev_offset, _) -> [dev, dev_offset]
+    | None -> []
+
+  (* Continguous span. *)
+  method contiguous offset =
+    let offset_in_extents = offset /^ extent_size in
+
+    (* Get the segment that this offset lies in. *)
+    match self#map offset_in_extents with
+    | Some (_, end_extent, dev, dev_offset, _) ->
+       (* Contiguous bytes up to the end of this extent. *)
+       end_extent *^ extent_size -^ offset
+    | None -> ~^0
+
+  (* NB. Use the superclass #read method. *)
 end
 
 (*----------------------------------------------------------------------*)
 (* Probe to see if it's an LVM2 PV. *)
-let rec probe_pv lvm_plugin_id dev =
+let rec probe dev =
   try
-    let uuid, _ = read_pv_label dev in
+    let uuid, _, _ = read_pv_label dev in
     if !debug then
       eprintf "LVM2 detected PV UUID %s\n%!" uuid;
-    { lvm_plugin_id = lvm_plugin_id; pv_uuid = uuid }
+    { pv_cb = callbacks (); pv_uuid = uuid; pv_dev = dev }
   with exn ->
     if !debug then prerr_endline (Printexc.to_string exn);
     raise Not_found
@@ -104,24 +122,22 @@ and read_pv_label dev =
    * the nineth sector contains some additional information about
    * the location of the current metadata.
    *)
-  let bits = dev#read_bitstring 0L (9 * sector_size) in
-
-  (*Bitmatch.hexdump_bitstring stdout bits;*)
+  let bits = dev#read_bitstring ~^0 (~^9 *^ sector_size) in
 
   bitmatch bits with
   | {
       (* sector 0 *)
-      sector0 : sector_size*8 : bitstring;
+      _ : sector_size_int*8 : bitstring;
 
       (* sector 1 *)
       "LABELONE" : 64 : string;                (* "LABELONE" *)
       _ : 128 : bitstring;             (* Seems to contain something. *)
       "LVM2 001" : 64 : string;                (* "LVM2 001" *)
-      uuid : 256 : string;             (* UUID *)
-      endsect : (sector_size-64)*8 : bitstring; (* to end of second sector *)
+      uuid : 256 : string;             (* PV UUID *)
+      _ : (sector_size_int-64)*8 : bitstring;(* to end of second sector *)
 
       (* sectors 2-7 *)
-      sectors234567 : sector_size*8 * 6 : bitstring;
+      _ : sector_size_int*8 * 6 : bitstring;
 
       (* sector 8 *)
       _ : 320 : bitstring;             (* start of sector 8 *)
@@ -131,64 +147,55 @@ and read_pv_label dev =
     } ->
 
       (* Metadata offset is relative to end of PV label. *)
-      let metadata_offset = metadata_offset +* 0x1000_l in
+      let metadata_offset = Int63.of_int32 metadata_offset +^ ~^0x1000 in
       (* Metadata length appears to include the trailing \000 which
-       * we don't want.
+       * we don't want, so subtract 1 to get the true length.
        *)
-      let metadata_length = metadata_length -* 1_l in
+      let metadata_length = Int63.of_int32 metadata_length -^ ~^1 in
 
-      let metadata = read_metadata dev metadata_offset metadata_length in
+      (* Check the metadata offset and length are sensible. *)
+      if metadata_offset <= ~^0x1200 || metadata_offset >= dev#size
+       || metadata_length <= ~^0
+       || metadata_offset +^ metadata_length >= dev#size then
+         invalid_arg "LVM2: read_metadata: bad metadata offset or length";
 
-      uuid, metadata
+      uuid, metadata_offset, metadata_length
 
   | { _ } ->
       invalid_arg
        (sprintf "LVM2: read_pv_label: %s: not an LVM2 physical volume"
           dev#name)
 
-and read_metadata dev offset32 len32 =
-  if !debug then
-    eprintf "metadata: offset 0x%lx len %ld bytes\n%!" offset32 len32;
-
-  (* Check the offset and length are sensible. *)
-  let offset64 =
-    if offset32 <= Int32.max_int then Int64.of_int32 offset32
-    else invalid_arg "LVM2: read_metadata: metadata offset too large" in
-  let len64 =
-    if len32 <= 2_147_483_647_l then Int64.of_int32 len32
-    else invalid_arg "LVM2: read_metadata: metadata length too large" in
-
-  if offset64 <= 0x1200L || offset64 >= dev#size
-    || len64 <= 0L || offset64 +^ len64 >= dev#size then
-      invalid_arg "LVM2: read_metadata: bad metadata offset or length";
-
-  (* If it is outside the disk boundaries, this will throw an exception,
-   * otherwise it will read and return the metadata string.
-   *)
-  dev#read offset64 (Int64.to_int len64)
-
 (*----------------------------------------------------------------------*)
 (* We are passed a list of devices which we previously identified
  * as PVs belonging to us.  From these produce a list of all LVs
  * (as devices) and return them.  Note that we don't try to detect
  * what is on these LVs - that will be done in the main code.
  *)
-let rec list_lvs devs =
-  (* Read the UUID and metadata (again) from each device to end up with
-   * an assoc list of PVs, keyed on the UUID.
+and list_lvs pvs =
+  (* Read the PV label (again) for each PV, and this time also
+   * read out the metadata, which is a big block of text.
    *)
-  let pvs = List.map (
-    fun dev ->
-      let uuid, metadata = read_pv_label dev in
+  let pvsmap = List.map (
+    fun { pv_dev = dev } ->
+      let uuid, metadata_offset, metadata_length = read_pv_label dev in
+      let metadata = dev#read metadata_offset metadata_length in
+
+      if !debug then
+       eprintf "list_lvs: metadata for PV %s (offset %s len %s):\n%s\n%!"
+         dev#name
+         (Int63.to_string metadata_offset) (Int63.to_string metadata_length)
+         metadata;
+
       (uuid, (metadata, dev))
-  ) devs in
+  ) pvs in
 
   (* Parse the metadata using the external lexer/parser. *)
-  let pvs = List.map (
+  let pvsmap = List.map (
     fun (uuid, (metadata, dev)) ->
       uuid, (Diskimage_lvm2_lexer.parse_lvm2_metadata_from_string metadata,
             dev)
-  ) pvs in
+  ) pvsmap in
 
   (* Print the parsed metadata. *)
   if !debug then
@@ -196,7 +203,7 @@ let rec list_lvs devs =
       fun (uuid, (metadata, dev)) ->
        eprintf "metadata for PV UUID %s on %s:\n" uuid dev#name;
        output_metadata stderr metadata
-    ) pvs;
+    ) pvsmap;
 
   (* Scan for volume groups.  The first entry in the metadata
    * appears to be the volume group name.  This gives us a
@@ -208,7 +215,7 @@ let rec list_lvs devs =
       | pvuuid, (((vgname, Metadata vgmeta) :: _), dev) ->
          Some (vgname, (pvuuid, vgmeta))
       | _ -> None
-    ) pvs in
+    ) pvsmap in
 
   let cmp ((a:string),_) ((b:string),_) = compare a b in
   let vgnames = List.sort ~cmp vgnames in
@@ -236,14 +243,13 @@ let rec list_lvs devs =
   (* Some useful getter functions.  If these can't get a value
    * from the metadata or if the type is wrong they raise Not_found.
    *)
-  let rec get_int64 field meta =
+  let rec get_int63 field meta =
     match List.assoc field meta with
     | Int i -> i
     | _ -> raise Not_found
-  and get_int field meta min max =
+  and get_int_bounded field meta max =
     match List.assoc field meta with
-    | Int i when Int64.of_int min <= i && i <= Int64.of_int max ->
-       Int64.to_int i
+    | Int i when i >= ~^0 && i <= Int63.of_int max -> Int63.to_int i
     | _ -> raise Not_found
   and get_string field meta =
     match List.assoc field meta with
@@ -281,8 +287,10 @@ let rec list_lvs devs =
       let pvdevs, extent_size =
        try
          (* NB: extent_size is in sectors here - we convert to bytes. *)
-         let extent_size = get_int "extent_size" vgmeta 0 (1024*1024) in
-         let extent_size = Int64.of_int extent_size *^ sector_size64 in
+         let extent_size =
+           get_int_bounded "extent_size" vgmeta (1024*1024) in
+         let extent_size = Int63.of_int extent_size in
+         let extent_size = extent_size *^ sector_size in
 
          (* Get the physical_volumes section of the metadata. *)
          let pvdevs = get_meta "physical_volumes" vgmeta in
@@ -295,14 +303,20 @@ let rec list_lvs devs =
                let pvuuid = canonical_uuid pvuuid in
 
                (* Get the underlying physical device. *)
-               let _, dev = List.assoc pvuuid pvs in
+               let _, dev = List.assoc pvuuid pvsmap in
 
                (* Construct a PV device. *)
-               let pe_start = get_int64 "pe_start" meta in
-               let pe_start = pe_start *^ sector_size64 in
-               let pe_count = get_int64 "pe_count" meta in
+               let pe_start = get_int63 "pe_start" meta in
+               let pe_start = pe_start *^ sector_size in
+               let pe_count = get_int63 "pe_count" meta in
                let pe_count = pe_count *^ extent_size in
-               let pvdev = new offset_device pvuuid pe_start pe_count dev in
+               let pvdev =
+                 new offset_device
+                   pvuuid (* name *)
+                   pe_start pe_count (* start, size in bytes *)
+                   (* don't really have a natural block size ... *)
+                   extent_size
+                   dev (* underlying device *) in
 
                Some (pvname, pvdev)
            | _ ->
@@ -310,7 +324,7 @@ let rec list_lvs devs =
          ) pvdevs, extent_size
        with
          (* Something went wrong - just return an empty map. *)
-         Not_found -> [], 0L in
+         Not_found -> [], ~^0 in
       (vgname, (pvuuids, vgmeta, pvdevs, extent_size))
   ) vgs in
 
@@ -327,7 +341,8 @@ let rec list_lvs devs =
            function
            | lvname, Metadata lvmeta ->
                (try
-                  let segment_count = get_int "segment_count" lvmeta 0 1024 in
+                  let segment_count =
+                    get_int_bounded "segment_count" lvmeta 1024 in
 
                   (* Get the segments for this LV. *)
                   let segments = range 1 (segment_count+1) in
@@ -340,9 +355,9 @@ let rec list_lvs devs =
                     List.map (
                       fun segmeta ->
                         let start_extent =
-                          get_int64 "start_extent" segmeta in
+                          get_int63 "start_extent" segmeta in
                         let extent_count =
-                          get_int64 "extent_count" segmeta in
+                          get_int63 "extent_count" segmeta in
                         let segtype = get_string "type" segmeta in
 
                         (* Can only handle striped segments at the
@@ -351,7 +366,7 @@ let rec list_lvs devs =
                         if segtype <> "striped" then raise Not_found;
 
                         let stripe_count =
-                          get_int "stripe_count" segmeta 0 1024 in
+                          get_int_bounded "stripe_count" segmeta 1024 in
                         let stripes = get_stripes "stripes" segmeta in
 
                         if List.length stripes <> stripe_count then
@@ -385,24 +400,29 @@ let rec list_lvs devs =
   if !debug then (
     List.iter (
       fun (vgname, (pvuuids, vgmeta, pvdevs, extent_size, lvs)) ->
-       eprintf "VG %s: (extent_size = %Ld bytes)\n" vgname extent_size;
+       eprintf "VG %s: (extent_size = %s bytes)\n" vgname
+         (Int63.to_string extent_size);
        List.iter (
          fun (lvname, segments) ->
            eprintf "  %s/%s:\n" vgname lvname;
            List.iter (
              fun (start_extent, extent_count, pvname, pvoffset) ->
-               eprintf "    start %Ld count %Ld at %s:%Ld\n"
-                 start_extent extent_count pvname pvoffset
+               eprintf "    start %s count %s at %s:%s\n"
+                 (Int63.to_string start_extent)
+                 (Int63.to_string extent_count)
+                 pvname (Int63.to_string pvoffset)
            ) segments
        ) lvs
     ) vgs;
     flush stderr
   );
 
+(*  List.iter (fun pv -> attach_private_data pv vgs) pvs; *)
+
   (* Finally we can set up devices for the LVs. *)
   let lvs =
     List.map (
-      fun (vgname, (pvuuid, vgmeta, pvdevs, extent_size, lvs)) ->
+      fun (vgname, (pvuuids, vgmeta, pvdevs, extent_size, lvs)) ->
        try
          List.map (
            fun (lvname, segments) ->
@@ -428,3 +448,20 @@ let rec list_lvs devs =
 
   (* Return the list of LV devices. *)
   lvs
+
+(* XXX We need to reparse the metadata in a different way in
+ * order to calculate this.  Need to generalize metadata handling.
+ *)
+and offset_is_free _ _ = false
+
+and callbacks =
+  let i = ref 0 in
+  fun () -> {
+    lvm_cb_uq = (incr i; !i);
+    lvm_cb_name = id;
+    lvm_cb_list_lvs = list_lvs;
+    lvm_cb_offset_is_free = offset_is_free;
+  }
+
+(* Register the plugin. *)
+let () = register_plugin ~lvm:probe id