From 0501664a7d40755d0d0aaed39fb88b50e44bcfa2 Mon Sep 17 00:00:00 2001 From: Rudi Grinberg Date: Wed, 2 Jun 2021 12:48:53 -0700 Subject: [PATCH] [RPC] remove dead code related to --persistent Signed-off-by: Rudi Grinberg --- otherlibs/dune-rpc/dune_rpc.ml | 7 --- otherlibs/dune-rpc/dune_rpc.mli | 7 --- .../dune-rpc/private/dune_rpc_private.ml | 62 ------------------- .../dune-rpc/private/dune_rpc_private.mli | 28 --------- 4 files changed, 104 deletions(-) diff --git a/otherlibs/dune-rpc/dune_rpc.ml b/otherlibs/dune-rpc/dune_rpc.ml index ab9770c28d0..b227758a926 100644 --- a/otherlibs/dune-rpc/dune_rpc.ml +++ b/otherlibs/dune-rpc/dune_rpc.ml @@ -71,12 +71,5 @@ module V1 = struct -> Initialize.t -> f:(t -> 'a fiber) -> 'a fiber - - val connect_persistent : - ?on_disconnect:('a -> unit fiber) - -> chan - -> on_connect:(unit -> ('a * Initialize.t * Handler.t option) fiber) - -> on_connected:('a -> t -> unit fiber) - -> unit fiber end end diff --git a/otherlibs/dune-rpc/dune_rpc.mli b/otherlibs/dune-rpc/dune_rpc.mli index ba087000882..ecfcf3d7b70 100644 --- a/otherlibs/dune-rpc/dune_rpc.mli +++ b/otherlibs/dune-rpc/dune_rpc.mli @@ -262,13 +262,6 @@ module V1 : sig -> Initialize.t -> f:(t -> 'a fiber) -> 'a fiber - - val connect_persistent : - ?on_disconnect:('a -> unit fiber) - -> chan - -> on_connect:(unit -> ('a * Initialize.t * Handler.t option) fiber) - -> on_connected:('a -> t -> unit fiber) - -> unit fiber end (** Functor to create a client implementation *) diff --git a/otherlibs/dune-rpc/private/dune_rpc_private.ml b/otherlibs/dune-rpc/private/dune_rpc_private.ml index f2c7a3e51dc..cab28cd2a17 100644 --- a/otherlibs/dune-rpc/private/dune_rpc_private.ml +++ b/otherlibs/dune-rpc/private/dune_rpc_private.ml @@ -458,13 +458,6 @@ module type S = sig -> Initialize.Request.t -> f:(t -> 'a fiber) -> 'a fiber - - val connect_persistent : - ?on_disconnect:('a -> unit fiber) - -> chan - -> on_connect:(unit -> ('a * Initialize.Request.t * Handler.t option) fiber) - -> on_connected:('a -> t -> unit fiber) - -> unit fiber end module Client (Fiber : sig @@ -512,9 +505,6 @@ struct ; mutable closed_write : bool } - let make read write = - { read; write; closed_read = false; closed_write = false } - let of_chan c = { read = (fun () -> Chan.read c) ; write = (fun s -> Chan.write c s) @@ -533,8 +523,6 @@ struct t.write None ) - let close_read t = t.closed_read <- true - let read t = if t.closed_read then Fiber.return None @@ -843,56 +831,6 @@ struct in connect_raw chan initialize ~f ~on_notification - let connect_persistent ?(on_disconnect = fun _ -> Fiber.return ()) chan - ~on_connect ~on_connected = - let chan = Chan.of_chan chan in - let packets () = - let+ read = Chan.read chan in - Option.map read ~f:(fun sexp -> - match Conv.of_sexp Persistent.In.sexp sexp ~version:(0, 0) with - | Ok m -> m - | Error e -> raise (Invalid_session e)) - in - let make_chan packets = - let read () = - let+ packet = packets () in - match (packet : Persistent.In.t option) with - | None - | Some Close_connection -> - None - | Some (Packet csexp) -> Some csexp - | Some New_connection -> - Code_error.raise "Unexpected new connection." [] - in - let write p = - let packets = - match p with - | Some p -> List.map p ~f:(fun p -> Persistent.Out.Packet p) - | None -> [ Close_connection ] - in - let sexps = List.map packets ~f:(Conv.to_sexp Persistent.Out.sexp) in - Chan.write chan (Some sexps) - in - Chan.make read write - in - let rec loop () = - let* packet = packets () in - match packet with - | Some New_connection -> - let* a, init, handler = on_connect () in - let chan = make_chan packets in - let* () = connect ?handler chan init ~f:(on_connected a) in - Chan.close_read chan; - let* () = on_disconnect a in - loop () - | Some Close_connection -> loop () - | None -> Fiber.return () - | Some (Packet p) -> - Code_error.raise "Expected new connection" - [ ("received", Sexp.to_dyn p) ] - in - loop () - let connect_raw chan init ~on_notification ~f = let chan = Chan.of_chan chan in connect_raw chan init ~on_notification ~f diff --git a/otherlibs/dune-rpc/private/dune_rpc_private.mli b/otherlibs/dune-rpc/private/dune_rpc_private.mli index e4a3771f474..73d971d9880 100644 --- a/otherlibs/dune-rpc/private/dune_rpc_private.mli +++ b/otherlibs/dune-rpc/private/dune_rpc_private.mli @@ -298,13 +298,6 @@ module type S = sig -> Initialize.Request.t -> f:(t -> 'a fiber) -> 'a fiber - - val connect_persistent : - ?on_disconnect:('a -> unit fiber) - -> chan - -> on_connect:(unit -> ('a * Initialize.Request.t * Handler.t option) fiber) - -> on_connected:('a -> t -> unit fiber) - -> unit fiber end module Client (Fiber : sig @@ -342,27 +335,6 @@ end) (Chan : sig val read : t -> Csexp.t option Fiber.t end) : S with type 'a fiber := 'a Fiber.t and type chan := Chan.t -module Persistent : sig - module In : sig - (** The type of incoming packets when hosting multiple connections in - sequence over a single channel *) - type t = - | New_connection - | Packet of Csexp.t - | Close_connection - - val sexp : t Conv.value - end - - module Out : sig - type t = - | Packet of Csexp.t - | Close_connection - - val sexp : t Conv.value - end -end - module Packet : sig module Reply : sig type t =