sig
  module Defined :
    sig
      type t = [ `Added | `Unknown of int | `Updated ]
      val to_string : Libvirt.Event.Defined.t -> string
    end
  module Undefined :
    sig
      type t = [ `Removed | `Unknown of int ]
      val to_string : Libvirt.Event.Undefined.t -> string
    end
  module Started :
    sig
      type t =
          [ `Booted
          | `FromSnapshot
          | `Migrated
          | `Restored
          | `Unknown of int
          | `Wakeup ]
      val to_string : Libvirt.Event.Started.t -> string
    end
  module Suspended :
    sig
      type t =
          [ `APIError
          | `FromSnapshot
          | `IOError
          | `Migrated
          | `Paused
          | `Restored
          | `Unknown of int
          | `Watchdog ]
      val to_string : Libvirt.Event.Suspended.t -> string
    end
  module Resumed :
    sig
      type t = [ `FromSnapshot | `Migrated | `Unknown of int | `Unpaused ]
      val to_string : Libvirt.Event.Resumed.t -> string
    end
  module Stopped :
    sig
      type t =
          [ `Crashed
          | `Destroyed
          | `Failed
          | `FromSnapshot
          | `Migrated
          | `Saved
          | `Shutdown
          | `Unknown of int ]
      val to_string : Libvirt.Event.Stopped.t -> string
    end
  module PM_suspended :
    sig
      type t = [ `Disk | `Memory | `Unknown of int ]
      val to_string : Libvirt.Event.PM_suspended.t -> string
    end
  module Lifecycle :
    sig
      type t =
          [ `Defined of Libvirt.Event.Defined.t
          | `PMSuspended of Libvirt.Event.PM_suspended.t
          | `Resumed of Libvirt.Event.Resumed.t
          | `Shutdown
          | `Started of Libvirt.Event.Started.t
          | `Stopped of Libvirt.Event.Stopped.t
          | `Suspended of Libvirt.Event.Suspended.t
          | `Undefined of Libvirt.Event.Undefined.t
          | `Unknown of int ]
      val to_string : Libvirt.Event.Lifecycle.t -> string
    end
  module Reboot :
    sig type t = unit val to_string : Libvirt.Event.Reboot.t -> string end
  module Rtc_change :
    sig
      type t = int64
      val to_string : Libvirt.Event.Rtc_change.t -> string
    end
  module Watchdog :
    sig
      type t =
          [ `Debug
          | `None
          | `Pause
          | `Poweroff
          | `Reset
          | `Shutdown
          | `Unknown of int ]
      val to_string : Libvirt.Event.Watchdog.t -> string
    end
  module Io_error :
    sig
      type action = [ `None | `Pause | `Report | `Unknown of int ]
      type t = {
        src_path : string option;
        dev_alias : string option;
        action : Libvirt.Event.Io_error.action;
        reason : string option;
      }
      val to_string : Libvirt.Event.Io_error.t -> string
    end
  module Graphics_address :
    sig
      type family = [ `Ipv4 | `Ipv6 | `Unix | `Unknown of int ]
      type t = {
        family : Libvirt.Event.Graphics_address.family;
        node : string option;
        service : string option;
      }
      val to_string : Libvirt.Event.Graphics_address.t -> string
    end
  module Graphics_subject :
    sig
      type identity = { ty : string option; name : string option; }
      type t = Libvirt.Event.Graphics_subject.identity list
      val to_string : Libvirt.Event.Graphics_subject.t -> string
    end
  module Graphics :
    sig
      type phase = [ `Connect | `Disconnect | `Initialize | `Unknown of int ]
      type t = {
        phase : Libvirt.Event.Graphics.phase;
        local : Libvirt.Event.Graphics_address.t;
        remote : Libvirt.Event.Graphics_address.t;
        auth_scheme : string option;
        subject : Libvirt.Event.Graphics_subject.t;
      }
      val to_string : Libvirt.Event.Graphics.t -> string
    end
  module Control_error :
    sig
      type t = unit
      val to_string : Libvirt.Event.Control_error.t -> string
    end
  module Block_job :
    sig
      type ty = [ `Commit | `Copy | `KnownUnknown | `Pull | `Unknown of int ]
      type status =
          [ `Cancelled | `Completed | `Failed | `Ready | `Unknown of int ]
      type t = {
        disk : string option;
        ty : Libvirt.Event.Block_job.ty;
        status : Libvirt.Event.Block_job.status;
      }
      val to_string : Libvirt.Event.Block_job.t -> string
    end
  module Disk_change :
    sig
      type reason = [ `MissingOnStart | `Unknown of int ]
      type t = {
        old_src_path : string option;
        new_src_path : string option;
        dev_alias : string option;
        reason : Libvirt.Event.Disk_change.reason;
      }
      val to_string : Libvirt.Event.Disk_change.t -> string
    end
  module Tray_change :
    sig
      type reason = [ `Close | `Open | `Unknown of int ]
      type t = {
        dev_alias : string option;
        reason : Libvirt.Event.Tray_change.reason;
      }
      val to_string : Libvirt.Event.Tray_change.t -> string
    end
  module PM_wakeup :
    sig
      type reason = [ `Unknown of int ]
      type t = Libvirt.Event.PM_wakeup.reason
      val to_string : Libvirt.Event.PM_wakeup.t -> string
    end
  module PM_suspend :
    sig
      type reason = [ `Unknown of int ]
      type t = Libvirt.Event.PM_suspend.reason
      val to_string : Libvirt.Event.PM_suspend.t -> string
    end
  module Balloon_change :
    sig
      type t = int64
      val to_string : Libvirt.Event.Balloon_change.t -> string
    end
  module PM_suspend_disk :
    sig
      type reason = [ `Unknown of int ]
      type t = Libvirt.Event.PM_suspend_disk.reason
      val to_string : Libvirt.Event.PM_suspend_disk.t -> string
    end
  module Device_removed :
    sig
      type t = string
      val to_string : Libvirt.Event.Device_removed.t -> string
    end
  type callback =
      Lifecycle of
        ([ `R ] Libvirt.Domain.t -> Libvirt.Event.Lifecycle.t -> unit)
    | Reboot of ([ `R ] Libvirt.Domain.t -> Libvirt.Event.Reboot.t -> unit)
    | RtcChange of
        ([ `R ] Libvirt.Domain.t -> Libvirt.Event.Rtc_change.t -> unit)
    | Watchdog of
        ([ `R ] Libvirt.Domain.t -> Libvirt.Event.Watchdog.t -> unit)
    | IOError of
        ([ `R ] Libvirt.Domain.t -> Libvirt.Event.Io_error.t -> unit)
    | Graphics of
        ([ `R ] Libvirt.Domain.t -> Libvirt.Event.Graphics.t -> unit)
    | IOErrorReason of
        ([ `R ] Libvirt.Domain.t -> Libvirt.Event.Io_error.t -> unit)
    | ControlError of
        ([ `R ] Libvirt.Domain.t -> Libvirt.Event.Control_error.t -> unit)
    | BlockJob of
        ([ `R ] Libvirt.Domain.t -> Libvirt.Event.Block_job.t -> unit)
    | DiskChange of
        ([ `R ] Libvirt.Domain.t -> Libvirt.Event.Disk_change.t -> unit)
    | TrayChange of
        ([ `R ] Libvirt.Domain.t -> Libvirt.Event.Tray_change.t -> unit)
    | PMWakeUp of
        ([ `R ] Libvirt.Domain.t -> Libvirt.Event.PM_wakeup.t -> unit)
    | PMSuspend of
        ([ `R ] Libvirt.Domain.t -> Libvirt.Event.PM_suspend.t -> unit)
    | BalloonChange of
        ([ `R ] Libvirt.Domain.t -> Libvirt.Event.Balloon_change.t -> unit)
    | PMSuspendDisk of
        ([ `R ] Libvirt.Domain.t -> Libvirt.Event.PM_suspend_disk.t -> unit)
    | DeviceRemoved of
        ([ `R ] Libvirt.Domain.t -> Libvirt.Event.Device_removed.t -> unit)
  val register_default_impl : unit -> unit
  val run_default_impl : unit -> unit
  type callback_id
  val register_any :
    'Libvirt.Connect.t ->
    ?dom:'Libvirt.Domain.t ->
    Libvirt.Event.callback -> Libvirt.Event.callback_id
  val deregister_any :
    'Libvirt.Connect.t -> Libvirt.Event.callback_id -> unit
  type timer_id
  val add_timeout :
    'Libvirt.Connect.t -> int -> (unit -> unit) -> Libvirt.Event.timer_id
  val remove_timeout : 'Libvirt.Connect.t -> Libvirt.Event.timer_id -> unit
end