Split FunctionRegistry into multiple files
This commit is contained in:
parent
0b85b12551
commit
2c0dc75403
|
@ -256,158 +256,3 @@ module Registry = {
|
|||
}
|
||||
}
|
||||
}
|
||||
|
||||
let impossibleError = "Wrong inputs / Logically impossible"
|
||||
|
||||
module Prepare = {
|
||||
let recordWithTwoArgsToValues = (inputs: array<value>): result<array<value>, string> =>
|
||||
switch inputs {
|
||||
| [Record([(_, n1), (_, n2)])] => Ok([n1, n2])
|
||||
| _ => Error(impossibleError)
|
||||
}
|
||||
|
||||
let twoNumberInputs = (inputs: array<value>): result<(float, float), string> => {
|
||||
switch inputs {
|
||||
| [Number(n1), Number(n2)] => Ok(n1, n2)
|
||||
| _ => Error(impossibleError)
|
||||
}
|
||||
}
|
||||
|
||||
let twoDistOrNumber = (values: array<value>): result<(distOrNumber, distOrNumber), string> => {
|
||||
switch values {
|
||||
| [DistOrNumber(a1), DistOrNumber(a2)] => Ok(a1, a2)
|
||||
| _ => Error(impossibleError)
|
||||
}
|
||||
}
|
||||
|
||||
let twoDistOrNumberFromRecord = (values: array<value>) =>
|
||||
values->recordWithTwoArgsToValues->E.R.bind(twoDistOrNumber)
|
||||
}
|
||||
|
||||
module Wrappers = {
|
||||
let symbolic = r => DistributionTypes.Symbolic(r)
|
||||
let evDistribution = r => ReducerInterface_ExpressionValue.EvDistribution(r)
|
||||
let symbolicEvDistribution = r => r->Symbolic->evDistribution
|
||||
}
|
||||
|
||||
module Process = {
|
||||
let twoDistsOrNumbersToDist = (
|
||||
~fn: ((float, float)) => result<DistributionTypes.genericDist, string>,
|
||||
~values: (distOrNumber, distOrNumber),
|
||||
) => {
|
||||
let toSampleSet = r => GenericDist.toSampleSetDist(r, 1000)
|
||||
let sampleSetToExpressionValue = (
|
||||
b: Belt.Result.t<QuriSquiggleLang.SampleSetDist.t, QuriSquiggleLang.DistributionTypes.error>,
|
||||
) =>
|
||||
switch b {
|
||||
| Ok(r) => Ok(ReducerInterface_ExpressionValue.EvDistribution(SampleSet(r)))
|
||||
| Error(d) => Error(DistributionTypes.Error.toString(d))
|
||||
}
|
||||
|
||||
let mapFnResult = r =>
|
||||
switch r {
|
||||
| Ok(r) => Ok(GenericDist.sample(r))
|
||||
| Error(r) => Error(Operation.Other(r))
|
||||
}
|
||||
|
||||
let singleVarSample = (a, fn) => {
|
||||
let sampleSetResult =
|
||||
toSampleSet(a) |> E.R2.bind(dist =>
|
||||
SampleSetDist.samplesMap(
|
||||
~fn=f => fn(f)->mapFnResult,
|
||||
dist,
|
||||
)->E.R2.errMap(r => DistributionTypes.SampleSetError(r))
|
||||
)
|
||||
sampleSetResult->sampleSetToExpressionValue
|
||||
}
|
||||
|
||||
switch values {
|
||||
| (Number(a1), Number(a2)) => fn((a1, a2))->E.R2.fmap(Wrappers.evDistribution)
|
||||
| (Dist(a1), Number(a2)) => singleVarSample(a1, r => fn((r, a2)))
|
||||
| (Number(a1), Dist(a2)) => singleVarSample(a2, r => fn((a1, r)))
|
||||
| (Dist(a1), Dist(a2)) => {
|
||||
let altFn = (a, b) => fn((a, b))->mapFnResult
|
||||
let sampleSetResult =
|
||||
E.R.merge(toSampleSet(a1), toSampleSet(a2))
|
||||
->E.R2.errMap(DistributionTypes.Error.toString)
|
||||
->E.R.bind(((t1, t2)) => {
|
||||
SampleSetDist.map2(~fn=altFn, ~t1, ~t2)->E.R2.errMap(Operation.Error.toString)
|
||||
})
|
||||
->E.R2.errMap(r => DistributionTypes.OtherError(r))
|
||||
sampleSetResult->sampleSetToExpressionValue
|
||||
}
|
||||
}
|
||||
}
|
||||
|
||||
let twoDistsOrNumbersToDistUsingSymbolicDist = (
|
||||
~fn: ((float, float)) => result<SymbolicDistTypes.symbolicDist, string>,
|
||||
~values,
|
||||
) => {
|
||||
twoDistsOrNumbersToDist(~fn=r => r->fn->E.R2.fmap(Wrappers.symbolic), ~values)
|
||||
}
|
||||
}
|
||||
|
||||
let twoArgs = (fn, (a1, a2)) => fn(a1, a2)
|
||||
|
||||
let process = (~fn, r) =>
|
||||
r->E.R.bind(Process.twoDistsOrNumbersToDistUsingSymbolicDist(~fn, ~values=_))
|
||||
|
||||
module NormalFn = {
|
||||
let fnName = "normal"
|
||||
let mainInputType = I_DistOrNumber
|
||||
|
||||
let toFn = Function.make(
|
||||
~name="Normal",
|
||||
~definitions=[
|
||||
Function.makeDefinition(~name=fnName, ~inputs=[mainInputType, mainInputType], ~run=inputs => {
|
||||
inputs->Prepare.twoDistOrNumber->process(~fn=twoArgs(SymbolicDist.Normal.make))
|
||||
}),
|
||||
Function.makeDefinition(
|
||||
~name=fnName,
|
||||
~inputs=[I_Record([("mean", mainInputType), ("stdev", mainInputType)])],
|
||||
~run=inputs =>
|
||||
inputs->Prepare.twoDistOrNumberFromRecord->process(~fn=twoArgs(SymbolicDist.Normal.make)),
|
||||
),
|
||||
Function.makeDefinition(
|
||||
~name=fnName,
|
||||
~inputs=[I_Record([("p5", mainInputType), ("p95", mainInputType)])],
|
||||
~run=inputs =>
|
||||
inputs
|
||||
->Prepare.twoDistOrNumberFromRecord
|
||||
->process(~fn=r => twoArgs(SymbolicDist.Normal.from90PercentCI, r)->Ok),
|
||||
),
|
||||
],
|
||||
)
|
||||
}
|
||||
|
||||
module LognormalFn = {
|
||||
let fnName = "lognormal"
|
||||
let mainInputType = I_DistOrNumber
|
||||
|
||||
let toFn = Function.make(
|
||||
~name="Lognormal",
|
||||
~definitions=[
|
||||
Function.makeDefinition(~name=fnName, ~inputs=[mainInputType, mainInputType], ~run=inputs =>
|
||||
inputs->Prepare.twoDistOrNumber->process(~fn=twoArgs(SymbolicDist.Lognormal.make))
|
||||
),
|
||||
Function.makeDefinition(
|
||||
~name=fnName,
|
||||
~inputs=[I_Record([("p5", mainInputType), ("p95", mainInputType)])],
|
||||
~run=inputs =>
|
||||
inputs
|
||||
->Prepare.twoDistOrNumberFromRecord
|
||||
->process(~fn=r => twoArgs(SymbolicDist.Lognormal.from90PercentCI, r)->Ok),
|
||||
),
|
||||
Function.makeDefinition(
|
||||
~name=fnName,
|
||||
~inputs=[I_Record([("mean", mainInputType), ("stdev", mainInputType)])],
|
||||
~run=inputs =>
|
||||
inputs
|
||||
->Prepare.twoDistOrNumberFromRecord
|
||||
->process(~fn=twoArgs(SymbolicDist.Lognormal.fromMeanAndStdev)),
|
||||
),
|
||||
],
|
||||
)
|
||||
}
|
||||
|
||||
let allFunctions = [NormalFn.toFn, LognormalFn.toFn]
|
|
@ -0,0 +1,91 @@
|
|||
open FunctionRegistry_Core
|
||||
|
||||
let impossibleError = "Wrong inputs / Logically impossible"
|
||||
|
||||
module Wrappers = {
|
||||
let symbolic = r => DistributionTypes.Symbolic(r)
|
||||
let evDistribution = r => ReducerInterface_ExpressionValue.EvDistribution(r)
|
||||
let symbolicEvDistribution = r => r->Symbolic->evDistribution
|
||||
}
|
||||
|
||||
module Prepare = {
|
||||
let recordWithTwoArgsToValues = (inputs: array<value>): result<array<value>, string> =>
|
||||
switch inputs {
|
||||
| [Record([(_, n1), (_, n2)])] => Ok([n1, n2])
|
||||
| _ => Error(impossibleError)
|
||||
}
|
||||
|
||||
let twoNumberInputs = (inputs: array<value>): result<(float, float), string> => {
|
||||
switch inputs {
|
||||
| [Number(n1), Number(n2)] => Ok(n1, n2)
|
||||
| _ => Error(impossibleError)
|
||||
}
|
||||
}
|
||||
|
||||
let twoDistOrNumber = (values: array<value>): result<(distOrNumber, distOrNumber), string> => {
|
||||
switch values {
|
||||
| [DistOrNumber(a1), DistOrNumber(a2)] => Ok(a1, a2)
|
||||
| _ => Error(impossibleError)
|
||||
}
|
||||
}
|
||||
|
||||
let twoDistOrNumberFromRecord = (values: array<value>) =>
|
||||
values->recordWithTwoArgsToValues->E.R.bind(twoDistOrNumber)
|
||||
}
|
||||
|
||||
module Process = {
|
||||
let twoDistsOrNumbersToDist = (
|
||||
~fn: ((float, float)) => result<DistributionTypes.genericDist, string>,
|
||||
~values: (distOrNumber, distOrNumber),
|
||||
) => {
|
||||
let toSampleSet = r => GenericDist.toSampleSetDist(r, 1000)
|
||||
let sampleSetToExpressionValue = (
|
||||
b: Belt.Result.t<QuriSquiggleLang.SampleSetDist.t, QuriSquiggleLang.DistributionTypes.error>,
|
||||
) =>
|
||||
switch b {
|
||||
| Ok(r) => Ok(ReducerInterface_ExpressionValue.EvDistribution(SampleSet(r)))
|
||||
| Error(d) => Error(DistributionTypes.Error.toString(d))
|
||||
}
|
||||
|
||||
let mapFnResult = r =>
|
||||
switch r {
|
||||
| Ok(r) => Ok(GenericDist.sample(r))
|
||||
| Error(r) => Error(Operation.Other(r))
|
||||
}
|
||||
|
||||
let singleVarSample = (a, fn) => {
|
||||
let sampleSetResult =
|
||||
toSampleSet(a) |> E.R2.bind(dist =>
|
||||
SampleSetDist.samplesMap(
|
||||
~fn=f => fn(f)->mapFnResult,
|
||||
dist,
|
||||
)->E.R2.errMap(r => DistributionTypes.SampleSetError(r))
|
||||
)
|
||||
sampleSetResult->sampleSetToExpressionValue
|
||||
}
|
||||
|
||||
switch values {
|
||||
| (Number(a1), Number(a2)) => fn((a1, a2))->E.R2.fmap(Wrappers.evDistribution)
|
||||
| (Dist(a1), Number(a2)) => singleVarSample(a1, r => fn((r, a2)))
|
||||
| (Number(a1), Dist(a2)) => singleVarSample(a2, r => fn((a1, r)))
|
||||
| (Dist(a1), Dist(a2)) => {
|
||||
let altFn = (a, b) => fn((a, b))->mapFnResult
|
||||
let sampleSetResult =
|
||||
E.R.merge(toSampleSet(a1), toSampleSet(a2))
|
||||
->E.R2.errMap(DistributionTypes.Error.toString)
|
||||
->E.R.bind(((t1, t2)) => {
|
||||
SampleSetDist.map2(~fn=altFn, ~t1, ~t2)->E.R2.errMap(Operation.Error.toString)
|
||||
})
|
||||
->E.R2.errMap(r => DistributionTypes.OtherError(r))
|
||||
sampleSetResult->sampleSetToExpressionValue
|
||||
}
|
||||
}
|
||||
}
|
||||
|
||||
let twoDistsOrNumbersToDistUsingSymbolicDist = (
|
||||
~fn: ((float, float)) => result<SymbolicDistTypes.symbolicDist, string>,
|
||||
~values,
|
||||
) => {
|
||||
twoDistsOrNumbersToDist(~fn=r => r->fn->E.R2.fmap(Wrappers.symbolic), ~values)
|
||||
}
|
||||
}
|
|
@ -0,0 +1,67 @@
|
|||
open FunctionRegistry_Core
|
||||
open FunctionRegistry_Helpers
|
||||
|
||||
let twoArgs = (fn, (a1, a2)) => fn(a1, a2)
|
||||
|
||||
let process = (~fn, r) =>
|
||||
r->E.R.bind(Process.twoDistsOrNumbersToDistUsingSymbolicDist(~fn, ~values=_))
|
||||
|
||||
module NormalFn = {
|
||||
let fnName = "normal"
|
||||
let mainInputType = I_DistOrNumber
|
||||
|
||||
let toFn = Function.make(
|
||||
~name="Normal",
|
||||
~definitions=[
|
||||
Function.makeDefinition(~name=fnName, ~inputs=[mainInputType, mainInputType], ~run=inputs => {
|
||||
inputs->Prepare.twoDistOrNumber->process(~fn=twoArgs(SymbolicDist.Normal.make))
|
||||
}),
|
||||
Function.makeDefinition(
|
||||
~name=fnName,
|
||||
~inputs=[I_Record([("mean", mainInputType), ("stdev", mainInputType)])],
|
||||
~run=inputs =>
|
||||
inputs->Prepare.twoDistOrNumberFromRecord->process(~fn=twoArgs(SymbolicDist.Normal.make)),
|
||||
),
|
||||
Function.makeDefinition(
|
||||
~name=fnName,
|
||||
~inputs=[I_Record([("p5", mainInputType), ("p95", mainInputType)])],
|
||||
~run=inputs =>
|
||||
inputs
|
||||
->Prepare.twoDistOrNumberFromRecord
|
||||
->process(~fn=r => twoArgs(SymbolicDist.Normal.from90PercentCI, r)->Ok),
|
||||
),
|
||||
],
|
||||
)
|
||||
}
|
||||
|
||||
module LognormalFn = {
|
||||
let fnName = "lognormal"
|
||||
let mainInputType = I_DistOrNumber
|
||||
|
||||
let toFn = Function.make(
|
||||
~name="Lognormal",
|
||||
~definitions=[
|
||||
Function.makeDefinition(~name=fnName, ~inputs=[mainInputType, mainInputType], ~run=inputs =>
|
||||
inputs->Prepare.twoDistOrNumber->process(~fn=twoArgs(SymbolicDist.Lognormal.make))
|
||||
),
|
||||
Function.makeDefinition(
|
||||
~name=fnName,
|
||||
~inputs=[I_Record([("p5", mainInputType), ("p95", mainInputType)])],
|
||||
~run=inputs =>
|
||||
inputs
|
||||
->Prepare.twoDistOrNumberFromRecord
|
||||
->process(~fn=r => twoArgs(SymbolicDist.Lognormal.from90PercentCI, r)->Ok),
|
||||
),
|
||||
Function.makeDefinition(
|
||||
~name=fnName,
|
||||
~inputs=[I_Record([("mean", mainInputType), ("stdev", mainInputType)])],
|
||||
~run=inputs =>
|
||||
inputs
|
||||
->Prepare.twoDistOrNumberFromRecord
|
||||
->process(~fn=twoArgs(SymbolicDist.Lognormal.fromMeanAndStdev)),
|
||||
),
|
||||
],
|
||||
)
|
||||
}
|
||||
|
||||
let allFunctions = [NormalFn.toFn, LognormalFn.toFn]
|
|
@ -387,13 +387,12 @@ let genericOutputToReducerValue = (o: DistributionOperation.outputType): result<
|
|||
| GenDistError(err) => Error(REDistributionError(err))
|
||||
}
|
||||
|
||||
let registered = FunctionRegistry.allFunctions
|
||||
let registered = FunctionRegistry_Library.allFunctions
|
||||
|
||||
let tryRegistry = (call: ExpressionValue.functionCall) => {
|
||||
let (fnName, args) = call
|
||||
let response = FunctionRegistry.Registry.matchAndRun(registered, fnName, args)
|
||||
let foo = response->E.O2.fmap(r => r->E.R2.errMap(s => Reducer_ErrorValue.RETodo(s)))
|
||||
foo
|
||||
let tryRegistry = ((fnName, args): ExpressionValue.functionCall) => {
|
||||
FunctionRegistry_Core.Registry.matchAndRun(registered, fnName, args)->E.O2.fmap(
|
||||
E.R2.errMap(_, s => Reducer_ErrorValue.RETodo(s)),
|
||||
)
|
||||
}
|
||||
|
||||
let dispatch = (call: ExpressionValue.functionCall, environment) => {
|
||||
|
|
Loading…
Reference in New Issue
Block a user