time-to-botec/ocaml/samples.ml

62 lines
1.9 KiB
OCaml
Raw Normal View History

2023-10-14 18:59:56 +00:00
(* Constants *)
let pi = acos (-1.)
2023-10-14 19:12:42 +00:00
let normal_95_ci_length = 1.6448536269514722
2023-10-14 18:59:56 +00:00
2023-10-14 19:50:25 +00:00
(* Array manipulation helpers *)
let sumFloats xs = Array.fold_left(fun acc x -> acc +. x) 0.0 xs
2023-10-14 19:57:21 +00:00
let normalizeXs xs =
let sum_xs = sumFloats xs in
Array.map(fun x -> x /. sum_xs) xs
2023-10-14 19:50:25 +00:00
let cumsumXs xs =
let _, cum_sum = Array.fold_left(fun (sum, ys) x ->
2023-10-14 19:50:25 +00:00
let new_sum = sum +. x in
new_sum, ys @ [new_sum]
) (0.0, []) xs in
cum_sum
2023-10-14 22:48:11 +00:00
let findIndex xs test =
let rec recursiveHelper ys i =
match ys with
| [] -> None
| z :: zs -> if test z then Some i else recursiveHelper zs (i+1)
in
recursiveHelper xs 0
2023-10-14 19:50:25 +00:00
2023-10-14 18:59:56 +00:00
(* Basic samplers *)
let sampleZeroToOne () : float = Random.float 1.0
2023-10-14 18:59:56 +00:00
let sampleStandardNormal (): float =
let u1 = sampleZeroToOne () in
let u2 = sampleZeroToOne () in
let z = sqrt(-2.0 *. log(u1)) *. sin(2.0 *. pi *. u2) in
z
2023-10-14 19:12:42 +00:00
let sampleNormal mean std = mean +. std *. (sampleStandardNormal ())
2023-10-14 19:12:42 +00:00
let sampleLognormal logmean logstd = exp(sampleNormal logmean logstd)
2023-10-14 19:12:42 +00:00
let sampleTo low high =
let loglow = log(low) in
let loghigh = log(high) in
let logmean = (loglow +. loghigh) /. 2.0 in
let logstd = (loghigh -. loglow) /. (2.0 -. normal_95_ci_length ) in
sampleLognormal logmean logstd
2023-10-14 22:59:40 +00:00
let mixture (samplers: (unit -> float) array) (weights: float array): float option =
if (Array.length samplers == Array.length weights)
then None
else
let normalized_weights = normalizeXs weights in
let cumsummed_normalized_weights = cumsumXs normalized_weights in
let p = sampleZeroToOne () in
let chosenSamplerIndex = findIndex cumsummed_normalized_weights (fun x -> x < p) in
let sample = match chosenSamplerIndex with
| None -> None
| Some(i) -> Some (samplers.(i) ())
in
sample
2023-10-14 18:59:56 +00:00
let () =
Random.init 1;
Printf.printf "%f\n" (sampleZeroToOne());
Printf.printf "%f\n" (sampleZeroToOne());