Merge pull request #424 from quantified-uncertainty/log-score-attempt
First attempt at LogScore
This commit is contained in:
commit
c95f94be61
|
@ -0,0 +1,57 @@
|
|||
open Jest
|
||||
open Expect
|
||||
open TestHelpers
|
||||
open FastCheck
|
||||
open Arbitrary
|
||||
open Property.Sync
|
||||
|
||||
describe("dotSubtract", () => {
|
||||
test("mean of normal minus exponential (unit)", () => {
|
||||
let mean = 0.0
|
||||
let rate = 10.0
|
||||
exception MeanFailed
|
||||
let dotDifference = DistributionOperation.Constructors.pointwiseSubtract(
|
||||
~env,
|
||||
mkNormal(mean, 1.0),
|
||||
mkExponential(rate),
|
||||
)
|
||||
let meanResult = E.R2.bind(DistributionOperation.Constructors.mean(~env), dotDifference)
|
||||
let meanAnalytical =
|
||||
mean -.
|
||||
SymbolicDist.Exponential.mean({rate: rate})->E.R2.toExn(
|
||||
"On trusted input this should never happen",
|
||||
)
|
||||
switch meanResult {
|
||||
| Ok(meanValue) => meanValue->expect->toBeCloseTo(meanAnalytical)
|
||||
| Error(_) => raise(MeanFailed)
|
||||
}
|
||||
})
|
||||
/*
|
||||
It seems like this test should work, and it's plausible that
|
||||
there's some bug in `pointwiseSubtract`
|
||||
*/
|
||||
Skip.test("mean of normal minus exponential (property)", () => {
|
||||
assert_(
|
||||
property2(float_(), floatRange(1e-5, 1e5), (mean, rate) => {
|
||||
// We limit ourselves to stdev=1 so that the integral is trivial
|
||||
let dotDifference = DistributionOperation.Constructors.pointwiseSubtract(
|
||||
~env,
|
||||
mkNormal(mean, 1.0),
|
||||
mkExponential(rate),
|
||||
)
|
||||
let meanResult = E.R2.bind(DistributionOperation.Constructors.mean(~env), dotDifference)
|
||||
// according to algebra or random variables,
|
||||
let meanAnalytical =
|
||||
mean -.
|
||||
SymbolicDist.Exponential.mean({rate: rate})->E.R2.toExn(
|
||||
"On trusted input this should never happen",
|
||||
)
|
||||
switch meanResult {
|
||||
| Ok(meanValue) => abs_float(meanValue -. meanAnalytical) /. abs_float(meanValue) < 1e-2 // 1% relative error
|
||||
| Error(err) => err === DistributionTypes.OperationError(DivisionByZeroError)
|
||||
}
|
||||
}),
|
||||
)
|
||||
pass
|
||||
})
|
||||
})
|
|
@ -0,0 +1,112 @@
|
|||
open Jest
|
||||
open Expect
|
||||
open TestHelpers
|
||||
|
||||
describe("kl divergence", () => {
|
||||
let klDivergence = DistributionOperation.Constructors.klDivergence(~env)
|
||||
exception KlFailed
|
||||
|
||||
let testUniform = (lowAnswer, highAnswer, lowPrediction, highPrediction) => {
|
||||
test("of two uniforms is equal to the analytic expression", () => {
|
||||
let answer =
|
||||
uniformMakeR(lowAnswer, highAnswer)->E.R2.errMap(s => DistributionTypes.ArgumentError(s))
|
||||
let prediction =
|
||||
uniformMakeR(
|
||||
lowPrediction,
|
||||
highPrediction,
|
||||
)->E.R2.errMap(s => DistributionTypes.ArgumentError(s))
|
||||
// integral along the support of the answer of answer.pdf(x) times log of prediction.pdf(x) divided by answer.pdf(x) dx
|
||||
let analyticalKl = Js.Math.log((highPrediction -. lowPrediction) /. (highAnswer -. lowAnswer))
|
||||
let kl = E.R.liftJoin2(klDivergence, prediction, answer)
|
||||
switch kl {
|
||||
| Ok(kl') => kl'->expect->toBeCloseTo(analyticalKl)
|
||||
| Error(err) => {
|
||||
Js.Console.log(DistributionTypes.Error.toString(err))
|
||||
raise(KlFailed)
|
||||
}
|
||||
}
|
||||
})
|
||||
}
|
||||
// The pair on the right (the answer) can be wider than the pair on the left (the prediction), but not the other way around.
|
||||
testUniform(0.0, 1.0, -1.0, 2.0)
|
||||
testUniform(0.0, 1.0, 0.0, 2.0) // equal left endpoints
|
||||
testUniform(0.0, 1.0, -1.0, 1.0) // equal rightendpoints
|
||||
testUniform(0.0, 1e1, 0.0, 1e1) // equal (klDivergence = 0)
|
||||
// testUniform(-1.0, 1.0, 0.0, 2.0)
|
||||
|
||||
test("of two normals is equal to the formula", () => {
|
||||
// This test case comes via Nuño https://github.com/quantified-uncertainty/squiggle/issues/433
|
||||
let mean1 = 4.0
|
||||
let mean2 = 1.0
|
||||
let stdev1 = 4.0
|
||||
let stdev2 = 1.0
|
||||
|
||||
let prediction =
|
||||
normalMakeR(mean1, stdev1)->E.R2.errMap(s => DistributionTypes.ArgumentError(s))
|
||||
let answer = normalMakeR(mean2, stdev2)->E.R2.errMap(s => DistributionTypes.ArgumentError(s))
|
||||
// https://stats.stackexchange.com/questions/7440/kl-divergence-between-two-univariate-gaussians
|
||||
let analyticalKl =
|
||||
Js.Math.log(stdev1 /. stdev2) +.
|
||||
(stdev2 ** 2.0 +. (mean2 -. mean1) ** 2.0) /. (2.0 *. stdev1 ** 2.0) -. 0.5
|
||||
let kl = E.R.liftJoin2(klDivergence, prediction, answer)
|
||||
|
||||
switch kl {
|
||||
| Ok(kl') => kl'->expect->toBeCloseTo(analyticalKl)
|
||||
| Error(err) => {
|
||||
Js.Console.log(DistributionTypes.Error.toString(err))
|
||||
raise(KlFailed)
|
||||
}
|
||||
}
|
||||
})
|
||||
})
|
||||
|
||||
describe("combine along support test", () => {
|
||||
// This tests the version of the function that we're NOT using. Haven't deleted the test in case we use the code later.
|
||||
test("combine along support test", _ => {
|
||||
let combineAlongSupportOfSecondArgument = XYShape.PointwiseCombination.combineAlongSupportOfSecondArgument0
|
||||
let lowAnswer = 0.0
|
||||
let highAnswer = 1.0
|
||||
let lowPrediction = 0.0
|
||||
let highPrediction = 2.0
|
||||
|
||||
let answer =
|
||||
uniformMakeR(lowAnswer, highAnswer)->E.R2.errMap(s => DistributionTypes.ArgumentError(s))
|
||||
let prediction =
|
||||
uniformMakeR(lowPrediction, highPrediction)->E.R2.errMap(s => DistributionTypes.ArgumentError(
|
||||
s,
|
||||
))
|
||||
let answerWrapped = E.R.fmap(a => run(FromDist(ToDist(ToPointSet), a)), answer)
|
||||
let predictionWrapped = E.R.fmap(a => run(FromDist(ToDist(ToPointSet), a)), prediction)
|
||||
|
||||
let interpolator = XYShape.XtoY.continuousInterpolator(#Stepwise, #UseZero)
|
||||
let integrand = PointSetDist_Scoring.KLDivergence.integrand
|
||||
|
||||
let result = switch (answerWrapped, predictionWrapped) {
|
||||
| (Ok(Dist(PointSet(Continuous(a)))), Ok(Dist(PointSet(Continuous(b))))) =>
|
||||
Some(combineAlongSupportOfSecondArgument(integrand, interpolator, a.xyShape, b.xyShape))
|
||||
| _ => None
|
||||
}
|
||||
result
|
||||
->expect
|
||||
->toEqual(
|
||||
Some(
|
||||
Ok({
|
||||
xs: [
|
||||
0.0,
|
||||
MagicNumbers.Epsilon.ten,
|
||||
2.0 *. MagicNumbers.Epsilon.ten,
|
||||
1.0 -. MagicNumbers.Epsilon.ten,
|
||||
1.0,
|
||||
],
|
||||
ys: [
|
||||
-0.34657359027997264,
|
||||
-0.34657359027997264,
|
||||
-0.34657359027997264,
|
||||
-0.34657359027997264,
|
||||
-0.34657359027997264,
|
||||
],
|
||||
}),
|
||||
),
|
||||
)
|
||||
})
|
||||
})
|
|
@ -0,0 +1,38 @@
|
|||
open Jest
|
||||
open Expect
|
||||
open TestHelpers
|
||||
|
||||
describe("Scale logarithm", () => {
|
||||
/* These tests may not be important, because scalelog isn't normalized
|
||||
The first one may be failing for a number of reasons.
|
||||
*/
|
||||
Skip.test("mean of the base e scalar logarithm of an exponential(10)", () => {
|
||||
let rate = 10.0
|
||||
let scalelog = DistributionOperation.Constructors.scaleLogarithm(
|
||||
~env,
|
||||
mkExponential(rate),
|
||||
MagicNumbers.Math.e,
|
||||
)
|
||||
|
||||
let meanResult = E.R2.bind(DistributionOperation.Constructors.mean(~env), scalelog)
|
||||
// expected value of log of exponential distribution.
|
||||
let meanAnalytical = Js.Math.log(rate) +. 1.0
|
||||
switch meanResult {
|
||||
| Ok(meanValue) => meanValue->expect->toBeCloseTo(meanAnalytical)
|
||||
| Error(err) => err->expect->toBe(DistributionTypes.OperationError(DivisionByZeroError))
|
||||
}
|
||||
})
|
||||
let low = 10.0
|
||||
let high = 100.0
|
||||
let scalelog = DistributionOperation.Constructors.scaleLogarithm(~env, mkUniform(low, high), 2.0)
|
||||
|
||||
test("mean of the base 2 scalar logarithm of a uniform(10, 100)", () => {
|
||||
//For uniform pdf `_ => 1 / (b - a)`, the expected value of log of uniform is `integral from a to b of x * log(1 / (b -a)) dx`
|
||||
let meanResult = E.R2.bind(DistributionOperation.Constructors.mean(~env), scalelog)
|
||||
let meanAnalytical = -.Js.Math.log2(high -. low) /. 2.0 *. (high ** 2.0 -. low ** 2.0) // -. Js.Math.log2(high -. low)
|
||||
switch meanResult {
|
||||
| Ok(meanValue) => meanValue->expect->toBeCloseTo(meanAnalytical)
|
||||
| Error(err) => err->expect->toEqual(DistributionTypes.OperationError(NegativeInfinityError))
|
||||
}
|
||||
})
|
||||
})
|
|
@ -60,3 +60,13 @@ let cauchyMake = SymbolicDist.Cauchy.make
|
|||
let lognormalMake = SymbolicDist.Lognormal.make
|
||||
let triangularMake = SymbolicDist.Triangular.make
|
||||
let floatMake = SymbolicDist.Float.make
|
||||
|
||||
let fmapGenDist = symbdistres => E.R.fmap(s => DistributionTypes.Symbolic(s), symbdistres)
|
||||
let normalMakeR = (mean, stdev) => fmapGenDist(SymbolicDist.Normal.make(mean, stdev))
|
||||
let betaMakeR = (alpha, beta) => fmapGenDist(SymbolicDist.Beta.make(alpha, beta))
|
||||
let exponentialMakeR = rate => fmapGenDist(SymbolicDist.Exponential.make(rate))
|
||||
let uniformMakeR = (low, high) => fmapGenDist(SymbolicDist.Uniform.make(low, high))
|
||||
let cauchyMakeR = (local, rate) => fmapGenDist(SymbolicDist.Cauchy.make(local, rate))
|
||||
let lognormalMakeR = (mu, sigma) => fmapGenDist(SymbolicDist.Lognormal.make(mu, sigma))
|
||||
let triangularMakeR = (low, mode, high) =>
|
||||
fmapGenDist(SymbolicDist.Triangular.make(low, mode, high))
|
||||
|
|
|
@ -38,19 +38,6 @@ describe("XYShapes", () => {
|
|||
)
|
||||
})
|
||||
|
||||
describe("logScorePoint", () => {
|
||||
makeTest("When identical", XYShape.logScorePoint(30, pointSetDist1, pointSetDist1), Some(0.0))
|
||||
makeTest(
|
||||
"When similar",
|
||||
XYShape.logScorePoint(30, pointSetDist1, pointSetDist2),
|
||||
Some(1.658971191043856),
|
||||
)
|
||||
makeTest(
|
||||
"When very different",
|
||||
XYShape.logScorePoint(30, pointSetDist1, pointSetDist3),
|
||||
Some(210.3721280423322),
|
||||
)
|
||||
})
|
||||
describe("integrateWithTriangles", () =>
|
||||
makeTest(
|
||||
"integrates correctly",
|
||||
|
|
|
@ -20,7 +20,8 @@
|
|||
],
|
||||
"suffix": ".bs.js",
|
||||
"namespace": true,
|
||||
"bs-dependencies": ["@glennsl/rescript-jest", "bisect_ppx"],
|
||||
"bs-dependencies": ["bisect_ppx"],
|
||||
"bs-dev-dependencies": ["@glennsl/rescript-jest", "rescript-fast-check"],
|
||||
"gentypeconfig": {
|
||||
"language": "typescript",
|
||||
"module": "commonjs",
|
||||
|
|
|
@ -38,7 +38,7 @@
|
|||
"rescript": "^9.1.4",
|
||||
"jstat": "^1.9.5",
|
||||
"pdfast": "^0.2.0",
|
||||
"mathjs": "^10.5.0"
|
||||
"mathjs": "10.5.0"
|
||||
},
|
||||
"devDependencies": {
|
||||
"bisect_ppx": "^2.7.1",
|
||||
|
|
|
@ -10,8 +10,8 @@ type env = {
|
|||
}
|
||||
|
||||
let defaultEnv = {
|
||||
sampleCount: 10000,
|
||||
xyPointLength: 10000,
|
||||
sampleCount: MagicNumbers.Environment.defaultSampleCount,
|
||||
xyPointLength: MagicNumbers.Environment.defaultXYPointLength,
|
||||
}
|
||||
|
||||
type outputType =
|
||||
|
@ -128,7 +128,7 @@ let rec run = (~env, functionCallInfo: functionCallInfo): outputType => {
|
|||
let fromDistFn = (
|
||||
subFnName: DistributionTypes.DistributionOperation.fromDist,
|
||||
dist: genericDist,
|
||||
) => {
|
||||
): outputType => {
|
||||
let response = switch subFnName {
|
||||
| ToFloat(distToFloatOperation) =>
|
||||
GenericDist.toFloatOperation(dist, ~toPointSetFn, ~distToFloatOperation)
|
||||
|
@ -144,6 +144,10 @@ let rec run = (~env, functionCallInfo: functionCallInfo): outputType => {
|
|||
Dist(dist)
|
||||
}
|
||||
| ToDist(Normalize) => dist->GenericDist.normalize->Dist
|
||||
| ToScore(KLDivergence(t2)) =>
|
||||
GenericDist.klDivergence(dist, t2, ~toPointSetFn)
|
||||
->E.R2.fmap(r => Float(r))
|
||||
->OutputLocal.fromResult
|
||||
| ToBool(IsNormalized) => dist->GenericDist.isNormalized->Bool
|
||||
| ToDist(Truncate(leftCutoff, rightCutoff)) =>
|
||||
GenericDist.truncate(~toPointSetFn, ~leftCutoff, ~rightCutoff, dist, ())
|
||||
|
@ -159,6 +163,15 @@ let rec run = (~env, functionCallInfo: functionCallInfo): outputType => {
|
|||
->GenericDist.toPointSet(~xyPointLength, ~sampleCount, ())
|
||||
->E.R2.fmap(r => Dist(PointSet(r)))
|
||||
->OutputLocal.fromResult
|
||||
| ToDist(Scale(#LogarithmWithThreshold(eps), f)) =>
|
||||
dist
|
||||
->GenericDist.pointwiseCombinationFloat(
|
||||
~toPointSetFn,
|
||||
~algebraicCombination=#LogarithmWithThreshold(eps),
|
||||
~f,
|
||||
)
|
||||
->E.R2.fmap(r => Dist(r))
|
||||
->OutputLocal.fromResult
|
||||
| ToDist(Scale(#Logarithm, f)) =>
|
||||
dist
|
||||
->GenericDist.pointwiseCombinationFloat(~toPointSetFn, ~algebraicCombination=#Logarithm, ~f)
|
||||
|
@ -248,6 +261,7 @@ module Constructors = {
|
|||
let pdf = (~env, dist, f) => C.pdf(dist, f)->run(~env)->toFloatR
|
||||
let normalize = (~env, dist) => C.normalize(dist)->run(~env)->toDistR
|
||||
let isNormalized = (~env, dist) => C.isNormalized(dist)->run(~env)->toBoolR
|
||||
let klDivergence = (~env, dist1, dist2) => C.klDivergence(dist1, dist2)->run(~env)->toFloatR
|
||||
let toPointSet = (~env, dist) => C.toPointSet(dist)->run(~env)->toDistR
|
||||
let toSampleSet = (~env, dist, n) => C.toSampleSet(dist, n)->run(~env)->toDistR
|
||||
let fromSamples = (~env, xs) => C.fromSamples(xs)->run(~env)->toDistR
|
||||
|
@ -266,6 +280,8 @@ module Constructors = {
|
|||
let algebraicLogarithm = (~env, dist1, dist2) =>
|
||||
C.algebraicLogarithm(dist1, dist2)->run(~env)->toDistR
|
||||
let algebraicPower = (~env, dist1, dist2) => C.algebraicPower(dist1, dist2)->run(~env)->toDistR
|
||||
let scalePower = (~env, dist, n) => C.scalePower(dist, n)->run(~env)->toDistR
|
||||
let scaleLogarithm = (~env, dist, n) => C.scaleLogarithm(dist, n)->run(~env)->toDistR
|
||||
let pointwiseAdd = (~env, dist1, dist2) => C.pointwiseAdd(dist1, dist2)->run(~env)->toDistR
|
||||
let pointwiseMultiply = (~env, dist1, dist2) =>
|
||||
C.pointwiseMultiply(dist1, dist2)->run(~env)->toDistR
|
||||
|
|
|
@ -60,6 +60,8 @@ module Constructors: {
|
|||
@genType
|
||||
let isNormalized: (~env: env, genericDist) => result<bool, error>
|
||||
@genType
|
||||
let klDivergence: (~env: env, genericDist, genericDist) => result<float, error>
|
||||
@genType
|
||||
let toPointSet: (~env: env, genericDist) => result<genericDist, error>
|
||||
@genType
|
||||
let toSampleSet: (~env: env, genericDist, int) => result<genericDist, error>
|
||||
|
@ -86,6 +88,10 @@ module Constructors: {
|
|||
@genType
|
||||
let algebraicPower: (~env: env, genericDist, genericDist) => result<genericDist, error>
|
||||
@genType
|
||||
let scaleLogarithm: (~env: env, genericDist, float) => result<genericDist, error>
|
||||
@genType
|
||||
let scalePower: (~env: env, genericDist, float) => result<genericDist, error>
|
||||
@genType
|
||||
let pointwiseAdd: (~env: env, genericDist, genericDist) => result<genericDist, error>
|
||||
@genType
|
||||
let pointwiseMultiply: (~env: env, genericDist, genericDist) => result<genericDist, error>
|
||||
|
|
|
@ -72,6 +72,7 @@ module DistributionOperation = {
|
|||
type toScaleFn = [
|
||||
| #Power
|
||||
| #Logarithm
|
||||
| #LogarithmWithThreshold(float)
|
||||
]
|
||||
|
||||
type toDist =
|
||||
|
@ -90,9 +91,12 @@ module DistributionOperation = {
|
|||
| ToString
|
||||
| ToSparkline(int)
|
||||
|
||||
type toScore = KLDivergence(genericDist)
|
||||
|
||||
type fromDist =
|
||||
| ToFloat(toFloat)
|
||||
| ToDist(toDist)
|
||||
| ToScore(toScore)
|
||||
| ToDistCombination(direction, Operation.Algebraic.t, [#Dist(genericDist) | #Float(float)])
|
||||
| ToString(toString)
|
||||
| ToBool(toBool)
|
||||
|
@ -115,6 +119,7 @@ module DistributionOperation = {
|
|||
| ToFloat(#Pdf(r)) => `pdf(${E.Float.toFixed(r)})`
|
||||
| ToFloat(#Sample) => `sample`
|
||||
| ToFloat(#IntegralSum) => `integralSum`
|
||||
| ToScore(KLDivergence(_)) => `klDivergence`
|
||||
| ToDist(Normalize) => `normalize`
|
||||
| ToDist(ToPointSet) => `toPointSet`
|
||||
| ToDist(ToSampleSet(r)) => `toSampleSet(${E.I.toString(r)})`
|
||||
|
@ -122,6 +127,8 @@ module DistributionOperation = {
|
|||
| ToDist(Inspect) => `inspect`
|
||||
| ToDist(Scale(#Power, r)) => `scalePower(${E.Float.toFixed(r)})`
|
||||
| ToDist(Scale(#Logarithm, r)) => `scaleLog(${E.Float.toFixed(r)})`
|
||||
| ToDist(Scale(#LogarithmWithThreshold(eps), r)) =>
|
||||
`scaleLogWithThreshold(${E.Float.toFixed(r)}, epsilon=${E.Float.toFixed(eps)})`
|
||||
| ToString(ToString) => `toString`
|
||||
| ToString(ToSparkline(n)) => `toSparkline(${E.I.toString(n)})`
|
||||
| ToBool(IsNormalized) => `isNormalized`
|
||||
|
@ -153,8 +160,13 @@ module Constructors = {
|
|||
let fromSamples = (xs): t => FromSamples(xs)
|
||||
let truncate = (dist, left, right): t => FromDist(ToDist(Truncate(left, right)), dist)
|
||||
let inspect = (dist): t => FromDist(ToDist(Inspect), dist)
|
||||
let klDivergence = (dist1, dist2): t => FromDist(ToScore(KLDivergence(dist2)), dist1)
|
||||
let scalePower = (dist, n): t => FromDist(ToDist(Scale(#Power, n)), dist)
|
||||
let scaleLogarithm = (dist, n): t => FromDist(ToDist(Scale(#Logarithm, n)), dist)
|
||||
let scaleLogarithmWithThreshold = (dist, n, eps): t => FromDist(
|
||||
ToDist(Scale(#LogarithmWithThreshold(eps), n)),
|
||||
dist,
|
||||
)
|
||||
let toString = (dist): t => FromDist(ToString(ToString), dist)
|
||||
let toSparkline = (dist, n): t => FromDist(ToString(ToSparkline(n)), dist)
|
||||
let algebraicAdd = (dist1, dist2: genericDist): t => FromDist(
|
||||
|
|
|
@ -59,6 +59,13 @@ let integralEndY = (t: t): float =>
|
|||
|
||||
let isNormalized = (t: t): bool => Js.Math.abs_float(integralEndY(t) -. 1.0) < 1e-7
|
||||
|
||||
let klDivergence = (t1, t2, ~toPointSetFn: toPointSetFn): result<float, error> => {
|
||||
let pointSets = E.R.merge(toPointSetFn(t1), toPointSetFn(t2))
|
||||
pointSets |> E.R2.bind(((a, b)) =>
|
||||
PointSetDist.T.klDivergence(a, b)->E.R2.errMap(x => DistributionTypes.OperationError(x))
|
||||
)
|
||||
}
|
||||
|
||||
let toFloatOperation = (
|
||||
t,
|
||||
~toPointSetFn: toPointSetFn,
|
||||
|
@ -384,14 +391,12 @@ let pointwiseCombinationFloat = (
|
|||
~algebraicCombination: Operation.algebraicOperation,
|
||||
~f: float,
|
||||
): result<t, error> => {
|
||||
let m = switch algebraicCombination {
|
||||
| #Add | #Subtract => Error(DistributionTypes.DistributionVerticalShiftIsInvalid)
|
||||
| (#Multiply | #Divide | #Power | #Logarithm) as arithmeticOperation =>
|
||||
let executeCombination = arithOp =>
|
||||
toPointSetFn(t)->E.R.bind(t => {
|
||||
//TODO: Move to PointSet codebase
|
||||
let fn = (secondary, main) => Operation.Scale.toFn(arithmeticOperation, main, secondary)
|
||||
let integralSumCacheFn = Operation.Scale.toIntegralSumCacheFn(arithmeticOperation)
|
||||
let integralCacheFn = Operation.Scale.toIntegralCacheFn(arithmeticOperation)
|
||||
let fn = (secondary, main) => Operation.Scale.toFn(arithOp, main, secondary)
|
||||
let integralSumCacheFn = Operation.Scale.toIntegralSumCacheFn(arithOp)
|
||||
let integralCacheFn = Operation.Scale.toIntegralCacheFn(arithOp)
|
||||
PointSetDist.T.mapYResult(
|
||||
~integralSumCacheFn=integralSumCacheFn(f),
|
||||
~integralCacheFn=integralCacheFn(f),
|
||||
|
@ -399,6 +404,11 @@ let pointwiseCombinationFloat = (
|
|||
t,
|
||||
)->E.R2.errMap(x => DistributionTypes.OperationError(x))
|
||||
})
|
||||
let m = switch algebraicCombination {
|
||||
| #Add | #Subtract => Error(DistributionTypes.DistributionVerticalShiftIsInvalid)
|
||||
| (#Multiply | #Divide | #Power | #Logarithm) as arithmeticOperation =>
|
||||
executeCombination(arithmeticOperation)
|
||||
| #LogarithmWithThreshold(eps) => executeCombination(#LogarithmWithThreshold(eps))
|
||||
}
|
||||
m->E.R2.fmap(r => DistributionTypes.PointSet(r))
|
||||
}
|
||||
|
|
|
@ -23,6 +23,8 @@ let toFloatOperation: (
|
|||
~distToFloatOperation: DistributionTypes.DistributionOperation.toFloat,
|
||||
) => result<float, error>
|
||||
|
||||
let klDivergence: (t, t, ~toPointSetFn: toPointSetFn) => result<float, error>
|
||||
|
||||
@genType
|
||||
let toPointSet: (
|
||||
t,
|
||||
|
|
|
@ -86,6 +86,7 @@ let stepwiseToLinear = (t: t): t =>
|
|||
|
||||
// Note: This results in a distribution with as many points as the sum of those in t1 and t2.
|
||||
let combinePointwise = (
|
||||
~combiner=XYShape.PointwiseCombination.combine,
|
||||
~integralSumCachesFn=(_, _) => None,
|
||||
~distributionType: PointSetTypes.distributionType=#PDF,
|
||||
fn: (float, float) => result<float, Operation.Error.t>,
|
||||
|
@ -119,7 +120,7 @@ let combinePointwise = (
|
|||
|
||||
let interpolator = XYShape.XtoY.continuousInterpolator(t1.interpolation, extrapolation)
|
||||
|
||||
XYShape.PointwiseCombination.combine(fn, interpolator, t1.xyShape, t2.xyShape)->E.R2.fmap(x =>
|
||||
combiner(fn, interpolator, t1.xyShape, t2.xyShape)->E.R2.fmap(x =>
|
||||
make(~integralSumCache=combinedIntegralSum, x)
|
||||
)
|
||||
}
|
||||
|
@ -269,11 +270,27 @@ module T = Dist({
|
|||
}
|
||||
let variance = (t: t): float =>
|
||||
XYShape.Analysis.getVarianceDangerously(t, mean, Analysis.getMeanOfSquares)
|
||||
|
||||
let klDivergence = (prediction: t, answer: t) => {
|
||||
let newShape = XYShape.PointwiseCombination.combineAlongSupportOfSecondArgument(
|
||||
PointSetDist_Scoring.KLDivergence.integrand,
|
||||
prediction.xyShape,
|
||||
answer.xyShape,
|
||||
)
|
||||
let xyShapeToContinuous: XYShape.xyShape => t = xyShape => {
|
||||
xyShape: xyShape,
|
||||
interpolation: #Linear,
|
||||
integralSumCache: None,
|
||||
integralCache: None,
|
||||
}
|
||||
newShape->E.R2.fmap(x => x->xyShapeToContinuous->integralEndY)
|
||||
}
|
||||
})
|
||||
|
||||
let isNormalized = (t: t): bool => {
|
||||
let areaUnderIntegral = t |> updateIntegralCache(Some(T.integral(t))) |> T.integralEndY
|
||||
areaUnderIntegral < 1. +. 1e-7 && areaUnderIntegral > 1. -. 1e-7
|
||||
areaUnderIntegral < 1. +. MagicNumbers.Epsilon.seven &&
|
||||
areaUnderIntegral > 1. -. MagicNumbers.Epsilon.seven
|
||||
}
|
||||
|
||||
let downsampleEquallyOverX = (length, t): t =>
|
||||
|
|
|
@ -33,28 +33,26 @@ let shapeFn = (fn, t: t) => t |> getShape |> fn
|
|||
let lastY = (t: t) => t |> getShape |> XYShape.T.lastY
|
||||
|
||||
let combinePointwise = (
|
||||
~combiner=XYShape.PointwiseCombination.combine,
|
||||
~integralSumCachesFn=(_, _) => None,
|
||||
fn,
|
||||
~fn=(a, b) => Ok(a +. b),
|
||||
t1: PointSetTypes.discreteShape,
|
||||
t2: PointSetTypes.discreteShape,
|
||||
): result<PointSetTypes.discreteShape, 'e> => {
|
||||
let combinedIntegralSum = Common.combineIntegralSums(
|
||||
integralSumCachesFn,
|
||||
t1.integralSumCache,
|
||||
t2.integralSumCache,
|
||||
)
|
||||
// let combinedIntegralSum = Common.combineIntegralSums(
|
||||
// integralSumCachesFn,
|
||||
// t1.integralSumCache,
|
||||
// t2.integralSumCache,
|
||||
// )
|
||||
|
||||
// TODO: does it ever make sense to pointwise combine the integrals here?
|
||||
// It could be done for pointwise additions, but is that ever needed?
|
||||
|
||||
make(
|
||||
~integralSumCache=combinedIntegralSum,
|
||||
XYShape.PointwiseCombination.combine(
|
||||
fn,
|
||||
XYShape.XtoY.discreteInterpolator,
|
||||
t1.xyShape,
|
||||
t2.xyShape,
|
||||
)->E.R.toExn("Addition operation should never fail", _),
|
||||
combiner(fn, XYShape.XtoY.discreteInterpolator, t1.xyShape, t2.xyShape)->E.R.toExn(
|
||||
"Addition operation should never fail",
|
||||
_,
|
||||
),
|
||||
)->Ok
|
||||
}
|
||||
|
||||
|
@ -63,7 +61,7 @@ let reduce = (
|
|||
fn: (float, float) => result<float, 'e>,
|
||||
discreteShapes: array<PointSetTypes.discreteShape>,
|
||||
): result<t, 'e> => {
|
||||
let merge = combinePointwise(~integralSumCachesFn, fn)
|
||||
let merge = combinePointwise(~integralSumCachesFn, ~fn)
|
||||
discreteShapes |> E.A.R.foldM(merge, empty)
|
||||
}
|
||||
|
||||
|
@ -165,6 +163,7 @@ module T = Dist({
|
|||
}
|
||||
|
||||
let integralEndY = (t: t) => t.integralSumCache |> E.O.default(t |> integral |> Continuous.lastY)
|
||||
let integralEndYResult = (t: t) => t->integralEndY->Ok
|
||||
let minX = shapeFn(XYShape.T.minX)
|
||||
let maxX = shapeFn(XYShape.T.maxX)
|
||||
let toDiscreteProbabilityMassFraction = _ => 1.0
|
||||
|
@ -228,4 +227,13 @@ module T = Dist({
|
|||
let getMeanOfSquares = t => t |> shapeMap(XYShape.T.square) |> mean
|
||||
XYShape.Analysis.getVarianceDangerously(t, mean, getMeanOfSquares)
|
||||
}
|
||||
|
||||
let klDivergence = (prediction: t, answer: t) => {
|
||||
combinePointwise(
|
||||
~combiner=XYShape.PointwiseCombination.combineAlongSupportOfSecondArgument0,
|
||||
~fn=PointSetDist_Scoring.KLDivergence.integrand,
|
||||
prediction,
|
||||
answer,
|
||||
) |> E.R2.bind(integralEndYResult)
|
||||
}
|
||||
})
|
||||
|
|
|
@ -33,6 +33,7 @@ module type dist = {
|
|||
|
||||
let mean: t => float
|
||||
let variance: t => float
|
||||
let klDivergence: (t, t) => result<float, Operation.Error.t>
|
||||
}
|
||||
|
||||
module Dist = (T: dist) => {
|
||||
|
@ -55,6 +56,7 @@ module Dist = (T: dist) => {
|
|||
let mean = T.mean
|
||||
let variance = T.variance
|
||||
let integralEndY = T.integralEndY
|
||||
let klDivergence = T.klDivergence
|
||||
|
||||
let updateIntegralCache = T.updateIntegralCache
|
||||
|
||||
|
|
|
@ -36,6 +36,47 @@ let updateIntegralCache = (integralCache, t: t): t => {
|
|||
integralCache: integralCache,
|
||||
}
|
||||
|
||||
let combinePointwise = (
|
||||
~integralSumCachesFn=(_, _) => None,
|
||||
~integralCachesFn=(_, _) => None,
|
||||
fn: (float, float) => result<float, 'e>,
|
||||
t1: t,
|
||||
t2: t,
|
||||
): result<t, 'e> => {
|
||||
let reducedDiscrete =
|
||||
[t1, t2]
|
||||
|> E.A.fmap(toDiscrete)
|
||||
|> E.A.O.concatSomes
|
||||
|> Discrete.reduce(~integralSumCachesFn, fn)
|
||||
|> E.R.toExn("Theoretically unreachable state")
|
||||
|
||||
let reducedContinuous =
|
||||
[t1, t2]
|
||||
|> E.A.fmap(toContinuous)
|
||||
|> E.A.O.concatSomes
|
||||
|> Continuous.reduce(~integralSumCachesFn, fn)
|
||||
|
||||
let combinedIntegralSum = Common.combineIntegralSums(
|
||||
integralSumCachesFn,
|
||||
t1.integralSumCache,
|
||||
t2.integralSumCache,
|
||||
)
|
||||
|
||||
let combinedIntegral = Common.combineIntegrals(
|
||||
integralCachesFn,
|
||||
t1.integralCache,
|
||||
t2.integralCache,
|
||||
)
|
||||
reducedContinuous->E.R2.fmap(continuous =>
|
||||
make(
|
||||
~integralSumCache=combinedIntegralSum,
|
||||
~integralCache=combinedIntegral,
|
||||
~discrete=reducedDiscrete,
|
||||
~continuous,
|
||||
)
|
||||
)
|
||||
}
|
||||
|
||||
module T = Dist({
|
||||
type t = PointSetTypes.mixedShape
|
||||
type integral = PointSetTypes.continuousShape
|
||||
|
@ -259,6 +300,12 @@ module T = Dist({
|
|||
| _ => XYShape.Analysis.getVarianceDangerously(t, mean, getMeanOfSquares)
|
||||
}
|
||||
}
|
||||
|
||||
let klDivergence = (prediction: t, answer: t) => {
|
||||
combinePointwise(PointSetDist_Scoring.KLDivergence.integrand, prediction, answer) |> E.R.fmap(
|
||||
integralEndY,
|
||||
)
|
||||
}
|
||||
})
|
||||
|
||||
let combineAlgebraically = (op: Operation.convolutionOperation, t1: t, t2: t): t => {
|
||||
|
|
|
@ -86,7 +86,7 @@ let combinePointwise = (
|
|||
| (Discrete(m1), Discrete(m2)) =>
|
||||
Discrete.combinePointwise(
|
||||
~integralSumCachesFn,
|
||||
fn,
|
||||
~fn,
|
||||
m1,
|
||||
m2,
|
||||
)->E.R2.fmap(x => PointSetTypes.Discrete(x))
|
||||
|
@ -195,6 +195,12 @@ module T = Dist({
|
|||
| Discrete(m) => Discrete.T.variance(m)
|
||||
| Continuous(m) => Continuous.T.variance(m)
|
||||
}
|
||||
|
||||
let klDivergence = (t1: t, t2: t) =>
|
||||
switch (t1, t2) {
|
||||
| (Continuous(t1), Continuous(t2)) => Continuous.T.klDivergence(t1, t2)
|
||||
| _ => Error(NotYetImplemented)
|
||||
}
|
||||
})
|
||||
|
||||
let pdf = (f: float, t: t) => {
|
||||
|
|
|
@ -0,0 +1,15 @@
|
|||
module KLDivergence = {
|
||||
let logFn = Js.Math.log // base e
|
||||
let integrand = (predictionElement: float, answerElement: float): result<
|
||||
float,
|
||||
Operation.Error.t,
|
||||
> =>
|
||||
if answerElement == 0.0 {
|
||||
Ok(0.0)
|
||||
} else if predictionElement == 0.0 {
|
||||
Error(Operation.NegativeInfinityError)
|
||||
} else {
|
||||
let quot = predictionElement /. answerElement
|
||||
quot < 0.0 ? Error(Operation.ComplexNumberError) : Ok(-.answerElement *. logFn(quot))
|
||||
}
|
||||
}
|
|
@ -396,8 +396,9 @@ module T = {
|
|||
| (#ByWeight, #Uniform(n)) =>
|
||||
// In `ByWeight mode, uniform distributions get special treatment because we need two x's
|
||||
// on either side for proper rendering (just left and right of the discontinuities).
|
||||
let dx = 0.00001 *. (n.high -. n.low)
|
||||
[n.low -. dx, n.low +. dx, n.high -. dx, n.high +. dx]
|
||||
let distance = n.high -. n.low
|
||||
let dx = MagicNumbers.Epsilon.ten *. distance
|
||||
[n.low -. dx, n.low, n.low +. dx, n.high -. dx, n.high, n.high +. dx]
|
||||
| (#ByWeight, _) =>
|
||||
let ys = E.A.Floats.range(minCdfValue, maxCdfValue, n)
|
||||
ys |> E.A.fmap(y => inv(y, dist))
|
||||
|
|
|
@ -6,6 +6,7 @@ module Math = {
|
|||
module Epsilon = {
|
||||
let ten = 1e-10
|
||||
let seven = 1e-7
|
||||
let five = 1e-5
|
||||
}
|
||||
|
||||
module Environment = {
|
||||
|
|
|
@ -14,7 +14,7 @@ let eArray = anArray => anArray->BExpressionValue.EvArray->BExpressionT.EValue
|
|||
let eArrayString = anArray => anArray->BExpressionValue.EvArrayString->BExpressionT.EValue
|
||||
|
||||
let eBindings = (anArray: array<(string, BExpressionValue.expressionValue)>) =>
|
||||
anArray->Js.Dict.fromArray->EvRecord->BExpressionT.EValue
|
||||
anArray->Js.Dict.fromArray->BExpressionValue.EvRecord->BExpressionT.EValue
|
||||
|
||||
let eBool = aBool => aBool->BExpressionValue.EvBool->BExpressionT.EValue
|
||||
|
||||
|
|
|
@ -79,6 +79,7 @@ module Helpers = {
|
|||
dist1,
|
||||
)->runGenericOperation
|
||||
}
|
||||
|
||||
let parseNumber = (args: expressionValue): Belt.Result.t<float, string> =>
|
||||
switch args {
|
||||
| EvNumber(x) => Ok(x)
|
||||
|
@ -212,6 +213,8 @@ let dispatchToGenericOutput = (call: ExpressionValue.functionCall, _environment)
|
|||
a,
|
||||
)->Some
|
||||
| ("normalize", [EvDistribution(dist)]) => Helpers.toDistFn(Normalize, dist)
|
||||
| ("klDivergence", [EvDistribution(a), EvDistribution(b)]) =>
|
||||
Some(runGenericOperation(FromDist(ToScore(KLDivergence(b)), a)))
|
||||
| ("isNormalized", [EvDistribution(dist)]) => Helpers.toBoolFn(IsNormalized, dist)
|
||||
| ("toPointSet", [EvDistribution(dist)]) => Helpers.toDistFn(ToPointSet, dist)
|
||||
| ("scaleLog", [EvDistribution(dist)]) =>
|
||||
|
@ -219,6 +222,8 @@ let dispatchToGenericOutput = (call: ExpressionValue.functionCall, _environment)
|
|||
| ("scaleLog10", [EvDistribution(dist)]) => Helpers.toDistFn(Scale(#Logarithm, 10.0), dist)
|
||||
| ("scaleLog", [EvDistribution(dist), EvNumber(float)]) =>
|
||||
Helpers.toDistFn(Scale(#Logarithm, float), dist)
|
||||
| ("scaleLogWithThreshold", [EvDistribution(dist), EvNumber(base), EvNumber(eps)]) =>
|
||||
Helpers.toDistFn(Scale(#LogarithmWithThreshold(eps), base), dist)
|
||||
| ("scalePow", [EvDistribution(dist), EvNumber(float)]) =>
|
||||
Helpers.toDistFn(Scale(#Power, float), dist)
|
||||
| ("scaleExp", [EvDistribution(dist)]) =>
|
||||
|
|
|
@ -607,6 +607,9 @@ module A = {
|
|||
let filter = Js.Array.filter
|
||||
let joinWith = Js.Array.joinWith
|
||||
|
||||
let all = (p: 'a => bool, xs: array<'a>): bool => length(filter(p, xs)) == length(xs)
|
||||
let any = (p: 'a => bool, xs: array<'a>): bool => length(filter(p, xs)) > 0
|
||||
|
||||
module O = {
|
||||
let concatSomes = (optionals: array<option<'a>>): array<'a> =>
|
||||
optionals
|
||||
|
|
|
@ -8,6 +8,7 @@ type algebraicOperation = [
|
|||
| #Divide
|
||||
| #Power
|
||||
| #Logarithm
|
||||
| #LogarithmWithThreshold(float)
|
||||
]
|
||||
|
||||
type convolutionOperation = [
|
||||
|
@ -18,7 +19,7 @@ type convolutionOperation = [
|
|||
|
||||
@genType
|
||||
type pointwiseOperation = [#Add | #Multiply | #Power]
|
||||
type scaleOperation = [#Multiply | #Power | #Logarithm | #Divide]
|
||||
type scaleOperation = [#Multiply | #Power | #Logarithm | #LogarithmWithThreshold(float) | #Divide]
|
||||
type distToFloatOperation = [
|
||||
| #Pdf(float)
|
||||
| #Cdf(float)
|
||||
|
@ -35,7 +36,7 @@ module Convolution = {
|
|||
| #Add => Some(#Add)
|
||||
| #Subtract => Some(#Subtract)
|
||||
| #Multiply => Some(#Multiply)
|
||||
| #Divide | #Power | #Logarithm => None
|
||||
| #Divide | #Power | #Logarithm | #LogarithmWithThreshold(_) => None
|
||||
}
|
||||
|
||||
let canDoAlgebraicOperation = (op: algebraicOperation): bool =>
|
||||
|
@ -52,6 +53,10 @@ module Convolution = {
|
|||
type operationError =
|
||||
| DivisionByZeroError
|
||||
| ComplexNumberError
|
||||
| InfinityError
|
||||
| NegativeInfinityError
|
||||
| LogicallyInconsistentPathwayError
|
||||
| NotYetImplemented // should be removed when `klDivergence` for mixed and discrete is implemented.
|
||||
|
||||
@genType
|
||||
module Error = {
|
||||
|
@ -62,6 +67,10 @@ module Error = {
|
|||
switch err {
|
||||
| DivisionByZeroError => "Cannot divide by zero"
|
||||
| ComplexNumberError => "Operation returned complex result"
|
||||
| InfinityError => "Operation returned positive infinity"
|
||||
| NegativeInfinityError => "Operation returned negative infinity"
|
||||
| LogicallyInconsistentPathwayError => "This pathway should have been logically unreachable"
|
||||
| NotYetImplemented => "This pathway is not yet implemented"
|
||||
}
|
||||
}
|
||||
|
||||
|
@ -86,6 +95,8 @@ let logarithm = (a: float, b: float): result<float, Error.t> =>
|
|||
Ok(0.)
|
||||
} else if a > 0.0 && b > 0.0 {
|
||||
Ok(log(a) /. log(b))
|
||||
} else if a == 0.0 {
|
||||
Error(NegativeInfinityError)
|
||||
} else {
|
||||
Error(ComplexNumberError)
|
||||
}
|
||||
|
@ -102,6 +113,12 @@ module Algebraic = {
|
|||
| #Power => power(a, b)
|
||||
| #Divide => divide(a, b)
|
||||
| #Logarithm => logarithm(a, b)
|
||||
| #LogarithmWithThreshold(eps) =>
|
||||
if a < eps {
|
||||
Ok(0.0)
|
||||
} else {
|
||||
logarithm(a, b)
|
||||
}
|
||||
}
|
||||
|
||||
let toString = x =>
|
||||
|
@ -112,6 +129,7 @@ module Algebraic = {
|
|||
| #Power => "**"
|
||||
| #Divide => "/"
|
||||
| #Logarithm => "log"
|
||||
| #LogarithmWithThreshold(_) => "log"
|
||||
}
|
||||
|
||||
let format = (a, b, c) => b ++ (" " ++ (toString(a) ++ (" " ++ c)))
|
||||
|
@ -151,6 +169,12 @@ module Scale = {
|
|||
| #Divide => divide(a, b)
|
||||
| #Power => power(a, b)
|
||||
| #Logarithm => logarithm(a, b)
|
||||
| #LogarithmWithThreshold(eps) =>
|
||||
if a < eps {
|
||||
Ok(0.0)
|
||||
} else {
|
||||
logarithm(a, b)
|
||||
}
|
||||
}
|
||||
|
||||
let format = (operation: t, value, scaleBy) =>
|
||||
|
@ -159,14 +183,14 @@ module Scale = {
|
|||
| #Divide => j`verticalDivide($value, $scaleBy) `
|
||||
| #Power => j`verticalPower($value, $scaleBy) `
|
||||
| #Logarithm => j`verticalLog($value, $scaleBy) `
|
||||
| #LogarithmWithThreshold(eps) => j`verticalLog($value, $scaleBy, epsilon=$eps) `
|
||||
}
|
||||
|
||||
let toIntegralSumCacheFn = x =>
|
||||
switch x {
|
||||
| #Multiply => (a, b) => Some(a *. b)
|
||||
| #Divide => (a, b) => Some(a /. b)
|
||||
| #Power => (_, _) => None
|
||||
| #Logarithm => (_, _) => None
|
||||
| #Power | #Logarithm | #LogarithmWithThreshold(_) => (_, _) => None
|
||||
}
|
||||
|
||||
let toIntegralCacheFn = x =>
|
||||
|
@ -175,6 +199,7 @@ module Scale = {
|
|||
| #Divide => (_, _) => None
|
||||
| #Power => (_, _) => None
|
||||
| #Logarithm => (_, _) => None
|
||||
| #LogarithmWithThreshold(_) => (_, _) => None
|
||||
}
|
||||
}
|
||||
|
||||
|
|
|
@ -96,7 +96,21 @@ module T = {
|
|||
let fromZippedArray = (pairs: array<(float, float)>): t => pairs |> Belt.Array.unzip |> fromArray
|
||||
let equallyDividedXs = (t: t, newLength) => E.A.Floats.range(minX(t), maxX(t), newLength)
|
||||
let toJs = (t: t) => {"xs": t.xs, "ys": t.ys}
|
||||
|
||||
let filterYValues = (fn, t: t): t => t |> zip |> E.A.filter(((_, y)) => fn(y)) |> fromZippedArray
|
||||
let filterOkYs = (xs: array<float>, ys: array<result<float, 'b>>): t => {
|
||||
let n = E.A.length(xs) // Assume length(xs) == length(ys)
|
||||
let newXs = []
|
||||
let newYs = []
|
||||
for i in 0 to n - 1 {
|
||||
switch ys[i] {
|
||||
| Ok(y) =>
|
||||
let _ = Js.Array.push(xs[i], newXs)
|
||||
let _ = Js.Array.push(y, newYs)
|
||||
| Error(_) => ()
|
||||
}
|
||||
}
|
||||
{xs: newXs, ys: newYs}
|
||||
}
|
||||
module Validator = {
|
||||
let fnName = "XYShape validate"
|
||||
let notSortedError = (p: string): error => NotSorted(p)
|
||||
|
@ -376,6 +390,90 @@ module PointwiseCombination = {
|
|||
}
|
||||
`)
|
||||
|
||||
/*
|
||||
This is from an approach to kl divergence that was ultimately rejected. Leaving it in for now because it may help us factor `combine` out of raw javascript soon.
|
||||
*/
|
||||
let combineAlongSupportOfSecondArgument0: (
|
||||
(float, float) => result<float, Operation.Error.t>,
|
||||
interpolator,
|
||||
T.t,
|
||||
T.t,
|
||||
) => result<T.t, Operation.Error.t> = (fn, interpolator, t1, t2) => {
|
||||
let newYs = []
|
||||
let newXs = []
|
||||
let (l1, l2) = (E.A.length(t1.xs), E.A.length(t2.xs))
|
||||
let (i, j) = (ref(0), ref(0))
|
||||
let minX = t2.xs[0]
|
||||
let maxX = t2.xs[l2 - 1]
|
||||
while j.contents < l2 - 1 && i.contents < l1 - 1 {
|
||||
let someTuple = {
|
||||
let x1 = t1.xs[i.contents + 1]
|
||||
let x2 = t2.xs[j.contents + 1]
|
||||
if (
|
||||
/* if t1 has to catch up to t2 */
|
||||
i.contents < l1 - 1 && j.contents < l2 && x1 < x2 && minX <= x1 && x2 <= maxX
|
||||
) {
|
||||
i := i.contents + 1
|
||||
let x = x1
|
||||
let y1 = t1.ys[i.contents]
|
||||
let y2 = interpolator(t2, j.contents, x)
|
||||
Some((x, y1, y2))
|
||||
} else if (
|
||||
/* if t2 has to catch up to t1 */
|
||||
i.contents < l1 && j.contents < l2 - 1 && x1 > x2 && x2 >= minX && maxX >= x1
|
||||
) {
|
||||
j := j.contents + 1
|
||||
let x = x2
|
||||
let y1 = interpolator(t1, i.contents, x)
|
||||
let y2 = t2.ys[j.contents]
|
||||
Some((x, y1, y2))
|
||||
} else if (
|
||||
/* move both ahead if they are equal */
|
||||
i.contents < l1 - 1 && j.contents < l2 - 1 && x1 == x2 && x1 >= minX && maxX >= x2
|
||||
) {
|
||||
i := i.contents + 1
|
||||
j := j.contents + 1
|
||||
let x = x1
|
||||
let y1 = t1.ys[i.contents]
|
||||
let y2 = t2.ys[j.contents]
|
||||
Some((x, y1, y2))
|
||||
} else {
|
||||
i := i.contents + 1
|
||||
None
|
||||
}
|
||||
}
|
||||
switch someTuple {
|
||||
| Some((x, y1, y2)) => {
|
||||
let _ = Js.Array.push(fn(y1, y2), newYs)
|
||||
let _ = Js.Array.push(x, newXs)
|
||||
}
|
||||
| None => ()
|
||||
}
|
||||
}
|
||||
T.filterOkYs(newXs, newYs)->Ok
|
||||
}
|
||||
|
||||
// This function is used for klDivergence
|
||||
let combineAlongSupportOfSecondArgument: (
|
||||
(float, float) => result<float, Operation.Error.t>,
|
||||
T.t,
|
||||
T.t,
|
||||
) => result<T.t, Operation.Error.t> = (fn, prediction, answer) => {
|
||||
let combineWithFn = (answerX: float, i: int) => {
|
||||
let answerY = answer.ys[i]
|
||||
let predictionY = XtoY.linear(answerX, prediction)
|
||||
fn(predictionY, answerY)
|
||||
}
|
||||
let newYsWithError = Js.Array.mapi((x, i) => combineWithFn(x, i), answer.xs)
|
||||
let newYsOrError = E.A.R.firstErrorOrOpen(newYsWithError)
|
||||
let result = switch newYsOrError {
|
||||
| Ok(a) => Ok({xs: answer.xs, ys: a})
|
||||
| Error(b) => Error(b)
|
||||
}
|
||||
|
||||
result
|
||||
}
|
||||
|
||||
let addCombine = (interpolator: interpolator, t1: T.t, t2: T.t): T.t =>
|
||||
combine((a, b) => Ok(a +. b), interpolator, t1, t2)->E.R.toExn(
|
||||
"Add operation should never fail",
|
||||
|
@ -467,7 +565,7 @@ module Range = {
|
|||
// TODO: I think this isn't needed by any functions anymore.
|
||||
let stepsToContinuous = t => {
|
||||
// TODO: It would be nicer if this the diff didn't change the first element, and also maybe if there were a more elegant way of doing this.
|
||||
let diff = T.xTotalRange(t) |> (r => r *. 0.00001)
|
||||
let diff = T.xTotalRange(t) |> (r => r *. MagicNumbers.Epsilon.five)
|
||||
let items = switch E.A.toRanges(Belt.Array.zip(t.xs, t.ys)) {
|
||||
| Ok(items) =>
|
||||
Some(
|
||||
|
@ -489,25 +587,6 @@ module Range = {
|
|||
}
|
||||
}
|
||||
|
||||
let pointLogScore = (prediction, answer) =>
|
||||
switch answer {
|
||||
| 0. => 0.0
|
||||
| answer => answer *. Js.Math.log2(Js.Math.abs_float(prediction /. answer))
|
||||
}
|
||||
|
||||
let logScorePoint = (sampleCount, t1, t2) =>
|
||||
PointwiseCombination.combineEvenXs(
|
||||
~fn=pointLogScore,
|
||||
~xToYSelection=XtoY.linear,
|
||||
sampleCount,
|
||||
t1,
|
||||
t2,
|
||||
)
|
||||
|> Range.integrateWithTriangles
|
||||
|> E.O.fmap(T.accumulateYs(\"+."))
|
||||
|> E.O.fmap(Pairs.last)
|
||||
|> E.O.fmap(Pairs.y)
|
||||
|
||||
module Analysis = {
|
||||
let getVarianceDangerously = (t: 't, mean: 't => float, getMeanOfSquares: 't => float): float => {
|
||||
let meanSquared = mean(t) ** 2.0
|
||||
|
|
|
@ -10,7 +10,11 @@ export default function PlaygroundPage() {
|
|||
maxWidth: 2000,
|
||||
}}
|
||||
>
|
||||
<SquigglePlayground initialSquiggleString="normal(0,1)" height={700} />
|
||||
<SquigglePlayground
|
||||
initialSquiggleString="normal(0,1)"
|
||||
height={700}
|
||||
showTypes={true}
|
||||
/>
|
||||
</div>
|
||||
</Layout>
|
||||
);
|
||||
|
|
502
yarn.lock
502
yarn.lock
|
@ -188,12 +188,7 @@
|
|||
dependencies:
|
||||
"@babel/highlight" "^7.16.7"
|
||||
|
||||
"@babel/compat-data@^7.13.11", "@babel/compat-data@^7.17.0", "@babel/compat-data@^7.17.7":
|
||||
version "7.17.7"
|
||||
resolved "https://registry.yarnpkg.com/@babel/compat-data/-/compat-data-7.17.7.tgz#078d8b833fbbcc95286613be8c716cef2b519fa2"
|
||||
integrity sha512-p8pdE6j0a29TNGebNm7NzYZWB3xVZJBZ7XGs42uAKzQo8VQ3F0By/cQCtUEABwIqw5zo6WA4NbmxsfzADzMKnQ==
|
||||
|
||||
"@babel/compat-data@^7.17.10":
|
||||
"@babel/compat-data@^7.13.11", "@babel/compat-data@^7.17.0", "@babel/compat-data@^7.17.10":
|
||||
version "7.17.10"
|
||||
resolved "https://registry.yarnpkg.com/@babel/compat-data/-/compat-data-7.17.10.tgz#711dc726a492dfc8be8220028b1b92482362baab"
|
||||
integrity sha512-GZt/TCsG70Ms19gfZO1tM4CVnXsPgEPBCpJu+Qz3L0LUDsY5nZqFZglIoPC1kIYOtNBZlrnFT+klg12vFGZXrw==
|
||||
|
@ -274,17 +269,7 @@
|
|||
"@babel/helper-explode-assignable-expression" "^7.16.7"
|
||||
"@babel/types" "^7.16.7"
|
||||
|
||||
"@babel/helper-compilation-targets@^7.13.0", "@babel/helper-compilation-targets@^7.16.7":
|
||||
version "7.17.7"
|
||||
resolved "https://registry.yarnpkg.com/@babel/helper-compilation-targets/-/helper-compilation-targets-7.17.7.tgz#a3c2924f5e5f0379b356d4cfb313d1414dc30e46"
|
||||
integrity sha512-UFzlz2jjd8kroj0hmCFV5zr+tQPi1dpC2cRsDV/3IEW8bJfCPrPpmcSN6ZS8RqIq4LXcmpipCQFPddyFA5Yc7w==
|
||||
dependencies:
|
||||
"@babel/compat-data" "^7.17.7"
|
||||
"@babel/helper-validator-option" "^7.16.7"
|
||||
browserslist "^4.17.5"
|
||||
semver "^6.3.0"
|
||||
|
||||
"@babel/helper-compilation-targets@^7.17.10":
|
||||
"@babel/helper-compilation-targets@^7.13.0", "@babel/helper-compilation-targets@^7.16.7", "@babel/helper-compilation-targets@^7.17.10":
|
||||
version "7.17.10"
|
||||
resolved "https://registry.yarnpkg.com/@babel/helper-compilation-targets/-/helper-compilation-targets-7.17.10.tgz#09c63106d47af93cf31803db6bc49fef354e2ebe"
|
||||
integrity sha512-gh3RxjWbauw/dFiU/7whjd0qN9K6nPJMqe6+Er7rOavFh0CQUSwhAE3IcTho2rywPJFxej6TUUHDkWcYI6gGqQ==
|
||||
|
@ -496,12 +481,7 @@
|
|||
chalk "^2.0.0"
|
||||
js-tokens "^4.0.0"
|
||||
|
||||
"@babel/parser@^7.1.0", "@babel/parser@^7.12.11", "@babel/parser@^7.12.7", "@babel/parser@^7.14.7", "@babel/parser@^7.16.7":
|
||||
version "7.17.9"
|
||||
resolved "https://registry.yarnpkg.com/@babel/parser/-/parser-7.17.9.tgz#9c94189a6062f0291418ca021077983058e171ef"
|
||||
integrity sha512-vqUSBLP8dQHFPdPi9bc5GK9vRkYHJ49fsZdtoJ8EQ8ibpwk5rPKfvNIwChB0KVXcIjcepEBBd2VHC5r9Gy8ueg==
|
||||
|
||||
"@babel/parser@^7.17.10":
|
||||
"@babel/parser@^7.1.0", "@babel/parser@^7.12.11", "@babel/parser@^7.12.7", "@babel/parser@^7.14.7", "@babel/parser@^7.16.7", "@babel/parser@^7.17.10":
|
||||
version "7.17.10"
|
||||
resolved "https://registry.yarnpkg.com/@babel/parser/-/parser-7.17.10.tgz#873b16db82a8909e0fbd7f115772f4b739f6ce78"
|
||||
integrity sha512-n2Q6i+fnJqzOaq2VkdXxy2TCPCWQZHiCo0XqmrCvDWcZQKRyZzYi4Z0yxlBuN0w+r2ZHmre+Q087DSrw3pbJDQ==
|
||||
|
@ -827,9 +807,9 @@
|
|||
"@babel/helper-plugin-utils" "^7.14.5"
|
||||
|
||||
"@babel/plugin-syntax-typescript@^7.16.7", "@babel/plugin-syntax-typescript@^7.7.2":
|
||||
version "7.16.7"
|
||||
resolved "https://registry.yarnpkg.com/@babel/plugin-syntax-typescript/-/plugin-syntax-typescript-7.16.7.tgz#39c9b55ee153151990fb038651d58d3fd03f98f8"
|
||||
integrity sha512-YhUIJHHGkqPgEcMYkPCKTyGUdoGKWtopIycQyjJH8OjvRgOYsXsaKehLVPScKJWAULPxMa4N1vCe6szREFlZ7A==
|
||||
version "7.17.10"
|
||||
resolved "https://registry.yarnpkg.com/@babel/plugin-syntax-typescript/-/plugin-syntax-typescript-7.17.10.tgz#80031e6042cad6a95ed753f672ebd23c30933195"
|
||||
integrity sha512-xJefea1DWXW09pW4Tm9bjwVlPDyYA2it3fWlmEjpYz6alPvTUjL0EOzNzI/FEOyI3r4/J7uVH5UqKgl1TQ5hqQ==
|
||||
dependencies:
|
||||
"@babel/helper-plugin-utils" "^7.16.7"
|
||||
|
||||
|
@ -1324,15 +1304,7 @@
|
|||
debug "^4.1.0"
|
||||
globals "^11.1.0"
|
||||
|
||||
"@babel/types@^7.0.0", "@babel/types@^7.12.11", "@babel/types@^7.12.6", "@babel/types@^7.12.7", "@babel/types@^7.15.6", "@babel/types@^7.16.0", "@babel/types@^7.16.7", "@babel/types@^7.16.8", "@babel/types@^7.17.0", "@babel/types@^7.2.0", "@babel/types@^7.3.0", "@babel/types@^7.3.3", "@babel/types@^7.4.4":
|
||||
version "7.17.0"
|
||||
resolved "https://registry.yarnpkg.com/@babel/types/-/types-7.17.0.tgz#a826e368bccb6b3d84acd76acad5c0d87342390b"
|
||||
integrity sha512-TmKSNO4D5rzhL5bjWFcVHHLETzfQ/AmbKpKPOSjlP0WoHZ6L911fgoOKY4Alp/emzG4cHJdyN49zpgkbXFEHHw==
|
||||
dependencies:
|
||||
"@babel/helper-validator-identifier" "^7.16.7"
|
||||
to-fast-properties "^2.0.0"
|
||||
|
||||
"@babel/types@^7.17.10":
|
||||
"@babel/types@^7.0.0", "@babel/types@^7.12.11", "@babel/types@^7.12.6", "@babel/types@^7.12.7", "@babel/types@^7.15.6", "@babel/types@^7.16.0", "@babel/types@^7.16.7", "@babel/types@^7.16.8", "@babel/types@^7.17.0", "@babel/types@^7.17.10", "@babel/types@^7.2.0", "@babel/types@^7.3.0", "@babel/types@^7.3.3", "@babel/types@^7.4.4":
|
||||
version "7.17.10"
|
||||
resolved "https://registry.yarnpkg.com/@babel/types/-/types-7.17.10.tgz#d35d7b4467e439fcf06d195f8100e0fea7fc82c4"
|
||||
integrity sha512-9O26jG0mBYfGkUYCYZRnBwbVLd1UZOICEr2Em6InB6jVfsAv1GKgwXHmrSg+WFWDmeKTA6vyTZiN8tCSM5Oo3A==
|
||||
|
@ -1439,6 +1411,18 @@
|
|||
dependencies:
|
||||
postcss-value-parser "^4.2.0"
|
||||
|
||||
"@csstools/postcss-stepped-value-functions@^1.0.0":
|
||||
version "1.0.0"
|
||||
resolved "https://registry.yarnpkg.com/@csstools/postcss-stepped-value-functions/-/postcss-stepped-value-functions-1.0.0.tgz#f8ffc05e163ba7bcbefc5fdcaf264ce9fd408c16"
|
||||
integrity sha512-q8c4bs1GumAiRenmFjASBcWSLKrbzHzWl6C2HcaAxAXIiL2rUlUWbqQZUjwVG5tied0rld19j/Mm90K3qI26vw==
|
||||
dependencies:
|
||||
postcss-value-parser "^4.2.0"
|
||||
|
||||
"@csstools/postcss-unset-value@^1.0.0":
|
||||
version "1.0.0"
|
||||
resolved "https://registry.yarnpkg.com/@csstools/postcss-unset-value/-/postcss-unset-value-1.0.0.tgz#f6e0e58376f09e381a49bd553772a97a477da3fd"
|
||||
integrity sha512-T5ZyNSw9G0x0UDFiXV40a7VjKw2b+l4G+S0sctKqxhx8cg9QtMUAGwJBVU9mHPDPoZEmwm0tEoukjl4zb9MU7Q==
|
||||
|
||||
"@ctrl/tinycolor@^3.4.0":
|
||||
version "3.4.1"
|
||||
resolved "https://registry.yarnpkg.com/@ctrl/tinycolor/-/tinycolor-3.4.1.tgz#75b4c27948c81e88ccd3a8902047bcd797f38d32"
|
||||
|
@ -1980,9 +1964,9 @@
|
|||
jest "^27.3.1"
|
||||
|
||||
"@hapi/hoek@^9.0.0":
|
||||
version "9.2.1"
|
||||
resolved "https://registry.yarnpkg.com/@hapi/hoek/-/hoek-9.2.1.tgz#9551142a1980503752536b5050fd99f4a7f13b17"
|
||||
integrity sha512-gfta+H8aziZsm8pZa0vj04KO6biEiisppNgA1kbJvFrrWu9Vm7eaUEy76DIxsuTaWvti5fkJVhllWc6ZTE+Mdw==
|
||||
version "9.3.0"
|
||||
resolved "https://registry.yarnpkg.com/@hapi/hoek/-/hoek-9.3.0.tgz#8368869dcb735be2e7f5cb7647de78e167a251fb"
|
||||
integrity sha512-/c6rf4UJlmHlC9b5BaNvzAcFv7HZ2QHaV0D4/HNlBdvFnvQq8RI4kYdhyPCl7Xj+oWvTWQ8ujhqS53LIgAe6KQ==
|
||||
|
||||
"@hapi/topo@^5.0.0":
|
||||
version "5.1.0"
|
||||
|
@ -2040,16 +2024,16 @@
|
|||
jest-util "^27.5.1"
|
||||
slash "^3.0.0"
|
||||
|
||||
"@jest/console@^28.0.2":
|
||||
version "28.0.2"
|
||||
resolved "https://registry.yarnpkg.com/@jest/console/-/console-28.0.2.tgz#d11e8b43ae431ae9b3112656848417ae4008fcad"
|
||||
integrity sha512-tiRpnMeeyQuuzgL5UNSeiqMwF8UOWPbAE5rzcu/1zyq4oPG2Ox6xm4YCOruwbp10F8odWc+XwVxTyGzMSLMqxA==
|
||||
"@jest/console@^28.1.0":
|
||||
version "28.1.0"
|
||||
resolved "https://registry.yarnpkg.com/@jest/console/-/console-28.1.0.tgz#db78222c3d3b0c1db82f1b9de51094c2aaff2176"
|
||||
integrity sha512-tscn3dlJFGay47kb4qVruQg/XWlmvU0xp3EJOjzzY+sBaI+YgwKcvAmTcyYU7xEiLLIY5HCdWRooAL8dqkFlDA==
|
||||
dependencies:
|
||||
"@jest/types" "^28.0.2"
|
||||
"@jest/types" "^28.1.0"
|
||||
"@types/node" "*"
|
||||
chalk "^4.0.0"
|
||||
jest-message-util "^28.0.2"
|
||||
jest-util "^28.0.2"
|
||||
jest-message-util "^28.1.0"
|
||||
jest-util "^28.1.0"
|
||||
slash "^3.0.0"
|
||||
|
||||
"@jest/core@^27.5.1":
|
||||
|
@ -2174,13 +2158,13 @@
|
|||
"@types/istanbul-lib-coverage" "^2.0.0"
|
||||
collect-v8-coverage "^1.0.0"
|
||||
|
||||
"@jest/test-result@^28.0.2":
|
||||
version "28.0.2"
|
||||
resolved "https://registry.yarnpkg.com/@jest/test-result/-/test-result-28.0.2.tgz#bc8e15a95347e3c2149572ae06a5a6fed939c522"
|
||||
integrity sha512-4EUqgjq9VzyUiVTvZfI9IRJD6t3NYBNP4f+Eq8Zr93+hkJ0RrGU4OBTw8tfNzidKX+bmuYzn8FxqpxOPIGGCMA==
|
||||
"@jest/test-result@^28.1.0":
|
||||
version "28.1.0"
|
||||
resolved "https://registry.yarnpkg.com/@jest/test-result/-/test-result-28.1.0.tgz#fd149dee123510dd2fcadbbf5f0020f98ad7f12c"
|
||||
integrity sha512-sBBFIyoPzrZho3N+80P35A5oAkSKlGfsEFfXFWuPGBsW40UAjCkGakZhn4UQK4iQlW2vgCDMRDOob9FGKV8YoQ==
|
||||
dependencies:
|
||||
"@jest/console" "^28.0.2"
|
||||
"@jest/types" "^28.0.2"
|
||||
"@jest/console" "^28.1.0"
|
||||
"@jest/types" "^28.1.0"
|
||||
"@types/istanbul-lib-coverage" "^2.0.0"
|
||||
collect-v8-coverage "^1.0.0"
|
||||
|
||||
|
@ -2258,10 +2242,10 @@
|
|||
"@types/yargs" "^16.0.0"
|
||||
chalk "^4.0.0"
|
||||
|
||||
"@jest/types@^28.0.2":
|
||||
version "28.0.2"
|
||||
resolved "https://registry.yarnpkg.com/@jest/types/-/types-28.0.2.tgz#70b9538c1863fb060b2f438ca008b5563d00c5b4"
|
||||
integrity sha512-hi3jUdm9iht7I2yrV5C4s3ucCJHUP8Eh3W6rQ1s4n/Qw9rQgsda4eqCt+r3BKRi7klVmZfQlMx1nGlzNMP2d8A==
|
||||
"@jest/types@^28.1.0":
|
||||
version "28.1.0"
|
||||
resolved "https://registry.yarnpkg.com/@jest/types/-/types-28.1.0.tgz#508327a89976cbf9bd3e1cc74641a29fd7dfd519"
|
||||
integrity sha512-xmEggMPr317MIOjjDoZ4ejCSr9Lpbt/u34+dvc99t7DS8YirW5rwZEhzKPC2BMUFkUhI48qs6qLUSGw5FuL0GA==
|
||||
dependencies:
|
||||
"@jest/schemas" "^28.0.2"
|
||||
"@types/istanbul-lib-coverage" "^2.0.0"
|
||||
|
@ -2279,24 +2263,24 @@
|
|||
"@jridgewell/sourcemap-codec" "^1.4.10"
|
||||
|
||||
"@jridgewell/resolve-uri@^3.0.3":
|
||||
version "3.0.6"
|
||||
resolved "https://registry.yarnpkg.com/@jridgewell/resolve-uri/-/resolve-uri-3.0.6.tgz#4ac237f4dabc8dd93330386907b97591801f7352"
|
||||
integrity sha512-R7xHtBSNm+9SyvpJkdQl+qrM3Hm2fea3Ef197M3mUug+v+yR+Rhfbs7PBtcBUVnIWJ4JcAdjvij+c8hXS9p5aw==
|
||||
version "3.0.7"
|
||||
resolved "https://registry.yarnpkg.com/@jridgewell/resolve-uri/-/resolve-uri-3.0.7.tgz#30cd49820a962aff48c8fffc5cd760151fca61fe"
|
||||
integrity sha512-8cXDaBBHOr2pQ7j77Y6Vp5VDT2sIqWyWQ56TjEq4ih/a4iST3dItRe8Q9fp0rrIl9DoKhWQtUQz/YpOxLkXbNA==
|
||||
|
||||
"@jridgewell/set-array@^1.0.0":
|
||||
version "1.1.0"
|
||||
resolved "https://registry.yarnpkg.com/@jridgewell/set-array/-/set-array-1.1.0.tgz#1179863356ac8fbea64a5a4bcde93a4871012c01"
|
||||
integrity sha512-SfJxIxNVYLTsKwzB3MoOQ1yxf4w/E6MdkvTgrgAt1bfxjSrLUoHMKrDOykwN14q65waezZIdqDneUIPh4/sKxg==
|
||||
version "1.1.1"
|
||||
resolved "https://registry.yarnpkg.com/@jridgewell/set-array/-/set-array-1.1.1.tgz#36a6acc93987adcf0ba50c66908bd0b70de8afea"
|
||||
integrity sha512-Ct5MqZkLGEXTVmQYbGtx9SVqD2fqwvdubdps5D3djjAkgkKwT918VNOz65pEHFaYTeWcukmJmH5SwsA9Tn2ObQ==
|
||||
|
||||
"@jridgewell/sourcemap-codec@^1.4.10":
|
||||
version "1.4.11"
|
||||
resolved "https://registry.yarnpkg.com/@jridgewell/sourcemap-codec/-/sourcemap-codec-1.4.11.tgz#771a1d8d744eeb71b6adb35808e1a6c7b9b8c8ec"
|
||||
integrity sha512-Fg32GrJo61m+VqYSdRSjRXMjQ06j8YIYfcTqndLYVAaHmroZHLJZCydsWBOTDqXS2v+mjxohBWEMfg97GXmYQg==
|
||||
version "1.4.13"
|
||||
resolved "https://registry.yarnpkg.com/@jridgewell/sourcemap-codec/-/sourcemap-codec-1.4.13.tgz#b6461fb0c2964356c469e115f504c95ad97ab88c"
|
||||
integrity sha512-GryiOJmNcWbovBxTfZSF71V/mXbgcV3MewDe3kIMCLyIh5e7SKAeUZs+rMnJ8jkMolZ/4/VsdBmMrw3l+VdZ3w==
|
||||
|
||||
"@jridgewell/trace-mapping@^0.3.7", "@jridgewell/trace-mapping@^0.3.9":
|
||||
version "0.3.9"
|
||||
resolved "https://registry.yarnpkg.com/@jridgewell/trace-mapping/-/trace-mapping-0.3.9.tgz#6534fd5933a53ba7cbf3a17615e273a0d1273ff9"
|
||||
integrity sha512-3Belt6tdc8bPgAtbcmdtNJlirVoTmEb5e2gC94PnkwEW9jI6CAHUeoG85tjWP5WquqfavoMtMwiG4P926ZKKuQ==
|
||||
version "0.3.10"
|
||||
resolved "https://registry.yarnpkg.com/@jridgewell/trace-mapping/-/trace-mapping-0.3.10.tgz#db436f0917d655393851bc258918c00226c9b183"
|
||||
integrity sha512-Q0YbBd6OTsXm8Y21+YUSDXupHnodNC2M4O18jtd3iwJ3+vMZNdKGols0a9G6JOK0dcJ3IdUUHoh908ZI6qhk8Q==
|
||||
dependencies:
|
||||
"@jridgewell/resolve-uri" "^3.0.3"
|
||||
"@jridgewell/sourcemap-codec" "^1.4.10"
|
||||
|
@ -3922,9 +3906,9 @@
|
|||
"@types/estree" "*"
|
||||
|
||||
"@types/eslint@*":
|
||||
version "8.4.1"
|
||||
resolved "https://registry.yarnpkg.com/@types/eslint/-/eslint-8.4.1.tgz#c48251553e8759db9e656de3efc846954ac32304"
|
||||
integrity sha512-GE44+DNEyxxh2Kc6ro/VkIj+9ma0pO0bwv9+uHSyBrikYOHr8zYcdPvnBOp1aw8s+CjRvuSx7CyWqRrNFQ59mA==
|
||||
version "8.4.2"
|
||||
resolved "https://registry.yarnpkg.com/@types/eslint/-/eslint-8.4.2.tgz#48f2ac58ab9c631cb68845c3d956b28f79fad575"
|
||||
integrity sha512-Z1nseZON+GEnFjJc04sv4NSALGjhFwy6K0HXt7qsn5ArfAKtb63dXNJHf+1YW6IpOIYRBGUbu3GwJdj8DGnCjA==
|
||||
dependencies:
|
||||
"@types/estree" "*"
|
||||
"@types/json-schema" "*"
|
||||
|
@ -4017,9 +4001,9 @@
|
|||
integrity sha512-oh/6byDPnL1zeNXFrDXFLyZjkr1MsBG667IM792caf1L2UPOOMf65NFzjUH/ltyfwjAGfs1rsX1eftK0jC/KIg==
|
||||
|
||||
"@types/http-proxy@^1.17.8":
|
||||
version "1.17.8"
|
||||
resolved "https://registry.yarnpkg.com/@types/http-proxy/-/http-proxy-1.17.8.tgz#968c66903e7e42b483608030ee85800f22d03f55"
|
||||
integrity sha512-5kPLG5BKpWYkw/LVOGWpiq3nEVqxiN32rTgI53Sk12/xHFQ2rG3ehI9IO+O3W2QoKeyB92dJkoka8SUm6BX1pA==
|
||||
version "1.17.9"
|
||||
resolved "https://registry.yarnpkg.com/@types/http-proxy/-/http-proxy-1.17.9.tgz#7f0e7931343761efde1e2bf48c40f02f3f75705a"
|
||||
integrity sha512-QsbSjA/fSk7xB+UXlCT3wHBy5ai9wOcNDWwZAtud+jXhwOM3l+EYZh8Lng4+/6n8uar0J7xILzqftJdJ/Wdfkw==
|
||||
dependencies:
|
||||
"@types/node" "*"
|
||||
|
||||
|
@ -4387,13 +4371,13 @@
|
|||
"@types/yargs-parser" "*"
|
||||
|
||||
"@typescript-eslint/eslint-plugin@^5.5.0":
|
||||
version "5.21.0"
|
||||
resolved "https://registry.yarnpkg.com/@typescript-eslint/eslint-plugin/-/eslint-plugin-5.21.0.tgz#bfc22e0191e6404ab1192973b3b4ea0461c1e878"
|
||||
integrity sha512-fTU85q8v5ZLpoZEyn/u1S2qrFOhi33Edo2CZ0+q1gDaWWm0JuPh3bgOyU8lM0edIEYgKLDkPFiZX2MOupgjlyg==
|
||||
version "5.22.0"
|
||||
resolved "https://registry.yarnpkg.com/@typescript-eslint/eslint-plugin/-/eslint-plugin-5.22.0.tgz#7b52a0de2e664044f28b36419210aea4ab619e2a"
|
||||
integrity sha512-YCiy5PUzpAeOPGQ7VSGDEY2NeYUV1B0swde2e0HzokRsHBYjSdF6DZ51OuRZxVPHx0032lXGLvOMls91D8FXlg==
|
||||
dependencies:
|
||||
"@typescript-eslint/scope-manager" "5.21.0"
|
||||
"@typescript-eslint/type-utils" "5.21.0"
|
||||
"@typescript-eslint/utils" "5.21.0"
|
||||
"@typescript-eslint/scope-manager" "5.22.0"
|
||||
"@typescript-eslint/type-utils" "5.22.0"
|
||||
"@typescript-eslint/utils" "5.22.0"
|
||||
debug "^4.3.2"
|
||||
functional-red-black-tree "^1.0.1"
|
||||
ignore "^5.1.8"
|
||||
|
@ -4402,75 +4386,75 @@
|
|||
tsutils "^3.21.0"
|
||||
|
||||
"@typescript-eslint/experimental-utils@^5.0.0":
|
||||
version "5.21.0"
|
||||
resolved "https://registry.yarnpkg.com/@typescript-eslint/experimental-utils/-/experimental-utils-5.21.0.tgz#489275ca792f5de7e0d1f4be1f15576ea56b6ca2"
|
||||
integrity sha512-mzF6ert/6iQoESV0z9v5/mEaJRKL4fv68rHoZ6exM38xjxkw4MNx54B7ferrnMTM/GIRKLDaJ3JPRi+Dxa5Hlg==
|
||||
version "5.22.0"
|
||||
resolved "https://registry.yarnpkg.com/@typescript-eslint/experimental-utils/-/experimental-utils-5.22.0.tgz#a2b40eaa52ae1d1e316bc861069c40883a7ccf6e"
|
||||
integrity sha512-rKxoCUtAHwEH6IcAoVpqipY6Th+YKW7WFspAKu0IFdbdKZpveFBeqxxE9Xn+GWikhq1o03V3VXbxIe+GdhggiQ==
|
||||
dependencies:
|
||||
"@typescript-eslint/utils" "5.21.0"
|
||||
"@typescript-eslint/utils" "5.22.0"
|
||||
|
||||
"@typescript-eslint/parser@^5.5.0":
|
||||
version "5.21.0"
|
||||
resolved "https://registry.yarnpkg.com/@typescript-eslint/parser/-/parser-5.21.0.tgz#6cb72673dbf3e1905b9c432175a3c86cdaf2071f"
|
||||
integrity sha512-8RUwTO77hstXUr3pZoWZbRQUxXcSXafZ8/5gpnQCfXvgmP9gpNlRGlWzvfbEQ14TLjmtU8eGnONkff8U2ui2Eg==
|
||||
version "5.22.0"
|
||||
resolved "https://registry.yarnpkg.com/@typescript-eslint/parser/-/parser-5.22.0.tgz#7bedf8784ef0d5d60567c5ba4ce162460e70c178"
|
||||
integrity sha512-piwC4krUpRDqPaPbFaycN70KCP87+PC5WZmrWs+DlVOxxmF+zI6b6hETv7Quy4s9wbkV16ikMeZgXsvzwI3icQ==
|
||||
dependencies:
|
||||
"@typescript-eslint/scope-manager" "5.21.0"
|
||||
"@typescript-eslint/types" "5.21.0"
|
||||
"@typescript-eslint/typescript-estree" "5.21.0"
|
||||
"@typescript-eslint/scope-manager" "5.22.0"
|
||||
"@typescript-eslint/types" "5.22.0"
|
||||
"@typescript-eslint/typescript-estree" "5.22.0"
|
||||
debug "^4.3.2"
|
||||
|
||||
"@typescript-eslint/scope-manager@5.21.0":
|
||||
version "5.21.0"
|
||||
resolved "https://registry.yarnpkg.com/@typescript-eslint/scope-manager/-/scope-manager-5.21.0.tgz#a4b7ed1618f09f95e3d17d1c0ff7a341dac7862e"
|
||||
integrity sha512-XTX0g0IhvzcH/e3393SvjRCfYQxgxtYzL3UREteUneo72EFlt7UNoiYnikUtmGVobTbhUDByhJ4xRBNe+34kOQ==
|
||||
"@typescript-eslint/scope-manager@5.22.0":
|
||||
version "5.22.0"
|
||||
resolved "https://registry.yarnpkg.com/@typescript-eslint/scope-manager/-/scope-manager-5.22.0.tgz#590865f244ebe6e46dc3e9cab7976fc2afa8af24"
|
||||
integrity sha512-yA9G5NJgV5esANJCO0oF15MkBO20mIskbZ8ijfmlKIvQKg0ynVKfHZ15/nhAJN5m8Jn3X5qkwriQCiUntC9AbA==
|
||||
dependencies:
|
||||
"@typescript-eslint/types" "5.21.0"
|
||||
"@typescript-eslint/visitor-keys" "5.21.0"
|
||||
"@typescript-eslint/types" "5.22.0"
|
||||
"@typescript-eslint/visitor-keys" "5.22.0"
|
||||
|
||||
"@typescript-eslint/type-utils@5.21.0":
|
||||
version "5.21.0"
|
||||
resolved "https://registry.yarnpkg.com/@typescript-eslint/type-utils/-/type-utils-5.21.0.tgz#ff89668786ad596d904c21b215e5285da1b6262e"
|
||||
integrity sha512-MxmLZj0tkGlkcZCSE17ORaHl8Th3JQwBzyXL/uvC6sNmu128LsgjTX0NIzy+wdH2J7Pd02GN8FaoudJntFvSOw==
|
||||
"@typescript-eslint/type-utils@5.22.0":
|
||||
version "5.22.0"
|
||||
resolved "https://registry.yarnpkg.com/@typescript-eslint/type-utils/-/type-utils-5.22.0.tgz#0c0e93b34210e334fbe1bcb7250c470f4a537c19"
|
||||
integrity sha512-iqfLZIsZhK2OEJ4cQ01xOq3NaCuG5FQRKyHicA3xhZxMgaxQazLUHbH/B2k9y5i7l3+o+B5ND9Mf1AWETeMISA==
|
||||
dependencies:
|
||||
"@typescript-eslint/utils" "5.21.0"
|
||||
"@typescript-eslint/utils" "5.22.0"
|
||||
debug "^4.3.2"
|
||||
tsutils "^3.21.0"
|
||||
|
||||
"@typescript-eslint/types@5.21.0":
|
||||
version "5.21.0"
|
||||
resolved "https://registry.yarnpkg.com/@typescript-eslint/types/-/types-5.21.0.tgz#8cdb9253c0dfce3f2ab655b9d36c03f72e684017"
|
||||
integrity sha512-XnOOo5Wc2cBlq8Lh5WNvAgHzpjnEzxn4CJBwGkcau7b/tZ556qrWXQz4DJyChYg8JZAD06kczrdgFPpEQZfDsA==
|
||||
"@typescript-eslint/types@5.22.0":
|
||||
version "5.22.0"
|
||||
resolved "https://registry.yarnpkg.com/@typescript-eslint/types/-/types-5.22.0.tgz#50a4266e457a5d4c4b87ac31903b28b06b2c3ed0"
|
||||
integrity sha512-T7owcXW4l0v7NTijmjGWwWf/1JqdlWiBzPqzAWhobxft0SiEvMJB56QXmeCQjrPuM8zEfGUKyPQr/L8+cFUBLw==
|
||||
|
||||
"@typescript-eslint/typescript-estree@5.21.0":
|
||||
version "5.21.0"
|
||||
resolved "https://registry.yarnpkg.com/@typescript-eslint/typescript-estree/-/typescript-estree-5.21.0.tgz#9f0c233e28be2540eaed3df050f0d54fb5aa52de"
|
||||
integrity sha512-Y8Y2T2FNvm08qlcoSMoNchh9y2Uj3QmjtwNMdRQkcFG7Muz//wfJBGBxh8R7HAGQFpgYpdHqUpEoPQk+q9Kjfg==
|
||||
"@typescript-eslint/typescript-estree@5.22.0":
|
||||
version "5.22.0"
|
||||
resolved "https://registry.yarnpkg.com/@typescript-eslint/typescript-estree/-/typescript-estree-5.22.0.tgz#e2116fd644c3e2fda7f4395158cddd38c0c6df97"
|
||||
integrity sha512-EyBEQxvNjg80yinGE2xdhpDYm41so/1kOItl0qrjIiJ1kX/L/L8WWGmJg8ni6eG3DwqmOzDqOhe6763bF92nOw==
|
||||
dependencies:
|
||||
"@typescript-eslint/types" "5.21.0"
|
||||
"@typescript-eslint/visitor-keys" "5.21.0"
|
||||
"@typescript-eslint/types" "5.22.0"
|
||||
"@typescript-eslint/visitor-keys" "5.22.0"
|
||||
debug "^4.3.2"
|
||||
globby "^11.0.4"
|
||||
is-glob "^4.0.3"
|
||||
semver "^7.3.5"
|
||||
tsutils "^3.21.0"
|
||||
|
||||
"@typescript-eslint/utils@5.21.0", "@typescript-eslint/utils@^5.13.0":
|
||||
version "5.21.0"
|
||||
resolved "https://registry.yarnpkg.com/@typescript-eslint/utils/-/utils-5.21.0.tgz#51d7886a6f0575e23706e5548c7e87bce42d7c18"
|
||||
integrity sha512-q/emogbND9wry7zxy7VYri+7ydawo2HDZhRZ5k6yggIvXa7PvBbAAZ4PFH/oZLem72ezC4Pr63rJvDK/sTlL8Q==
|
||||
"@typescript-eslint/utils@5.22.0", "@typescript-eslint/utils@^5.13.0":
|
||||
version "5.22.0"
|
||||
resolved "https://registry.yarnpkg.com/@typescript-eslint/utils/-/utils-5.22.0.tgz#1f2c4897e2cf7e44443c848a13c60407861babd8"
|
||||
integrity sha512-HodsGb037iobrWSUMS7QH6Hl1kppikjA1ELiJlNSTYf/UdMEwzgj0WIp+lBNb6WZ3zTwb0tEz51j0Wee3iJ3wQ==
|
||||
dependencies:
|
||||
"@types/json-schema" "^7.0.9"
|
||||
"@typescript-eslint/scope-manager" "5.21.0"
|
||||
"@typescript-eslint/types" "5.21.0"
|
||||
"@typescript-eslint/typescript-estree" "5.21.0"
|
||||
"@typescript-eslint/scope-manager" "5.22.0"
|
||||
"@typescript-eslint/types" "5.22.0"
|
||||
"@typescript-eslint/typescript-estree" "5.22.0"
|
||||
eslint-scope "^5.1.1"
|
||||
eslint-utils "^3.0.0"
|
||||
|
||||
"@typescript-eslint/visitor-keys@5.21.0":
|
||||
version "5.21.0"
|
||||
resolved "https://registry.yarnpkg.com/@typescript-eslint/visitor-keys/-/visitor-keys-5.21.0.tgz#453fb3662409abaf2f8b1f65d515699c888dd8ae"
|
||||
integrity sha512-SX8jNN+iHqAF0riZQMkm7e8+POXa/fXw5cxL+gjpyP+FI+JVNhii53EmQgDAfDcBpFekYSlO0fGytMQwRiMQCA==
|
||||
"@typescript-eslint/visitor-keys@5.22.0":
|
||||
version "5.22.0"
|
||||
resolved "https://registry.yarnpkg.com/@typescript-eslint/visitor-keys/-/visitor-keys-5.22.0.tgz#f49c0ce406944ffa331a1cfabeed451ea4d0909c"
|
||||
integrity sha512-DbgTqn2Dv5RFWluG88tn0pP6Ex0ROF+dpDO1TNNZdRtLjUr6bdznjA6f/qNqJLjd2PgguAES2Zgxh/JzwzETDg==
|
||||
dependencies:
|
||||
"@typescript-eslint/types" "5.21.0"
|
||||
"@typescript-eslint/types" "5.22.0"
|
||||
eslint-visitor-keys "^3.0.0"
|
||||
|
||||
"@webassemblyjs/ast@1.11.1":
|
||||
|
@ -5039,9 +5023,9 @@ ansi-to-html@^0.6.11:
|
|||
entities "^2.0.0"
|
||||
|
||||
antd@^4.20.0:
|
||||
version "4.20.1"
|
||||
resolved "https://registry.yarnpkg.com/antd/-/antd-4.20.1.tgz#6cd5a406c7172d61a5d0693ea52ee908650cf674"
|
||||
integrity sha512-asKxOV0a6AijqonbcXkO08/q+XvqS/HmGfaRIS6ZH1ALR3FS2q+kTW52rJZO9rfoOb/ldPhEBVSWiNrbiB+uCQ==
|
||||
version "4.20.2"
|
||||
resolved "https://registry.yarnpkg.com/antd/-/antd-4.20.2.tgz#1ed2042a091eecfebd9650c014a1a2e57430ff2b"
|
||||
integrity sha512-b+Gq1EY8LmcS/ARei/dGI0bWQlJ/j3f3oJ6XjM+ryyT5YWxvf7X3mGc++bTGuLmjn6+/icRL1zItIgcvplcomg==
|
||||
dependencies:
|
||||
"@ant-design/colors" "^6.0.0"
|
||||
"@ant-design/icons" "^4.7.0"
|
||||
|
@ -5072,7 +5056,7 @@ antd@^4.20.0:
|
|||
rc-progress "~3.2.1"
|
||||
rc-rate "~2.9.0"
|
||||
rc-resize-observer "^1.2.0"
|
||||
rc-segmented "~2.0.0"
|
||||
rc-segmented "~2.1.0 "
|
||||
rc-select "~14.1.1"
|
||||
rc-slider "~10.0.0"
|
||||
rc-steps "~4.1.0"
|
||||
|
@ -5210,13 +5194,13 @@ array-flatten@^2.1.2:
|
|||
integrity sha512-hNfzcOV8W4NdualtqBFPyVO+54DSJuZGY9qT4pRroB6S9e3iiido2ISIC5h9R2sPJ8H3FHCIiEnsv1lPXO3KtQ==
|
||||
|
||||
array-includes@^3.0.3, array-includes@^3.1.4:
|
||||
version "3.1.4"
|
||||
resolved "https://registry.yarnpkg.com/array-includes/-/array-includes-3.1.4.tgz#f5b493162c760f3539631f005ba2bb46acb45ba9"
|
||||
integrity sha512-ZTNSQkmWumEbiHO2GF4GmWxYVTiQyJy2XOTa15sdQSrvKn7l+180egQMqlrMOUMCyLMD7pmyQe4mMDUT6Behrw==
|
||||
version "3.1.5"
|
||||
resolved "https://registry.yarnpkg.com/array-includes/-/array-includes-3.1.5.tgz#2c320010db8d31031fd2a5f6b3bbd4b1aad31bdb"
|
||||
integrity sha512-iSDYZMMyTPkiFasVqfuAQnWAYcvO/SeBSCGKePoEthjp4LEMTe4uLc7b025o4jAZpHhihh8xPo99TNWUWWkGDQ==
|
||||
dependencies:
|
||||
call-bind "^1.0.2"
|
||||
define-properties "^1.1.3"
|
||||
es-abstract "^1.19.1"
|
||||
define-properties "^1.1.4"
|
||||
es-abstract "^1.19.5"
|
||||
get-intrinsic "^1.1.1"
|
||||
is-string "^1.0.7"
|
||||
|
||||
|
@ -5358,13 +5342,13 @@ atob@^2.1.2:
|
|||
resolved "https://registry.yarnpkg.com/atob/-/atob-2.1.2.tgz#6d9517eb9e030d2436666651e86bd9f6f13533c9"
|
||||
integrity sha512-Wm6ukoaOGJi/73p/cl2GvLjTI5JM1k/O14isD73YML8StrH/7/lRFgmg8nICZgD3bZZvjwCGxtMOD3wWNAu8cg==
|
||||
|
||||
autoprefixer@^10.3.7, autoprefixer@^10.4.5:
|
||||
version "10.4.5"
|
||||
resolved "https://registry.yarnpkg.com/autoprefixer/-/autoprefixer-10.4.5.tgz#662193c744094b53d3637f39be477e07bd904998"
|
||||
integrity sha512-Fvd8yCoA7lNX/OUllvS+aS1I7WRBclGXsepbvT8ZaPgrH24rgXpZzF0/6Hh3ZEkwg+0AES/Osd196VZmYoEFtw==
|
||||
autoprefixer@^10.3.7, autoprefixer@^10.4.5, autoprefixer@^10.4.6:
|
||||
version "10.4.7"
|
||||
resolved "https://registry.yarnpkg.com/autoprefixer/-/autoprefixer-10.4.7.tgz#1db8d195f41a52ca5069b7593be167618edbbedf"
|
||||
integrity sha512-ypHju4Y2Oav95SipEcCcI5J7CGPuvz8oat7sUtYj3ClK44bldfvtvcxK6IEK++7rqB7YchDGzweZIBG+SD0ZAA==
|
||||
dependencies:
|
||||
browserslist "^4.20.2"
|
||||
caniuse-lite "^1.0.30001332"
|
||||
browserslist "^4.20.3"
|
||||
caniuse-lite "^1.0.30001335"
|
||||
fraction.js "^4.2.0"
|
||||
normalize-range "^0.1.2"
|
||||
picocolors "^1.0.0"
|
||||
|
@ -5983,7 +5967,7 @@ browserify-zlib@^0.2.0:
|
|||
dependencies:
|
||||
pako "~1.0.5"
|
||||
|
||||
browserslist@^4.0.0, browserslist@^4.12.0, browserslist@^4.14.5, browserslist@^4.16.6, browserslist@^4.17.5, browserslist@^4.18.1, browserslist@^4.20.2, browserslist@^4.20.3:
|
||||
browserslist@^4.0.0, browserslist@^4.12.0, browserslist@^4.14.5, browserslist@^4.16.6, browserslist@^4.18.1, browserslist@^4.20.2, browserslist@^4.20.3:
|
||||
version "4.20.3"
|
||||
resolved "https://registry.yarnpkg.com/browserslist/-/browserslist-4.20.3.tgz#eb7572f49ec430e054f56d52ff0ebe9be915f8bf"
|
||||
integrity sha512-NBhymBQl1zM0Y5dQT/O+xiLP9/rzOIQdKM/eMJBAq7yBgaB6krIYLGejrwVYnSHZdqjscB1SPuAjHwxjvN6Wdg==
|
||||
|
@ -6204,10 +6188,10 @@ caniuse-api@^3.0.0:
|
|||
lodash.memoize "^4.1.2"
|
||||
lodash.uniq "^4.5.0"
|
||||
|
||||
caniuse-lite@^1.0.0, caniuse-lite@^1.0.30001109, caniuse-lite@^1.0.30001332:
|
||||
version "1.0.30001334"
|
||||
resolved "https://registry.yarnpkg.com/caniuse-lite/-/caniuse-lite-1.0.30001334.tgz#892e9965b35285033fc2b8a8eff499fe02f13d8b"
|
||||
integrity sha512-kbaCEBRRVSoeNs74sCuq92MJyGrMtjWVfhltoHUCW4t4pXFvGjUBrfo47weBRViHkiV3eBYyIsfl956NtHGazw==
|
||||
caniuse-lite@^1.0.0, caniuse-lite@^1.0.30001109, caniuse-lite@^1.0.30001332, caniuse-lite@^1.0.30001335:
|
||||
version "1.0.30001338"
|
||||
resolved "https://registry.yarnpkg.com/caniuse-lite/-/caniuse-lite-1.0.30001338.tgz#b5dd7a7941a51a16480bdf6ff82bded1628eec0d"
|
||||
integrity sha512-1gLHWyfVoRDsHieO+CaeYe7jSo/MT7D7lhaXUiwwbuR5BwQxORs0f1tAwUSQr3YbxRXJvxHM/PA5FfPQRnsPeQ==
|
||||
|
||||
capture-exit@^2.0.0:
|
||||
version "2.0.0"
|
||||
|
@ -6833,15 +6817,7 @@ copy-webpack-plugin@^10.2.4:
|
|||
schema-utils "^4.0.0"
|
||||
serialize-javascript "^6.0.0"
|
||||
|
||||
core-js-compat@^3.21.0, core-js-compat@^3.8.1:
|
||||
version "3.22.3"
|
||||
resolved "https://registry.yarnpkg.com/core-js-compat/-/core-js-compat-3.22.3.tgz#9b10d786052d042bc97ee8df9c0d1fb6a49c2005"
|
||||
integrity sha512-wliMbvPI2idgFWpFe7UEyHMvu6HWgW8WA+HnDRtgzoSDYvXFMpoGX1H3tPDDXrcfUSyXafCLDd7hOeMQHEZxGw==
|
||||
dependencies:
|
||||
browserslist "^4.20.3"
|
||||
semver "7.0.0"
|
||||
|
||||
core-js-compat@^3.22.1:
|
||||
core-js-compat@^3.21.0, core-js-compat@^3.22.1, core-js-compat@^3.8.1:
|
||||
version "3.22.4"
|
||||
resolved "https://registry.yarnpkg.com/core-js-compat/-/core-js-compat-3.22.4.tgz#d700f451e50f1d7672dcad0ac85d910e6691e579"
|
||||
integrity sha512-dIWcsszDezkFZrfm1cnB4f/J85gyhiCpxbgBdohWCDtSVuAaChTSpPV7ldOQf/Xds2U5xCIJZOK82G4ZPAIswA==
|
||||
|
@ -6850,9 +6826,9 @@ core-js-compat@^3.22.1:
|
|||
semver "7.0.0"
|
||||
|
||||
core-js-pure@^3.20.2, core-js-pure@^3.8.1, core-js-pure@^3.8.2:
|
||||
version "3.22.3"
|
||||
resolved "https://registry.yarnpkg.com/core-js-pure/-/core-js-pure-3.22.3.tgz#181d1b6321fb29fe99c16a1f28beb840ab84ad36"
|
||||
integrity sha512-oN88zz7nmKROMy8GOjs+LN+0LedIvbMdnB5XsTlhcOg1WGARt9l0LFg0zohdoFmCsEZ1h2ZbSQ6azj3M+vhzwQ==
|
||||
version "3.22.4"
|
||||
resolved "https://registry.yarnpkg.com/core-js-pure/-/core-js-pure-3.22.4.tgz#a992210f4cad8b32786b8654563776c56b0e0d0a"
|
||||
integrity sha512-4iF+QZkpzIz0prAFuepmxwJ2h5t4agvE8WPYqs2mjLJMNNwJOnpch76w2Q7bUfCPEv/V7wpvOfog0w273M+ZSw==
|
||||
|
||||
core-js@^2.4.0:
|
||||
version "2.6.12"
|
||||
|
@ -7196,10 +7172,10 @@ css@^3.0.0:
|
|||
source-map "^0.6.1"
|
||||
source-map-resolve "^0.6.0"
|
||||
|
||||
cssdb@^6.5.0:
|
||||
version "6.5.0"
|
||||
resolved "https://registry.yarnpkg.com/cssdb/-/cssdb-6.5.0.tgz#61264b71f29c834f09b59cb3e5b43c8226590122"
|
||||
integrity sha512-Rh7AAopF2ckPXe/VBcoUS9JrCZNSyc60+KpgE6X25vpVxA32TmiqvExjkfhwP4wGSb6Xe8Z/JIyGqwgx/zZYFA==
|
||||
cssdb@^6.6.1:
|
||||
version "6.6.1"
|
||||
resolved "https://registry.yarnpkg.com/cssdb/-/cssdb-6.6.1.tgz#2637fdc57eab452849488de7e8d961ec06f2fe8f"
|
||||
integrity sha512-0/nZEYfp8SFEzJkMud8NxZJsGfD7RHDJti6GRBLZptIwAzco6RTx1KgwFl4mGWsYS0ZNbCrsY9QryhQ4ldF3Mg==
|
||||
|
||||
cssesc@^3.0.0:
|
||||
version "3.0.0"
|
||||
|
@ -7455,9 +7431,9 @@ date-fns@2.x:
|
|||
integrity sha512-8d35hViGYx/QH0icHYCeLmsLmMUheMmTyV9Fcm6gvNwdw31yXXH+O85sOBJ+OLnLQMKZowvpKb6FgMIQjcpvQw==
|
||||
|
||||
dayjs@1.x:
|
||||
version "1.11.1"
|
||||
resolved "https://registry.yarnpkg.com/dayjs/-/dayjs-1.11.1.tgz#90b33a3dda3417258d48ad2771b415def6545eb0"
|
||||
integrity sha512-ER7EjqVAMkRRsxNCC5YqJ9d9VQYuWdGt7aiH2qA5R5wt8ZmWaP2dLUSIK6y/kVzLMlmh1Tvu5xUf4M/wdGJ5KA==
|
||||
version "1.11.2"
|
||||
resolved "https://registry.yarnpkg.com/dayjs/-/dayjs-1.11.2.tgz#fa0f5223ef0d6724b3d8327134890cfe3d72fbe5"
|
||||
integrity sha512-F4LXf1OeU9hrSYRPTTj/6FbO4HTjPKXvEIC1P2kcnFurViINCVk3ZV0xAS3XVx9MkMsXbbqlK6hjseaYbgKEHw==
|
||||
|
||||
debug@2.6.9, debug@^2.2.0, debug@^2.3.3, debug@^2.6.0, debug@^2.6.8, debug@^2.6.9:
|
||||
version "2.6.9"
|
||||
|
@ -7551,7 +7527,7 @@ define-lazy-prop@^2.0.0:
|
|||
resolved "https://registry.yarnpkg.com/define-lazy-prop/-/define-lazy-prop-2.0.0.tgz#3f7ae421129bcaaac9bc74905c98a0009ec9ee7f"
|
||||
integrity sha512-Ds09qNh8yw3khSjiJjiUInaGX9xlqZDY7JVryGxdxV7NPeuqQfplOpQ66yJFZut3jLa5zOwkXw1g9EI2uKh4Og==
|
||||
|
||||
define-properties@^1.1.2, define-properties@^1.1.3:
|
||||
define-properties@^1.1.2, define-properties@^1.1.3, define-properties@^1.1.4:
|
||||
version "1.1.4"
|
||||
resolved "https://registry.yarnpkg.com/define-properties/-/define-properties-1.1.4.tgz#0b14d7bd7fbeb2f3572c3a7eda80ea5d57fb05b1"
|
||||
integrity sha512-uckOqKcfaVvtBdsVkdPv3XjveQJsNQqmhXgRi8uhvWWuPYZCNlzT8qAyblUgNoXdHdjMTzAqeGjAoli8f+bzPA==
|
||||
|
@ -7948,9 +7924,9 @@ ejs@^3.1.6:
|
|||
jake "^10.8.5"
|
||||
|
||||
electron-to-chromium@^1.4.118:
|
||||
version "1.4.127"
|
||||
resolved "https://registry.yarnpkg.com/electron-to-chromium/-/electron-to-chromium-1.4.127.tgz#4ef19d5d920abe2676d938f4170729b44f7f423a"
|
||||
integrity sha512-nhD6S8nKI0O2MueC6blNOEZio+/PWppE/pevnf3LOlQA/fKPCrDp2Ao4wx4LFwmIkJpVdFdn2763YWLy9ENIZg==
|
||||
version "1.4.136"
|
||||
resolved "https://registry.yarnpkg.com/electron-to-chromium/-/electron-to-chromium-1.4.136.tgz#b6a3595a9c29d6d8f60e092d40ac24f997e4e7ef"
|
||||
integrity sha512-GnITX8rHnUrIVnTxU9UlsTnSemHUA2iF+6QrRqxFbp/mf0vfuSc/goEyyQhUX3TUUCE3mv/4BNuXOtaJ4ur0eA==
|
||||
|
||||
element-resize-detector@^1.2.2:
|
||||
version "1.2.4"
|
||||
|
@ -8090,17 +8066,19 @@ error-stack-parser@^2.0.6:
|
|||
dependencies:
|
||||
stackframe "^1.1.1"
|
||||
|
||||
es-abstract@^1.17.2, es-abstract@^1.19.0, es-abstract@^1.19.1, es-abstract@^1.19.2:
|
||||
version "1.19.5"
|
||||
resolved "https://registry.yarnpkg.com/es-abstract/-/es-abstract-1.19.5.tgz#a2cb01eb87f724e815b278b0dd0d00f36ca9a7f1"
|
||||
integrity sha512-Aa2G2+Rd3b6kxEUKTF4TaW67czBLyAv3z7VOhYRU50YBx+bbsYZ9xQP4lMNazePuFlybXI0V4MruPos7qUo5fA==
|
||||
es-abstract@^1.17.2, es-abstract@^1.19.0, es-abstract@^1.19.1, es-abstract@^1.19.2, es-abstract@^1.19.5:
|
||||
version "1.20.0"
|
||||
resolved "https://registry.yarnpkg.com/es-abstract/-/es-abstract-1.20.0.tgz#b2d526489cceca004588296334726329e0a6bfb6"
|
||||
integrity sha512-URbD8tgRthKD3YcC39vbvSDrX23upXnPcnGAjQfgxXF5ID75YcENawc9ZX/9iTP9ptUyfCLIxTTuMYoRfiOVKA==
|
||||
dependencies:
|
||||
call-bind "^1.0.2"
|
||||
es-to-primitive "^1.2.1"
|
||||
function-bind "^1.1.1"
|
||||
function.prototype.name "^1.1.5"
|
||||
get-intrinsic "^1.1.1"
|
||||
get-symbol-description "^1.0.0"
|
||||
has "^1.0.3"
|
||||
has-property-descriptors "^1.0.0"
|
||||
has-symbols "^1.0.3"
|
||||
internal-slot "^1.0.3"
|
||||
is-callable "^1.2.4"
|
||||
|
@ -8112,9 +8090,10 @@ es-abstract@^1.17.2, es-abstract@^1.19.0, es-abstract@^1.19.1, es-abstract@^1.19
|
|||
object-inspect "^1.12.0"
|
||||
object-keys "^1.1.1"
|
||||
object.assign "^4.1.2"
|
||||
string.prototype.trimend "^1.0.4"
|
||||
string.prototype.trimstart "^1.0.4"
|
||||
unbox-primitive "^1.0.1"
|
||||
regexp.prototype.flags "^1.4.1"
|
||||
string.prototype.trimend "^1.0.5"
|
||||
string.prototype.trimstart "^1.0.5"
|
||||
unbox-primitive "^1.0.2"
|
||||
|
||||
es-array-method-boxes-properly@^1.0.0:
|
||||
version "1.0.0"
|
||||
|
@ -8157,9 +8136,9 @@ es-to-primitive@^1.2.1:
|
|||
is-symbol "^1.0.2"
|
||||
|
||||
es5-shim@^4.5.13:
|
||||
version "4.6.6"
|
||||
resolved "https://registry.yarnpkg.com/es5-shim/-/es5-shim-4.6.6.tgz#1e0e95bedfdcd933a2d4931a3ac6c79164f18de6"
|
||||
integrity sha512-Ay5QQE78I2WKUoZVZjL0AIuiIjsmXwZGkyCTH9+n6J1anPbb0ymDA27ASa2Lt0rhOpAlEKy2W0d17gJ1XOQ5eQ==
|
||||
version "4.6.7"
|
||||
resolved "https://registry.yarnpkg.com/es5-shim/-/es5-shim-4.6.7.tgz#bc67ae0fc3dd520636e0a1601cc73b450ad3e955"
|
||||
integrity sha512-jg21/dmlrNQI7JyyA2w7n+yifSxBng0ZralnSfVZjoCawgNTCnS+yBCyVM9DL5itm7SUnDGgv7hcq2XCZX4iRQ==
|
||||
|
||||
es6-error@^4.0.1:
|
||||
version "4.1.1"
|
||||
|
@ -8586,9 +8565,9 @@ expect@^27.5.1:
|
|||
jest-message-util "^27.5.1"
|
||||
|
||||
express@^4.17.1, express@^4.17.3:
|
||||
version "4.18.0"
|
||||
resolved "https://registry.yarnpkg.com/express/-/express-4.18.0.tgz#7a426773325d0dd5406395220614c0db10b6e8e2"
|
||||
integrity sha512-EJEXxiTQJS3lIPrU1AE2vRuT7X7E+0KBbpm5GSoK524yl0K8X+er8zS2P14E64eqsVNoWbMCT7MpmQ+ErAhgRg==
|
||||
version "4.18.1"
|
||||
resolved "https://registry.yarnpkg.com/express/-/express-4.18.1.tgz#7797de8b9c72c857b9cd0e14a5eea80666267caf"
|
||||
integrity sha512-zZBcOX9TfehHQhtupq57OF8lFZ3UZi08Y97dwFCkD8p9d/d2Y3M+ykKcwaMDEL+4qyUolgBDX6AblpR3fL212Q==
|
||||
dependencies:
|
||||
accepts "~1.3.8"
|
||||
array-flatten "1.1.1"
|
||||
|
@ -8952,9 +8931,9 @@ flux@^4.0.1:
|
|||
fbjs "^3.0.1"
|
||||
|
||||
follow-redirects@^1.0.0, follow-redirects@^1.14.7:
|
||||
version "1.14.9"
|
||||
resolved "https://registry.yarnpkg.com/follow-redirects/-/follow-redirects-1.14.9.tgz#dd4ea157de7bfaf9ea9b3fbd85aa16951f78d8d7"
|
||||
integrity sha512-MQDfihBQYMcyy5dhRDJUHcw7lb2Pv/TuE6xP1vyraLukNDHKbDxDNaOE3NbCAdKQApno+GPRyo1YAp89yCjK4w==
|
||||
version "1.15.0"
|
||||
resolved "https://registry.yarnpkg.com/follow-redirects/-/follow-redirects-1.15.0.tgz#06441868281c86d0dda4ad8bdaead2d02dca89d4"
|
||||
integrity sha512-aExlJShTV4qOUOL7yF1U5tvLCB0xQuudbf6toyYA0E/acBNw71mvjFTnLaRp50aQaYocMR0a/RMMBIHeZnGyjQ==
|
||||
|
||||
for-in@^1.0.2:
|
||||
version "1.0.2"
|
||||
|
@ -9125,7 +9104,7 @@ function-bind@^1.1.1:
|
|||
resolved "https://registry.yarnpkg.com/function-bind/-/function-bind-1.1.1.tgz#a56899d3ea3c9bab874bb9773b7c5ede92f4895d"
|
||||
integrity sha512-yIovAzMX49sF8Yl58fSCWJ5svSLuaibPxXQJFLmBObTuCr0Mf1KiPopGM9NiFjiYBCbfaa2Fh6breQ6ANVTI0A==
|
||||
|
||||
function.prototype.name@^1.1.0:
|
||||
function.prototype.name@^1.1.0, function.prototype.name@^1.1.5:
|
||||
version "1.1.5"
|
||||
resolved "https://registry.yarnpkg.com/function.prototype.name/-/function.prototype.name-1.1.5.tgz#cce0505fe1ffb80503e6f9e46cc64e46a12a9621"
|
||||
integrity sha512-uN7m/BzVKQnCUF/iW8jYea67v++2u7m5UgENbHRtdDVclOUP+FMPlCNdmk0h/ysGyo2tavMJEDqJAkJdRa1vMA==
|
||||
|
@ -10941,18 +10920,18 @@ jest-message-util@^27.5.1:
|
|||
slash "^3.0.0"
|
||||
stack-utils "^2.0.3"
|
||||
|
||||
jest-message-util@^28.0.2:
|
||||
version "28.0.2"
|
||||
resolved "https://registry.yarnpkg.com/jest-message-util/-/jest-message-util-28.0.2.tgz#f3cf36be72be4c4c4058cb34bd6673996d26dee3"
|
||||
integrity sha512-knK7XyojvwYh1XiF2wmVdskgM/uN11KsjcEWWHfnMZNEdwXCrqB4sCBO94F4cfiAwCS8WFV6CDixDwPlMh/wdA==
|
||||
jest-message-util@^28.1.0:
|
||||
version "28.1.0"
|
||||
resolved "https://registry.yarnpkg.com/jest-message-util/-/jest-message-util-28.1.0.tgz#7e8f0b9049e948e7b94c2a52731166774ba7d0af"
|
||||
integrity sha512-RpA8mpaJ/B2HphDMiDlrAZdDytkmwFqgjDZovM21F35lHGeUeCvYmm6W+sbQ0ydaLpg5bFAUuWG1cjqOl8vqrw==
|
||||
dependencies:
|
||||
"@babel/code-frame" "^7.12.13"
|
||||
"@jest/types" "^28.0.2"
|
||||
"@jest/types" "^28.1.0"
|
||||
"@types/stack-utils" "^2.0.0"
|
||||
chalk "^4.0.0"
|
||||
graceful-fs "^4.2.9"
|
||||
micromatch "^4.0.4"
|
||||
pretty-format "^28.0.2"
|
||||
pretty-format "^28.1.0"
|
||||
slash "^3.0.0"
|
||||
stack-utils "^2.0.3"
|
||||
|
||||
|
@ -11132,12 +11111,12 @@ jest-util@^27.0.0, jest-util@^27.5.1:
|
|||
graceful-fs "^4.2.9"
|
||||
picomatch "^2.2.3"
|
||||
|
||||
jest-util@^28.0.2:
|
||||
version "28.0.2"
|
||||
resolved "https://registry.yarnpkg.com/jest-util/-/jest-util-28.0.2.tgz#8e22cdd6e0549e0a393055f0e2da7eacc334b143"
|
||||
integrity sha512-EVdpIRCC8lzqhp9A0u0aAKlsFIzufK6xKxNK7awsnebTdOP4hpyQW5o6Ox2qPl8gbeUKYF+POLyItaND53kpGA==
|
||||
jest-util@^28.1.0:
|
||||
version "28.1.0"
|
||||
resolved "https://registry.yarnpkg.com/jest-util/-/jest-util-28.1.0.tgz#d54eb83ad77e1dd441408738c5a5043642823be5"
|
||||
integrity sha512-qYdCKD77k4Hwkose2YBEqQk7PzUf/NSE+rutzceduFveQREeH6b+89Dc9+wjX9dAwHcgdx4yedGA3FQlU/qCTA==
|
||||
dependencies:
|
||||
"@jest/types" "^28.0.2"
|
||||
"@jest/types" "^28.1.0"
|
||||
"@types/node" "*"
|
||||
chalk "^4.0.0"
|
||||
ci-info "^3.2.0"
|
||||
|
@ -11183,17 +11162,17 @@ jest-watcher@^27.5.1:
|
|||
string-length "^4.0.1"
|
||||
|
||||
jest-watcher@^28.0.0:
|
||||
version "28.0.2"
|
||||
resolved "https://registry.yarnpkg.com/jest-watcher/-/jest-watcher-28.0.2.tgz#649fa24df531d4071be5784b6274d494d788c88b"
|
||||
integrity sha512-uIVJLpQ/5VTGQWBiBatHsi7jrCqHjHl0e0dFHMWzwuIfUbdW/muk0DtSr0fteY2T7QTFylv+7a5Rm8sBKrE12Q==
|
||||
version "28.1.0"
|
||||
resolved "https://registry.yarnpkg.com/jest-watcher/-/jest-watcher-28.1.0.tgz#aaa7b4164a4e77eeb5f7d7b25ede5e7b4e9c9aaf"
|
||||
integrity sha512-tNHMtfLE8Njcr2IRS+5rXYA4BhU90gAOwI9frTGOqd+jX0P/Au/JfRSNqsf5nUTcWdbVYuLxS1KjnzILSoR5hA==
|
||||
dependencies:
|
||||
"@jest/test-result" "^28.0.2"
|
||||
"@jest/types" "^28.0.2"
|
||||
"@jest/test-result" "^28.1.0"
|
||||
"@jest/types" "^28.1.0"
|
||||
"@types/node" "*"
|
||||
ansi-escapes "^4.2.1"
|
||||
chalk "^4.0.0"
|
||||
emittery "^0.10.2"
|
||||
jest-util "^28.0.2"
|
||||
jest-util "^28.1.0"
|
||||
string-length "^4.0.1"
|
||||
|
||||
jest-worker@^26.2.1, jest-worker@^26.5.0, jest-worker@^26.6.2:
|
||||
|
@ -11398,9 +11377,9 @@ jstat@^1.9.5:
|
|||
integrity sha512-cWnp4vObF5GmB2XsIEzxI/1ZTcYlcfNqxQ/9Fp5KFUa0Jf/4tO0ZkGVnqoEHDisJvYgvn5n3eWZbd2xTVJJPUQ==
|
||||
|
||||
"jsx-ast-utils@^2.4.1 || ^3.0.0", jsx-ast-utils@^3.2.1:
|
||||
version "3.2.2"
|
||||
resolved "https://registry.yarnpkg.com/jsx-ast-utils/-/jsx-ast-utils-3.2.2.tgz#6ab1e52c71dfc0c0707008a91729a9491fe9f76c"
|
||||
integrity sha512-HDAyJ4MNQBboGpUnHAVUNJs6X0lh058s6FuixsFGP7MgJYpD6Vasd6nzSG5iIfXu1zAYlHJ/zsOKNlrenTUBnw==
|
||||
version "3.3.0"
|
||||
resolved "https://registry.yarnpkg.com/jsx-ast-utils/-/jsx-ast-utils-3.3.0.tgz#e624f259143b9062c92b6413ff92a164c80d3ccb"
|
||||
integrity sha512-XzO9luP6L0xkxwhIJMTJQpZo/eeN60K08jHdexfD569AGxeNug6UketeHXEhROoM8aR7EcUoOQmIhcJQjcuq8Q==
|
||||
dependencies:
|
||||
array-includes "^3.1.4"
|
||||
object.assign "^4.1.2"
|
||||
|
@ -11827,7 +11806,7 @@ markdown-to-jsx@^7.1.3:
|
|||
resolved "https://registry.yarnpkg.com/markdown-to-jsx/-/markdown-to-jsx-7.1.7.tgz#a5f22102fb12241c8cea1ca6a4050bb76b23a25d"
|
||||
integrity sha512-VI3TyyHlGkO8uFle0IOibzpO1c1iJDcXcS/zBrQrXQQvJ2tpdwVzVZ7XdKsyRz1NdRmre4dqQkMZzUHaKIG/1w==
|
||||
|
||||
mathjs@^10.5.0:
|
||||
mathjs@10.5.0:
|
||||
version "10.5.0"
|
||||
resolved "https://registry.yarnpkg.com/mathjs/-/mathjs-10.5.0.tgz#f81d0518fe7b4b2a0b85e1125b8ecfc364fb0292"
|
||||
integrity sha512-gRnSY9psN9zgiB2QV9F4XbuX5hwjxY5Ou7qoTFWDbn2vZ3UEs+sjfK/SRg2WP30TNfZWpwlGdp8H1knFJnpFdA==
|
||||
|
@ -12273,12 +12252,7 @@ nano-css@^5.3.1:
|
|||
stacktrace-js "^2.0.2"
|
||||
stylis "^4.0.6"
|
||||
|
||||
nanoid@^3.1.23:
|
||||
version "3.3.3"
|
||||
resolved "https://registry.yarnpkg.com/nanoid/-/nanoid-3.3.3.tgz#fd8e8b7aa761fe807dba2d1b98fb7241bb724a25"
|
||||
integrity sha512-p1sjXuopFs0xg+fPASzQ28agW1oHD7xDsd9Xkf3T15H3c/cifrFHVwrh74PdoklAPi+i7MdRsE47vm2r6JoB+w==
|
||||
|
||||
nanoid@^3.3.3:
|
||||
nanoid@^3.1.23, nanoid@^3.3.3:
|
||||
version "3.3.4"
|
||||
resolved "https://registry.yarnpkg.com/nanoid/-/nanoid-3.3.4.tgz#730b67e3cd09e2deacf03c027c81c9d9dbc5e8ab"
|
||||
integrity sha512-MqBkQh/OHTS2egovRtLk45wEyNXwF+cokD+1YPf9u5VfJiRdAiRwB2froX5Co9Rh20xs4siNPm8naNotSD6RBw==
|
||||
|
@ -12602,12 +12576,12 @@ object.getownpropertydescriptors@^2.0.3, object.getownpropertydescriptors@^2.1.0
|
|||
es-abstract "^1.19.1"
|
||||
|
||||
object.hasown@^1.1.0:
|
||||
version "1.1.0"
|
||||
resolved "https://registry.yarnpkg.com/object.hasown/-/object.hasown-1.1.0.tgz#7232ed266f34d197d15cac5880232f7a4790afe5"
|
||||
integrity sha512-MhjYRfj3GBlhSkDHo6QmvgjRLXQ2zndabdf3nX0yTyZK9rPfxb6uRpAac8HXNLy1GpqWtZ81Qh4v3uOls2sRAg==
|
||||
version "1.1.1"
|
||||
resolved "https://registry.yarnpkg.com/object.hasown/-/object.hasown-1.1.1.tgz#ad1eecc60d03f49460600430d97f23882cf592a3"
|
||||
integrity sha512-LYLe4tivNQzq4JdaWW6WO3HMZZJWzkkH8fnI6EebWl0VZth2wL2Lovm74ep2/gZzlaTdV62JZHEqHQ2yVn8Q/A==
|
||||
dependencies:
|
||||
define-properties "^1.1.3"
|
||||
es-abstract "^1.19.1"
|
||||
define-properties "^1.1.4"
|
||||
es-abstract "^1.19.5"
|
||||
|
||||
object.pick@^1.3.0:
|
||||
version "1.3.0"
|
||||
|
@ -13629,9 +13603,9 @@ postcss-place@^7.0.4:
|
|||
postcss-value-parser "^4.2.0"
|
||||
|
||||
postcss-preset-env@^7.0.1:
|
||||
version "7.4.4"
|
||||
resolved "https://registry.yarnpkg.com/postcss-preset-env/-/postcss-preset-env-7.4.4.tgz#069e34e31e2a7345154da7936b9fc1fcbdbd6d43"
|
||||
integrity sha512-MqzSEx/QsvOk562iV9mLTgIvLFEOq1os9QBQfkgnq8TW6yKhVFPGh0gdXSK5ZlmjuNQEga6/x833e86XZF/lug==
|
||||
version "7.5.0"
|
||||
resolved "https://registry.yarnpkg.com/postcss-preset-env/-/postcss-preset-env-7.5.0.tgz#0c1f23933597d55dab4a90f61eda30b76e710658"
|
||||
integrity sha512-0BJzWEfCdTtK2R3EiKKSdkE51/DI/BwnhlnicSW482Ym6/DGHud8K0wGLcdjip1epVX0HKo4c8zzTeV/SkiejQ==
|
||||
dependencies:
|
||||
"@csstools/postcss-color-function" "^1.1.0"
|
||||
"@csstools/postcss-font-format-keywords" "^1.0.0"
|
||||
|
@ -13641,12 +13615,14 @@ postcss-preset-env@^7.0.1:
|
|||
"@csstools/postcss-normalize-display-values" "^1.0.0"
|
||||
"@csstools/postcss-oklab-function" "^1.1.0"
|
||||
"@csstools/postcss-progressive-custom-properties" "^1.3.0"
|
||||
autoprefixer "^10.4.5"
|
||||
"@csstools/postcss-stepped-value-functions" "^1.0.0"
|
||||
"@csstools/postcss-unset-value" "^1.0.0"
|
||||
autoprefixer "^10.4.6"
|
||||
browserslist "^4.20.3"
|
||||
css-blank-pseudo "^3.0.3"
|
||||
css-has-pseudo "^3.0.4"
|
||||
css-prefers-color-scheme "^6.0.3"
|
||||
cssdb "^6.5.0"
|
||||
cssdb "^6.6.1"
|
||||
postcss-attribute-case-insensitive "^5.0.0"
|
||||
postcss-clamp "^4.1.0"
|
||||
postcss-color-functional-notation "^4.2.2"
|
||||
|
@ -13678,9 +13654,9 @@ postcss-preset-env@^7.0.1:
|
|||
postcss-value-parser "^4.2.0"
|
||||
|
||||
postcss-pseudo-class-any-link@^7.1.2:
|
||||
version "7.1.2"
|
||||
resolved "https://registry.yarnpkg.com/postcss-pseudo-class-any-link/-/postcss-pseudo-class-any-link-7.1.2.tgz#81ec491aa43f97f9015e998b7a14263b4630bdf0"
|
||||
integrity sha512-76XzEQv3g+Vgnz3tmqh3pqQyRojkcJ+pjaePsyhcyf164p9aZsu3t+NWxkZYbcHLK1ju5Qmalti2jPI5IWCe5w==
|
||||
version "7.1.3"
|
||||
resolved "https://registry.yarnpkg.com/postcss-pseudo-class-any-link/-/postcss-pseudo-class-any-link-7.1.3.tgz#0e4753518b9f6caa8b649c75b56e69e391d0c12f"
|
||||
integrity sha512-I9Yp1VV2r8xFwg/JrnAlPCcKmutv6f6Ig6/CHFPqGJiDgYXM9C+0kgLfK4KOXbKNw+63QYl4agRUB0Wi9ftUIg==
|
||||
dependencies:
|
||||
postcss-selector-parser "^6.0.10"
|
||||
|
||||
|
@ -13830,10 +13806,10 @@ pretty-format@^27.0.0, pretty-format@^27.0.2, pretty-format@^27.5.1:
|
|||
ansi-styles "^5.0.0"
|
||||
react-is "^17.0.1"
|
||||
|
||||
pretty-format@^28.0.2:
|
||||
version "28.0.2"
|
||||
resolved "https://registry.yarnpkg.com/pretty-format/-/pretty-format-28.0.2.tgz#6a24d71cbb61a5e5794ba7513fe22101675481bc"
|
||||
integrity sha512-UmGZ1IERwS3yY35LDMTaBUYI1w4udZDdJGGT/DqQeKG9ZLDn7/K2Jf/JtYSRiHCCKMHvUA+zsEGSmHdpaVp1yw==
|
||||
pretty-format@^28.1.0:
|
||||
version "28.1.0"
|
||||
resolved "https://registry.yarnpkg.com/pretty-format/-/pretty-format-28.1.0.tgz#8f5836c6a0dfdb834730577ec18029052191af55"
|
||||
integrity sha512-79Z4wWOYCdvQkEoEuSlBhHJqWeZ8D8YRPiPctJFCtvuaClGpiwiQYSCUOE6IEKUbbFukKOTFIUAXE8N4EQTo1Q==
|
||||
dependencies:
|
||||
"@jest/schemas" "^28.0.2"
|
||||
ansi-regex "^5.0.1"
|
||||
|
@ -14210,9 +14186,9 @@ rc-dropdown@~3.5.0:
|
|||
rc-util "^5.17.0"
|
||||
|
||||
rc-field-form@~1.26.1:
|
||||
version "1.26.3"
|
||||
resolved "https://registry.yarnpkg.com/rc-field-form/-/rc-field-form-1.26.3.tgz#4050000eae0d879fde85672a965c9558ed6ff04b"
|
||||
integrity sha512-wzQToAwdr8fiq/Nb1KFq+9WYFeALJXKwNGk5/MaCu1AUS7PpVQaN2anzVfWdVBFiiM2N+3DOh64JSOH8s1w3FQ==
|
||||
version "1.26.4"
|
||||
resolved "https://registry.yarnpkg.com/rc-field-form/-/rc-field-form-1.26.4.tgz#78553e0f317f0ed7ceea70b1b89d43865dddeb83"
|
||||
integrity sha512-eCCyiNNaN0NTYTyoziQHD4Fj6mUED21lWkw66vg+kttg0eDw+miD6LsaJbTD5c2bzKjUJTf10AitPG+f5zT4+A==
|
||||
dependencies:
|
||||
"@babel/runtime" "^7.8.4"
|
||||
async-validator "^4.1.0"
|
||||
|
@ -14238,18 +14214,18 @@ rc-input-number@~7.3.0:
|
|||
rc-util "^5.9.8"
|
||||
|
||||
rc-input@~0.0.1-alpha.5:
|
||||
version "0.0.1-alpha.6"
|
||||
resolved "https://registry.yarnpkg.com/rc-input/-/rc-input-0.0.1-alpha.6.tgz#b9bcfb41251ca07aa183c03a3574fbc14fa2e426"
|
||||
integrity sha512-kgpmbxa9vp6kPLW7IP5/Lf6wuaMq+pUq+dPz98vIM58h4wkEKgBQlkMIg9OCEVQIiR8rEPEoe4dO2fc9R0aypQ==
|
||||
version "0.0.1-alpha.7"
|
||||
resolved "https://registry.yarnpkg.com/rc-input/-/rc-input-0.0.1-alpha.7.tgz#53e3f13871275c21d92b51f80b698f389ad45dd3"
|
||||
integrity sha512-eozaqpCYWSY5LBMwlHgC01GArkVEP+XlJ84OMvdkwUnJBSv83Yxa15pZpn7vACAj84uDC4xOA2CoFdbLuqB08Q==
|
||||
dependencies:
|
||||
"@babel/runtime" "^7.11.1"
|
||||
classnames "^2.2.1"
|
||||
rc-util "^5.18.1"
|
||||
|
||||
rc-mentions@~1.7.0:
|
||||
version "1.7.0"
|
||||
resolved "https://registry.yarnpkg.com/rc-mentions/-/rc-mentions-1.7.0.tgz#717be883e92b9085df900ab5a3ffab7379247bfa"
|
||||
integrity sha512-d3tZWCQIseQrn5ZpnUuaeKTQctgGwVzcEUVpVswxvnsLB1/e2H12xHzVqH87AvPkHMs9m3oFZINbuC5Qxevv6g==
|
||||
version "1.7.1"
|
||||
resolved "https://registry.yarnpkg.com/rc-mentions/-/rc-mentions-1.7.1.tgz#480ad04af4460ee01b6ccd9137fcea23067aa9be"
|
||||
integrity sha512-JbCS9bTqt6BYN2vfTPythlScLuc42rIlX85n7975RnkfawXlJjskHOlR3o8EpD4asl4KuA2jKTy0dj39DtSVqg==
|
||||
dependencies:
|
||||
"@babel/runtime" "^7.10.1"
|
||||
classnames "^2.2.6"
|
||||
|
@ -14272,9 +14248,9 @@ rc-menu@~9.5.1, rc-menu@~9.5.5:
|
|||
shallowequal "^1.1.0"
|
||||
|
||||
rc-motion@^2.0.0, rc-motion@^2.0.1, rc-motion@^2.2.0, rc-motion@^2.3.0, rc-motion@^2.3.4, rc-motion@^2.4.3, rc-motion@^2.4.4, rc-motion@^2.5.1:
|
||||
version "2.5.1"
|
||||
resolved "https://registry.yarnpkg.com/rc-motion/-/rc-motion-2.5.1.tgz#3eceb7d891079c0f67a72639d30e168b91839e03"
|
||||
integrity sha512-h3GKMjFJkK+4z6fNfVlIMrb7WFCZsreivVvHOBb38cKcpKDx5g3kpHwn5Ekbo1+g0nnC02Dtap2trfCAPGxllw==
|
||||
version "2.6.0"
|
||||
resolved "https://registry.yarnpkg.com/rc-motion/-/rc-motion-2.6.0.tgz#c60c3e7f15257f55a8cd7794a539f0e2cc751399"
|
||||
integrity sha512-1MDWA9+i174CZ0SIDenSYm2Wb9YbRkrexjZWR0CUFu7D6f23E8Y0KsTgk9NGOLJsGak5ELZK/Y5lOlf5wQdzbw==
|
||||
dependencies:
|
||||
"@babel/runtime" "^7.11.1"
|
||||
classnames "^2.2.1"
|
||||
|
@ -14350,10 +14326,10 @@ rc-resize-observer@^1.0.0, rc-resize-observer@^1.1.0, rc-resize-observer@^1.2.0:
|
|||
rc-util "^5.15.0"
|
||||
resize-observer-polyfill "^1.5.1"
|
||||
|
||||
rc-segmented@~2.0.0:
|
||||
version "2.0.0"
|
||||
resolved "https://registry.yarnpkg.com/rc-segmented/-/rc-segmented-2.0.0.tgz#209b55bec85c1a8b1821c30e62d3ebef4da04b52"
|
||||
integrity sha512-YsdS+aP7E6ZMEY35WSlewJIsrjPbBSP4X/7RvZtzLExKDZwFvXdCPCbWFVDNks4jOYY9TUPYt7qlVifEu9/zXA==
|
||||
"rc-segmented@~2.1.0 ":
|
||||
version "2.1.0"
|
||||
resolved "https://registry.yarnpkg.com/rc-segmented/-/rc-segmented-2.1.0.tgz#0e0afe646c1a0e44a0e18785f518c42633ec8efc"
|
||||
integrity sha512-hUlonro+pYoZcwrH6Vm56B2ftLfQh046hrwif/VwLIw1j3zGt52p5mREBwmeVzXnSwgnagpOpfafspzs1asjGw==
|
||||
dependencies:
|
||||
"@babel/runtime" "^7.11.1"
|
||||
classnames "^2.2.1"
|
||||
|
@ -14361,9 +14337,9 @@ rc-segmented@~2.0.0:
|
|||
rc-util "^5.17.0"
|
||||
|
||||
rc-select@~14.1.0, rc-select@~14.1.1:
|
||||
version "14.1.1"
|
||||
resolved "https://registry.yarnpkg.com/rc-select/-/rc-select-14.1.1.tgz#87a51ce515aba5cfa083ae0f5be15e7c550ad93f"
|
||||
integrity sha512-l2TSSy/rwvfob0SmQ0sPQ1pUMUq65u6U4Y9lc9dvQOMSMzDSga4b3tEgIgzN1YKzakV65wGXMOBVecjixPEZ4Q==
|
||||
version "14.1.2"
|
||||
resolved "https://registry.yarnpkg.com/rc-select/-/rc-select-14.1.2.tgz#59a73726ef82a87b174ed0784cddfccc7e797e4b"
|
||||
integrity sha512-/QgarL/T/d7MIPcoRmTca2TWHBoHBM1EQIgdaFmvl3qsYRSbrb8NpWcQuJoc9fprXERWxdYSTUThQObHvdEVBQ==
|
||||
dependencies:
|
||||
"@babel/runtime" "^7.10.1"
|
||||
classnames "2.x"
|
||||
|
@ -15436,9 +15412,9 @@ rollup-plugin-terser@^7.0.0:
|
|||
terser "^5.0.0"
|
||||
|
||||
rollup@^2.43.1:
|
||||
version "2.70.2"
|
||||
resolved "https://registry.yarnpkg.com/rollup/-/rollup-2.70.2.tgz#808d206a8851628a065097b7ba2053bd83ba0c0d"
|
||||
integrity sha512-EitogNZnfku65I1DD5Mxe8JYRUCy0hkK5X84IlDtUs+O6JRMpRciXTzyCUuX11b5L5pvjH+OmFXiQ3XjabcXgg==
|
||||
version "2.72.0"
|
||||
resolved "https://registry.yarnpkg.com/rollup/-/rollup-2.72.0.tgz#f94280b003bcf9f2f1f2594059a9db5abced371e"
|
||||
integrity sha512-KqtR2YcO35/KKijg4nx4STO3569aqCUeGRkKWnJ6r+AvBBrVY9L4pmf4NHVrQr4mTOq6msbohflxr2kpihhaOA==
|
||||
optionalDependencies:
|
||||
fsevents "~2.3.2"
|
||||
|
||||
|
@ -16342,21 +16318,23 @@ string.prototype.padstart@^3.0.0:
|
|||
define-properties "^1.1.3"
|
||||
es-abstract "^1.19.1"
|
||||
|
||||
string.prototype.trimend@^1.0.4:
|
||||
version "1.0.4"
|
||||
resolved "https://registry.yarnpkg.com/string.prototype.trimend/-/string.prototype.trimend-1.0.4.tgz#e75ae90c2942c63504686c18b287b4a0b1a45f80"
|
||||
integrity sha512-y9xCjw1P23Awk8EvTpcyL2NIr1j7wJ39f+k6lvRnSMz+mz9CGz9NYPelDk42kOz6+ql8xjfK8oYzy3jAP5QU5A==
|
||||
string.prototype.trimend@^1.0.5:
|
||||
version "1.0.5"
|
||||
resolved "https://registry.yarnpkg.com/string.prototype.trimend/-/string.prototype.trimend-1.0.5.tgz#914a65baaab25fbdd4ee291ca7dde57e869cb8d0"
|
||||
integrity sha512-I7RGvmjV4pJ7O3kdf+LXFpVfdNOxtCW/2C8f6jNiW4+PQchwxkCDzlk1/7p+Wl4bqFIZeF47qAHXLuHHWKAxog==
|
||||
dependencies:
|
||||
call-bind "^1.0.2"
|
||||
define-properties "^1.1.3"
|
||||
define-properties "^1.1.4"
|
||||
es-abstract "^1.19.5"
|
||||
|
||||
string.prototype.trimstart@^1.0.4:
|
||||
version "1.0.4"
|
||||
resolved "https://registry.yarnpkg.com/string.prototype.trimstart/-/string.prototype.trimstart-1.0.4.tgz#b36399af4ab2999b4c9c648bd7a3fb2bb26feeed"
|
||||
integrity sha512-jh6e984OBfvxS50tdY2nRZnoC5/mLFKOREQfw8t5yytkoUsJRNxvI/E39qu1sD0OtWI3OC0XgKSmcWwziwYuZw==
|
||||
string.prototype.trimstart@^1.0.5:
|
||||
version "1.0.5"
|
||||
resolved "https://registry.yarnpkg.com/string.prototype.trimstart/-/string.prototype.trimstart-1.0.5.tgz#5466d93ba58cfa2134839f81d7f42437e8c01fef"
|
||||
integrity sha512-THx16TJCGlsN0o6dl2o6ncWUsdgnLRSA23rRE5pyGBw/mLr3Ej/R2LaqCtgP8VNMGZsvMWnf9ooZPyY2bHvUFg==
|
||||
dependencies:
|
||||
call-bind "^1.0.2"
|
||||
define-properties "^1.1.3"
|
||||
define-properties "^1.1.4"
|
||||
es-abstract "^1.19.5"
|
||||
|
||||
string_decoder@^1.0.0, string_decoder@^1.1.1:
|
||||
version "1.3.0"
|
||||
|
@ -17143,7 +17121,7 @@ uglify-js@^3.1.4:
|
|||
resolved "https://registry.yarnpkg.com/uglify-js/-/uglify-js-3.15.4.tgz#fa95c257e88f85614915b906204b9623d4fa340d"
|
||||
integrity sha512-vMOPGDuvXecPs34V74qDKk4iJ/SN4vL3Ow/23ixafENYvtrNvtbcgUeugTcUGRGsOF/5fU8/NYSL5Hyb3l1OJA==
|
||||
|
||||
unbox-primitive@^1.0.1:
|
||||
unbox-primitive@^1.0.2:
|
||||
version "1.0.2"
|
||||
resolved "https://registry.yarnpkg.com/unbox-primitive/-/unbox-primitive-1.0.2.tgz#29032021057d5e6cdbd08c5129c226dff8ed6f9e"
|
||||
integrity sha512-61pPlCD9h51VoreyJ0BReideM3MDKMKnh6+V9L08331ipq6Q8OFXZYiqP6n/tbHx4s5I9uRhcye6BrbkizkBDw==
|
||||
|
@ -18644,9 +18622,9 @@ ws@^7.3.1, ws@^7.4.6:
|
|||
integrity sha512-KMvVuFzpKBuiIXW3E4u3mySRO2/mCHSyZDJQM5NQ9Q9KHWHWh0NHgfbRMLLrceUK5qAL4ytALJbpRMjixFZh8A==
|
||||
|
||||
ws@^8.2.3, ws@^8.4.2:
|
||||
version "8.5.0"
|
||||
resolved "https://registry.yarnpkg.com/ws/-/ws-8.5.0.tgz#bfb4be96600757fe5382de12c670dab984a1ed4f"
|
||||
integrity sha512-BWX0SWVgLPzYwF8lTzEy1egjhS4S4OEAHfsO8o65WOVsrnSRGaSiUaa9e0ggGlkMTtBlmOpEXiie9RUcBO86qg==
|
||||
version "8.6.0"
|
||||
resolved "https://registry.yarnpkg.com/ws/-/ws-8.6.0.tgz#e5e9f1d9e7ff88083d0c0dd8281ea662a42c9c23"
|
||||
integrity sha512-AzmM3aH3gk0aX7/rZLYvjdvZooofDu3fFOzGqcSnQ1tOcTWwhM/o+q++E8mAyVVIyUdajrkzWUGftaVSDLn1bw==
|
||||
|
||||
xdg-basedir@^4.0.0:
|
||||
version "4.0.0"
|
||||
|
|
Loading…
Reference in New Issue
Block a user