TportaudioThin bindings to the portaudio library.
Consult the portaudio documentation and an example.
module Error : sig ... endErrors.
val error_string : ('a, error) Stdlib.result -> ('a, string) Stdlib.resulterror_string r is Result.map_error Error.message r.
val initialize : unit -> (unit, error) Stdlib.resultinitialize () initializes the library.
val terminate : unit -> (unit, error) Stdlib.resultterminate () terminates the library. This must be called before exiting a program that used initialize.
val bracket : (unit -> 'a) -> ('a, error) Stdlib.resultbracket f runs f () after an initialize and calls terminate after it finished, however it returned.
module Host_api_info : sig ... endHost API info.
The type for host API indexes ranges from [0;get_host_api_count ()].
val get_host_api_count : unit -> (int, error) Stdlib.resultget_host_api_count () is the number of available host APIs.
val get_default_host_api : unit -> (host_api_index, error) Stdlib.resultdefault_host_api () is the index of the default host API.
val get_host_api_info :
host_api_index ->
(Host_api_info.t, error) Stdlib.resultget_host_api_info ai is the host API info for index ai.
val fold_host_api_infos :
(host_api_index -> Host_api_info.t -> 'a -> 'a) ->
'a ->
('a, error) Stdlib.resultfold_host_api_infos f acc folds over the host APIs.
module Device_info : sig ... endDevice information.
val get_device_count : unit -> (int, error) Stdlib.resultget_device_count () is the number of available devices.
val get_default_input_device : unit -> device_index optionget_default_input_device () is the index of the default input device.
val get_default_output_device : unit -> device_index optionget_default_output_device () is the index of the default output device.
val get_device_info : device_index -> (Device_info.t, error) Stdlib.resultget_device_info di is the device information fo index di.
val fold_device_infos :
(device_index -> Device_info.t -> 'a -> 'a) ->
'a ->
('a, error) Stdlib.resultfold_device_infos f acc folds over devices.
type ('a, 'b) sample_format = | Uint8 : (int, Stdlib.Bigarray.int8_unsigned_elt) sample_format| Int8 : (int, Stdlib.Bigarray.int8_signed_elt) sample_format| Int16 : (int, Stdlib.Bigarray.int16_signed_elt) sample_format| Int24 : (int32, Stdlib.Bigarray.int32_elt) sample_format| Int32 : (int32, Stdlib.Bigarray.int32_elt) sample_format| Float32 : (float, Stdlib.Bigarray.float32_elt) sample_formatThe type for sample formats.
val zero_sample : ('a, 'b) sample_format -> 'azero_sample sf is the silence for sample format sf.
module Buffer : sig ... endAudio buffers.
The type for streams parameters. The type parameters witness the sample format.
val stream_parameters :
device:device_index ->
channel_count:int ->
('a, 'b) sample_format ->
Buffer.layout ->
suggested_latency:time ->
('a, 'b) stream_parametersstream_parameters ~device ~channel_count sample_format bf
~suggested_latency are stream parameters with the given attributes.
val is_format_supported :
input:('i, 'is) stream_parameters option ->
output:('o, 'os) stream_parameters option ->
sample_rate_hz:float ->
(unit, error) Stdlib.resultis_format_supported ~input ~output ~sample_rate_hz is Ok () if the given format is supported.
Warning. You must not use streams after a terminate this may lead to segfaults.
module Stream_flags : sig ... endStream flags.
The type for streams. The type parameters respectively track the sample format of input and output channels.
Note. After a stream is closed any function on the stream raises Invalid_argument. However at the moment using an unclosed stream value after a library terminate will likely result in a segmentation fault.
val open_stream :
?stream_flags:Stream_flags.t ->
input:('i, 'is) stream_parameters option ->
output:('o, 'os) stream_parameters option ->
sample_rate_hz:float ->
frames_per_buffer:int option ->
unit ->
(('i, 'is, 'o, 'os) stream, error) Stdlib.resultopen_stream ~input ~output ~sample_rate_hz ~frames_per_buffer open a stream a with given parameters.
val open_default_stream :
input_channel_count:int ->
output_channel_count:int ->
('a, 'b) sample_format ->
Buffer.layout ->
sample_rate_hz:float ->
frames_per_buffer:int option ->
(('a, 'b, 'a, 'b) stream, error) Stdlib.resultopen_default_stream ~input_channel_count ~output_channel_count
bf ~sample_rate_hz opens a stream on the default device with given parameters.
close_stream s closes stream s (discards any pending buffers). Once s is closed any call on s raises Invalid_argument.
get_stream_info s is the triple input_latency, output_latency, sample_rate_hz for s.
start_stream s starts audio processing in s.
stop_stream s stops audio processing in s. Blocks until pending buffers have been processed before it returns. See also abort_stream.
stop_stream s stops audio processing in s. Discards pending bufffers. See also stop_stream.
is_stream_active s determines if s is active (playing or recording audio).
is_stream_stopped s determines if s is stopped (stop_stream or abort_stream was called).
get_stream_time s is the current time of s.
get_stream_read_available s is the number of frames that can be read from s without blocking.
get_stream_write_available s is the number of frames that can be written to s without blocking.
val write_stream :
('i, 'is, 'o, 'os) stream ->
('o, 'os) Buffer.t ->
frame_count:int ->
(unit, error) Stdlib.resultwrite_stream s fs ~count writes frame_count frames from fs to stream s, this may block.
val read_stream :
('i, 'is, 'o, 'os) stream ->
('i, 'is) Buffer.t ->
frame_count:int ->
(unit, error) Stdlib.resultread_stream s fs ~count reads frame_count frames from s into fs.
This example passes the default audio input to the default audio output.
let ( let* ) = Result.bind
let log fmt = Format.kfprintf (Fun.const ()) Format.std_formatter (fmt ^^ "@.")
let log_if_error ~use = function
| Ok v -> v | Error e -> log "Error: %s" (Tportaudio.Error.message e); use
let log_stream_info iinfo oinfo s =
let ms_lat l = truncate (l *. 1000.) in
let iname, oname = Tportaudio.Device_info.(name iinfo, name oinfo) in
let* ilat, olat, srate = Tportaudio.get_stream_info s in
log "%s (lat:%dms) -- %gHz --> %s (lat:%dms)"
iname (ms_lat ilat) srate oname (ms_lat olat);
Ok ()
let io_stream sf layout ~sample_rate_hz ~frame_count ~i ~o =
let* iinfo = Tportaudio.get_device_info i in
let* oinfo = Tportaudio.get_device_info o in
let channel_count =
let ic = Tportaudio.Device_info.max_input_channels iinfo in
let oc = Tportaudio.Device_info.max_output_channels oinfo in
Int.min ic oc
in
let input =
let ilat = Tportaudio.Device_info.default_low_input_latency iinfo in
Option.some @@ Tportaudio.stream_parameters
~device:i ~channel_count sf layout ~suggested_latency:ilat
in
let output =
let olat = Tportaudio.Device_info.default_low_output_latency oinfo in
Option.some @@ Tportaudio.stream_parameters
~device:o ~channel_count sf layout ~suggested_latency:olat
in
let frames_per_buffer = Some frame_count in
let* s =
Tportaudio.open_stream ~input ~output ~sample_rate_hz ~frames_per_buffer ()
in
Ok (iinfo, oinfo, channel_count, s)
let forward stop ~i ~o =
let sample_rate_hz = 44100. and frame_count = 256 in
let sf = Tportaudio.Float32 and layout = `Interleaved in
let* ii, oi, c, s = io_stream sf layout ~sample_rate_hz ~frame_count ~i ~o in
let* () = log_stream_info ii oi s in
let buf = Tportaudio.Buffer.create ~channel_count:c sf layout ~frame_count in
let finally () = ignore (Tportaudio.close_stream) in
Fun.protect ~finally @@ fun () ->
let* () = Tportaudio.start_stream s in
let rec loop stop =
if !stop then Tportaudio.stop_stream s else
begin
log_if_error ~use:() (Tportaudio.write_stream s buf ~frame_count);
log_if_error ~use:() (Tportaudio.read_stream s buf ~frame_count);
loop stop
end
in
loop stop
let default_io_devices () =
let none = Tportaudio.Error.device_unavailable in
let* i = Option.to_result ~none @@ Tportaudio.get_default_input_device () in
let* o = Option.to_result ~none @@ Tportaudio.get_default_output_device () in
Ok (i, o)
let signal_stopper () =
let stop = ref false in
let stop_it = Sys.Signal_handle (fun _ -> stop := true) in
Sys.set_signal Sys.sigint stop_it;
Sys.set_signal Sys.sigabrt stop_it;
stop
let main () =
log_if_error ~use:1 @@ Result.join @@ Tportaudio.bracket @@ fun () ->
let stop = signal_stopper () in
let* i, o = default_io_devices () in
Result.map (fun () -> 0) (forward stop ~i ~o)
let () = if !Sys.interactive then () else exit (main ())