~ubuntu-branches/ubuntu/quantal/xen-api/quantal

« back to all changes in this revision

Viewing changes to ocaml/xapi/xha_statefile.ml

  • Committer: Package Import Robot
  • Author(s): Jon Ludlam
  • Date: 2011-07-07 21:50:18 UTC
  • Revision ID: package-import@ubuntu.com-20110707215018-3t9ekbh7qy5y2b1p
Tags: upstream-1.3
ImportĀ upstreamĀ versionĀ 1.3

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
(*
 
2
 * Copyright (C) 2006-2009 Citrix Systems Inc.
 
3
 *
 
4
 * This program is free software; you can redistribute it and/or modify
 
5
 * it under the terms of the GNU Lesser General Public License as published
 
6
 * by the Free Software Foundation; version 2.1 only. with the special
 
7
 * exception on linking described in file LICENSE.
 
8
 *
 
9
 * This program is distributed in the hope that it will be useful,
 
10
 * but WITHOUT ANY WARRANTY; without even the implied warranty of
 
11
 * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
 
12
 * GNU Lesser General Public License for more details.
 
13
 *)
 
14
(** Manage the lifecycle of HA statefiles
 
15
 * @group High Availability (HA)
 
16
 *)
 
17
 
 
18
module D = Debug.Debugger(struct let name="xapi" end)
 
19
open D
 
20
 
 
21
(** Reason associated with the static VDI attach, to help identify these later *)
 
22
let reason = "HA statefile"
 
23
 
 
24
(** CA-17239: special signal to the backend to give us a raw block device (not not a vhd format thing, for example *)
 
25
let statefile_sm_config = [ "type", "raw" ]
 
26
 
 
27
open Client
 
28
open Listext
 
29
open Stringext
 
30
 
 
31
(** Return the minimum size of an HA statefile, as of
 
32
    XenServer HA state-file description vsn 1.3 *)
 
33
let minimum_size =
 
34
        let ( ** ) = Int64.mul
 
35
        and ( ++ ) = Int64.add in
 
36
 
 
37
        let global_section_size = 4096L
 
38
        and host_section_size = 4096L
 
39
  and maximum_number_of_hosts = 64L in
 
40
        global_section_size ++ maximum_number_of_hosts ** host_section_size
 
41
 
 
42
let set_difference a b = List.filter (fun x -> not(List.mem x b)) a
 
43
 
 
44
let assert_sr_can_host_statefile ~__context ~sr =
 
45
        (* Check that each host has a PBD to this SR *)
 
46
        let pbds = Db.SR.get_PBDs ~__context ~self:sr in
 
47
        let connected_hosts = List.setify (List.map (fun self -> Db.PBD.get_host ~__context ~self) pbds) in
 
48
        let all_hosts = Db.Host.get_all ~__context in
 
49
        if List.length connected_hosts < (List.length all_hosts) then begin
 
50
                error "Cannot place statefile in SR %s: some hosts lack a PBD: [ %s ]"
 
51
                        (Ref.string_of sr)
 
52
                        (String.concat "; " (List.map Ref.string_of (set_difference all_hosts connected_hosts)));
 
53
                raise (Api_errors.Server_error(Api_errors.sr_no_pbds, [ Ref.string_of sr ]))
 
54
        end;
 
55
        (* Check that each PBD is plugged in *)
 
56
        List.iter (fun self ->
 
57
                if not(Db.PBD.get_currently_attached ~__context ~self) then begin
 
58
                        error "Cannot place statefile in SR %s: PBD %s is not plugged"
 
59
                                (Ref.string_of sr) (Ref.string_of self);
 
60
                        (* Same exception is used in this case (see Helpers.assert_pbd_is_plugged) *)
 
61
                        raise (Api_errors.Server_error(Api_errors.sr_no_pbds, [ Ref.string_of sr ]))
 
62
                end) pbds;
 
63
        (* Check the exported capabilities of the SR's SM plugin *)
 
64
        let srtype = Db.SR.get_type ~__context ~self:sr in
 
65
        if not (List.mem Smint.Vdi_generate_config (Sm.capabilities_of_driver srtype))
 
66
        then raise (Api_errors.Server_error (Api_errors.sr_operation_not_supported, [Ref.string_of sr]))
 
67
 
 
68
let list_srs_which_can_host_statefile ~__context =
 
69
        List.filter (fun sr -> try assert_sr_can_host_statefile ~__context ~sr; true
 
70
        with _ -> false) (Db.SR.get_all ~__context)
 
71
 
 
72
let create ~__context ~sr =
 
73
        assert_sr_can_host_statefile ~__context ~sr;
 
74
        let size = minimum_size in
 
75
        Helpers.call_api_functions ~__context
 
76
                (fun rpc session_id ->
 
77
                        Client.VDI.create ~rpc ~session_id
 
78
                                ~name_label:"Statefile for HA"
 
79
                                ~name_description:"Used for storage heartbeating"
 
80
                                ~sR:sr ~virtual_size:size ~_type:`ha_statefile
 
81
                                ~sharable:true ~read_only:false ~other_config:[] ~xenstore_data:[] ~sm_config:statefile_sm_config ~tags:[]
 
82
                )
 
83
 
 
84
(** Return a reference to a valid statefile VDI in the given SR.
 
85
    This function prefers to reuse existing VDIs to avoid confusing the heartbeat component:
 
86
    it expects to see a poisoned VDI but not necessarily a stale or corrupted one. Consider that
 
87
    when using LVM-based SRs the VDI could be deleted on the master but the slaves would still
 
88
    have access to stale data. *)
 
89
let find_or_create ~__context ~sr =
 
90
        assert_sr_can_host_statefile ~__context ~sr;
 
91
        let size = minimum_size in
 
92
        match
 
93
                List.filter
 
94
                        (fun self -> true
 
95
                                && (Db.VDI.get_type ~__context ~self = `ha_statefile)
 
96
                                && (Db.VDI.get_virtual_size ~__context ~self >= size))
 
97
                        (Db.SR.get_VDIs ~__context ~self:sr) with
 
98
                                | x :: _ ->
 
99
                                        info "re-using existing statefile: %s" (Db.VDI.get_uuid ~__context ~self:x);
 
100
                                        x
 
101
                                | [] ->
 
102
                                        info "no suitable existing statefile found; creating a fresh one";
 
103
                                        create ~__context ~sr
 
104
 
 
105
let list_existing_statefiles () =
 
106
        List.filter (fun x -> x.Static_vdis.reason = reason) (Static_vdis.list ())
 
107
 
 
108
(** Detach all statefiles attached with reason 'HA statefile', to clear stale state *)
 
109
let detach_existing_statefiles ~__context =
 
110
        let statefile_uuids = List.map (fun vdi -> vdi.Static_vdis.uuid) (list_existing_statefiles ()) in
 
111
        List.iter (fun uuid -> Static_vdis.permanent_vdi_detach_by_uuid ~__context ~uuid) statefile_uuids
 
112
 
 
113
(** Added for CA-48539. Deactivate and detach all statefiles attached
 
114
        with reason 'HA statefile', to clear stale state *)
 
115
let deactivate_and_detach_existing_statefiles ~__context =
 
116
        let statefile_uuids = List.map (fun vdi -> vdi.Static_vdis.uuid) (list_existing_statefiles ()) in
 
117
        List.iter (fun uuid -> Static_vdis.permanent_vdi_deactivate_by_uuid ~__context ~uuid) statefile_uuids ;
 
118
        List.iter (fun uuid -> Static_vdis.permanent_vdi_detach_by_uuid ~__context ~uuid) statefile_uuids