1(* 2 * Copyright (C) 2006-2007 XenSource Ltd. 3 * Copyright (C) 2008 Citrix Ltd. 4 * Author Vincent Hanquez <vincent.hanquez@eu.citrix.com> 5 * 6 * This program is free software; you can redistribute it and/or modify 7 * it under the terms of the GNU Lesser General Public License as published 8 * by the Free Software Foundation; version 2.1 only. with the special 9 * exception on linking described in file LICENSE. 10 * 11 * This program is distributed in the hope that it will be useful, 12 * but WITHOUT ANY WARRANTY; without even the implied warranty of 13 * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the 14 * GNU Lesser General Public License for more details. 15 *) 16 17open Xenbus 18 19exception Partial_not_empty 20exception Unexpected_packet of string 21 22(** Thrown when a path looks invalid e.g. if it contains "//" *) 23exception Invalid_path of string 24 25let unexpected_packet expected received = 26 let s = Printf.sprintf "expecting %s received %s" 27 (Xb.Op.to_string expected) 28 (Xb.Op.to_string received) in 29 raise (Unexpected_packet s) 30 31type con = { 32 xb: Xenbus.Xb.t; 33 watchevents: (string * string) Queue.t; 34} 35 36let close con = 37 Xb.close con.xb 38 39let open_fd fd = { 40 xb = Xb.open_fd fd; 41 watchevents = Queue.create (); 42} 43 44let rec split_string ?limit:(limit=(-1)) c s = 45 let i = try String.index s c with Not_found -> -1 in 46 let nlimit = if limit = -1 || limit = 0 then limit else limit - 1 in 47 if i = -1 || nlimit = 0 then 48 [ s ] 49 else 50 let a = String.sub s 0 i 51 and b = String.sub s (i + 1) (String.length s - i - 1) in 52 a :: (split_string ~limit: nlimit c b) 53 54type perm = PERM_NONE | PERM_READ | PERM_WRITE | PERM_RDWR 55 56type perms = int * perm * (int * perm) list 57 58let string_of_perms perms = 59 let owner, other, acl = perms in 60 let char_of_perm perm = 61 match perm with PERM_NONE -> 'n' | PERM_READ -> 'r' 62 | PERM_WRITE -> 'w' | PERM_RDWR -> 'b' in 63 let string_of_perm (id, perm) = Printf.sprintf "%c%u" (char_of_perm perm) id in 64 String.concat "\000" (List.map string_of_perm ((owner,other) :: acl)) 65 66let perms_of_string s = 67 let perm_of_char c = 68 match c with 'n' -> PERM_NONE | 'r' -> PERM_READ 69 | 'w' -> PERM_WRITE | 'b' -> PERM_RDWR 70 | c -> invalid_arg (Printf.sprintf "unknown permission type: %c" c) in 71 let perm_of_string s = 72 if String.length s < 2 73 then invalid_arg (Printf.sprintf "perm of string: length = %d; contents=\"%s\"" (String.length s) s) 74 else 75 begin 76 int_of_string (String.sub s 1 (String.length s - 1)), 77 perm_of_char s.[0] 78 end in 79 let rec split s = 80 try let i = String.index s '\000' in 81 String.sub s 0 i :: split (String.sub s (i + 1) (String.length s - 1 - i)) 82 with Not_found -> if s = "" then [] else [ s ] in 83 let l = List.map perm_of_string (split s) in 84 match l with h :: l -> (fst h, snd h, l) | [] -> (0, PERM_NONE, []) 85 86(* send one packet - can sleep *) 87let pkt_send con = 88 if Xb.has_old_output con.xb then 89 raise Partial_not_empty; 90 let workdone = ref false in 91 while not !workdone 92 do 93 workdone := Xb.output con.xb 94 done 95 96(* receive one packet - can sleep *) 97let pkt_recv con = 98 let workdone = ref false in 99 while not !workdone 100 do 101 workdone := Xb.input con.xb 102 done; 103 Xb.get_in_packet con.xb 104 105let pkt_recv_timeout con timeout = 106 let fd = Xb.get_fd con.xb in 107 let r, _, _ = Unix.select [ fd ] [] [] timeout in 108 if r = [] then 109 true, None 110 else ( 111 let workdone = Xb.input con.xb in 112 if workdone then 113 false, (Some (Xb.get_in_packet con.xb)) 114 else 115 false, None 116 ) 117 118let queue_watchevent con data = 119 let ls = split_string ~limit:2 '\000' data in 120 if List.length ls != 2 then 121 raise (Xb.Packet.DataError "arguments number mismatch"); 122 let event = List.nth ls 0 123 and event_data = List.nth ls 1 in 124 Queue.push (event, event_data) con.watchevents 125 126let has_watchevents con = Queue.length con.watchevents > 0 127let get_watchevent con = Queue.pop con.watchevents 128 129let read_watchevent con = 130 let pkt = pkt_recv con in 131 match Xb.Packet.get_ty pkt with 132 | Xb.Op.Watchevent -> 133 queue_watchevent con (Xb.Packet.get_data pkt); 134 Queue.pop con.watchevents 135 | ty -> unexpected_packet Xb.Op.Watchevent ty 136 137(* send one packet in the queue, and wait for reply *) 138let rec sync_recv ty con = 139 let pkt = pkt_recv con in 140 match Xb.Packet.get_ty pkt with 141 | Xb.Op.Error -> ( 142 match Xb.Packet.get_data pkt with 143 | "ENOENT" -> raise Xb.Noent 144 | "EAGAIN" -> raise Xb.Eagain 145 | "EINVAL" -> raise Xb.Invalid 146 | s -> raise (Xb.Packet.Error s)) 147 | Xb.Op.Watchevent -> 148 queue_watchevent con (Xb.Packet.get_data pkt); 149 sync_recv ty con 150 | rty when rty = ty -> Xb.Packet.get_data pkt 151 | rty -> unexpected_packet ty rty 152 153let sync f con = 154 (* queue a query using function f *) 155 f con.xb; 156 if Xb.output_len con.xb = 0 then 157 Printf.printf "output len = 0\n%!"; 158 let ty = Xb.Packet.get_ty (Xb.peek_output con.xb) in 159 pkt_send con; 160 sync_recv ty con 161 162let ack s = 163 if s = "OK" then () else raise (Xb.Packet.DataError s) 164 165(** Check paths are suitable for read/write/mkdir/rm/directory etc (NOT watches) *) 166let validate_path path = 167 (* Paths shouldn't have a "//" in the middle *) 168 let bad = "//" in 169 for offset = 0 to String.length path - (String.length bad) do 170 if String.sub path offset (String.length bad) = bad then 171 raise (Invalid_path path) 172 done; 173 (* Paths shouldn't have a "/" at the end, except for the root *) 174 if path <> "/" && path <> "" && path.[String.length path - 1] = '/' then 175 raise (Invalid_path path) 176 177(** Check to see if a path is suitable for watches *) 178let validate_watch_path path = 179 (* Check for stuff like @releaseDomain etc first *) 180 if path <> "" && path.[0] = '@' then () 181 else validate_path path 182 183let debug command con = 184 sync (Queueop.debug command) con 185 186let directory tid path con = 187 validate_path path; 188 let data = sync (Queueop.directory tid path) con in 189 split_string '\000' data 190 191let read tid path con = 192 validate_path path; 193 sync (Queueop.read tid path) con 194 195let readv tid dir vec con = 196 List.map (fun path -> validate_path path; read tid path con) 197 (if dir <> "" then 198 (List.map (fun v -> dir ^ "/" ^ v) vec) else vec) 199 200let getperms tid path con = 201 validate_path path; 202 perms_of_string (sync (Queueop.getperms tid path) con) 203 204let watch path data con = 205 validate_watch_path path; 206 ack (sync (Queueop.watch path data) con) 207 208let unwatch path data con = 209 validate_watch_path path; 210 ack (sync (Queueop.unwatch path data) con) 211 212let transaction_start con = 213 let data = sync (Queueop.transaction_start) con in 214 try 215 int_of_string data 216 with 217 _ -> raise (Packet.DataError (Printf.sprintf "int expected; got '%s'" data)) 218 219let transaction_end tid commit con = 220 try 221 ack (sync (Queueop.transaction_end tid commit) con); 222 true 223 with 224 Xb.Eagain -> false 225 226let introduce domid mfn port con = 227 ack (sync (Queueop.introduce domid mfn port) con) 228 229let release domid con = 230 ack (sync (Queueop.release domid) con) 231 232let resume domid con = 233 ack (sync (Queueop.resume domid) con) 234 235let getdomainpath domid con = 236 sync (Queueop.getdomainpath domid) con 237 238let write tid path value con = 239 validate_path path; 240 ack (sync (Queueop.write tid path value) con) 241 242let writev tid dir vec con = 243 List.iter (fun (entry, value) -> 244 let path = (if dir <> "" then dir ^ "/" ^ entry else entry) in 245 validate_path path; 246 write tid path value con) vec 247 248let mkdir tid path con = 249 validate_path path; 250 ack (sync (Queueop.mkdir tid path) con) 251 252let rm tid path con = 253 validate_path path; 254 try 255 ack (sync (Queueop.rm tid path) con) 256 with 257 Xb.Noent -> () 258 259let setperms tid path perms con = 260 validate_path path; 261 ack (sync (Queueop.setperms tid path (string_of_perms perms)) con) 262 263let setpermsv tid dir vec perms con = 264 List.iter (fun entry -> 265 let path = (if dir <> "" then dir ^ "/" ^ entry else entry) in 266 validate_path path; 267 setperms tid path perms con) vec 268