@@ -47,52 +47,123 @@ let vgs_offline =
4747 )
4848 )
4949
50- let lvchange_offline =
51- " lvchange vg/lv --offline: check that we can activate volumes offline" > ::
52- fun () ->
53- with_temp_file (fun filename' ->
54- with_loop_device filename' (fun loop ->
55- xenvm [ " vgcreate" ; vg; loop ] |> ignore_string;
50+ let with_xenvmd ?existing_vg ?(cleanup_vg =true ) (f : string -> 'a ) =
51+ let with_xenvmd_running loop =
5652 xenvm [ " set-vg-info" ; " --pvpath" ; loop; " -S" ; " /tmp/xenvmd" ; vg; " --local-allocator-path" ; " /tmp/xenvm-local-allocator" ; " --uri" ; " file://local/services/xenvmd/" ^ vg ] |> ignore_string;
5753 file_of_string " test.xenvmd.conf" (" ( (listenPort ()) (listenPath (Some \" /tmp/xenvmd\" )) (host_allocation_quantum 128) (host_low_water_mark 8) (vg " ^ vg^ " ) (devices (" ^ loop^ " )))" );
5854 xenvmd [ " --config" ; " ./test.xenvmd.conf" ; " --daemon" ] |> ignore_string;
5955 Xenvm_client.Rpc. uri := " file://local/services/xenvmd/" ^ vg;
6056 Xenvm_client. unix_domain_socket_path := " /tmp/xenvmd" ;
61- let name = Uuid. (to_string (create () )) in
6257 finally
63- (fun () ->
64- xenvm [ " lvcreate" ; " -n" ; name; " -L" ; " 3" ; vg ] |> ignore_string;
65- ) (fun () ->
66- xenvm [ " shutdown" ; " /dev/" ^ vg ] |> ignore_string
67- );
68- xenvm [ " lvchange" ; " -ay" ; vg ^ " /" ^ name; " --offline" ] |> ignore_string;
58+ (fun () -> f vg)
59+ (fun () -> xenvm [ " shutdown" ; " /dev/" ^ vg ] |> ignore_string) in
60+ match existing_vg with
61+ | Some path -> with_xenvmd_running path
62+ | None ->
63+ with_temp_file ~delete: cleanup_vg (fun filename ->
64+ with_loop_device filename (fun loop ->
65+ xenvm [ " vgcreate" ; vg; loop ] |> ignore_string;
66+ with_xenvmd_running loop
67+ )
6968 )
70- )
69+
70+ let lvchange_offline =
71+ " lvchange vg/lv --offline: check that we can activate volumes offline" > ::
72+ fun () ->
73+ let name = Uuid. (to_string (create () )) in
74+ with_xenvmd ~cleanup_vg: false (fun vg ->
75+ xenvm [ " lvcreate" ; " -n" ; name; " -L" ; " 3" ; vg ] |> ignore_string);
76+ xenvm [ " lvchange" ; " -ay" ; vg ^ " /" ^ name; " --offline" ] |> ignore_string
7177
7278let pvremove =
7379 " pvremove <device>: check that we can make a PV unrecognisable" > ::
7480 (fun () ->
7581 with_temp_file (fun filename ->
7682 xenvm [ " vgcreate" ; vg; filename ] |> ignore_string;
77- mkdir_rec " /tmp/xenvm.d" 0o0755 ;
78- xenvm [ " set-vg-info" ; " --pvpath" ; filename; " -S" ; " /tmp/xenvmd" ; vg; " --local-allocator-path" ; " /tmp/xenvm-local-allocator" ; " --uri" ; " file://local/services/xenvmd/" ^ vg ] |> ignore_string;
7983 xenvm [ " vgs" ; vg ] |> ignore_string;
8084 xenvm [ " pvremove" ; filename ] |> ignore_string;
81- begin
82- try
83- xenvm [ " vgs" ; vg ] |> ignore_string;
84- failwith " pvremove failed to hide a VG from vgs"
85- with Bad_exit (1 , _ , _ , _ , _ ) ->
86- ()
87- end
85+ try
86+ xenvm [ " vgs" ; vg ] |> ignore_string;
87+ failwith " pvremove failed to hide a VG from vgs"
88+ with Bad_exit (1 , _ , _ , _ , _ ) -> ()
8889 )
8990 )
9091
92+ let upgrade =
93+ " Check that we can upgrade an LVM volume to XenVM" > :: fun () ->
94+ with_temp_file (fun filename ->
95+ let t =
96+ with_block filename (fun block ->
97+ Result. get_ok (Pv.Name. of_string " pv0" ) |> fun pv ->
98+ Vg_IO. format ~magic: `Lvm " vg" [ pv, block ] >> |= fun () ->
99+ Vg_IO. connect ~flush_interval: 0. [ block ] `RW >> |= fun vg ->
100+ (* there should be no LVs on this (not even a redo log) *)
101+ assert_equal ~msg: " Formated volume (LVM magic) has non-zero LV count"
102+ ~printer: string_of_int 0 (LVs. cardinal (Vg_IO. metadata_of vg).Vg. lvs);
103+ (* create a couple of LVs *)
104+ let lv0 = (Uuid. (to_string (create () )), Int64. (10L * mib)) in
105+ let lv1 = (Uuid. (to_string (create () )), Int64. (20L * mib)) in
106+ Lwt_list. iter_p (fun (name , size ) ->
107+ Vg. create (Vg_IO. metadata_of vg) name size >> *= fun (_ , op ) ->
108+ Vg_IO. update vg [ op ] >> |= fun () ->
109+ Vg_IO. sync vg >> |= fun () ->
110+ return ()
111+ ) [ lv0; lv1 ] >> = fun () ->
112+ (* check that these LVs are there *)
113+ assert_equal ~msg: " Unexpected number of LVs on LVM volume"
114+ ~printer: string_of_int 2 (LVs. cardinal (Vg_IO. metadata_of vg).Vg. lvs);
115+
116+ (* Upgrade the volume to journalled *)
117+ xenvm [ " upgrade" ; " vg" ] |> ignore_string;
118+ (* Check it's idempotent *)
119+ xenvm [ " upgrade" ; " vg" ] |> ignore_string;
120+
121+ (* check the changing of the magic persisted *)
122+ let module Label_IO = Label. Make (Block ) in
123+ let (>>:=) m f = m >> = function `Ok x -> f x | `Error (`Msg e ) -> fail (Failure e) in
124+ Label_IO. read block >>:= fun label ->
125+ assert_equal ~msg: " PV label was not as expected after upgrade"
126+ ~printer: (function None -> " " | Some m -> Sexplib.Sexp. to_string_hum (Magic. sexp_of_t m))
127+ (Some `Journalled ) Label. (Label_header. magic_of label.label_header);
128+ (* Check we now have 1 more volume than before (the redo log) *)
129+ Vg_IO. connect ~flush_interval: 0. [ block ] `RO >> |= fun vg ->
130+ assert_equal ~msg: " Unexpected number of LVs on LVM after upgrade"
131+ ~printer: string_of_int 3 (LVs. cardinal (Vg_IO. metadata_of vg).Vg. lvs);
132+ (* Check xenvmd is happy to connect *)
133+ with_xenvmd ~existing_vg: filename (fun vg ->
134+ let lv_count =
135+ xenvm [ " vgs" ; " /dev/" ^ vg; " --noheadings" ; " -o" ; " lv_count" ]
136+ |> String. trim |> int_of_string in
137+ assert_equal ~msg: " Xenvmd reported wrong number of LVs"
138+ ~printer: string_of_int 3 lv_count;
139+ xenvm [ " lvs" ; " /dev/" ^ vg ] |> ignore_string;
140+ );
141+
142+ (* Downgrade the volume to lvm2 *)
143+ xenvm [ " downgrade" ; " vg" ] |> ignore_string;
144+ (* Check it's idempotent *)
145+ xenvm [ " downgrade" ; " vg" ] |> ignore_string;
146+
147+ (* check the changing of the magic persisted *)
148+ Label_IO. read block >>:= fun label ->
149+ assert_equal ~msg: " PV label was not as expected after downgrade"
150+ ~printer: (function None -> " " | Some m -> Sexplib.Sexp. to_string_hum (Magic. sexp_of_t m))
151+ (Some `Lvm ) Label. (Label_header. magic_of label.label_header);
152+ (* Check we now have 1 more volume than before (the redo log) *)
153+ Vg_IO. connect ~flush_interval: 0. [ block ] `RO >> |= fun vg ->
154+ assert_equal ~msg: " Unexpected number of LVs on LVM after downgrade"
155+ ~printer: string_of_int 2 (LVs. cardinal (Vg_IO. metadata_of vg).Vg. lvs);
156+ return ()
157+ ) in
158+ Lwt_main. run t
159+ )
160+
91161let no_xenvmd_suite = " Commands which should work without xenvmd" > ::: [
92162 vgcreate;
93163 vgs_offline;
94164 lvchange_offline;
95165 pvremove;
166+ upgrade;
96167]
97168
98169let assert_lv_exists ?expected_size_in_extents name =
@@ -145,8 +216,8 @@ let lvcreate_percent =
145216let kib = 1024L
146217let mib = Int64. mul kib 1024L
147218let gib = Int64. mul mib 1024L
148- let tib = Int64. mul mib 1024L
149- let xib = Int64. mul tib 1024L
219+ let tib = Int64. mul gib 1024L
220+ let pib = Int64. mul tib 1024L
150221
151222let contains s1 s2 =
152223 let re = Str. regexp_string s2 in
@@ -160,21 +231,21 @@ let lvcreate_toobig =
160231 fun () ->
161232 Lwt_main. run (
162233 Lwt. catch
163- (fun () -> Client. create " toobig" xib " unknown" 0L [] )
234+ (fun () -> Client. create " toobig" tib " unknown" 0L [] )
164235 (function Xenvm_interface. Insufficient_free_space (needed , available ) -> return ()
165236 | e -> failwith (Printf. sprintf " Did not get Insufficient_free_space: %s" (Printexc. to_string e)))
166237 );
167238 try
168239 let name = Uuid. (to_string (create () )) in
169- xenvm [ " lvcreate" ; " -n" ; name; " -l" ; Int64. to_string xib ; vg ] |> ignore_string;
240+ xenvm [ " lvcreate" ; " -n" ; name; " -l" ; Int64. to_string tib ; vg ] |> ignore_string;
170241 failwith " Did not get Insufficient_free_space"
171242 with
172243 | Bad_exit (5 , _ , _ , stdout , stderr ) ->
173244 let expected = " insufficient free space" in
174245 if not (contains stderr expected)
175246 then failwith (Printf. sprintf " stderr [%s] did not have expected string [%s]" stderr expected)
176- | _ ->
177- failwith " Expected exit code 5"
247+ | e ->
248+ failwith ( Printf. sprintf " Expected exit code 5; got exception: %s " ( Printexc. to_string e))
178249
179250let lvextend_toobig =
180251 " lvextend packer-virtualbox-iso-vg/swap_1 -L 1T: check that the failure is nice" > ::
@@ -184,12 +255,12 @@ let lvextend_toobig =
184255 begin
185256 Lwt_main. run (
186257 Lwt. catch
187- (fun () -> Client. resize name xib )
258+ (fun () -> Client. resize name tib )
188259 (function Xenvm_interface. Insufficient_free_space (needed , available ) -> return ()
189260 | e -> failwith (Printf. sprintf " Did not get Insufficient_free_space: %s" (Printexc. to_string e)))
190261 );
191262 try
192- xenvm [ " lvextend" ; vg ^ " /" ^ name; " -L" ; Int64. to_string xib ] |> ignore_string;
263+ xenvm [ " lvextend" ; vg ^ " /" ^ name; " -L" ; Int64. to_string tib ] |> ignore_string;
193264 failwith " Did not get Insufficient_free_space"
194265 with
195266 | Bad_exit (5 , _ , _ , stdout , stderr ) ->
@@ -297,21 +368,10 @@ let xenvmd_suite = "Commands which require xenvmd" >::: [
297368]
298369
299370let _ =
371+ Random. self_init () ;
300372 mkdir_rec " /tmp/xenvm.d" 0o0755 ;
301- run_test_tt_main no_xenvmd_suite |> ignore;
302- with_temp_file (fun filename' ->
303- with_loop_device filename' (fun loop ->
304- xenvm [ " vgcreate" ; vg; loop ] |> ignore_string;
305- xenvm [ " set-vg-info" ; " --pvpath" ; loop; " -S" ; " /tmp/xenvmd" ; vg; " --local-allocator-path" ; " /tmp/xenvm-local-allocator" ; " --uri" ; " file://local/services/xenvmd/" ^ vg ] |> ignore_string;
306- file_of_string " test.xenvmd.conf" (" ( (listenPort ()) (listenPath (Some \" /tmp/xenvmd\" )) (host_allocation_quantum 128) (host_low_water_mark 8) (vg " ^ vg^ " ) (devices (" ^ loop^ " )))" );
307- xenvmd [ " --config" ; " ./test.xenvmd.conf" ; " --daemon" ] |> ignore_string;
308- Xenvm_client.Rpc. uri := " file://local/services/xenvmd/" ^ vg;
309- Xenvm_client. unix_domain_socket_path := " /tmp/xenvmd" ;
310- finally
311- (fun () ->
312- run_test_tt_main xenvmd_suite |> ignore;
313- ) (fun () ->
314- xenvm [ " shutdown" ; " /dev/" ^ vg ] |> ignore_string
315- )
316- )
317- )
373+ let check_results_with_exit_code results =
374+ if List. exists (function RFailure _ | RError _ -> true | _ -> false ) results
375+ then exit 1 in
376+ run_test_tt_main no_xenvmd_suite |> check_results_with_exit_code;
377+ with_xenvmd (fun _ -> run_test_tt_main xenvmd_suite |> check_results_with_exit_code);
0 commit comments