sig
type 'a scheduler
val create : ?compare:('a -> 'a -> int) -> unit -> 'a Duppy.scheduler
val queue :
?log:(string -> unit) ->
?priorities:('a -> bool) -> 'a Duppy.scheduler -> string -> unit
val stop : 'a Duppy.scheduler -> unit
module Task :
sig
type ('a, 'b) task = {
priority : 'a;
events : 'b list;
handler : 'b list -> ('a, 'b) Duppy.Task.task list;
}
type event =
[ `Delay of float
| `Exception of Unix.file_descr
| `Read of Unix.file_descr
| `Write of Unix.file_descr ]
val add :
'a Duppy.scheduler ->
('a, [< Duppy.Task.event ]) Duppy.Task.task -> unit
end
module Async :
sig
type t
exception Stopped
val add :
priority:'a -> 'a Duppy.scheduler -> (unit -> float) -> Duppy.Async.t
val wake_up : Duppy.Async.t -> unit
val stop : Duppy.Async.t -> unit
end
module type Transport_t =
sig
type t
type bigarray =
(char, Bigarray.int8_unsigned_elt, Bigarray.c_layout)
Bigarray.Array1.t
val sock : Duppy.Transport_t.t -> Unix.file_descr
val read : Duppy.Transport_t.t -> Stdlib.Bytes.t -> int -> int -> int
val write : Duppy.Transport_t.t -> Stdlib.Bytes.t -> int -> int -> int
val ba_write :
Duppy.Transport_t.t ->
Duppy.Transport_t.bigarray -> int -> int -> int
end
module type Io_t =
sig
type socket
type marker = Length of int | Split of string
type bigarray =
(char, Bigarray.int8_unsigned_elt, Bigarray.c_layout)
Bigarray.Array1.t
type failure =
Io_error
| Unix of Unix.error * string * string
| Unknown of exn
| Timeout
val read :
?recursive:bool ->
?init:string ->
?on_error:(string * Duppy.Io_t.failure -> unit) ->
?timeout:float ->
priority:'a ->
'a Duppy.scheduler ->
Duppy.Io_t.socket ->
Duppy.Io_t.marker -> (string * string option -> unit) -> unit
val write :
?exec:(unit -> unit) ->
?on_error:(Duppy.Io_t.failure -> unit) ->
?bigarray:Duppy.Io_t.bigarray ->
?string:Stdlib.Bytes.t ->
?timeout:float ->
priority:'a -> 'a Duppy.scheduler -> Duppy.Io_t.socket -> unit
end
module MakeIo :
functor (Transport : Transport_t) ->
sig
type socket = Transport.t
type marker = Length of int | Split of string
type bigarray =
(char, Bigarray.int8_unsigned_elt, Bigarray.c_layout)
Bigarray.Array1.t
type failure =
Io_error
| Unix of Unix.error * string * string
| Unknown of exn
| Timeout
val read :
?recursive:bool ->
?init:string ->
?on_error:(string * failure -> unit) ->
?timeout:float ->
priority:'a ->
'a scheduler ->
socket -> marker -> (string * string option -> unit) -> unit
val write :
?exec:(unit -> unit) ->
?on_error:(failure -> unit) ->
?bigarray:bigarray ->
?string:Bytes.t ->
?timeout:float -> priority:'a -> 'a scheduler -> socket -> unit
end
module Io :
sig
type socket = Unix.file_descr
type marker = Length of int | Split of string
type bigarray =
(char, Bigarray.int8_unsigned_elt, Bigarray.c_layout)
Bigarray.Array1.t
type failure =
Io_error
| Unix of Unix.error * string * string
| Unknown of exn
| Timeout
val read :
?recursive:bool ->
?init:string ->
?on_error:(string * failure -> unit) ->
?timeout:float ->
priority:'a ->
'a scheduler ->
socket -> marker -> (string * string option -> unit) -> unit
val write :
?exec:(unit -> unit) ->
?on_error:(failure -> unit) ->
?bigarray:bigarray ->
?string:Bytes.t ->
?timeout:float -> priority:'a -> 'a scheduler -> socket -> unit
end
module Monad :
sig
type ('a, 'b) t
val return : 'a -> ('a, 'b) Duppy.Monad.t
val raise : 'b -> ('a, 'b) Duppy.Monad.t
val bind :
('a, 'b) Duppy.Monad.t ->
('a -> ('c, 'b) Duppy.Monad.t) -> ('c, 'b) Duppy.Monad.t
val ( >>= ) :
('a, 'b) Duppy.Monad.t ->
('a -> ('c, 'b) Duppy.Monad.t) -> ('c, 'b) Duppy.Monad.t
val run :
return:('a -> unit) ->
raise:('b -> unit) -> ('a, 'b) Duppy.Monad.t -> unit
val catch :
('a, 'b) Duppy.Monad.t ->
('b -> ('a, 'c) Duppy.Monad.t) -> ('a, 'c) Duppy.Monad.t
val ( =<< ) :
('b -> ('a, 'c) Duppy.Monad.t) ->
('a, 'b) Duppy.Monad.t -> ('a, 'c) Duppy.Monad.t
val fold_left :
('a -> 'b -> ('a, 'c) Duppy.Monad.t) ->
'a -> 'b list -> ('a, 'c) Duppy.Monad.t
val iter :
('a -> (unit, 'b) Duppy.Monad.t) ->
'a list -> (unit, 'b) Duppy.Monad.t
module Mutex :
sig
module type Mutex_control =
sig
type priority
val scheduler :
Duppy.Monad.Mutex.Mutex_control.priority Duppy.scheduler
val priority : Duppy.Monad.Mutex.Mutex_control.priority
end
module type Mutex_t =
sig
type mutex
module Control : Mutex_control
val create : unit -> Duppy.Monad.Mutex.Mutex_t.mutex
val lock :
Duppy.Monad.Mutex.Mutex_t.mutex -> (unit, 'a) Duppy.Monad.t
val try_lock :
Duppy.Monad.Mutex.Mutex_t.mutex -> (bool, 'a) Duppy.Monad.t
val unlock :
Duppy.Monad.Mutex.Mutex_t.mutex -> (unit, 'a) Duppy.Monad.t
end
module Factory : functor (Control : Mutex_control) -> Mutex_t
end
module Condition :
sig
module Factory :
functor (Mutex : Mutex.Mutex_t) ->
sig
type condition
val create : unit -> Duppy.Monad.Condition.Factory.condition
val wait :
Duppy.Monad.Condition.Factory.condition ->
Mutex.mutex -> (unit, 'a) Duppy.Monad.t
val broadcast :
Duppy.Monad.Condition.Factory.condition ->
(unit, 'a) Duppy.Monad.t
val signal :
Duppy.Monad.Condition.Factory.condition ->
(unit, 'a) Duppy.Monad.t
end
end
module type Monad_io_t =
sig
type socket
module Io :
sig
type socket = socket
type marker = Length of int | Split of string
type bigarray =
(char, Bigarray.int8_unsigned_elt, Bigarray.c_layout)
Bigarray.Array1.t
type failure =
Io_error
| Unix of Unix.error * string * string
| Unknown of exn
| Timeout
val read :
?recursive:bool ->
?init:string ->
?on_error:(string * failure -> unit) ->
?timeout:float ->
priority:'a ->
'a scheduler ->
socket -> marker -> (string * string option -> unit) -> unit
val write :
?exec:(unit -> unit) ->
?on_error:(failure -> unit) ->
?bigarray:bigarray ->
?string:Bytes.t ->
?timeout:float ->
priority:'a -> 'a scheduler -> socket -> unit
end
type ('a, 'b) handler = {
scheduler : 'a Duppy.scheduler;
socket : Duppy.Monad.Monad_io_t.Io.socket;
mutable data : string;
on_error : Duppy.Monad.Monad_io_t.Io.failure -> 'b;
}
val exec :
?delay:float ->
priority:'a ->
('a, 'b) Duppy.Monad.Monad_io_t.handler ->
('c, 'b) Duppy.Monad.t -> ('c, 'b) Duppy.Monad.t
val delay :
priority:'a ->
('a, 'b) Duppy.Monad.Monad_io_t.handler ->
float -> (unit, 'b) Duppy.Monad.t
val read :
?timeout:float ->
priority:'a ->
marker:Duppy.Monad.Monad_io_t.Io.marker ->
('a, 'b) Duppy.Monad.Monad_io_t.handler ->
(string, 'b) Duppy.Monad.t
val read_all :
?timeout:float ->
priority:'a ->
'a Duppy.scheduler ->
Duppy.Monad.Monad_io_t.Io.socket ->
(string, string * Duppy.Monad.Monad_io_t.Io.failure)
Duppy.Monad.t
val write :
?timeout:float ->
priority:'a ->
('a, 'b) Duppy.Monad.Monad_io_t.handler ->
Stdlib.Bytes.t -> (unit, 'b) Duppy.Monad.t
val write_bigarray :
?timeout:float ->
priority:'a ->
('a, 'b) Duppy.Monad.Monad_io_t.handler ->
Duppy.Monad.Monad_io_t.Io.bigarray -> (unit, 'b) Duppy.Monad.t
end
module MakeIo :
functor (Io : Io_t) ->
sig
type socket = Io.socket
module Io :
sig
type socket = Io.socket
type marker = Io.marker = Length of int | Split of string
type bigarray =
(char, Bigarray.int8_unsigned_elt, Bigarray.c_layout)
Bigarray.Array1.t
type failure =
Io.failure =
Io_error
| Unix of Unix.error * string * string
| Unknown of exn
| Timeout
val read :
?recursive:bool ->
?init:string ->
?on_error:(string * failure -> unit) ->
?timeout:float ->
priority:'a ->
'a scheduler ->
socket ->
marker -> (string * string option -> unit) -> unit
val write :
?exec:(unit -> unit) ->
?on_error:(failure -> unit) ->
?bigarray:bigarray ->
?string:Bytes.t ->
?timeout:float ->
priority:'a -> 'a scheduler -> socket -> unit
end
type ('a, 'b) handler = {
scheduler : 'a scheduler;
socket : Io.socket;
mutable data : string;
on_error : Io.failure -> 'b;
}
val exec :
?delay:float ->
priority:'a -> ('a, 'b) handler -> ('c, 'b) t -> ('c, 'b) t
val delay :
priority:'a -> ('a, 'b) handler -> float -> (unit, 'b) t
val read :
?timeout:float ->
priority:'a ->
marker:Io.marker -> ('a, 'b) handler -> (string, 'b) t
val read_all :
?timeout:float ->
priority:'a ->
'a scheduler -> Io.socket -> (string, string * Io.failure) t
val write :
?timeout:float ->
priority:'a -> ('a, 'b) handler -> Bytes.t -> (unit, 'b) t
val write_bigarray :
?timeout:float ->
priority:'a -> ('a, 'b) handler -> Io.bigarray -> (unit, 'b) t
end
module Io :
sig
type socket = Unix.file_descr
module Io :
sig
type socket = Unix.file_descr
type marker = Io.marker = Length of int | Split of string
type bigarray =
(char, Bigarray.int8_unsigned_elt, Bigarray.c_layout)
Bigarray.Array1.t
type failure =
Io.failure =
Io_error
| Unix of Unix.error * string * string
| Unknown of exn
| Timeout
val read :
?recursive:bool ->
?init:string ->
?on_error:(string * failure -> unit) ->
?timeout:float ->
priority:'a ->
'a scheduler ->
socket -> marker -> (string * string option -> unit) -> unit
val write :
?exec:(unit -> unit) ->
?on_error:(failure -> unit) ->
?bigarray:bigarray ->
?string:Bytes.t ->
?timeout:float ->
priority:'a -> 'a scheduler -> socket -> unit
end
type ('a, 'b) handler = {
scheduler : 'a scheduler;
socket : Io.socket;
mutable data : string;
on_error : Io.failure -> 'b;
}
val exec :
?delay:float ->
priority:'a -> ('a, 'b) handler -> ('c, 'b) t -> ('c, 'b) t
val delay :
priority:'a -> ('a, 'b) handler -> float -> (unit, 'b) t
val read :
?timeout:float ->
priority:'a ->
marker:Io.marker -> ('a, 'b) handler -> (string, 'b) t
val read_all :
?timeout:float ->
priority:'a ->
'a scheduler -> Io.socket -> (string, string * Io.failure) t
val write :
?timeout:float ->
priority:'a -> ('a, 'b) handler -> Bytes.t -> (unit, 'b) t
val write_bigarray :
?timeout:float ->
priority:'a -> ('a, 'b) handler -> Io.bigarray -> (unit, 'b) t
end
end
end