diff --git a/DistributionMomentTruncation.wl b/DistributionMomentTruncation.wl new file mode 100644 index 0000000..518128a --- /dev/null +++ b/DistributionMomentTruncation.wl @@ -0,0 +1,294 @@ +(* ::Package:: *) + +(* ::Title:: *) +(*Queue-SDP-OOP*) + + +(* ::Subsubsection:: *) +(*Preamble*) + + +(* ::Input::Initialization:: *) +ResourceFunction[ResourceObject[Association["Name" -> "DarkMode", "ShortName" -> "DarkMode", "UUID" -> "6ae9b15e-dd80-4d11-be6e-434bf9ac9265", "ResourceType" -> "Function", "Version" -> "2.0.0", "Description" -> "Restyle notebooks into dark mode", "RepositoryLocation" -> URL["https://www.wolframcloud.com/objects/resourcesystem/api/1.0"], "SymbolName" -> "FunctionRepository`$f2abd2063089401aafe135eb354a8d92`DarkMode", "FunctionLocation" -> CloudObject["https://www.wolframcloud.com/obj/91755122-26ae-43f1-8e41-4043472dcf8a"]], ResourceSystemBase -> Automatic]]; +SetOptions[SelectedNotebook[],PrintingStyleEnvironment->"Printout",ShowSyntaxStyles->True] +ClearAll[Evaluate[ToString[Context[]]<>"*"]] + + +(* ::Section:: *) +(*Definitions-OOP*) + + +(* ::Subsection:: *) +(*Related Symbols*) + + +(* ::Input:: *) +(*Names["*Process*"];*) + + +(* ::Input:: *) +(*Names["*Distribution*"];*) + + +(* ::Input:: *) +(*MapThread[Construct,{{f,g,h},{a,b,c}}]*) + + +(* ::Subsection::Closed:: *) +(*Algebra*) + + +(* ::Input:: *) +(*ClearAll[Algebra];*) +(*Options[Algebra]={"MultTable"->None,"Generators"->None,"Dimension"->None};*) +(*Algebra[ops:OptionsPattern[]]:=Algebra[canonicalizeAlgebraData[ops]];*) +(*(*do the minimum work necessary to make sure all the data for the Algebra is there*)*) +(*canonicalizeAlgebraData[ops:OptionsPattern[]]:=Association[ops];*) + + +(* ::Input:: *) +(*(*make some validators so you can always be sure you have a valid algebra without constantly having to check it*)validateAlgebraData[a_Association]:=Length[a]>0;(*reimplement this*)Algebra[a_Association]?NotAlgebraQ:=System`Private`HoldSetValid[Algebra[a]]/;validateAlgebraData[a];*) +(*AlgebraQ[a_Algebra]:=System`Private`HoldValidQ[a];*) +(*AlgebraQ[_]:=False;*) +(*AlgebraQ[s_Symbol]:=(Head[s]===Algebra&&AlgebraQ[Evaluate[s]]);*) +(*AlgebraQ~SetAttributes~HoldFirst;*) +(*NotAlgebraQ[a_]:=Not[AlgebraQ[a]];*) +(*NotAlgebraQ~SetAttributes~HoldFirst;*) + + +(* ::Input:: *) +(*(*define formatting if you want to*)Format[Algebra[a_]?AlgebraQ,StandardForm]:=RawBoxes@BoxForm`ArrangeSummaryBox[Algebra,Algebra[a],None,{"Put summary info here"},{},StandardForm]*) + + +(* ::Input:: *) +(*(*define some accessors/methods on your alebgra*)Algebra[a_]?AlgebraQ[k_]:=Lookup[a,k];(*general lookup*)(g:Algebra[a_]?AlgebraQ)["Generators"]:=getAlgebraicGenerators[g];*) +(*(g:Algebra[a_]?AlgebraQ)["Dimensions"]:=getAlgebraDimension[g];*) + + +(* ::Input:: *) +(*(*define some overloads for your algebra*)Algebra/:Dimensions[a_Algebra?AlgebraQ]:=a["Dimensions"];*) +(*Algebra/:a_Algebra?AlgebraQ[[el_]]:=AlgebraicElement[a,el];(*getting elements*)AlgebraicElement/:NonCommutativeMultiply[AlgebraicElement[a_Algebra?AlgebraQ,el1_],AlgebraicElement[a_Algebra?AlgebraQ,el2_]]:=getAlgebraProduct[a,{el1,el2}];*) + + +(* ::Input:: *) +(*(*allow for natural modifications of the algebraic structure*)mutateAlgebra[Algebra[a_]?AlgebraQ,changes_Association]:=Algebra[Join[changes,a]];*) +(*mutateAlgebra[a_Algebra,changes_]:=mutateAlgebra[a,Association@changes]*) +(*algebraMutationHandler~SetAttributes~HoldAllComplete;*) +(*algebraMutationHandler[AssociateTo[s_Symbol?AlgebraQ,stuff_]]:=(s=mutateAlgebra[s,stuff]);*) +(*algebraMutationHandler[Set[s_Symbol?AlgebraQ[key_],val_]]:=(s=mutateAlgebra[s,key->val]);*) +(*Language`SetMutationHandler[Algebra,algebraMutationHandler];*) + + +(* ::Input:: *) +(*(*implement the core algebra calculations some other way*)getAlgebraGenerators[a_Algebra?AlgebraQ]:="Generator, TBD";*) +(*getAlgebraDimension[a_Algebra?AlgebraQ]:="Dimension, TBD";*) +(*getAlgebraProduct[a_Algebra?AlgebraQ,{el1_,el2_}]:="Product, TBD";*) + + +(* ::Input:: *) +(*a=Algebra["MultTable"->{}]*) +(*(*Out:Algebra[<|"MultTable"\[Rule]{}|>]*)*) + + +(* ::Subsection:: *) +(*Mine*) + + +(* ::Input::Initialization:: *) +ClearAll["Global`*"] + + +(* ::Text:: *) +(*Note : I will follow the paradigm suggested in this post. I propose to implement two wrappers: DistributionMomentTruncation and ProcessMomentTruncation. *) + + +(* ::Subsubsection:: *) +(*Clearing definitions*) + + +(* ::Input::Initialization:: *) +ClearAll[DistributionMomentTruncation]; +ClearAll[$DistributionDomainCanonicalizer,$DistributionDomainStylizer,$DistributionMomentTruncationSummaryThumbnail]; +ClearAll[canonicalizeDistributionMomentTruncation,validateDistributionMomentTruncation,instantiateDistributionMomentTruncation] +ClearAll[DistributionMomentTruncationQ,NotDistributionMomentTruncationQ] +ClearAll[ProcessMomentTruncation,QueueMomentTruncation]; +Options[DistributionMomentTruncation]={(*This allow for setting default values; *) +"TruncationOrder"->None,(*major parameter*) +"OriginalDistribution"->None,(*if supplied, the moment sequence is always generated using the moment function of the original distribution; there may be need for memoisation*) + +(*"IndependentMargins"\[Rule]None,(*If this is true, MomentData is represented by a matrix only; only meaningful for multi-dimensional distributions, should be set to None for 1-d distributions, and is deleted if IdenticalMargins is True.*) +"IdenticalMargins"\[Rule]None,(*If this is true, MomentData can be represented as a vector; only meaningful for multi-dimensional distributions should be set to None for 1-d distributions.*)*) +"MarginalProperty"->None, +"MomentForm"->"Moment",(*following the specification of MomentConvert, absolute, factorial, central moments and cumulants; may also support truncated probability sequence for *) +"MomentData"->None,(*an association (is this really a good idea?) of the moments, with (lists of) non negative integers as keys; an all-zero key can be used to denote an alternative unitisation (a single zero can be used as a shorthand). not instantiated if there is an original distribution.*)(*I decide that we should only support two types of moment data; see "MomentDataShape" below*) +"MomentDataShape"->None,(*allowed types are "Full", "Overall" and "Function"; "Full" should be assumed. If IndependentMargins is True, this specification is ignored; only meaningful for multi-dimensional distributions, should be set to None for 1-d distributions. not instantiated if there is an original distribution.*) +(*"Dimensions"\[Rule]None,(*is this really needed?*)*) +"Domain"->None(*"DistributionDomain"\[Rule]None,*)(*These two should always be synonymous; the latter should not be stored, but only handled in interfaces. We must handle conversions between "domains" and "intervals/spans"*) +(*,"SummaryThumbnail"\[Rule]None*)(*Default to a plot of the moment matched polynomial; if there is an original distribution, it will also be plotted so that their difference is clearly seen. When any of these are hard to evaluate, a default thumbnail will be shown; this may should not be part of the structure, since it is expensive to store.*) +}; + + +(* ::Subsubsection:: *) +(*Initializers*) + + +(* ::ItemNumbered:: *) +(*From a distribution*) + + +(* ::Input::Initialization:: *) +DistributionMomentTruncation[dist_?DistributionParameterQ]:=dist +DistributionMomentTruncation[dist_?DistributionParameterQ,type:"Moment"|"FactorialMoment"|"CentralMoment"|"Cumulant"][r_]:=Symbol[type][dist,r] + +DistributionMomentTruncation[trunc_Integer?Positive|trunc_Symbol|trunc:Infinity,type:"Moment"|"FactorialMoment"|"CentralMoment"|"Cumulant":"Moment",ops:OptionsPattern[]][dist_?DistributionParameterQ]:=DistributionMomentTruncation[trunc,dist,type,ops] +DistributionMomentTruncation[trunc_Integer?Positive|trunc_Symbol,dist_?DistributionParameterQ,type:"Moment"|"FactorialMoment"|"CentralMoment"|"Cumulant":"Moment",ops:OptionsPattern[]]:=DistributionMomentTruncation[trunc,dist,"MomentForm"->type,Sequence@@FilterRules[{ops},Except["TruncationOrder"|"OriginalDistribution"|"MomentForm"|"MomentData"|"MomentDataShape"]]] +DistributionMomentTruncation[trunc_Integer?Positive|trunc_Symbol,dist_?DistributionParameterQ,ops:OptionsPattern[]]:=DistributionMomentTruncation["TruncationOrder"->trunc,"OriginalDistribution"->dist,Sequence@@FilterRules[{ops},Except["TruncationOrder"|"OriginalDistribution"|"MomentData"|"MomentDataShape"]]] +DistributionMomentTruncation[Infinity,dist_?DistributionParameterQ,ops:OptionsPattern[]]:=dist(*when a distribution is not moment truncated, it gets cast into the original distribution*) + + +(* ::ItemNumbered:: *) +(*From a moment function*) + + +(* ::Input::Initialization:: *) +DistributionMomentTruncation[trunc_Integer?Positive|trunc_Symbol|trunc:Infinity,moments_Function|moments_Symbol,type:"Moment"|"FactorialMoment"|"CentralMoment"|"Cumulant":"Moment",ops:OptionsPattern[]]:=DistributionMomentTruncation[ +trunc,moments,"MomentForm"->type,Sequence@@FilterRules[{ops},Except["TruncationOrder"|"OriginalDistribution"|"MomentForm"|"MomentData"|"MomentDataShape"]]] +DistributionMomentTruncation[trunc_Integer?Positive|trunc_Symbol|trunc:Infinity,moments_Function|moments_Symbol,ops:OptionsPattern[]]:=DistributionMomentTruncation["TruncationOrder"->trunc,"MomentData"->moments,"MomentDataShape"->"Function",Sequence@@FilterRules[{ops},Except["TruncationOrder"|"OriginalDistribution"|"MomentData"|"MomentDataShape"]]] + + +(* ::ItemNumbered:: *) +(*From a moment array*) + + +(* ::Input::Initialization:: *) +DistributionMomentTruncation[moments_?VectorQ,ops:OptionsPattern[{"Domain"->Interval[{-\[Infinity],\[Infinity]}],DistributionMomentTruncation}]]:=DistributionMomentTruncation["TruncationOrder"->Length[moments],"MomentData"->moments,"Domain"->OptionValue["Domain"],If[!MatchQ[OptionValue["Domain"],_Interval|_Span](*one dimensional*),"MarginalProperty"->"Identical",Unevaluated@Sequence[]],Sequence@@FilterRules[{ops},Except["TruncationOrder"|"OriginalDistribution"|"MomentData"|"Domain"|"MarginalProperty"]]](*default to a 1-d distribution*) +DistributionMomentTruncation[moments_?MatrixQ,ops:OptionsPattern[{"Domain"->None,DistributionMomentTruncation}]]:=(*This is for independent margins*)Module[{domain=OptionValue["Domain"]}, +If[SquareMatrixQ[moments]&&Not@MatchQ[OptionValue["MarginalProperty"],"Identical"|"Independent"]&& +(OptionValue["MomentDataShape"]==="Full"|| +(MatchQ[domain,{_Interval|_Span,_Interval|_Span}]&&Length[moments]>2)),(*handle the case when the distribution happens to be 2-d*) +If[domain===None,domain=Table[Interval[{-\[Infinity],\[Infinity]}],2]]; +DistributionMomentTruncation[ +"TruncationOrder"->Length[moments]-1(*note this*),"MomentData"->moments,"Domain"->domain,"MarginalProperty"->None,Sequence@@FilterRules[{ops},Except["TruncationOrder"|"OriginalDistribution"|"MomentData"|"Domain"|"MarginalProperty"]] +], +If[domain===None,domain=Table[Interval[{-\[Infinity],\[Infinity]}],Length[moments]]]; +DistributionMomentTruncation[ +"TruncationOrder"->Length[moments],"MomentData"->moments,"Domain"->domain,"MarginalProperty"->"Independent",Sequence@@FilterRules[{ops},Except["TruncationOrder"|"OriginalDistribution"|"MomentData"|"Domain"|"MarginalProperty"]] +] +] +] +DistributionMomentTruncation[moments_?ArrayQ,ops:OptionsPattern[{"Domain"->None,DistributionMomentTruncation}]]:=(*currently, only "MomentDataShape"\[Rule]"Full" is supported*) +Module[{domain=If[OptionValue["Domain"]===None,Table[Interval[{-\[Infinity],\[Infinity]}],ArrayDepth[moments]]]}, +DistributionMomentTruncation[ +"TruncationOrder"->Length[moments]-1(*note this*),"MomentData"->moments,"MomentDataShape"->"Full","Domain"->domain,"MarginalProperty"->None,Sequence@@FilterRules[{ops},Except["TruncationOrder"|"OriginalDistribution"|"MomentData"|"Domain"|"MarginalProperty"]] +] +] +DistributionMomentTruncation[ops:OptionsPattern[]]:=DistributionMomentTruncation[canonicalizeDistributionMomentTruncation[ops]] + + +(* ::Item:: *) +(*Canonicalize the Truncation*) + + +(* ::Input::Initialization:: *) +(*do the minimum work necessary to make sure all the data for the DistributionMomentTruncation is there*) +DistributionMomentTruncation::nocanon="Cannot construct a valid DistributionMomentTruncation from the given options `1`."; +DistributionMomentTruncation::noentry="Cannot construct a valid DistributionMomentTruncation because the entry `1` is not provided and cannot be inferred."; +DistributionMomentTruncation::noimplm="The required feature `1` is not implemented yet."; +$DistributionDomainCanonicalizer=Dispatch@{ +Reals->Interval[{-\[Infinity],\[Infinity]}],Integers->(-\[Infinity];;\[Infinity]), +NonNegativeReals->Interval[{0,\[Infinity]}],NonPositiveReals->Interval[{-\[Infinity],0}], +NonNegativeIntegers->(0;;\[Infinity]),NonPositiveIntegers->(-\[Infinity];;0), +PositiveIntegers->(1;;\[Infinity]),NegativeIntegers->(-\[Infinity];;-1)}; +canonicalizeDistributionMomentTruncation[ops:OptionsPattern[DistributionMomentTruncation]]:=Which[ +Length@{ops}<1,Message[DistributionMomentTruncation::nocanon,{ops}];$Failed, +OptionValue["MomentDataShape"]==="Function"&&(OptionValue["Domain"]===None),Message[DistributionMomentTruncation::noentry,{"Domain"}];$Failed, +True,Module[{truncdata={ops}}, +If [OptionValue["MomentDataShape"]==="Overall", +Message[DistributionMomentTruncation::noimplm,"MomentDataShape"->"Overall"];AppendTo[truncdata,"MomentDataShape"->"Full"]]; +AppendTo[truncdata,"Domain"->OptionValue["Domain"]/.$DistributionDomainCanonicalizer]; +If [DistributionParameterQ[OptionValue["OriginalDistribution"]],AppendTo[truncdata,"Domain"->DistributionDomain[OptionValue["OriginalDistribution"]]]]; +AppendTo[truncdata,"MomentForm"->OptionValue["MomentForm"]]; +Sort@Association[truncdata] +] +] + + +(* ::Subsubsection:: *) +(*Validators*) + + +(* ::Input::Initialization:: *) +(*make some validators so you can always be sure you have a valid DistributionMomentTruncation without constantly having to check it*)validateDistributionMomentTruncation[assoc_Association]:=And[ +Length[assoc]>0,KeyMemberQ["TruncationOrder"] +](*reimplement this*) +DistributionMomentTruncation[assoc_Association]?NotDistributionMomentTruncationQ:=System`Private`HoldSetValid[DistributionMomentTruncation[assoc]]/;validateDistributionMomentTruncation[assoc]; +DistributionMomentTruncationQ[distrlx_DistributionMomentTruncation]:=System`Private`HoldValidQ[distrlx]; +DistributionMomentTruncationQ[_]:=False; +DistributionMomentTruncationQ[symbol_Symbol]:=(Head[symbol]===DistributionMomentTruncation&&DistributionMomentTruncationQ[Evaluate[symbol]]); +DistributionMomentTruncationQ~SetAttributes~HoldFirst; +NotDistributionMomentTruncationQ[distrlx_]:=Not[DistributionMomentTruncationQ[distrlx]]; +NotDistributionMomentTruncationQ~SetAttributes~HoldFirst; + + +(* ::Input::Initialization:: *) +instantiateDistributionMomentTruncation[distrlx_DistributionMomentTruncation,ops:OptionsPattern[]]:=Missing["NotAvailable"](*Default to na\[IDoubleDot]ve polynomial moment matching; possible alternatives including orthogonal polynomials, piecewise-constant (histogram), point-masses, smooth-kernel distributions.*) + + +(* ::Subsubsection:: *) +(*Accessors*) + + +(* ::Input::Initialization:: *) +DistributionMomentTruncation::excdtrnc="The \!\(\*SuperscriptBox[\(`1`\), \(th\)]\) moment exceeds the order of the truncation."; +DistributionMomentTruncation[a_Association]["Moment"][0]:=1 +DistributionMomentTruncation[a_Association]["Moment"][r___]/;KeyMemberQ[a,"OriginalDistribution"]:= +(If[Max[r]>a["TruncationOrder"],Message[DistributionMomentTruncation::excdtrnc,r]];Moment[a["OriginalDistribution"],r]) +DistributionMomentTruncation[a_Association]["Moment"][r___]/;(a["MomentDataShape"]==="Function"):= +(If[Max[r]>a["TruncationOrder"],Message[DistributionMomentTruncation::excdtrnc,r]];a["MomentData"][r]) +DistributionMomentTruncation[a_Association]["Moment"][{r:Repeated[_Integer?Positive,{SequenceCount[a["Domain"],_Interval|_Span]}]}]/;(MatchQ[a,KeyValuePattern["MarginalProperty"->None]]):=(If[If[a["MomentDataShape"]==="Overall",Total,Max][{r}]>a["TruncationOrder"], +Message[DistributionMomentTruncation::excdtrnc,r];Missing["Indeterminate"], +a["MomentData"][[r]]]) +DistributionMomentTruncation[a_Association]["Moment"][{r:Repeated[_Integer?Positive,{SequenceCount[a["Domain"],_Interval|_Span]}]}]/;(MatchQ[a,KeyValuePattern["MarginalProperty"->"Independent"]]):=(If[Max[r]>a["TruncationOrder"], +Message[DistributionMomentTruncation::excdtrnc,r];Missing["Indeterminate"], +Times@@MapThread[Construct,{Extract/@{r},a["MomentData"]}]]) +DistributionMomentTruncation[a_Association]["Moment"][{r:Repeated[_Integer?Positive,{SequenceCount[a["Domain"],_Interval|_Span]}]}]/;(MatchQ[a,KeyValuePattern["MarginalProperty"->"Identical"]]):=(If[Max[r]>a["TruncationOrder"], +Message[DistributionMomentTruncation::excdtrnc,r];Missing["Indeterminate"], +Times@@a["MomentData"][{r}]]) +DistributionMomentTruncation[a_Association]["Moment"][r_Integer?Positive]/;MatchQ[a,KeyValuePattern["Domain"->(_Interval|_Span)]]:= +DistributionMomentTruncation[a]["Moment"][{r}] +DistributionMomentTruncation[a_Association]["Properties"]:=Sort@Keys[a] +DistributionMomentTruncation[a_Association][key___]:=a[key] + + +(* ::Subsubsection:: *) +(*Formatting*) + + +(* ::Input::Initialization:: *) +(*define formatting if you want to*) +$DistributionMomentTruncationSummaryThumbnail=DensityPlot[1-Exp[-5 (y-(.2+0.5E^(-8 (x+.5)^2)+1.0E^(-10 (x-.3)^2)))^2],{x,-1.,1.},{y,0,2},PlotRange->{{-1.,1.},{0.,2.}},AspectRatio->1,Frame->None,PlotTheme->"Monochrome"]; +$DistributionDomainStylizer=Dispatch[Reverse/@Normal[$DistributionDomainCanonicalizer]]; +SyntaxInformation[DistributionMomentTruncation]={"ArgumentsPattern"->{___,OptionsPattern[]},"OptionNames"->ToString/@First/@Options[DistributionMomentTruncation]}; +Format[DistributionMomentTruncation[a_Association]?DistributionMomentTruncationQ,StandardForm]:=Block[{}, +RawBoxes@BoxForm`ArrangeSummaryBox[DistributionMomentTruncation,DistributionMomentTruncation[a],$DistributionMomentTruncationSummaryThumbnail,{ +{BoxForm`MakeSummaryItem[{"TruncationOrder"<>": ",a["TruncationOrder"]},StandardForm], +BoxForm`MakeSummaryItem[{"Domain"<>": ",a["Domain"]/.$DistributionDomainStylizer},StandardForm]}, +If[KeyMemberQ[a,"MomentForm"]&&a["MomentForm"]=!="Moment", +{BoxForm`MakeSummaryItem[{"MomentForm"<>": ",a["MomentForm"]},StandardForm],SpanFromLeft},Unevaluated@Sequence[]], +If[KeyMemberQ[a,"OriginalDistribution"], +{BoxForm`MakeSummaryItem[{"OriginalDistribution"<>": ",a["OriginalDistribution"]},StandardForm],SpanFromLeft},Unevaluated@Sequence[]], +If[KeyMemberQ[a,"MarginalProperty"]&&a["MarginalProperty"]=!=None, +{BoxForm`MakeSummaryItem[{"MarginalProperty"<>": ",a["MarginalProperty"]},StandardForm],SpanFromLeft},Unevaluated@Sequence[]] +},{ +If[a["MomentForm"]==="Moment", +{BoxForm`MakeSummaryItem[{"MomentForm"<>": ",a["MomentForm"]},StandardForm],SpanFromLeft},Unevaluated@Sequence[]], +If[KeyMemberQ[a,"MomentDataShape"], +{BoxForm`MakeSummaryItem[{"MomentDataShape"<>": ",a["MomentDataShape"]},StandardForm],SpanFromLeft},Unevaluated@Sequence[]], +If[KeyMemberQ[a,"MomentData"], +{BoxForm`MakeSummaryItem[{"MomentData"<>": ",Short@a["MomentData"]},StandardForm],SpanFromLeft},Unevaluated@Sequence[]] +},StandardForm,"Interpretable"->Automatic] +] + + +(* ::Input:: *) +(*DistributionMomentTruncation[s,s,]*) diff --git a/QueueSDP.wl b/QueueSDP.wl new file mode 100644 index 0000000..cc6454d --- /dev/null +++ b/QueueSDP.wl @@ -0,0 +1,271 @@ +(* ::Package:: *) + +(* ::Title:: *) +(*queue-sdp*) + + +(* ::Author:: *) +(* Author: Gravifer *) +(* Date: 2021-02-21 *) +(* Version: 0.2.0 *) + + +BeginPackage["QueueSDP`"] +ClearAll[Evaluate[Context[] <> "*"]] + + +(* ::Section:: *) +(*Usage messages*) + + +(* ::Section:: *) +(*Definitions*) +QueueRelaxedRepresentation[]:=Identity + +Begin["`Private`"] +ClearAll[Evaluate[Context[] <> "*"]] + + +(* ::Subsection:: *) +(*Dependencies*) + + +(* ResourceFunction["IntegerCompositions"] *) +IntegerCompositions[n_, k_] := Map[( + Map[(#[[2]] - #[[1]] - 1)&, Partition[Join[{0}, #, {n + k}], 2, 1]] + )&, Subsets[Range[n + k - 1], {k - 1}]]; +IntegerCompositions::usage="Hard-embedded resource function; "<> + "gives a list of all compositions of integer $n$ into $k$ parts in canonical order. "<> + "The original resource function can be found at https://resources.wolframcloud.com/FunctionRepository/resources/IntegerCompositions" + +(* ::Subsection:: *) +(*Basic functions*) + + +integerCompositions[n_, k_] := integerCompositions[n, k] = Reverse[IntegerCompositions[n, k]]; +integerCompositions::usage="gives a list of all compositions of integer $n$ into $k$ parts in anti-canonical order." + +edg2mat = ((row \[Function] (col \[Function] (row + col)) /@ #) /@ #) &; + + +(* ::Subsection:: *) +(*SDP cone-matrix*) + + +(* ::Text:: *) +(*For the sake of clarity, the usually known multi-index notation is hereafter called a vecponent (i.e., vector exponent).*) + + +K::usage = "number of queues"; +r::usage = "rank of relaxation"; +K = 1; r = 1; + +\[Alpha]IC::usage = "concerned \[Alpha] vecponents"; +\[Alpha]IC = Join @@ Table[ + integerCompositions[\[FormalR], K], {\[FormalR], 0, 2 r}]; + +edgIC::usage = "concerned (\[Alpha],\[Beta]) vecponents"; +edgIC = Join @@ Table[ + ArrayReshape[#, {2, K}]& /@ + integerCompositions[\[FormalR], 2 K], {\[FormalR], 0, r}]; + +matIC::usage = "concerned semi-positive-definite matrix, represented as vecponents"; +matIC = edgIC // edg2mat; +matICdim = Dimensions[matIC, 2]; + +loc::usage = "look up a vecponent in matIC"; +loc[vecponent_] := loc[vecponent] = FirstPosition[matIC, vecponent, Missing["NotFound"], {2}]; + + +(* ::Subsubsection:: *) +(*Misc*) + + +matX::usage = "formal representation of matIC"; +matX[] = + Map[ Superscript[Style[\[FormalX], Larger], Style[MatrixForm[#, TableSpacing -> {0, 0}], Smaller]] &, matIC, {2}]; +matX[s_ : Except[All]] := matX[s] = + Map[Subsuperscript[Style[\[FormalX], Larger], s, Style[MatrixForm[#, TableSpacing -> {0, 0}], Smaller]] &, matIC, {2}]; +matX[All] = Table[matX[k], {k, 1, Power[2,K]}]; + + +(* ::Subsection:: *) +(*Known Moments*) + + +(* ::Text:: *) +(*In the semi-definite optimisation procedure, +m(\[Beta]) = \[DoubleStruckCapitalE][X^\[Beta]]=\[DoubleStruckCapitalE][(S-A)^\[Beta]], +the moments of the increments to the per-queue waiting times must be known. +The current version of our code uses the moments of the service time +and arrival time respectively to calculate these quantities.*) + + +\[Lambda]::usage = "arrival rate"; +\[Mu]::usage = "service rate"; +\[Lambda] = .5; \[Mu] = 1; + + +(* ::Subsubsection:: *) +(*Arrival*) + + +(* M = 2; +D0 = {{- 2 , 0 } , + { 0 , -1/2 }}; +D1 = {{ 3/5 , 7/5 } , + { 7/20, 3/20}}; +ArrivalPi = Normalize[First[NullSpace[D0 + D1]], Total]; +ArrivalMoment[k_Integer] := ArrivalMoment[k] = + Dot[Factorial[M]*ArrivalPi, MatrixPower[-D0, -k, Table[1, M]]] *) +inprobs::usage = "probabilities a ingoing package belonging to the corresponding queue"; +inprob = Table[1, K]/K; + +ArrivalMoment::usage = "Moments of the overall arrival"; +ArrivalMoment[k_Integer] := ArrivalMoment[k] = Moment[PoissonDistribution[1/\[Lambda]], k]; + +ArrivalMoment::usage = "Moments of per-queue arrivals; **currently unused**"; +ArrivalMoments[\[Beta]_List] := ArrivalMoment[\[Beta]] = + MapThread[(Power[#2, #1] * ArrivalMoment[#1])&, {\[Beta], inprobs}]; + + +(* ::Subsubsection:: *) +(*Service*) + + +outprobs = Table[1, K]/K; + +ServiceMoment::usage = "Moments of the overall service"; +ServiceMoment[k_Integer] := ServiceMoment[k] = Moment[PoissonDistribution[1/\[Mu]], k]; + +ServiceMoments::usage = "Moments of per-queue services; **currently unused**"; +ServiceMoments[\[Beta]_List] := ServiceMoments[\[Beta]] = + MapThread[(Power[#2, #1] * ServiceMoment[#1])&, {\[Beta], outprobs}]; + + +(* ::Subsubsection:: *) +(*Increment*) + +m::usage = "Moments of X; the generally true form from the arrival and service moments."; +m[\[Beta]_List] := m[\[Beta]] = + Product[ + Sum[( Binomial[\[Beta][[\[FormalK]]] , \[FormalL]] * + Power[ Part[outprobs, \[FormalK]], \[Beta][[\[FormalK]]] - \[FormalL]] * + ServiceMoment[ \[Beta][[\[FormalK]]] - \[FormalL]] * + Power[-Part[ inprobs, \[FormalK]], \[FormalL]] * + ArrivalMoment[ \[FormalL]] + ), {\[FormalL], 1, K}], {\[FormalK], 1, K}] + +Clear[m] +m::usage = "Moments of X; the one used in Bertsimas and Natarajan 2007."; +m[\[Beta]_List] := m[\[Beta]] = Times @@ MapThread[ + Expectation[Power[(#3 * \[FormalS] - #2 * \[FormalA]), #1], + { Distributed[\[FormalS], NormalDistribution[1/4, Sqrt[1/8] ] ], + Distributed[\[FormalA], NormalDistribution[1/2, Sqrt[1/8] ] ] } + ]&, {\[Beta], inprobs, outprobs}] + +Clear[m] +m::usage = "Moments of X; remained abstract."; +m[{0 ..}] := 1; +m[{\[Beta]_Integer}] := m[\[Beta]] = + Power[\[FormalM], Style[ \[Beta], Smaller]] ; +If[K > 1, m[\[Beta]_List] := m[\[Beta]] = + Power[\[FormalM], Style[TableForm[\[Beta], TableSpacing -> {0, 0}, TableDirections -> Row], Smaller]]]; + +m /: Power[m, \[Beta]_List] := m[\[Beta]]; + + +(* ::Subsection:: *) +(*Constraints LHS*) + + +ConstraintMatView::usage = "Show constraints as matrices; 3-d tensors are shown as a row of matrices."; +ConstraintEqnView::usage = "Show constraints as equations."; +ConstraintMatView[array_List | array_SparseArray] := + If[ArrayDepth @ # > 1, Map[Column, #, {ArrayDepth @ # - 1}] &, Identity] @ Map[Row, #, {ArrayDepth@# - 1}]& @ + (Map[MatrixForm, #, {ArrayDepth @ # - 2}]& @ Normal[array]); +ConstraintEqnView[array_List | array_SparseArray] := + If[ArrayDepth@array > 3, Column[Map[(Total[Times[#, matX[All]], {1, 3}] == 0) &, #, {ArrayDepth@array - 3}]]&, + (Total[Times[#, matX[All]], {1, 3}] == If[ArrayDepth @ array > 3, 0, 1]) &] @ Normal[array]; + +IndieA::usage="The constraint of independence; a list of 3-d arrays." +IndieA = (SparseArray /@ + Map[(\[FormalY] \[Function] + SparseArray[{Prepend[loc[\[FormalY] ], _] :> 1 }, Prepend[matICdim, Power[2,K]] ] - + SparseArray[{Prepend[loc[\[FormalY]*{1, 0}], _] :> m[\[FormalY][[-1]] ]}, Prepend[matICdim, Power[2,K]] ] + ), DeleteDuplicates[Flatten[#, 1]] + ] /. (SparseArray[{_ :> 0}, Prepend[matICdim, Power[2,K] ] ] -> Nothing) +) &@matIC; + +CombieA::usage="The constraint of combinatorics; a list of 3-d arrays." +CombieA = -(SparseArray@ + SparseArray[( + Flatten[ + Table[( + CoefficientRules[ + Times @@ ( + Power[( + Table[ + Indexed[\[FormalW], \[FormalK]] + + Indexed[\[FormalX], \[FormalK]] , + {\[FormalK], 1, K}] + ), #] /. + Thread[ + Table[ + Indexed[\[FormalW], \[FormalK]] + + Indexed[\[FormalX], \[FormalK]] , + {\[FormalK], Position[IntegerDigits[\[FormalS], 2, K], 0]}] + -> 0] + ), + Table[Indexed[\[FormalW], \[FormalK]], {\[FormalK], 1, K}] ~Join~ + Table[Indexed[\[FormalX], \[FormalK]], {\[FormalK], 1, K}] + ] /. ( + (list_ + -> coef_) :> + (Prepend[loc[ArrayReshape[list, {2, K}]], \[FormalS] + 1] + -> If[list[[;; K]] == #, coef - 1, coef]) + ) + ) , + {\[FormalS], 0, Power[2,K] - 1}], + 1] ~Join~ {Prepend[loc[{#, Table[0, K]}], _] -> -1} + ), Prepend[matICdim, Power[2,K]] + ] /. (SparseArray[{_ :> 0}, Prepend[matICdim, Power[2,K]]] -> Nothing) +)& /@ Rest[\[Alpha]IC]; + +UnieA::usage="The constraint of unitisation; a list of 3-d arrays."; +UnieA = SparseArray@ SparseArray[Prepend[loc[ConstantArray[0, {2, K}]], _] -> 1, Prepend[matICdim, Power[2,K]]]; + +CoinA::usage="Additional constraint due to coincident entries; only one 3-d array."; +CoinA = If[# != {}, SparseArray, Identity]@ Flatten[#, 1]& @( + (mat \[Function] + If[Length[mat] > 2, + SparseArray[#, matICdim] & /@ + ({mat[[1]] -> 1, # -> -1} & /@ mat[[2 ;; Ceiling[Length[mat]/2]]]), + Nothing] + ) /@ (Position[matIC, #, 2] & /@ DeleteDuplicates[Flatten[matIC, 1]]) +); + + +End[] + + +(* ::Section:: *) +(*Symbol protection*) + + +EndPackage[] + + +(* ::Section:: *) +(*Executed Code*) + + +(* ::Text:: *) +(*The following is only executed on the run, not when imported*) + + +(* main[]=None; +If[$Input==="", main[]];*) +(* If[$Input==="", Goto[mainBegin], Goto[mainEnd]]; +Label[mainBegin]; +Label[mainEnd]; *) diff --git a/queue-sdp-oop.nb b/queue-sdp-oop.nb new file mode 100644 index 0000000..3f1200e --- /dev/null +++ b/queue-sdp-oop.nb @@ -0,0 +1,2111 @@ +(* Content-type: application/vnd.wolfram.mathematica *) + +(* Beginning of Notebook Content *) +Notebook[{ + +Cell[CellGroupData[{ +Cell["Queue-SDP-OOP", "Title"], + +Cell[CellGroupData[{ + +Cell["Preamble", "Subsubsection", + CellGroupingRules->{"GroupTogetherGrouping", 10000.}], + +Cell[BoxData[{ + RowBox[{ + InterpretationBox[ + TagBox[ + DynamicModuleBox[{Typeset`open = False}, + FrameBox[ + PaneSelectorBox[{False->GridBox[{ + { + PaneBox[GridBox[{ + { + StyleBox[ + StyleBox[ + AdjustmentBox["\<\"[\[FilledSmallSquare]]\"\>", + BoxBaselineShift->-0.25, + BoxMargins->{{0, 0}, {-1, -1}}], "ResourceFunctionIcon", + + FontColor->RGBColor[ + 0.8745098039215686, 0.2784313725490196, 0.03137254901960784]], + ShowStringCharacters->False, + FontFamily->"Source Sans Pro Black", + FontSize->0.6538461538461539 Inherited, + FontWeight->"Heavy", + PrivateFontOptions->{"OperatorSubstitution"->False}], + StyleBox[ + RowBox[{ + StyleBox["DarkMode", "ResourceFunctionLabel"], " "}], + ShowAutoStyles->False, + ShowStringCharacters->False, + FontSize->Rational[12, 13] Inherited, + FontColor->GrayLevel[0.1]]} + }, + GridBoxSpacings->{"Columns" -> {{0.25}}}], + Alignment->Left, + BaseStyle->{LineSpacing -> {0, 0}, LineBreakWithin -> False}, + BaselinePosition->Baseline, + FrameMargins->{{3, 0}, {0, 0}}], + ItemBox[ + PaneBox[ + TogglerBox[Dynamic[Typeset`open], {True-> + + DynamicBox[FEPrivate`FrontEndResource[ + "FEBitmaps", "IconizeCloser"], + ImageSizeCache->{8.25, {1., 7.25}}], False-> + + DynamicBox[FEPrivate`FrontEndResource[ + "FEBitmaps", "IconizeOpener"], + ImageSizeCache->{8.25, {1., 7.25}}]}, + Appearance->None, + BaselinePosition->Baseline, + ContentPadding->False, + FrameMargins->0], + Alignment->Left, + BaselinePosition->Baseline, + FrameMargins->{{1, 1}, {0, 0}}], + Frame->{{ + RGBColor[ + 0.8313725490196079, 0.8470588235294118, 0.8509803921568627, + 0.5], False}, {False, False}}]} + }, + BaselinePosition->{1, 1}, + GridBoxAlignment->{"Columns" -> {{Left}}, "Rows" -> {{Baseline}}}, + GridBoxItemSize->{"Columns" -> {{Automatic}}, "Rows" -> {{Automatic}}}, + GridBoxSpacings->{"Columns" -> {{0}}, "Rows" -> {{0}}}], True-> + GridBox[{ + {GridBox[{ + { + PaneBox[GridBox[{ + { + StyleBox[ + StyleBox[ + AdjustmentBox["\<\"[\[FilledSmallSquare]]\"\>", + BoxBaselineShift->-0.25, + BoxMargins->{{0, 0}, {-1, -1}}], "ResourceFunctionIcon", + + FontColor->RGBColor[ + 0.8745098039215686, 0.2784313725490196, + 0.03137254901960784]], + ShowStringCharacters->False, + FontFamily->"Source Sans Pro Black", + FontSize->0.6538461538461539 Inherited, + FontWeight->"Heavy", + PrivateFontOptions->{"OperatorSubstitution"->False}], + StyleBox[ + RowBox[{ + StyleBox["DarkMode", "ResourceFunctionLabel"], " "}], + ShowAutoStyles->False, + ShowStringCharacters->False, + FontSize->Rational[12, 13] Inherited, + FontColor->GrayLevel[0.1]]} + }, + GridBoxSpacings->{"Columns" -> {{0.25}}}], + Alignment->Left, + BaseStyle->{LineSpacing -> {0, 0}, LineBreakWithin -> False}, + BaselinePosition->Baseline, + FrameMargins->{{3, 0}, {0, 0}}], + ItemBox[ + PaneBox[ + TogglerBox[Dynamic[Typeset`open], {True-> + + DynamicBox[FEPrivate`FrontEndResource[ + "FEBitmaps", "IconizeCloser"], + ImageSizeCache->{9.9, {2., 7.9}}], False-> + + DynamicBox[FEPrivate`FrontEndResource[ + "FEBitmaps", "IconizeOpener"], + ImageSizeCache->{9.9, {2., 7.9}}]}, + Appearance->None, + BaselinePosition->Baseline, + ContentPadding->False, + FrameMargins->0], + Alignment->Left, + BaselinePosition->Baseline, + FrameMargins->{{1, 1}, {0, 0}}], + Frame->{{ + RGBColor[ + 0.8313725490196079, 0.8470588235294118, 0.8509803921568627, + 0.5], False}, {False, False}}]} + }, + BaselinePosition->{1, 1}, + GridBoxAlignment->{"Columns" -> {{Left}}, "Rows" -> {{Baseline}}}, + + GridBoxItemSize->{ + "Columns" -> {{Automatic}}, "Rows" -> {{Automatic}}}, + GridBoxSpacings->{"Columns" -> {{0}}, "Rows" -> {{0}}}]}, + { + StyleBox[ + PaneBox[GridBox[{ + { + RowBox[{ + TagBox["\<\"Version (latest): \"\>", + "IconizedLabel"], " ", + TagBox["\<\"2.0.0\"\>", + "IconizedItem"]}]}, + { + TagBox[ + + TemplateBox[{ + "\"Documentation \[RightGuillemet]\"", + "https://resources.wolframcloud.com/FunctionRepository/\ +resources/DarkMode"}, + "HyperlinkURL"], + "IconizedItem"]} + }, + DefaultBaseStyle->"Column", + GridBoxAlignment->{"Columns" -> {{Left}}}, + + GridBoxItemSize->{ + "Columns" -> {{Automatic}}, "Rows" -> {{Automatic}}}], + Alignment->Left, + BaselinePosition->Baseline, + FrameMargins->{{5, 4}, {0, 4}}], "DialogStyle", + FontFamily->"Roboto", + FontSize->11]} + }, + BaselinePosition->{1, 1}, + GridBoxAlignment->{"Columns" -> {{Left}}, "Rows" -> {{Baseline}}}, + GridBoxDividers->{"Columns" -> {{None}}, "Rows" -> {False, { + GrayLevel[0.8]}, False}}, + GridBoxItemSize->{ + "Columns" -> {{Automatic}}, "Rows" -> {{Automatic}}}]}, Dynamic[ + Typeset`open], + BaselinePosition->Baseline, + ImageSize->Automatic], + Background->RGBColor[ + 0.9686274509803922, 0.9764705882352941, 0.984313725490196], + BaselinePosition->Baseline, + DefaultBaseStyle->{}, + FrameMargins->{{0, 0}, {1, 0}}, + FrameStyle->RGBColor[ + 0.8313725490196079, 0.8470588235294118, 0.8509803921568627], + RoundingRadius->4]], + {"FunctionResourceBox", + RGBColor[0.8745098039215686, 0.2784313725490196, 0.03137254901960784], + "DarkMode"}, + TagBoxNote->"FunctionResourceBox"], + ResourceFunction[ + ResourceObject[ + Association[ + "Name" -> "DarkMode", "ShortName" -> "DarkMode", "UUID" -> + "6ae9b15e-dd80-4d11-be6e-434bf9ac9265", "ResourceType" -> "Function", + "Version" -> "2.0.0", "Description" -> + "Restyle notebooks into dark mode", "RepositoryLocation" -> + URL["https://www.wolframcloud.com/objects/resourcesystem/api/1.0"], + "SymbolName" -> + "FunctionRepository`$f2abd2063089401aafe135eb354a8d92`DarkMode", + "FunctionLocation" -> + CloudObject[ + "https://www.wolframcloud.com/obj/91755122-26ae-43f1-8e41-\ +4043472dcf8a"]], ResourceSystemBase -> Automatic]], + Selectable->False], ";"}], "\[IndentingNewLine]", + RowBox[{"SetOptions", "[", + RowBox[{ + RowBox[{"SelectedNotebook", "[", "]"}], ",", + RowBox[{"PrintingStyleEnvironment", "\[Rule]", "\"\\""}], ",", + RowBox[{"ShowSyntaxStyles", "\[Rule]", "True"}]}], + "]"}], "\[IndentingNewLine]", + RowBox[{"ClearAll", "[", + RowBox[{"Evaluate", "[", + RowBox[{ + RowBox[{"ToString", "[", + RowBox[{"Context", "[", "]"}], "]"}], "<>", "\"\<*\>\""}], "]"}], + "]"}]}], "Input", + CellGroupingRules->{"GroupTogetherGrouping", 10000.}, + InitializationCell->True] +}]], + +Cell[CellGroupData[{ + +Cell["Definitions-OOP", "Section"], + +Cell[CellGroupData[{ + +Cell["Related Symbols", "Subsection"], + +Cell[BoxData[ + RowBox[{ + RowBox[{"Names", "[", "\"\<*Process*\>\"", "]"}], ";"}]], "Input"], + +Cell[BoxData[ + RowBox[{ + RowBox[{"Names", "[", "\"\<*Distribution*\>\"", "]"}], ";"}]], "Input"], + +Cell[CellGroupData[{ + +Cell[BoxData[ + RowBox[{"MapThread", "[", + RowBox[{"Construct", ",", + RowBox[{"{", + RowBox[{ + RowBox[{"{", + RowBox[{"f", ",", "g", ",", "h"}], "}"}], ",", + RowBox[{"{", + RowBox[{"a", ",", "b", ",", "c"}], "}"}]}], "}"}]}], "]"}]], "Input"] +}]] +}]], + +Cell[CellGroupData[{ + +Cell["Algebra", "Subsection"], + +Cell[BoxData[{ + RowBox[{ + RowBox[{"ClearAll", "[", "Algebra", "]"}], ";"}], "\n", + RowBox[{ + RowBox[{ + RowBox[{"Options", "[", "Algebra", "]"}], "=", + RowBox[{"{", + RowBox[{ + RowBox[{"\"\\"", "\[Rule]", "None"}], ",", + RowBox[{"\"\\"", "\[Rule]", "None"}], ",", + RowBox[{"\"\\"", "\[Rule]", "None"}]}], "}"}]}], ";"}], "\n", + RowBox[{ + RowBox[{ + RowBox[{ + RowBox[{"Algebra", "[", + RowBox[{"ops", ":", + RowBox[{"OptionsPattern", "[", "]"}]}], "]"}], ":=", + RowBox[{"Algebra", "[", + RowBox[{"canonicalizeAlgebraData", "[", "ops", "]"}], "]"}]}], ";"}], + "\n", + RowBox[{"(*", + RowBox[{ + "do", " ", "the", " ", "minimum", " ", "work", " ", "necessary", " ", "to", + " ", "make", " ", "sure", " ", "all", " ", "the", " ", "data", " ", + "for", " ", "the", " ", "Algebra", " ", "is", " ", "there"}], + "*)"}]}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{"canonicalizeAlgebraData", "[", + RowBox[{"ops", ":", + RowBox[{"OptionsPattern", "[", "]"}]}], "]"}], ":=", + RowBox[{"Association", "[", "ops", "]"}]}], ";"}]}], "Input"], + +Cell[BoxData[ + RowBox[{ + RowBox[{"(*", + RowBox[{ + "make", " ", "some", " ", "validators", " ", "so", " ", "you", " ", "can", + " ", "always", " ", "be", " ", "sure", " ", "you", " ", "have", " ", "a", + " ", "valid", " ", "algebra", " ", "without", " ", "constantly", " ", + "having", " ", "to", " ", "check", " ", "it"}], "*)"}], + RowBox[{ + RowBox[{ + RowBox[{ + RowBox[{"validateAlgebraData", "[", "a_Association", "]"}], ":=", + RowBox[{ + RowBox[{"Length", "[", "a", "]"}], ">", "0"}]}], ";", + RowBox[{"(*", + RowBox[{"reimplement", " ", "this"}], "*)"}], + RowBox[{ + RowBox[{ + RowBox[{"Algebra", "[", "a_Association", "]"}], "?", "NotAlgebraQ"}], ":=", + RowBox[{ + RowBox[{"System`Private`HoldSetValid", "[", + RowBox[{"Algebra", "[", "a", "]"}], "]"}], "/;", + RowBox[{"validateAlgebraData", "[", "a", "]"}]}]}], ";"}], "\n", + RowBox[{ + RowBox[{ + RowBox[{"AlgebraQ", "[", "a_Algebra", "]"}], ":=", + RowBox[{"System`Private`HoldValidQ", "[", "a", "]"}]}], ";"}], "\n", + RowBox[{ + RowBox[{ + RowBox[{"AlgebraQ", "[", "_", "]"}], ":=", "False"}], ";"}], "\n", + RowBox[{ + RowBox[{ + RowBox[{"AlgebraQ", "[", "s_Symbol", "]"}], ":=", + RowBox[{"(", + RowBox[{ + RowBox[{ + RowBox[{"Head", "[", "s", "]"}], "===", "Algebra"}], "&&", + RowBox[{"AlgebraQ", "[", + RowBox[{"Evaluate", "[", "s", "]"}], "]"}]}], ")"}]}], ";"}], "\n", + RowBox[{ + RowBox[{"AlgebraQ", "~", "SetAttributes", "~", "HoldFirst"}], ";"}], "\n", + RowBox[{ + RowBox[{ + RowBox[{"NotAlgebraQ", "[", "a_", "]"}], ":=", + RowBox[{"Not", "[", + RowBox[{"AlgebraQ", "[", "a", "]"}], "]"}]}], ";"}], "\n", + RowBox[{ + RowBox[{"NotAlgebraQ", "~", "SetAttributes", "~", "HoldFirst"}], + ";"}]}]}]], "Input"], + +Cell[BoxData[ + RowBox[{ + RowBox[{"(*", + RowBox[{ + "define", " ", "formatting", " ", "if", " ", "you", " ", "want", " ", + "to"}], "*)"}], + RowBox[{ + RowBox[{"Format", "[", + RowBox[{ + RowBox[{ + RowBox[{"Algebra", "[", "a_", "]"}], "?", "AlgebraQ"}], ",", + "StandardForm"}], "]"}], ":=", + RowBox[{"RawBoxes", "@", + RowBox[{"BoxForm`ArrangeSummaryBox", "[", + RowBox[{"Algebra", ",", + RowBox[{"Algebra", "[", "a", "]"}], ",", "None", ",", + RowBox[{"{", "\"\\"", "}"}], ",", + RowBox[{"{", "}"}], ",", "StandardForm"}], "]"}]}]}]}]], "Input"], + +Cell[BoxData[ + RowBox[{ + RowBox[{"(*", + RowBox[{"define", " ", "some", " ", + RowBox[{"accessors", "/", "methods"}], " ", "on", " ", "your", " ", + "alebgra"}], "*)"}], + RowBox[{ + RowBox[{ + RowBox[{ + RowBox[{ + RowBox[{ + RowBox[{"Algebra", "[", "a_", "]"}], "?", "AlgebraQ"}], "[", "k_", + "]"}], ":=", + RowBox[{"Lookup", "[", + RowBox[{"a", ",", "k"}], "]"}]}], ";", + RowBox[{"(*", + RowBox[{"general", " ", "lookup"}], "*)"}], + RowBox[{ + RowBox[{ + RowBox[{"(", + RowBox[{"g", ":", + RowBox[{ + RowBox[{"Algebra", "[", "a_", "]"}], "?", "AlgebraQ"}]}], ")"}], + "[", "\"\\"", "]"}], ":=", + RowBox[{"getAlgebraicGenerators", "[", "g", "]"}]}], ";"}], "\n", + RowBox[{ + RowBox[{ + RowBox[{ + RowBox[{"(", + RowBox[{"g", ":", + RowBox[{ + RowBox[{"Algebra", "[", "a_", "]"}], "?", "AlgebraQ"}]}], ")"}], + "[", "\"\\"", "]"}], ":=", + RowBox[{"getAlgebraDimension", "[", "g", "]"}]}], ";"}]}]}]], "Input"], + +Cell[BoxData[ + RowBox[{ + RowBox[{"(*", + RowBox[{ + "define", " ", "some", " ", "overloads", " ", "for", " ", "your", " ", + "algebra"}], "*)"}], + RowBox[{ + RowBox[{ + RowBox[{"Algebra", "/:", + RowBox[{"Dimensions", "[", + RowBox[{"a_Algebra", "?", "AlgebraQ"}], "]"}], ":=", + RowBox[{"a", "[", "\"\\"", "]"}]}], ";"}], "\n", + RowBox[{ + RowBox[{"Algebra", "/:", + RowBox[{ + RowBox[{"a_Algebra", "?", "AlgebraQ"}], "[", + RowBox[{"[", "el_", "]"}], "]"}], ":=", + RowBox[{"AlgebraicElement", "[", + RowBox[{"a", ",", "el"}], "]"}]}], ";", + RowBox[{"(*", + RowBox[{"getting", " ", "elements"}], "*)"}], + RowBox[{"AlgebraicElement", "/:", + RowBox[{"NonCommutativeMultiply", "[", + RowBox[{ + RowBox[{"AlgebraicElement", "[", + RowBox[{ + RowBox[{"a_Algebra", "?", "AlgebraQ"}], ",", "el1_"}], "]"}], ",", + RowBox[{"AlgebraicElement", "[", + RowBox[{ + RowBox[{"a_Algebra", "?", "AlgebraQ"}], ",", "el2_"}], "]"}]}], + "]"}], ":=", + RowBox[{"getAlgebraProduct", "[", + RowBox[{"a", ",", + RowBox[{"{", + RowBox[{"el1", ",", "el2"}], "}"}]}], "]"}]}], ";"}]}]}]], "Input"], + +Cell[BoxData[ + RowBox[{ + RowBox[{"(*", + RowBox[{ + "allow", " ", "for", " ", "natural", " ", "modifications", " ", "of", " ", + "the", " ", "algebraic", " ", "structure"}], "*)"}], + RowBox[{ + RowBox[{ + RowBox[{ + RowBox[{"mutateAlgebra", "[", + RowBox[{ + RowBox[{ + RowBox[{"Algebra", "[", "a_", "]"}], "?", "AlgebraQ"}], ",", + "changes_Association"}], "]"}], ":=", + RowBox[{"Algebra", "[", + RowBox[{"Join", "[", + RowBox[{"changes", ",", "a"}], "]"}], "]"}]}], ";"}], "\n", + RowBox[{ + RowBox[{"mutateAlgebra", "[", + RowBox[{"a_Algebra", ",", "changes_"}], "]"}], ":=", + RowBox[{"mutateAlgebra", "[", + RowBox[{"a", ",", + RowBox[{"Association", "@", "changes"}]}], "]"}]}], "\n", + RowBox[{ + RowBox[{ + "algebraMutationHandler", "~", "SetAttributes", "~", "HoldAllComplete"}], + ";"}], "\n", + RowBox[{ + RowBox[{ + RowBox[{"algebraMutationHandler", "[", + RowBox[{"AssociateTo", "[", + RowBox[{ + RowBox[{"s_Symbol", "?", "AlgebraQ"}], ",", "stuff_"}], "]"}], "]"}], + ":=", + RowBox[{"(", + RowBox[{"s", "=", + RowBox[{"mutateAlgebra", "[", + RowBox[{"s", ",", "stuff"}], "]"}]}], ")"}]}], ";"}], "\n", + RowBox[{ + RowBox[{ + RowBox[{"algebraMutationHandler", "[", + RowBox[{"Set", "[", + RowBox[{ + RowBox[{ + RowBox[{"s_Symbol", "?", "AlgebraQ"}], "[", "key_", "]"}], ",", + "val_"}], "]"}], "]"}], ":=", + RowBox[{"(", + RowBox[{"s", "=", + RowBox[{"mutateAlgebra", "[", + RowBox[{"s", ",", + RowBox[{"key", "\[Rule]", "val"}]}], "]"}]}], ")"}]}], ";"}], "\n", + RowBox[{ + RowBox[{"Language`SetMutationHandler", "[", + RowBox[{"Algebra", ",", "algebraMutationHandler"}], "]"}], + ";"}]}]}]], "Input"], + +Cell[BoxData[ + RowBox[{ + RowBox[{"(*", + RowBox[{ + "implement", " ", "the", " ", "core", " ", "algebra", " ", "calculations", + " ", "some", " ", "other", " ", "way"}], "*)"}], + RowBox[{ + RowBox[{ + RowBox[{ + RowBox[{"getAlgebraGenerators", "[", + RowBox[{"a_Algebra", "?", "AlgebraQ"}], "]"}], ":=", + "\"\\""}], ";"}], "\n", + RowBox[{ + RowBox[{ + RowBox[{"getAlgebraDimension", "[", + RowBox[{"a_Algebra", "?", "AlgebraQ"}], "]"}], ":=", + "\"\\""}], ";"}], "\n", + RowBox[{ + RowBox[{ + RowBox[{"getAlgebraProduct", "[", + RowBox[{ + RowBox[{"a_Algebra", "?", "AlgebraQ"}], ",", + RowBox[{"{", + RowBox[{"el1_", ",", "el2_"}], "}"}]}], "]"}], ":=", + "\"\\""}], ";"}]}]}]], "Input"], + +Cell[CellGroupData[{ + +Cell[BoxData[{ + RowBox[{"a", "=", + RowBox[{"Algebra", "[", + RowBox[{"\"\\"", "\[Rule]", + RowBox[{"{", "}"}]}], "]"}]}], "\n", + RowBox[{ + RowBox[{"(*", + RowBox[{"Out", ":", + RowBox[{"Algebra", "[", + RowBox[{"<|", + RowBox[{"\"\\"", "\[Rule]", + RowBox[{"{", "}"}]}], "|>"}], "]"}]}], "*)"}]}]}], "Input"] +}]] +}]], + +Cell[CellGroupData[{ + +Cell["Mine", "Subsection"], + +Cell[BoxData[ + RowBox[{"ClearAll", "[", "\"\\"", "]"}]], "Input", + InitializationCell->True], + +Cell[TextData[{ + "Note : I will follow the paradigm suggested in ", + ButtonBox["this post", + BaseStyle->"Hyperlink", + ButtonData->{ + URL["https://mathematica.stackexchange.com/a/213802"], None}, + ButtonNote->"https://mathematica.stackexchange.com/a/213802"], + ". I propose to implement two wrappers: ", + Cell[BoxData[ + FormBox[ + StyleBox["DistributionMomentTruncation", "Code"], TraditionalForm]], + ExpressionUUID->"f6370fb0-e1a8-4b8e-ac1f-8137a578f462"], + " and ", + Cell[BoxData[ + FormBox[ + StyleBox["ProcessMomentTruncation", "Code"], TraditionalForm]], + ExpressionUUID->"595c51cf-d79c-4fac-b150-61adc9f20594"], + ". " +}], "Text"], + +Cell[CellGroupData[{ + +Cell["Clearing definitions", "Subsubsection"], + +Cell[BoxData[{ + RowBox[{ + RowBox[{"ClearAll", "[", + StyleBox["DistributionMomentTruncation", "Code"], + StyleBox["]", "Code"]}], + StyleBox[";", "Code"]}], "\n", + RowBox[{ + RowBox[{ + StyleBox["ClearAll", "Code"], + StyleBox["[", "Code"], + RowBox[{ + "$DistributionDomainCanonicalizer", ",", "$DistributionDomainStylizer", + ",", "$DistributionMomentTruncationSummaryThumbnail"}], "]"}], + ";"}], "\[IndentingNewLine]", + RowBox[{"ClearAll", "[", + RowBox[{ + "canonicalizeDistributionMomentTruncation", ",", + "validateDistributionMomentTruncation", ",", + "instantiateDistributionMomentTruncation"}], "]"}], "\[IndentingNewLine]", + RowBox[{"ClearAll", "[", + RowBox[{ + "DistributionMomentTruncationQ", ",", "NotDistributionMomentTruncationQ"}], + "]"}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{"ClearAll", "[", + RowBox[{ + StyleBox["ProcessMomentTruncation", "Code"], + StyleBox[",", "Code"], "QueueMomentTruncation"}], "]"}], ";"}], "\n", + RowBox[{ + RowBox[{ + RowBox[{"Options", "[", "DistributionMomentTruncation", "]"}], "=", + RowBox[{"{", + RowBox[{"(*", + RowBox[{ + RowBox[{ + "This", " ", "allow", " ", "for", " ", "setting", " ", "default", " ", + "values"}], ";"}], " ", "*)"}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{"\"\\"", "\[Rule]", "None"}], ",", + RowBox[{"(*", + RowBox[{"major", " ", "parameter"}], "*)"}], "\[IndentingNewLine]", + RowBox[{"\"\\"", "\[Rule]", "None"}], ",", + RowBox[{"(*", + RowBox[{ + RowBox[{"if", " ", "supplied"}], ",", " ", + RowBox[{ + RowBox[{ + "the", " ", "moment", " ", "sequence", " ", "is", " ", "always", " ", + "generated", " ", "using", " ", "the", " ", "moment", " ", + "function", " ", "of", " ", "the", " ", "original", " ", + "distribution"}], ";", " ", + RowBox[{ + "there", " ", "may", " ", "be", " ", "need", " ", "for", " ", + "memoisation"}]}]}], "*)"}], "\[IndentingNewLine]", + "\[IndentingNewLine]", + RowBox[{"(*", + RowBox[{ + RowBox[{"\"\\"", "\[Rule]", "None"}], ",", + RowBox[{"(*", + RowBox[{ + StyleBox[ + RowBox[{"If", " ", "this", " ", "is", " ", "true"}], + FontColor->RGBColor[1, 0, 0]], + StyleBox[",", + FontColor->RGBColor[1, 0, 0]], + StyleBox[" ", + FontColor->RGBColor[1, 0, 0]], + RowBox[{ + StyleBox[ + RowBox[{ + "MomentData", " ", "is", " ", "represented", " ", "by", " ", "a", + " ", "matrix", " ", "only"}], + FontColor->RGBColor[1, 0, 0]], ";", " ", + RowBox[{ + RowBox[{"only", " ", "meaningful", " ", "for", " ", "multi"}], "-", + RowBox[{"dimensional", " ", "distributions"}]}]}], ",", " ", + StyleBox[ + RowBox[{ + RowBox[{ + "should", " ", "be", " ", "set", " ", "to", " ", "None", " ", + "for", " ", "1"}], "-", + RowBox[{"d", " ", "distributions"}]}], + FontColor->RGBColor[1, 0, 0]], + StyleBox[",", + FontColor->RGBColor[1, 0, 0]], + StyleBox[" ", + FontColor->RGBColor[1, 0, 0]], + RowBox[{ + StyleBox["and", + FontColor->RGBColor[1, 0, 0]], + StyleBox[" ", + FontColor->RGBColor[1, 0, 0]], + StyleBox["is", + FontColor->RGBColor[1, 0, 0]], + StyleBox[" ", + FontColor->RGBColor[1, 0, 0]], + StyleBox["deleted", + FontColor->RGBColor[1, 0, 0]], + StyleBox[" ", + FontColor->RGBColor[1, 0, 0]], + StyleBox["if", + FontColor->RGBColor[1, 0, 0]], + StyleBox[" ", + FontColor->RGBColor[1, 0, 0]], + StyleBox["IdenticalMargins", + FontColor->RGBColor[1, 0, 0]], + StyleBox[" ", + FontColor->RGBColor[1, 0, 0]], + StyleBox["is", + FontColor->RGBColor[1, 0, 0]], + StyleBox[" ", + FontColor->RGBColor[1, 0, 0]], + RowBox[{ + StyleBox["True", + FontColor->RGBColor[1, 0, 0]], "."}]}]}], "*)"}], + "\[IndentingNewLine]", + RowBox[{"\"\\"", "\[Rule]", "None"}], ","}], + RowBox[{"(*", + RowBox[{ + RowBox[{"If", " ", "this", " ", "is", " ", "true"}], ",", " ", + RowBox[{ + RowBox[{ + "MomentData", " ", "can", " ", "be", " ", "represented", " ", "as", + " ", "a", " ", "vector"}], ";", " ", + RowBox[{ + RowBox[{"only", " ", "meaningful", " ", "for", " ", "multi"}], "-", + RowBox[{"dimensional", " ", "distributions", " ", + StyleBox[ + RowBox[{ + "should", " ", "be", " ", "set", " ", "to", " ", "None", " ", + "for", " ", "1"}], + FontColor->RGBColor[1, 0, 0]]}], + StyleBox["-", + FontColor->RGBColor[1, 0, 0]], + RowBox[{ + StyleBox[ + RowBox[{"d", " ", "distributions"}], + FontColor->RGBColor[1, 0, 0]], "."}]}]}]}], "*)"}], "*)"}], + "\[IndentingNewLine]", + RowBox[{"\"\\"", "\[Rule]", "None"}], ",", + "\[IndentingNewLine]", + RowBox[{"\"\\"", "\[Rule]", "\"\\""}], ",", + RowBox[{"(*", + RowBox[{ + RowBox[{ + "following", " ", "the", " ", "specification", " ", "of", " ", Cell[ + TextData[ButtonBox["MomentConvert", + BaseStyle->"Hyperlink", + ButtonData->{ + URL[ + "http://reference.wolfram.com/language/ref/MomentConvert.html"], + None}, + ButtonNote-> + "http://reference.wolfram.com/language/ref/MomentConvert.html"]], + ExpressionUUID->"0d355b60-2f26-4882-8f4a-e655a5a82dba"]}], ",", " ", + "absolute", ",", " ", "factorial", ",", " ", + RowBox[{ + RowBox[{"central", " ", "moments", " ", "and", " ", "cumulants"}], + ";", " ", + RowBox[{ + "may", " ", "also", " ", "support", " ", "truncated", " ", + "probability", " ", "sequence", " ", "for"}]}]}], " ", "*)"}], + "\[IndentingNewLine]", + RowBox[{"\"\\"", "\[Rule]", "None"}], ",", + RowBox[{"(*", + RowBox[{ + RowBox[{"an", " ", "association", " ", + RowBox[{"(", + RowBox[{"is", " ", "this", " ", "really", " ", "a", " ", "good", " ", + RowBox[{"idea", "?"}]}], ")"}], " ", "of", " ", "the", " ", + "moments"}], ",", " ", + RowBox[{ + RowBox[{"with", " ", + RowBox[{"(", + RowBox[{"lists", " ", "of"}], ")"}], " ", "non", " ", "negative", + " ", "integers", " ", "as", " ", "keys"}], ";", " ", + RowBox[{ + RowBox[{"an", " ", "all"}], "-", + RowBox[{ + "zero", " ", "key", " ", "can", " ", "be", " ", "used", " ", "to", + " ", "denote", " ", "an", " ", "alternative", " ", "unitisation", + " ", + RowBox[{ + RowBox[{"(", + RowBox[{ + "a", " ", "single", " ", "zero", " ", "can", " ", "be", " ", + "used", " ", "as", " ", "a", " ", "shorthand"}], ")"}], ".", " ", + StyleBox["not", + FontColor->RGBColor[1, 0, 0]]}], + StyleBox[" ", + FontColor->RGBColor[1, 0, 0]], + StyleBox["instantiated", + FontColor->RGBColor[1, 0, 0]], + StyleBox[" ", + FontColor->RGBColor[1, 0, 0]], + StyleBox["if", + FontColor->RGBColor[1, 0, 0]], + StyleBox[" ", + FontColor->RGBColor[1, 0, 0]], + StyleBox["there", + FontColor->RGBColor[1, 0, 0]], + StyleBox[" ", + FontColor->RGBColor[1, 0, 0]], + StyleBox["is", + FontColor->RGBColor[1, 0, 0]], + StyleBox[" ", + FontColor->RGBColor[1, 0, 0]], + StyleBox["an", + FontColor->RGBColor[1, 0, 0]], + StyleBox[" ", + FontColor->RGBColor[1, 0, 0]], + StyleBox["original", + FontColor->RGBColor[1, 0, 0]], + StyleBox[" ", + FontColor->RGBColor[1, 0, 0]], + RowBox[{ + StyleBox["distribution", + FontColor->RGBColor[1, 0, 0]], "."}]}]}]}]}], "*)"}], + RowBox[{"(*", + RowBox[{ + RowBox[{ + "I", " ", "decide", " ", "that", " ", "we", " ", "should", " ", "only", + " ", "support", " ", "two", " ", "types", " ", "of", " ", "moment", + " ", "data"}], ";", " ", + RowBox[{"see", " ", "\"\\"", " ", "below"}]}], + "*)"}], "\[IndentingNewLine]", + RowBox[{"\"\\"", "\[Rule]", "None"}], ",", + RowBox[{"(*", + RowBox[{ + RowBox[{"allowed", " ", "types", " ", "are", " ", "\"\\""}], + ",", " ", + RowBox[{ + RowBox[{"\"\\"", " ", "and", " ", "\"\\""}], ";", + " ", + RowBox[{"\"\\"", " ", "should", " ", "be", " ", + RowBox[{"assumed", ".", " ", "If"}], " ", "IndependentMargins", " ", + "is", " ", "True"}]}], ",", " ", + RowBox[{ + RowBox[{"this", " ", "specification", " ", "is", " ", "ignored"}], + ";", " ", + RowBox[{ + RowBox[{"only", " ", "meaningful", " ", "for", " ", "multi"}], "-", + RowBox[{"dimensional", " ", "distributions"}]}]}], ",", " ", + RowBox[{ + StyleBox[ + RowBox[{ + "should", " ", "be", " ", "set", " ", "to", " ", "None", " ", "for", + " ", "1"}], + FontColor->RGBColor[1, 0, 0]], + StyleBox["-", + FontColor->RGBColor[1, 0, 0]], + RowBox[{ + StyleBox["d", + FontColor->RGBColor[1, 0, 0]], + StyleBox[" ", + FontColor->RGBColor[1, 0, 0]], + RowBox[{ + StyleBox["distributions", + FontColor->RGBColor[1, 0, 0]], ".", " ", + StyleBox["not", + FontColor->RGBColor[1, 0, 0]]}], + StyleBox[" ", + FontColor->RGBColor[1, 0, 0]], + StyleBox["instantiated", + FontColor->RGBColor[1, 0, 0]], + StyleBox[" ", + FontColor->RGBColor[1, 0, 0]], + StyleBox["if", + FontColor->RGBColor[1, 0, 0]], + StyleBox[" ", + FontColor->RGBColor[1, 0, 0]], + StyleBox["there", + FontColor->RGBColor[1, 0, 0]], + StyleBox[" ", + FontColor->RGBColor[1, 0, 0]], + StyleBox["is", + FontColor->RGBColor[1, 0, 0]], + StyleBox[" ", + FontColor->RGBColor[1, 0, 0]], + StyleBox["an", + FontColor->RGBColor[1, 0, 0]], + StyleBox[" ", + FontColor->RGBColor[1, 0, 0]], + StyleBox["original", + FontColor->RGBColor[1, 0, 0]], + StyleBox[" ", + FontColor->RGBColor[1, 0, 0]], + RowBox[{ + StyleBox["distribution", + FontColor->RGBColor[1, 0, 0]], "."}]}]}]}], "*)"}], + "\[IndentingNewLine]", + RowBox[{"(*", + RowBox[{ + RowBox[{"\"\\"", "\[Rule]", "None"}], ","}], + RowBox[{"(*", + StyleBox[ + RowBox[{"is", " ", "this", " ", "really", " ", + RowBox[{"needed", "?"}]}], + FontSlant->"Italic"], "*)"}], "*)"}], "\[IndentingNewLine]", + RowBox[{"\"\\"", "\[Rule]", "None"}]}], + RowBox[{"(*", + RowBox[{ + RowBox[{"\"\\"", "\[Rule]", "None"}], ","}], + "*)"}], + RowBox[{"(*", + RowBox[{ + RowBox[{ + RowBox[{"These", " ", "two", " ", "should", " ", + StyleBox["always", + FontSlant->"Italic"], + StyleBox[" ", + FontSlant->"Italic"], + StyleBox["be", + FontSlant->"Italic"], + StyleBox[" ", + FontSlant->"Italic"], + StyleBox["synonymous", + FontSlant->"Italic"]}], ";", " ", + RowBox[{ + "the", " ", "latter", " ", "should", " ", "not", " ", "be", " ", + "stored"}]}], ",", " ", + RowBox[{"but", " ", "only", " ", "handled", " ", "in", " ", + RowBox[{"interfaces", ".", " ", + StyleBox["We", + FontColor->RGBColor[1, 0, 0]]}], + StyleBox[" ", + FontColor->RGBColor[1, 0, 0]], + StyleBox["must", + FontColor->RGBColor[1, 0, 0]], + StyleBox[" ", + FontColor->RGBColor[1, 0, 0]], + StyleBox["handle", + FontColor->RGBColor[1, 0, 0]], + StyleBox[" ", + FontColor->RGBColor[1, 0, 0]], + StyleBox["conversions", + FontColor->RGBColor[1, 0, 0]], + StyleBox[" ", + FontColor->RGBColor[1, 0, 0]], + StyleBox["between", + FontColor->RGBColor[1, 0, 0]], + StyleBox[" ", + FontColor->RGBColor[1, 0, 0]], + StyleBox["\"\\"", + FontColor->RGBColor[1, 0, 0]], + StyleBox[" ", + FontColor->RGBColor[1, 0, 0]], + StyleBox["and", + FontColor->RGBColor[1, 0, 0]], + StyleBox[" ", + FontColor->RGBColor[1, 0, 0]], + StyleBox["\"\\"", + FontColor->RGBColor[1, 0, 0]]}]}], "*)"}], "\[IndentingNewLine]", + RowBox[{"(*", + RowBox[{",", + RowBox[{"\"\\"", "\[Rule]", "None"}]}], "*)"}], + RowBox[{"(*", + RowBox[{ + RowBox[{ + RowBox[{ + "Default", " ", "to", " ", "a", " ", "plot", " ", "of", " ", "the", + " ", "moment", " ", "matched", " ", "polynomial"}], ";", " ", + RowBox[{ + "if", " ", "there", " ", "is", " ", "an", " ", "original", " ", + "distribution"}]}], ",", " ", + RowBox[{ + "it", " ", "will", " ", "also", " ", "be", " ", "plotted", " ", "so", + " ", "that", " ", "their", " ", "difference", " ", "is", " ", + "clearly", " ", + RowBox[{"seen", ".", " ", "When"}], " ", "any", " ", "of", " ", + "these", " ", "are", " ", "hard", " ", "to", " ", "evaluate"}], ",", + " ", + RowBox[{ + RowBox[{ + "a", " ", "default", " ", "thumbnail", " ", "will", " ", "be", " ", + "shown"}], ";", " ", + StyleBox[ + RowBox[{ + "this", " ", "may", " ", "should", " ", "not", " ", "be", " ", "part", + " ", "of", " ", "the", " ", "structure"}], + FontColor->RGBColor[1, 0, 0]]}], + StyleBox[",", + FontColor->RGBColor[1, 0, 0]], + StyleBox[" ", + FontColor->RGBColor[1, 0, 0]], + RowBox[{ + StyleBox["since", + FontColor->RGBColor[1, 0, 0]], + StyleBox[" ", + FontColor->RGBColor[1, 0, 0]], + StyleBox["it", + FontColor->RGBColor[1, 0, 0]], + StyleBox[" ", + FontColor->RGBColor[1, 0, 0]], + StyleBox["is", + FontColor->RGBColor[1, 0, 0]], + StyleBox[" ", + FontColor->RGBColor[1, 0, 0]], + StyleBox["expensive", + FontColor->RGBColor[1, 0, 0]], + StyleBox[" ", + FontColor->RGBColor[1, 0, 0]], + StyleBox["to", + FontColor->RGBColor[1, 0, 0]], + StyleBox[" ", + FontColor->RGBColor[1, 0, 0]], + RowBox[{ + StyleBox["store", + FontColor->RGBColor[1, 0, 0]], "."}]}]}], "*)"}], + "\[IndentingNewLine]", "}"}]}], ";"}]}], "Input", + InitializationCell->True] +}]], + +Cell[CellGroupData[{ + +Cell["Initializers", "Subsubsection"], + +Cell[CellGroupData[{ + +Cell["From a distribution", "ItemNumbered"], + +Cell[BoxData[{ + RowBox[{ + RowBox[{"DistributionMomentTruncation", "[", + RowBox[{"dist_", "?", "DistributionParameterQ"}], "]"}], ":=", + "dist"}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{ + RowBox[{"DistributionMomentTruncation", "[", + RowBox[{ + RowBox[{"dist_", "?", "DistributionParameterQ"}], ",", + RowBox[{"type", ":", + RowBox[{ + "\"\\"", "|", "\"\\"", "|", + "\"\\"", "|", "\"\\""}]}]}], "]"}], "[", + "r_", "]"}], ":=", + RowBox[{ + RowBox[{"Symbol", "[", "type", "]"}], "[", + RowBox[{"dist", ",", "r"}], "]"}]}], + "\[IndentingNewLine]"}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{"DistributionMomentTruncation", "[", + RowBox[{ + RowBox[{ + RowBox[{"trunc_Integer", "?", "Positive"}], "|", "trunc_Symbol", "|", + RowBox[{"trunc", ":", "Infinity"}]}], ",", + RowBox[{"type", ":", + RowBox[{ + "\"\\"", "|", "\"\\"", "|", + "\"\\"", "|", "\"\\""}], ":", + "\"\\""}], ",", + RowBox[{"ops", ":", + RowBox[{"OptionsPattern", "[", "]"}]}]}], "]"}], "[", + RowBox[{"dist_", "?", "DistributionParameterQ"}], "]"}], ":=", + RowBox[{"DistributionMomentTruncation", "[", + RowBox[{"trunc", ",", "dist", ",", "type", ",", "ops"}], + "]"}]}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{"DistributionMomentTruncation", "[", + RowBox[{ + RowBox[{ + RowBox[{"trunc_Integer", "?", "Positive"}], "|", "trunc_Symbol"}], ",", + RowBox[{"dist_", "?", "DistributionParameterQ"}], ",", + RowBox[{"type", ":", + RowBox[{ + "\"\\"", "|", "\"\\"", "|", + "\"\\"", "|", "\"\\""}], ":", + "\"\\""}], ",", + RowBox[{"ops", ":", + RowBox[{"OptionsPattern", "[", "]"}]}]}], "]"}], ":=", + RowBox[{"DistributionMomentTruncation", "[", + RowBox[{"trunc", ",", "dist", ",", + RowBox[{"\"\\"", "\[Rule]", "type"}], ",", + RowBox[{"Sequence", "@@", + RowBox[{"FilterRules", "[", + RowBox[{ + RowBox[{"{", "ops", "}"}], ",", + RowBox[{"Except", "[", + RowBox[{ + "\"\\"", "|", "\"\\"", "|", + "\"\\"", "|", "\"\\"", "|", + "\"\\""}], "]"}]}], "]"}]}]}], + "]"}]}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{"DistributionMomentTruncation", "[", + RowBox[{ + RowBox[{ + RowBox[{"trunc_Integer", "?", "Positive"}], "|", "trunc_Symbol"}], ",", + RowBox[{"dist_", "?", "DistributionParameterQ"}], ",", + RowBox[{"ops", ":", + RowBox[{"OptionsPattern", "[", "]"}]}]}], "]"}], ":=", + RowBox[{"DistributionMomentTruncation", "[", + RowBox[{ + RowBox[{"\"\\"", "\[Rule]", "trunc"}], ",", + RowBox[{"\"\\"", "\[Rule]", "dist"}], ",", + RowBox[{"Sequence", "@@", + RowBox[{"FilterRules", "[", + RowBox[{ + RowBox[{"{", "ops", "}"}], ",", + RowBox[{"Except", "[", + RowBox[{ + "\"\\"", "|", "\"\\"", "|", + "\"\\"", "|", "\"\\""}], "]"}]}], + "]"}]}]}], "]"}]}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{"DistributionMomentTruncation", "[", + RowBox[{"Infinity", ",", + RowBox[{"dist_", "?", "DistributionParameterQ"}], ",", + RowBox[{"ops", ":", + RowBox[{"OptionsPattern", "[", "]"}]}]}], "]"}], ":=", "dist", + RowBox[{"(*", + RowBox[{ + RowBox[{ + "when", " ", "a", " ", "distribution", " ", "is", " ", "not", " ", + "moment", " ", "truncated"}], ",", " ", + RowBox[{ + "it", " ", "gets", " ", "cast", " ", "into", " ", "the", " ", "original", + " ", "distribution"}]}], "*)"}]}]}], "Input", + InitializationCell->True] +}]], + +Cell[CellGroupData[{ + +Cell["From a moment function", "ItemNumbered"], + +Cell[BoxData[{ + RowBox[{ + RowBox[{"DistributionMomentTruncation", "[", + RowBox[{ + RowBox[{ + RowBox[{"trunc_Integer", "?", "Positive"}], "|", "trunc_Symbol", "|", + RowBox[{"trunc", ":", "Infinity"}]}], ",", + RowBox[{"moments_Function", "|", "moments_Symbol"}], ",", + RowBox[{"type", ":", + RowBox[{ + "\"\\"", "|", "\"\\"", "|", + "\"\\"", "|", "\"\\""}], ":", + "\"\\""}], ",", + RowBox[{"ops", ":", + RowBox[{"OptionsPattern", "[", "]"}]}]}], "]"}], ":=", + RowBox[{"DistributionMomentTruncation", "[", "\[IndentingNewLine]", + RowBox[{"trunc", ",", "moments", ",", + RowBox[{"\"\\"", "\[Rule]", "type"}], ",", + RowBox[{"Sequence", "@@", + RowBox[{"FilterRules", "[", + RowBox[{ + RowBox[{"{", "ops", "}"}], ",", + RowBox[{"Except", "[", + RowBox[{ + "\"\\"", "|", "\"\\"", "|", + "\"\\"", "|", "\"\\"", "|", + "\"\\""}], "]"}]}], "]"}]}]}], + "]"}]}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{"DistributionMomentTruncation", "[", + RowBox[{ + RowBox[{ + RowBox[{"trunc_Integer", "?", "Positive"}], "|", "trunc_Symbol", "|", + RowBox[{"trunc", ":", "Infinity"}]}], ",", + RowBox[{"moments_Function", "|", "moments_Symbol"}], ",", + RowBox[{"ops", ":", + RowBox[{"OptionsPattern", "[", "]"}]}]}], "]"}], ":=", + RowBox[{"DistributionMomentTruncation", "[", + RowBox[{ + RowBox[{"\"\\"", "\[Rule]", "trunc"}], ",", + RowBox[{"\"\\"", "\[Rule]", "moments"}], ",", + RowBox[{"\"\\"", "\[Rule]", "\"\\""}], ",", + RowBox[{"Sequence", "@@", + RowBox[{"FilterRules", "[", + RowBox[{ + RowBox[{"{", "ops", "}"}], ",", + RowBox[{"Except", "[", + RowBox[{ + "\"\\"", "|", "\"\\"", "|", + "\"\\"", "|", "\"\\""}], "]"}]}], + "]"}]}]}], "]"}]}]}], "Input", + InitializationCell->True] +}]], + +Cell[CellGroupData[{ + +Cell["From a moment array", "ItemNumbered"], + +Cell[BoxData[{ + RowBox[{ + RowBox[{ + RowBox[{"DistributionMomentTruncation", "[", + RowBox[{ + RowBox[{"moments_", "?", "VectorQ"}], ",", + RowBox[{"ops", ":", + RowBox[{"OptionsPattern", "[", + RowBox[{"{", + RowBox[{ + RowBox[{"\"\\"", "\[Rule]", + RowBox[{"Interval", "[", + RowBox[{"{", + RowBox[{ + RowBox[{"-", "\[Infinity]"}], ",", "\[Infinity]"}], "}"}], + "]"}]}], ",", "DistributionMomentTruncation"}], "}"}], "]"}]}]}], + "]"}], ":=", + RowBox[{"DistributionMomentTruncation", "[", + RowBox[{ + RowBox[{"\"\\"", "\[Rule]", + RowBox[{"Length", "[", "moments", "]"}]}], ",", + RowBox[{"\"\\"", "\[Rule]", "moments"}], ",", + RowBox[{"\"\\"", "\[Rule]", + RowBox[{"OptionValue", "[", "\"\\"", "]"}]}], ",", + RowBox[{"If", "[", + RowBox[{ + RowBox[{"!", + RowBox[{"MatchQ", "[", + RowBox[{ + RowBox[{"OptionValue", "[", "\"\\"", "]"}], ",", + RowBox[{"_Interval", "|", "_Span"}]}], "]"}]}], + RowBox[{"(*", + RowBox[{"one", " ", "dimensional"}], "*)"}], ",", + RowBox[{"\"\\"", "\[Rule]", "\"\\""}], + ",", + RowBox[{"Unevaluated", "@", + RowBox[{"Sequence", "[", "]"}]}]}], "]"}], ",", + RowBox[{"Sequence", "@@", + RowBox[{"FilterRules", "[", + RowBox[{ + RowBox[{"{", "ops", "}"}], ",", + RowBox[{"Except", "[", + RowBox[{ + "\"\\"", "|", "\"\\"", "|", + "\"\\"", "|", "\"\\"", "|", + "\"\\""}], "]"}]}], "]"}]}]}], "]"}]}], + RowBox[{"(*", + RowBox[{ + RowBox[{"default", " ", "to", " ", "a", " ", "1"}], "-", + RowBox[{"d", " ", "distribution"}]}], "*)"}]}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{"DistributionMomentTruncation", "[", + RowBox[{ + RowBox[{"moments_", "?", "MatrixQ"}], ",", + RowBox[{"ops", ":", + RowBox[{"OptionsPattern", "[", + RowBox[{"{", + RowBox[{ + RowBox[{"\"\\"", "\[Rule]", "None"}], ",", + "DistributionMomentTruncation"}], "}"}], "]"}]}]}], "]"}], ":=", + RowBox[{"(*", + RowBox[{ + "This", " ", "is", " ", "for", " ", "independent", " ", "margins"}], + "*)"}], + RowBox[{"Module", "[", + RowBox[{ + RowBox[{"{", + RowBox[{"domain", "=", + RowBox[{"OptionValue", "[", "\"\\"", "]"}]}], "}"}], ",", + "\[IndentingNewLine]", + RowBox[{"If", "[", + RowBox[{ + RowBox[{ + RowBox[{"SquareMatrixQ", "[", "moments", "]"}], "&&", + RowBox[{"Not", "@", + RowBox[{"MatchQ", "[", + RowBox[{ + RowBox[{"OptionValue", "[", "\"\\"", "]"}], ",", + RowBox[{"\"\\"", "|", "\"\\""}]}], + "]"}]}], "&&", "\[IndentingNewLine]", + RowBox[{"(", + RowBox[{ + RowBox[{ + RowBox[{"OptionValue", "[", "\"\\"", "]"}], + "===", "\"\\""}], "||", "\[IndentingNewLine]", + RowBox[{"(", + RowBox[{ + RowBox[{"MatchQ", "[", + RowBox[{"domain", ",", + RowBox[{"{", + RowBox[{ + RowBox[{"_Interval", "|", "_Span"}], ",", + RowBox[{"_Interval", "|", "_Span"}]}], "}"}]}], "]"}], "&&", + RowBox[{ + RowBox[{"Length", "[", "moments", "]"}], ">", "2"}]}], ")"}]}], + ")"}]}], ",", + RowBox[{"(*", + RowBox[{ + RowBox[{ + "handle", " ", "the", " ", "case", " ", "when", " ", "the", " ", + "distribution", " ", "happens", " ", "to", " ", "be", " ", "2"}], + "-", "d"}], "*)"}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{"If", "[", + RowBox[{ + RowBox[{"domain", "===", "None"}], ",", + RowBox[{"domain", "=", + RowBox[{"Table", "[", + RowBox[{ + RowBox[{"Interval", "[", + RowBox[{"{", + RowBox[{ + RowBox[{"-", "\[Infinity]"}], ",", "\[Infinity]"}], "}"}], + "]"}], ",", "2"}], "]"}]}]}], "]"}], ";", "\[IndentingNewLine]", + RowBox[{"DistributionMomentTruncation", "[", "\[IndentingNewLine]", + RowBox[{ + RowBox[{"\"\\"", "\[Rule]", + RowBox[{ + RowBox[{"Length", "[", "moments", "]"}], "-", "1"}]}], + RowBox[{"(*", + StyleBox[ + RowBox[{"note", " ", "this"}], + FontColor->RGBColor[1, 0, 0]], "*)"}], ",", + RowBox[{"\"\\"", "\[Rule]", "moments"}], ",", + RowBox[{"\"\\"", "\[Rule]", "domain"}], ",", + RowBox[{"\"\\"", "\[Rule]", "None"}], ",", + RowBox[{"Sequence", "@@", + RowBox[{"FilterRules", "[", + RowBox[{ + RowBox[{"{", "ops", "}"}], ",", + RowBox[{"Except", "[", + RowBox[{ + "\"\\"", "|", "\"\\"", + "|", "\"\\"", "|", "\"\\"", "|", + "\"\\""}], "]"}]}], "]"}]}]}], + "\[IndentingNewLine]", "]"}]}], ",", "\[IndentingNewLine]", + RowBox[{ + RowBox[{"If", "[", + RowBox[{ + RowBox[{"domain", "===", "None"}], ",", + RowBox[{"domain", "=", + RowBox[{"Table", "[", + RowBox[{ + RowBox[{"Interval", "[", + RowBox[{"{", + RowBox[{ + RowBox[{"-", "\[Infinity]"}], ",", "\[Infinity]"}], "}"}], + "]"}], ",", + RowBox[{"Length", "[", "moments", "]"}]}], "]"}]}]}], "]"}], ";", + "\[IndentingNewLine]", + RowBox[{"DistributionMomentTruncation", "[", "\[IndentingNewLine]", + RowBox[{ + RowBox[{"\"\\"", "\[Rule]", + RowBox[{"Length", "[", "moments", "]"}]}], ",", + RowBox[{"\"\\"", "\[Rule]", "moments"}], ",", + RowBox[{"\"\\"", "\[Rule]", "domain"}], ",", + RowBox[{ + "\"\\"", "\[Rule]", "\"\\""}], ",", + RowBox[{"Sequence", "@@", + RowBox[{"FilterRules", "[", + RowBox[{ + RowBox[{"{", "ops", "}"}], ",", + RowBox[{"Except", "[", + RowBox[{ + "\"\\"", "|", "\"\\"", + "|", "\"\\"", "|", "\"\\"", "|", + "\"\\""}], "]"}]}], "]"}]}]}], + "\[IndentingNewLine]", "]"}]}]}], "\[IndentingNewLine]", "]"}]}], + "\[IndentingNewLine]", "]"}]}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{"DistributionMomentTruncation", "[", + RowBox[{ + RowBox[{"moments_", "?", "ArrayQ"}], ",", + RowBox[{"ops", ":", + RowBox[{"OptionsPattern", "[", + RowBox[{"{", + RowBox[{ + RowBox[{"\"\\"", "\[Rule]", "None"}], ",", + "DistributionMomentTruncation"}], "}"}], "]"}]}]}], "]"}], ":=", + RowBox[{"(*", + StyleBox[ + RowBox[{"currently", ",", " ", + RowBox[{ + RowBox[{"only", " ", "\"\\""}], "\[Rule]", + RowBox[{"\"\\"", " ", "is", " ", "supported"}]}]}], + FontColor->RGBColor[1, 0, 0]], "*)"}], "\[IndentingNewLine]", + RowBox[{"Module", "[", + RowBox[{ + RowBox[{"{", + RowBox[{"domain", "=", + RowBox[{"If", "[", + RowBox[{ + RowBox[{ + RowBox[{"OptionValue", "[", "\"\\"", "]"}], "===", "None"}], + ",", + RowBox[{"Table", "[", + RowBox[{ + RowBox[{"Interval", "[", + RowBox[{"{", + RowBox[{ + RowBox[{"-", "\[Infinity]"}], ",", "\[Infinity]"}], "}"}], "]"}], + ",", + RowBox[{"ArrayDepth", "[", "moments", "]"}]}], "]"}]}], "]"}]}], + "}"}], ",", "\[IndentingNewLine]", + RowBox[{"DistributionMomentTruncation", "[", "\[IndentingNewLine]", + RowBox[{ + RowBox[{"\"\\"", "\[Rule]", + RowBox[{ + RowBox[{"Length", "[", "moments", "]"}], "-", "1"}]}], + RowBox[{"(*", + StyleBox[ + RowBox[{"note", " ", "this"}], + FontColor->RGBColor[1, 0, 0]], "*)"}], ",", + RowBox[{"\"\\"", "\[Rule]", "moments"}], ",", + RowBox[{"\"\\"", "\[Rule]", "\"\\""}], ",", + RowBox[{"\"\\"", "\[Rule]", "domain"}], ",", + RowBox[{"\"\\"", "\[Rule]", "None"}], ",", + RowBox[{"Sequence", "@@", + RowBox[{"FilterRules", "[", + RowBox[{ + RowBox[{"{", "ops", "}"}], ",", + RowBox[{"Except", "[", + RowBox[{ + "\"\\"", "|", "\"\\"", + "|", "\"\\"", "|", "\"\\"", "|", + "\"\\""}], "]"}]}], "]"}]}]}], + "\[IndentingNewLine]", "]"}]}], "\[IndentingNewLine]", + "]"}]}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{"DistributionMomentTruncation", "[", + RowBox[{"ops", ":", + RowBox[{"OptionsPattern", "[", "]"}]}], "]"}], ":=", + RowBox[{"DistributionMomentTruncation", "[", + RowBox[{"canonicalizeDistributionMomentTruncation", "[", "ops", "]"}], + "]"}]}]}], "Input", + InitializationCell->True] +}]], + +Cell[CellGroupData[{ + +Cell["Canonicalize the Truncation", "Item"], + +Cell[BoxData[ + RowBox[{ + RowBox[{"(*", + RowBox[{ + "do", " ", "the", " ", "minimum", " ", "work", " ", "necessary", " ", "to", + " ", "make", " ", "sure", " ", "all", " ", "the", " ", "data", " ", + "for", " ", "the", " ", "DistributionMomentTruncation", " ", "is", " ", + "there"}], "*)"}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{ + RowBox[{"DistributionMomentTruncation", "::", "nocanon"}], "=", + "\"\\""}], ";"}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{"DistributionMomentTruncation", "::", "noentry"}], "=", + "\"\\""}], ";"}], + "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{"DistributionMomentTruncation", "::", "noimplm"}], "=", + "\"\\""}], ";"}], + "\[IndentingNewLine]", + RowBox[{ + RowBox[{"$DistributionDomainCanonicalizer", "=", + RowBox[{"Dispatch", "@", + RowBox[{"{", "\[IndentingNewLine]", + RowBox[{ + RowBox[{"Reals", "\[Rule]", + RowBox[{"Interval", "[", + RowBox[{"{", + RowBox[{ + RowBox[{"-", "\[Infinity]"}], ",", "\[Infinity]"}], "}"}], + "]"}]}], ",", + RowBox[{"Integers", "\[Rule]", + RowBox[{"(", + RowBox[{ + RowBox[{"-", "\[Infinity]"}], ";;", "\[Infinity]"}], ")"}]}], ",", + "\[IndentingNewLine]", + RowBox[{"NonNegativeReals", "\[Rule]", + RowBox[{"Interval", "[", + RowBox[{"{", + RowBox[{"0", ",", "\[Infinity]"}], "}"}], "]"}]}], ",", + RowBox[{"NonPositiveReals", "\[Rule]", + RowBox[{"Interval", "[", + RowBox[{"{", + RowBox[{ + RowBox[{"-", "\[Infinity]"}], ",", "0"}], "}"}], "]"}]}], ",", + "\[IndentingNewLine]", + RowBox[{"NonNegativeIntegers", "\[Rule]", + RowBox[{"(", + RowBox[{"0", ";;", "\[Infinity]"}], ")"}]}], ",", + RowBox[{"NonPositiveIntegers", "\[Rule]", + RowBox[{"(", + RowBox[{ + RowBox[{"-", "\[Infinity]"}], ";;", "0"}], ")"}]}], ",", + "\[IndentingNewLine]", + RowBox[{"PositiveIntegers", "\[Rule]", + RowBox[{"(", + RowBox[{"1", ";;", "\[Infinity]"}], ")"}]}], ",", + RowBox[{"NegativeIntegers", "\[Rule]", + RowBox[{"(", + RowBox[{ + RowBox[{"-", "\[Infinity]"}], ";;", + RowBox[{"-", "1"}]}], ")"}]}]}], "}"}]}]}], ";"}], + "\[IndentingNewLine]", + RowBox[{ + RowBox[{"canonicalizeDistributionMomentTruncation", "[", + RowBox[{"ops", ":", + RowBox[{"OptionsPattern", "[", "DistributionMomentTruncation", "]"}]}], + "]"}], ":=", + RowBox[{"Which", "[", "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{"Length", "@", + RowBox[{"{", "ops", "}"}]}], "<", "1"}], ",", + RowBox[{ + RowBox[{"Message", "[", + RowBox[{ + RowBox[{"DistributionMomentTruncation", "::", "nocanon"}], ",", + RowBox[{"{", "ops", "}"}]}], "]"}], ";", "$Failed"}], ",", + "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{"OptionValue", "[", "\"\\"", "]"}], "===", + "\"\\""}], "&&", + RowBox[{"(", + RowBox[{ + RowBox[{"OptionValue", "[", "\"\\"", "]"}], "===", "None"}], + ")"}]}], ",", + RowBox[{ + RowBox[{"Message", "[", + RowBox[{ + RowBox[{"DistributionMomentTruncation", "::", "noentry"}], ",", + RowBox[{"{", "\"\\"", "}"}]}], "]"}], ";", "$Failed"}], ",", + "\[IndentingNewLine]", "True", ",", + RowBox[{"Module", "[", + RowBox[{ + RowBox[{"{", + RowBox[{"truncdata", "=", + RowBox[{"{", "ops", "}"}]}], "}"}], ",", "\[IndentingNewLine]", + RowBox[{ + RowBox[{"If", " ", "[", + RowBox[{ + RowBox[{ + RowBox[{"OptionValue", "[", "\"\\"", "]"}], + "===", "\"\\""}], ",", "\[IndentingNewLine]", + RowBox[{ + RowBox[{"Message", "[", + RowBox[{ + RowBox[{"DistributionMomentTruncation", "::", "noimplm"}], ",", + RowBox[{ + "\"\\"", "\[Rule]", "\"\\""}]}], + "]"}], ";", + RowBox[{"AppendTo", "[", + RowBox[{"truncdata", ",", + RowBox[{ + "\"\\"", "\[Rule]", "\"\\""}]}], + "]"}]}]}], "]"}], ";", "\[IndentingNewLine]", + RowBox[{"AppendTo", "[", + RowBox[{"truncdata", ",", + RowBox[{ + RowBox[{"\"\\"", "\[Rule]", + RowBox[{"OptionValue", "[", "\"\\"", "]"}]}], "/.", + "$DistributionDomainCanonicalizer"}]}], "]"}], ";", + "\[IndentingNewLine]", + RowBox[{"If", " ", "[", + RowBox[{ + RowBox[{"DistributionParameterQ", "[", + RowBox[{"OptionValue", "[", "\"\\"", "]"}], + "]"}], ",", + RowBox[{"AppendTo", "[", + RowBox[{"truncdata", ",", + RowBox[{"\"\\"", "\[Rule]", + RowBox[{"DistributionDomain", "[", + RowBox[{ + "OptionValue", "[", "\"\\"", "]"}], + "]"}]}]}], "]"}]}], "]"}], ";", "\[IndentingNewLine]", + RowBox[{"AppendTo", "[", + RowBox[{"truncdata", ",", + RowBox[{"\"\\"", "\[Rule]", + RowBox[{"OptionValue", "[", "\"\\"", "]"}]}]}], + "]"}], ";", "\[IndentingNewLine]", + RowBox[{"Sort", "@", + RowBox[{"Association", "[", "truncdata", "]"}]}]}]}], + "\[IndentingNewLine]", "]"}]}], "\[IndentingNewLine]", + "]"}]}]}]}]], "Input", + InitializationCell->True] +}]] +}]], + +Cell[CellGroupData[{ + +Cell["Validators", "Subsubsection"], + +Cell[BoxData[ + RowBox[{ + RowBox[{"(*", + RowBox[{ + "make", " ", "some", " ", "validators", " ", "so", " ", "you", " ", "can", + " ", "always", " ", "be", " ", "sure", " ", "you", " ", "have", " ", "a", + " ", "valid", " ", "DistributionMomentTruncation", " ", "without", " ", + "constantly", " ", "having", " ", "to", " ", "check", " ", "it"}], "*)"}], + RowBox[{ + RowBox[{ + RowBox[{ + "validateDistributionMomentTruncation", "[", "assoc_Association", "]"}], ":=", + RowBox[{"And", "[", "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{"Length", "[", "assoc", "]"}], ">", "0"}], ",", + RowBox[{"KeyMemberQ", "[", "\"\\"", "]"}]}], + "\[IndentingNewLine]", "]"}]}], + RowBox[{"(*", + RowBox[{"reimplement", " ", "this"}], "*)"}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{ + RowBox[{"DistributionMomentTruncation", "[", "assoc_Association", "]"}], + "?", "NotDistributionMomentTruncationQ"}], ":=", + RowBox[{ + RowBox[{"System`Private`HoldSetValid", "[", + RowBox[{"DistributionMomentTruncation", "[", "assoc", "]"}], "]"}], "/;", + RowBox[{"validateDistributionMomentTruncation", "[", "assoc", "]"}]}]}], + ";"}], "\n", + RowBox[{ + RowBox[{ + RowBox[{ + "DistributionMomentTruncationQ", "[", + "distrlx_DistributionMomentTruncation", "]"}], ":=", + RowBox[{"System`Private`HoldValidQ", "[", "distrlx", "]"}]}], ";"}], + "\n", + RowBox[{ + RowBox[{ + RowBox[{"DistributionMomentTruncationQ", "[", "_", "]"}], ":=", + "False"}], ";"}], "\n", + RowBox[{ + RowBox[{ + RowBox[{"DistributionMomentTruncationQ", "[", "symbol_Symbol", "]"}], ":=", + RowBox[{"(", + RowBox[{ + RowBox[{ + RowBox[{"Head", "[", "symbol", "]"}], "===", + "DistributionMomentTruncation"}], "&&", + RowBox[{"DistributionMomentTruncationQ", "[", + RowBox[{"Evaluate", "[", "symbol", "]"}], "]"}]}], ")"}]}], ";"}], + "\n", + RowBox[{ + RowBox[{ + "DistributionMomentTruncationQ", "~", "SetAttributes", "~", "HoldFirst"}], + ";"}], "\n", + RowBox[{ + RowBox[{ + RowBox[{"NotDistributionMomentTruncationQ", "[", "distrlx_", "]"}], ":=", + RowBox[{"Not", "[", + RowBox[{"DistributionMomentTruncationQ", "[", "distrlx", "]"}], "]"}]}], + ";"}], "\n", + RowBox[{ + RowBox[{ + "NotDistributionMomentTruncationQ", "~", "SetAttributes", "~", + "HoldFirst"}], ";"}]}]}]], "Input", + InitializationCell->True], + +Cell[BoxData[ + RowBox[{ + RowBox[{"instantiateDistributionMomentTruncation", "[", + RowBox[{"distrlx_DistributionMomentTruncation", ",", + RowBox[{"ops", ":", + RowBox[{"OptionsPattern", "[", "]"}]}]}], "]"}], ":=", + RowBox[{"Missing", "[", "\"\\"", "]"}], + RowBox[{"(*", + RowBox[{ + RowBox[{ + RowBox[{ + "Default", " ", "to", " ", "na\[IDoubleDot]ve", " ", "polynomial", " ", + "moment", " ", "matching"}], ";", " ", + RowBox[{ + "possible", " ", "alternatives", " ", "including", " ", "orthogonal", + " ", "polynomials"}]}], ",", " ", + RowBox[{"piecewise", "-", + RowBox[{"constant", " ", + RowBox[{"(", "histogram", ")"}]}]}], ",", " ", + RowBox[{"point", "-", "masses"}], ",", " ", + RowBox[{"smooth", "-", + RowBox[{"kernel", " ", + RowBox[{"distributions", "."}]}]}]}], "*)"}]}]], "Input", + InitializationCell->True] +}]], + +Cell[CellGroupData[{ + +Cell["Accessors", "Subsubsection"], + +Cell[BoxData[{ + RowBox[{ + RowBox[{ + RowBox[{"DistributionMomentTruncation", "::", "excdtrnc"}], "=", + "\"\\""}], ";"}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{ + RowBox[{"DistributionMomentTruncation", "[", "a_Association", "]"}], "[", + "\"\\"", "]"}], "[", "0", "]"}], ":=", + "1"}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{ + RowBox[{ + RowBox[{"DistributionMomentTruncation", "[", "a_Association", "]"}], + "[", "\"\\"", "]"}], "[", "r___", "]"}], "/;", + RowBox[{"KeyMemberQ", "[", + RowBox[{"a", ",", "\"\\""}], "]"}]}], ":=", + "\[IndentingNewLine]", + RowBox[{"(", + RowBox[{ + RowBox[{"If", "[", + RowBox[{ + RowBox[{ + RowBox[{"Max", "[", "r", "]"}], ">", + RowBox[{"a", "[", "\"\\"", "]"}]}], ",", + RowBox[{"Message", "[", + RowBox[{ + RowBox[{"DistributionMomentTruncation", "::", "excdtrnc"}], ",", + "r"}], "]"}]}], "]"}], ";", + RowBox[{"Moment", "[", + RowBox[{ + RowBox[{"a", "[", "\"\\"", "]"}], ",", "r"}], + "]"}]}], ")"}]}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{ + RowBox[{ + RowBox[{"DistributionMomentTruncation", "[", "a_Association", "]"}], + "[", "\"\\"", "]"}], "[", "r___", "]"}], "/;", + RowBox[{"(", + RowBox[{ + RowBox[{"a", "[", "\"\\"", "]"}], "===", + "\"\\""}], ")"}]}], ":=", "\[IndentingNewLine]", + RowBox[{"(", + RowBox[{ + RowBox[{"If", "[", + RowBox[{ + RowBox[{ + RowBox[{"Max", "[", "r", "]"}], ">", + RowBox[{"a", "[", "\"\\"", "]"}]}], ",", + RowBox[{"Message", "[", + RowBox[{ + RowBox[{"DistributionMomentTruncation", "::", "excdtrnc"}], ",", "r"}] + , "]"}]}], "]"}], ";", + RowBox[{ + RowBox[{"a", "[", "\"\\"", "]"}], "[", "r", "]"}]}], + ")"}]}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{ + RowBox[{ + RowBox[{"DistributionMomentTruncation", "[", "a_Association", "]"}], + "[", "\"\\"", "]"}], "[", + RowBox[{"{", + RowBox[{"r", ":", + RowBox[{"Repeated", "[", + RowBox[{ + RowBox[{"_Integer", "?", "Positive"}], ",", + RowBox[{"{", + RowBox[{"SequenceCount", "[", + RowBox[{ + RowBox[{"a", "[", "\"\\"", "]"}], ",", + RowBox[{"_Interval", "|", "_Span"}]}], "]"}], "}"}]}], "]"}]}], + "}"}], "]"}], "/;", + RowBox[{"(", + RowBox[{"MatchQ", "[", + RowBox[{"a", ",", + RowBox[{"KeyValuePattern", "[", + RowBox[{"\"\\"", "\[Rule]", "None"}], "]"}]}], + "]"}], ")"}]}], ":=", + RowBox[{"(", + RowBox[{"If", "[", + RowBox[{ + RowBox[{ + RowBox[{ + RowBox[{"If", "[", + RowBox[{ + RowBox[{ + RowBox[{"a", "[", "\"\\"", "]"}], "===", + "\"\\""}], ",", "Total", ",", "Max"}], "]"}], "[", + RowBox[{"{", "r", "}"}], "]"}], ">", + RowBox[{"a", "[", "\"\\"", "]"}]}], ",", + "\[IndentingNewLine]", + RowBox[{ + RowBox[{"Message", "[", + RowBox[{ + RowBox[{"DistributionMomentTruncation", "::", "excdtrnc"}], ",", + "r"}], "]"}], ";", + RowBox[{"Missing", "[", "\"\\"", "]"}]}], ",", + "\[IndentingNewLine]", + RowBox[{ + RowBox[{"a", "[", "\"\\"", "]"}], "\[LeftDoubleBracket]", + "r", "\[RightDoubleBracket]"}]}], "]"}], ")"}]}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{ + RowBox[{ + RowBox[{"DistributionMomentTruncation", "[", "a_Association", "]"}], + "[", "\"\\"", "]"}], "[", + RowBox[{"{", + RowBox[{"r", ":", + RowBox[{"Repeated", "[", + RowBox[{ + RowBox[{"_Integer", "?", "Positive"}], ",", + RowBox[{"{", + RowBox[{"SequenceCount", "[", + RowBox[{ + RowBox[{"a", "[", "\"\\"", "]"}], ",", + RowBox[{"_Interval", "|", "_Span"}]}], "]"}], "}"}]}], "]"}]}], + "}"}], "]"}], "/;", + RowBox[{"(", + RowBox[{"MatchQ", "[", + RowBox[{"a", ",", + RowBox[{"KeyValuePattern", "[", + RowBox[{"\"\\"", "\[Rule]", "\"\\""}], + "]"}]}], "]"}], ")"}]}], ":=", + RowBox[{"(", + RowBox[{"If", "[", + RowBox[{ + RowBox[{ + RowBox[{"Max", "[", "r", "]"}], ">", + RowBox[{"a", "[", "\"\\"", "]"}]}], ",", + "\[IndentingNewLine]", + RowBox[{ + RowBox[{"Message", "[", + RowBox[{ + RowBox[{"DistributionMomentTruncation", "::", "excdtrnc"}], ",", + "r"}], "]"}], ";", + RowBox[{"Missing", "[", "\"\\"", "]"}]}], ",", + "\[IndentingNewLine]", + RowBox[{"Times", "@@", + RowBox[{"MapThread", "[", + RowBox[{"Construct", ",", + RowBox[{"{", + RowBox[{ + RowBox[{"Extract", "/@", + RowBox[{"{", "r", "}"}]}], ",", + RowBox[{"a", "[", "\"\\"", "]"}]}], "}"}]}], "]"}]}]}], + "]"}], ")"}]}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{ + RowBox[{ + RowBox[{"DistributionMomentTruncation", "[", "a_Association", "]"}], + "[", "\"\\"", "]"}], "[", + RowBox[{"{", + RowBox[{"r", ":", + RowBox[{"Repeated", "[", + RowBox[{ + RowBox[{"_Integer", "?", "Positive"}], ",", + RowBox[{"{", + RowBox[{"SequenceCount", "[", + RowBox[{ + RowBox[{"a", "[", "\"\\"", "]"}], ",", + RowBox[{"_Interval", "|", "_Span"}]}], "]"}], "}"}]}], "]"}]}], + "}"}], "]"}], "/;", + RowBox[{"(", + RowBox[{"MatchQ", "[", + RowBox[{"a", ",", + RowBox[{"KeyValuePattern", "[", + RowBox[{"\"\\"", "\[Rule]", "\"\\""}], + "]"}]}], "]"}], ")"}]}], ":=", + RowBox[{"(", + RowBox[{"If", "[", + RowBox[{ + RowBox[{ + RowBox[{"Max", "[", "r", "]"}], ">", + RowBox[{"a", "[", "\"\\"", "]"}]}], ",", + "\[IndentingNewLine]", + RowBox[{ + RowBox[{"Message", "[", + RowBox[{ + RowBox[{"DistributionMomentTruncation", "::", "excdtrnc"}], ",", + "r"}], "]"}], ";", + RowBox[{"Missing", "[", "\"\\"", "]"}]}], ",", + "\[IndentingNewLine]", + RowBox[{"Times", "@@", + RowBox[{ + RowBox[{"a", "[", "\"\\"", "]"}], "[", + RowBox[{"{", "r", "}"}], "]"}]}]}], "]"}], + ")"}]}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{ + RowBox[{ + RowBox[{"DistributionMomentTruncation", "[", "a_Association", "]"}], + "[", "\"\\"", "]"}], "[", + RowBox[{"r_Integer", "?", "Positive"}], "]"}], "/;", + RowBox[{"MatchQ", "[", + RowBox[{"a", ",", + RowBox[{"KeyValuePattern", "[", + RowBox[{"\"\\"", "\[Rule]", + RowBox[{"(", + RowBox[{"_Interval", "|", "_Span"}], ")"}]}], "]"}]}], "]"}]}], ":=", + "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{"DistributionMomentTruncation", "[", "a", "]"}], "[", + "\"\\"", "]"}], "[", + RowBox[{"{", "r", "}"}], "]"}]}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{"DistributionMomentTruncation", "[", "a_Association", "]"}], "[", + "\"\\"", "]"}], ":=", + RowBox[{"Sort", "@", + RowBox[{"Keys", "[", "a", "]"}]}]}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{"DistributionMomentTruncation", "[", "a_Association", "]"}], "[", + "key___", "]"}], ":=", + RowBox[{"a", "[", "key", "]"}]}]}], "Input", + InitializationCell->True] +}]], + +Cell[CellGroupData[{ + +Cell["Formatting", "Subsubsection"], + +Cell[BoxData[ + RowBox[{ + RowBox[{"(*", + RowBox[{ + "define", " ", "formatting", " ", "if", " ", "you", " ", "want", " ", + "to"}], "*)"}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{"$DistributionMomentTruncationSummaryThumbnail", "=", + RowBox[{"DensityPlot", "[", + RowBox[{ + RowBox[{"1", "-", + RowBox[{"Exp", "[", + RowBox[{ + RowBox[{"-", "5"}], + SuperscriptBox[ + RowBox[{"(", + RowBox[{"y", "-", + RowBox[{"(", + RowBox[{".2", "+", + RowBox[{"0.5", + SuperscriptBox["\[ExponentialE]", + RowBox[{ + RowBox[{"-", "8"}], + SuperscriptBox[ + RowBox[{"(", + RowBox[{"x", "+", ".5"}], ")"}], "2"]}]]}], "+", + RowBox[{"1.0", + SuperscriptBox["\[ExponentialE]", + RowBox[{ + RowBox[{"-", "10"}], + SuperscriptBox[ + RowBox[{"(", + RowBox[{"x", "-", ".3"}], ")"}], "2"]}]]}]}], ")"}]}], + ")"}], "2"]}], "]"}]}], ",", + RowBox[{"{", + RowBox[{"x", ",", + RowBox[{"-", "1."}], ",", "1."}], "}"}], ",", + RowBox[{"{", + RowBox[{"y", ",", "0", ",", "2"}], "}"}], ",", + RowBox[{"PlotRange", "\[Rule]", + RowBox[{"{", + RowBox[{ + RowBox[{"{", + RowBox[{ + RowBox[{"-", "1."}], ",", "1."}], "}"}], ",", + RowBox[{"{", + RowBox[{"0.", ",", "2."}], "}"}]}], "}"}]}], ",", + RowBox[{"AspectRatio", "\[Rule]", "1"}], ",", + RowBox[{"Frame", "\[Rule]", "None"}], ",", + RowBox[{"PlotTheme", "\[Rule]", "\"\\""}]}], "]"}]}], + ";"}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{"$DistributionDomainStylizer", "=", + RowBox[{"Dispatch", "[", + RowBox[{"Reverse", "/@", + RowBox[{"Normal", "[", "$DistributionDomainCanonicalizer", "]"}]}], + "]"}]}], ";"}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{"SyntaxInformation", "[", "DistributionMomentTruncation", "]"}], + "=", + RowBox[{"{", + RowBox[{ + RowBox[{"\"\\"", "\[Rule]", + RowBox[{"{", + RowBox[{"___", ",", + RowBox[{"OptionsPattern", "[", "]"}]}], "}"}]}], ",", + RowBox[{"\"\\"", "\[Rule]", + RowBox[{"ToString", "/@", + RowBox[{"First", "/@", + RowBox[{ + "Options", "[", "DistributionMomentTruncation", "]"}]}]}]}]}], + "}"}]}], ";"}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{"Format", "[", + RowBox[{ + RowBox[{ + RowBox[{"DistributionMomentTruncation", "[", "a_Association", "]"}], + "?", "DistributionMomentTruncationQ"}], ",", "StandardForm"}], "]"}], ":=", + RowBox[{"Block", "[", + RowBox[{ + RowBox[{"{", "}"}], ",", "\[IndentingNewLine]", + RowBox[{"RawBoxes", "@", + RowBox[{"BoxForm`ArrangeSummaryBox", "[", + RowBox[{"DistributionMomentTruncation", ",", + RowBox[{"DistributionMomentTruncation", "[", "a", "]"}], ",", + "$DistributionMomentTruncationSummaryThumbnail", ",", + RowBox[{"{", "\[IndentingNewLine]", + RowBox[{ + RowBox[{"{", + RowBox[{ + RowBox[{"BoxForm`MakeSummaryItem", "[", + RowBox[{ + RowBox[{"{", + RowBox[{ + RowBox[{"\"\\"", "<>", "\"\<: \>\""}], ",", + RowBox[{"a", "[", "\"\\"", "]"}]}], "}"}], + ",", "StandardForm"}], "]"}], ",", "\[IndentingNewLine]", + RowBox[{"BoxForm`MakeSummaryItem", "[", + RowBox[{ + RowBox[{"{", + RowBox[{ + RowBox[{"\"\\"", "<>", "\"\<: \>\""}], ",", + RowBox[{ + RowBox[{"a", "[", "\"\\"", "]"}], "/.", + "$DistributionDomainStylizer"}]}], "}"}], ",", + "StandardForm"}], "]"}]}], "}"}], ",", "\[IndentingNewLine]", + RowBox[{"If", "[", + RowBox[{ + RowBox[{ + RowBox[{"KeyMemberQ", "[", + RowBox[{"a", ",", "\"\\""}], "]"}], "&&", + RowBox[{ + RowBox[{"a", "[", "\"\\"", "]"}], "=!=", + "\"\\""}]}], ",", "\[IndentingNewLine]", + RowBox[{"{", + RowBox[{ + RowBox[{"BoxForm`MakeSummaryItem", "[", + RowBox[{ + RowBox[{"{", + RowBox[{ + RowBox[{"\"\\"", "<>", "\"\<: \>\""}], ",", + RowBox[{"a", "[", "\"\\"", "]"}]}], "}"}], + ",", "StandardForm"}], "]"}], ",", "SpanFromLeft"}], "}"}], + ",", + RowBox[{"Unevaluated", "@", + RowBox[{"Sequence", "[", "]"}]}]}], "]"}], ",", + "\[IndentingNewLine]", + RowBox[{"If", "[", + RowBox[{ + RowBox[{"KeyMemberQ", "[", + RowBox[{"a", ",", "\"\\""}], "]"}], ",", + "\[IndentingNewLine]", + RowBox[{"{", + RowBox[{ + RowBox[{"BoxForm`MakeSummaryItem", "[", + RowBox[{ + RowBox[{"{", + RowBox[{ + RowBox[{ + "\"\\"", "<>", "\"\<: \>\""}], ",", + RowBox[{"a", "[", "\"\\"", "]"}]}], + "}"}], ",", "StandardForm"}], "]"}], ",", "SpanFromLeft"}], + "}"}], ",", + RowBox[{"Unevaluated", "@", + RowBox[{"Sequence", "[", "]"}]}]}], "]"}], ",", + "\[IndentingNewLine]", + RowBox[{"If", "[", + RowBox[{ + RowBox[{ + RowBox[{"KeyMemberQ", "[", + RowBox[{"a", ",", "\"\\""}], "]"}], "&&", + RowBox[{ + RowBox[{"a", "[", "\"\\"", "]"}], "=!=", + "None"}]}], ",", "\[IndentingNewLine]", + RowBox[{"{", + RowBox[{ + RowBox[{"BoxForm`MakeSummaryItem", "[", + RowBox[{ + RowBox[{"{", + RowBox[{ + RowBox[{"\"\\"", "<>", "\"\<: \>\""}], + ",", + RowBox[{"a", "[", "\"\\"", "]"}]}], + "}"}], ",", "StandardForm"}], "]"}], ",", "SpanFromLeft"}], + "}"}], ",", + RowBox[{"Unevaluated", "@", + RowBox[{"Sequence", "[", "]"}]}]}], "]"}]}], + "\[IndentingNewLine]", "}"}], ",", + RowBox[{"{", "\[IndentingNewLine]", + RowBox[{ + RowBox[{"If", "[", + RowBox[{ + RowBox[{ + RowBox[{"a", "[", "\"\\"", "]"}], "===", + "\"\\""}], ",", "\[IndentingNewLine]", + RowBox[{"{", + RowBox[{ + RowBox[{"BoxForm`MakeSummaryItem", "[", + RowBox[{ + RowBox[{"{", + RowBox[{ + RowBox[{"\"\\"", "<>", "\"\<: \>\""}], ",", + RowBox[{"a", "[", "\"\\"", "]"}]}], "}"}], + ",", "StandardForm"}], "]"}], ",", "SpanFromLeft"}], "}"}], + ",", + RowBox[{"Unevaluated", "@", + RowBox[{"Sequence", "[", "]"}]}]}], "]"}], ",", + "\[IndentingNewLine]", + RowBox[{"If", "[", + RowBox[{ + RowBox[{"KeyMemberQ", "[", + RowBox[{"a", ",", "\"\\""}], "]"}], ",", + "\[IndentingNewLine]", + RowBox[{"{", + RowBox[{ + RowBox[{"BoxForm`MakeSummaryItem", "[", + RowBox[{ + RowBox[{"{", + RowBox[{ + RowBox[{"\"\\"", "<>", "\"\<: \>\""}], + ",", + RowBox[{"a", "[", "\"\\"", "]"}]}], + "}"}], ",", "StandardForm"}], "]"}], ",", "SpanFromLeft"}], + "}"}], ",", + RowBox[{"Unevaluated", "@", + RowBox[{"Sequence", "[", "]"}]}]}], "]"}], ",", + "\[IndentingNewLine]", + RowBox[{"If", "[", + RowBox[{ + RowBox[{"KeyMemberQ", "[", + RowBox[{"a", ",", "\"\\""}], "]"}], ",", + "\[IndentingNewLine]", + RowBox[{"{", + RowBox[{ + RowBox[{"BoxForm`MakeSummaryItem", "[", + RowBox[{ + RowBox[{"{", + RowBox[{ + RowBox[{"\"\\"", "<>", "\"\<: \>\""}], ",", + RowBox[{"Short", "@", + RowBox[{"a", "[", "\"\\"", "]"}]}]}], "}"}], + ",", "StandardForm"}], "]"}], ",", "SpanFromLeft"}], "}"}], + ",", + RowBox[{"Unevaluated", "@", + RowBox[{"Sequence", "[", "]"}]}]}], "]"}]}], + "\[IndentingNewLine]", "}"}], ",", "StandardForm", ",", + RowBox[{"\"\\"", "\[Rule]", "Automatic"}]}], + "]"}]}]}], "\[IndentingNewLine]", "]"}]}]}]}]], "Input", + InitializationCell->True], + +Cell[BoxData[ + RowBox[{"DistributionMomentTruncation", "[", + RowBox[{"s", ",", "s", ","}], "]"}]], "Input"] +}]] +}]] +}]] +}]] +}] +(* End of Notebook Content *) diff --git a/queue-sdp.nb b/queue-sdp.nb new file mode 100644 index 0000000..6dbf463 --- /dev/null +++ b/queue-sdp.nb @@ -0,0 +1,2002 @@ +(* Content-type: application/vnd.wolfram.mathematica *) + +(* Beginning of Notebook Content *) +Notebook[{ + +Cell[CellGroupData[{ +Cell["Queue-SDP", "Title"], + +Cell[CellGroupData[{ + +Cell["Preamble", "Subsubsection", + CellGroupingRules->{"GroupTogetherGrouping", 10000.}], + +Cell[BoxData[{ + RowBox[{ + InterpretationBox[ + TagBox[ + DynamicModuleBox[{Typeset`open = False}, + FrameBox[ + PaneSelectorBox[{False->GridBox[{ + { + PaneBox[GridBox[{ + { + StyleBox[ + StyleBox[ + AdjustmentBox["\<\"[\[FilledSmallSquare]]\"\>", + BoxBaselineShift->-0.25, + BoxMargins->{{0, 0}, {-1, -1}}], "ResourceFunctionIcon", + + FontColor->RGBColor[ + 0.8745098039215686, 0.2784313725490196, 0.03137254901960784]], + ShowStringCharacters->False, + FontFamily->"Source Sans Pro Black", + FontSize->0.6538461538461539 Inherited, + FontWeight->"Heavy", + PrivateFontOptions->{"OperatorSubstitution"->False}], + StyleBox[ + RowBox[{ + StyleBox["DarkMode", "ResourceFunctionLabel"], " "}], + ShowAutoStyles->False, + ShowStringCharacters->False, + FontSize->Rational[12, 13] Inherited, + FontColor->GrayLevel[0.1]]} + }, + GridBoxSpacings->{"Columns" -> {{0.25}}}], + Alignment->Left, + BaseStyle->{LineSpacing -> {0, 0}, LineBreakWithin -> False}, + BaselinePosition->Baseline, + FrameMargins->{{3, 0}, {0, 0}}], + ItemBox[ + PaneBox[ + TogglerBox[Dynamic[Typeset`open], {True-> + + DynamicBox[FEPrivate`FrontEndResource[ + "FEBitmaps", "IconizeCloser"], + ImageSizeCache->{8.25, {1., 7.25}}], False-> + + DynamicBox[FEPrivate`FrontEndResource[ + "FEBitmaps", "IconizeOpener"], + ImageSizeCache->{8.25, {1., 7.25}}]}, + Appearance->None, + BaselinePosition->Baseline, + ContentPadding->False, + FrameMargins->0], + Alignment->Left, + BaselinePosition->Baseline, + FrameMargins->{{1, 1}, {0, 0}}], + Frame->{{ + RGBColor[ + 0.8313725490196079, 0.8470588235294118, 0.8509803921568627, + 0.5], False}, {False, False}}]} + }, + BaselinePosition->{1, 1}, + GridBoxAlignment->{"Columns" -> {{Left}}, "Rows" -> {{Baseline}}}, + GridBoxItemSize->{"Columns" -> {{Automatic}}, "Rows" -> {{Automatic}}}, + GridBoxSpacings->{"Columns" -> {{0}}, "Rows" -> {{0}}}], True-> + GridBox[{ + {GridBox[{ + { + PaneBox[GridBox[{ + { + StyleBox[ + StyleBox[ + AdjustmentBox["\<\"[\[FilledSmallSquare]]\"\>", + BoxBaselineShift->-0.25, + BoxMargins->{{0, 0}, {-1, -1}}], "ResourceFunctionIcon", + + FontColor->RGBColor[ + 0.8745098039215686, 0.2784313725490196, + 0.03137254901960784]], + ShowStringCharacters->False, + FontFamily->"Source Sans Pro Black", + FontSize->0.6538461538461539 Inherited, + FontWeight->"Heavy", + PrivateFontOptions->{"OperatorSubstitution"->False}], + StyleBox[ + RowBox[{ + StyleBox["DarkMode", "ResourceFunctionLabel"], " "}], + ShowAutoStyles->False, + ShowStringCharacters->False, + FontSize->Rational[12, 13] Inherited, + FontColor->GrayLevel[0.1]]} + }, + GridBoxSpacings->{"Columns" -> {{0.25}}}], + Alignment->Left, + BaseStyle->{LineSpacing -> {0, 0}, LineBreakWithin -> False}, + BaselinePosition->Baseline, + FrameMargins->{{3, 0}, {0, 0}}], + ItemBox[ + PaneBox[ + TogglerBox[Dynamic[Typeset`open], {True-> + + DynamicBox[FEPrivate`FrontEndResource[ + "FEBitmaps", "IconizeCloser"], + ImageSizeCache->{9.9, {2., 7.9}}], False-> + + DynamicBox[FEPrivate`FrontEndResource[ + "FEBitmaps", "IconizeOpener"], + ImageSizeCache->{9.9, {2., 7.9}}]}, + Appearance->None, + BaselinePosition->Baseline, + ContentPadding->False, + FrameMargins->0], + Alignment->Left, + BaselinePosition->Baseline, + FrameMargins->{{1, 1}, {0, 0}}], + Frame->{{ + RGBColor[ + 0.8313725490196079, 0.8470588235294118, 0.8509803921568627, + 0.5], False}, {False, False}}]} + }, + BaselinePosition->{1, 1}, + GridBoxAlignment->{"Columns" -> {{Left}}, "Rows" -> {{Baseline}}}, + + GridBoxItemSize->{ + "Columns" -> {{Automatic}}, "Rows" -> {{Automatic}}}, + GridBoxSpacings->{"Columns" -> {{0}}, "Rows" -> {{0}}}]}, + { + StyleBox[ + PaneBox[GridBox[{ + { + RowBox[{ + TagBox["\<\"Version (latest): \"\>", + "IconizedLabel"], " ", + TagBox["\<\"2.0.0\"\>", + "IconizedItem"]}]}, + { + TagBox[ + + TemplateBox[{ + "\"Documentation \[RightGuillemet]\"", + "https://resources.wolframcloud.com/FunctionRepository/\ +resources/DarkMode"}, + "HyperlinkURL"], + "IconizedItem"]} + }, + DefaultBaseStyle->"Column", + GridBoxAlignment->{"Columns" -> {{Left}}}, + + GridBoxItemSize->{ + "Columns" -> {{Automatic}}, "Rows" -> {{Automatic}}}], + Alignment->Left, + BaselinePosition->Baseline, + FrameMargins->{{5, 4}, {0, 4}}], "DialogStyle", + FontFamily->"Roboto", + FontSize->11]} + }, + BaselinePosition->{1, 1}, + GridBoxAlignment->{"Columns" -> {{Left}}, "Rows" -> {{Baseline}}}, + GridBoxDividers->{"Columns" -> {{None}}, "Rows" -> {False, { + GrayLevel[0.8]}, False}}, + GridBoxItemSize->{ + "Columns" -> {{Automatic}}, "Rows" -> {{Automatic}}}]}, Dynamic[ + Typeset`open], + BaselinePosition->Baseline, + ImageSize->Automatic], + Background->RGBColor[ + 0.9686274509803922, 0.9764705882352941, 0.984313725490196], + BaselinePosition->Baseline, + DefaultBaseStyle->{}, + FrameMargins->{{0, 0}, {1, 0}}, + FrameStyle->RGBColor[ + 0.8313725490196079, 0.8470588235294118, 0.8509803921568627], + RoundingRadius->4]], + {"FunctionResourceBox", + RGBColor[0.8745098039215686, 0.2784313725490196, 0.03137254901960784], + "DarkMode"}, + TagBoxNote->"FunctionResourceBox"], + ResourceFunction[ + ResourceObject[ + Association[ + "Name" -> "DarkMode", "ShortName" -> "DarkMode", "UUID" -> + "6ae9b15e-dd80-4d11-be6e-434bf9ac9265", "ResourceType" -> "Function", + "Version" -> "2.0.0", "Description" -> + "Restyle notebooks into dark mode", "RepositoryLocation" -> + URL["https://www.wolframcloud.com/objects/resourcesystem/api/1.0"], + "SymbolName" -> + "FunctionRepository`$f2abd2063089401aafe135eb354a8d92`DarkMode", + "FunctionLocation" -> + CloudObject[ + "https://www.wolframcloud.com/obj/91755122-26ae-43f1-8e41-\ +4043472dcf8a"]], ResourceSystemBase -> Automatic]], + Selectable->False], ";"}], "\[IndentingNewLine]", + RowBox[{"SetOptions", "[", + RowBox[{ + RowBox[{"SelectedNotebook", "[", "]"}], ",", + RowBox[{"PrintingStyleEnvironment", "\[Rule]", "\"\\""}], ",", + RowBox[{"ShowSyntaxStyles", "\[Rule]", "True"}]}], + "]"}], "\[IndentingNewLine]", + RowBox[{"ClearAll", "[", + RowBox[{"Evaluate", "[", + RowBox[{ + RowBox[{"ToString", "[", + RowBox[{"Context", "[", "]"}], "]"}], "<>", "\"\<*\>\""}], "]"}], + "]"}]}], "Input", + CellGroupingRules->{"GroupTogetherGrouping", 10000.}, + InitializationCell->True] +}]], + +Cell[CellGroupData[{ + +Cell["Definitions", "Section"], + +Cell[CellGroupData[{ + +Cell["Basic Functions", "Subsection"], + +Cell[BoxData[{ + RowBox[{ + RowBox[{"integerCompositions", "=", + RowBox[{ + RowBox[{"Reverse", "[", + RowBox[{ + RowBox[{"ResourceFunction", "[", "\"\\"", "]"}], + "[", + RowBox[{"#1", ",", "#2"}], "]"}], "]"}], "&"}]}], + ";"}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{"edg2mat", "=", + RowBox[{ + RowBox[{"(", + RowBox[{ + RowBox[{"(", + RowBox[{"\[FormalX]", "\[Function]", + RowBox[{ + RowBox[{"(", + RowBox[{"\[FormalY]", "\[Function]", + RowBox[{"(", + RowBox[{"\[FormalX]", "+", "\[FormalY]"}], ")"}]}], ")"}], "/@", + "#"}]}], ")"}], "/@", "#"}], ")"}], "&"}]}], ";"}]}], "Input", + CellGroupingRules->{"GroupTogetherGrouping", 10000.}, + InitializationCell->True], + +Cell[CellGroupData[{ + +Cell[TextData[{ + "How ", + Cell[BoxData[ + FormBox["integerCompositions", TraditionalForm]], "Input", + FontSize->18,ExpressionUUID->"8e192a63-460a-4b0a-9ad8-7c54f703582f"], + " w", + StyleBox["or", + FontColor->RGBColor[ + 0.8235294117647058, 0.4906538490882734, 0.20227359426260777`]], + "ks" +}], "Subsubsection", + CellGroupingRules->{"GroupTogetherGrouping", 10001.}], + +Cell[TextData[{ + "The following lines breakdown the internal steps of ", + Cell[BoxData[ + FormBox[ + RowBox[{"ResourceFunction", "[", "\"\\"", "]"}], + TraditionalForm]],ExpressionUUID->"0612544d-83e9-4d76-85db-772ad69754fb"], + " and shows how the compositions are generated." +}], "Text", + CellGroupingRules->{"GroupTogetherGrouping", 10001.}], + +Cell[BoxData[{ + RowBox[{"Clear", "[", + RowBox[{"n", ",", "k"}], "]"}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{"n", "=", "2"}], ";", + RowBox[{"k", "=", "3"}], ";"}], "\[IndentingNewLine]", + RowBox[{"Range", "[", + RowBox[{"n", "+", "k", "-", "1"}], "]"}], "\[IndentingNewLine]", + RowBox[{"Subsets", "[", + RowBox[{"%", ",", + RowBox[{"{", + RowBox[{"k", "-", "1"}], "}"}]}], "]"}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{"Join", "[", + RowBox[{ + RowBox[{"{", "0", "}"}], ",", "#", ",", + RowBox[{"{", + RowBox[{"n", "+", "k"}], "}"}]}], "]"}], "&"}], "/@", + "%"}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{"Partition", "[", + RowBox[{"#", ",", "2", ",", "1"}], "]"}], "&"}], "/@", + "%"}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{"Reverse", "@", + RowBox[{"Map", "[", + RowBox[{ + RowBox[{ + RowBox[{"(", + RowBox[{ + RowBox[{"#", "\[LeftDoubleBracket]", "2", "\[RightDoubleBracket]"}], + "-", + RowBox[{"#", "\[LeftDoubleBracket]", "1", "\[RightDoubleBracket]"}]}], + ")"}], "&"}], ",", "%", ",", + RowBox[{"{", "2", "}"}]}], "]"}]}], "-", "1"}], "\[IndentingNewLine]", + RowBox[{"Clear", "[", + RowBox[{"n", ",", "k"}], "]"}]}], "Input", + CellGroupingRules->{"GroupTogetherGrouping", 10001.}] +}]], + +Cell[CellGroupData[{ + +Cell["Miscalleneous", "Subsubsection", + CellGroupingRules->{"GroupTogetherGrouping", 10000.}], + +Cell[BoxData[ + RowBox[{ + RowBox[{"(*", + RowBox[{ + RowBox[{"How", " ", "to", " ", "slice", " ", "a", " ", "4"}], "-", + RowBox[{ + "dimensional", " ", "array", " ", "and", " ", "save", " ", "as", " ", + RowBox[{"MATLAB", " ", ".", "mat"}], " ", "files"}]}], "*)"}], + "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{"ls", "=", + RowBox[{"ConstantArray", "[", + RowBox[{"1", ",", + RowBox[{"{", + RowBox[{"2", ",", "2", ",", "2", ",", "2"}], "}"}]}], "]"}]}], ";"}], + "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{ + RowBox[{"MapIndexed", "[", + RowBox[{ + RowBox[{ + RowBox[{"{", + RowBox[{"slc", ",", "idx"}], "}"}], "\[Function]", + RowBox[{"List", "[", + RowBox[{ + RowBox[{ + RowBox[{"StringTemplate", "[", "\"\<`1``2`.mat\>\"", "]"}], "[", + RowBox[{ + RowBox[{"ToString", "[", + RowBox[{"Unevaluated", "[", "#", "]"}], "]"}], ",", + RowBox[{"idx", "[", + RowBox[{"[", "1", "]"}], "]"}]}], "]"}], ",", "slc"}], "]"}]}], + ",", + RowBox[{"Evaluate", "[", + RowBox[{"Transpose", "[", "#", "]"}], "]"}]}], "]"}], "&"}], "@", + RowBox[{"Unevaluated", "@", "ls"}]}], ";"}], "\[IndentingNewLine]", + RowBox[{"(*", + RowBox[{ + "Unneeded", " ", "since", " ", "there", " ", "are", " ", "now", " ", + "HDF5", " ", "files"}], "*)"}]}]}]], "Input", + CellGroupingRules->{"GroupTogetherGrouping", 10000.}], + +Cell[BoxData[{ + RowBox[{"Clear", "[", "Ap0", "]"}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{"Ap0", "[", + RowBox[{"p_", ",", + RowBox[{"k_", ":", "1"}]}], "]"}], ":=", + RowBox[{ + RowBox[{"Ap0", "[", + RowBox[{"p", ",", "k"}], "]"}], "=", + RowBox[{"SparseArray", "[", + RowBox[{ + RowBox[{ + RowBox[{"loc", "[", + RowBox[{"{", + RowBox[{ + RowBox[{"p", " ", + RowBox[{"UnitVector", "[", + RowBox[{"K", ",", "k"}], "]"}]}], ",", + RowBox[{"ConstantArray", "[", + RowBox[{"0", ",", "K"}], "]"}]}], "}"}], "]"}], "\[Rule]", "1"}], + ",", "matICdim"}], "]"}]}]}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{"Ap0", "::", "usage"}], "=", + "\"\\"Italic\"]],ExpressionUUID->\"\ +68f4c655-4059-49e4-9908-e3afa40d9152\"]\)-th moment of the \ +\!\(\*Cell[TextData[StyleBox[\"que\",FontSlant->\"Italic\"]],ExpressionUUID->\ +\"86d09b70-5828-46a7-a5cc-bf7c03049d7e\"]\)-th queue as the SDP \ +objective\>\""}], ";"}]}], "Input", + CellGroupingRules->{"GroupTogetherGrouping", 10000.}] +}]] +}]], + +Cell[CellGroupData[{ + +Cell["SDP cone-matrix", "Subsection"], + +Cell[CellGroupData[{ + +Cell[TextData[{ + "For the sake of clarity, the usually known ", + ButtonBox["multi-index notation", + BaseStyle->"Hyperlink", + ButtonData->{ + URL["https://en.wikipedia.org/wiki/Multi-index_notation"], None}, + ButtonNote->"https://en.wikipedia.org/wiki/Multi-index_notation"], + " is hereafter called a vecponent (i.e., ", + ButtonBox["vector exponent", + BaseStyle->"Hyperlink", + ButtonData->{ + URL["https://mathworld.wolfram.com/ExponentVector.html"], None}, + ButtonNote->"https://mathworld.wolfram.com/ExponentVector.html"], + ")." +}], "Text", + CellGroupingRules->{"GroupTogetherGrouping", 10001.}], + +Cell[BoxData[ + RowBox[{ + RowBox[{"(*", + RowBox[{ + "Only", " ", "memoized", " ", "recursives", " ", "are", " ", "explicitly", + " ", "cleared", " ", "before", " ", "definition"}], "*)"}], + "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{ + RowBox[{"K", "::", "usage"}], "=", "\"\\""}], ";"}], + "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{"r", "::", "usage"}], "=", "\"\\""}], ";"}], + "\[IndentingNewLine]", + RowBox[{ + RowBox[{"K", "=", "3"}], ";", + RowBox[{"r", "=", "3"}], ";"}], "\[IndentingNewLine]", + "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{"\[Alpha]IC", "::", "usage"}], "=", + "\"\12,FontWeight->\"Bold\"]],\ +ExpressionUUID->\"8ab6b8df-cf8b-4ebf-b553-1292cd24f184\"]\) vecponents\>\""}], + ";"}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{"\[Alpha]IC", "=", + RowBox[{"Join", "@@", + RowBox[{"Table", "[", + RowBox[{ + RowBox[{"integerCompositions", "[", + RowBox[{"\[FormalR]", ",", "K"}], "]"}], ",", + RowBox[{"{", + RowBox[{"\[FormalR]", ",", "0", ",", + RowBox[{"2", "r"}]}], "}"}]}], "]"}]}]}], ";"}], + "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{"edgIC", "::", "usage"}], "=", + "\"\12], +StyleBox[\"\[Alpha]\",FontSize->12,FontWeight->\"Bold\"], +StyleBox[\",\[Beta])\",FontSize->12] +}],ExpressionUUID->\"c3b0083a-6358-403e-a84d-f2841e0f07bb\"]\) \ +vecponents\>\""}], ";"}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{"edgIC", "=", + RowBox[{"Join", "@@", + RowBox[{"Table", "[", + RowBox[{ + RowBox[{ + RowBox[{ + RowBox[{"ArrayReshape", "[", + RowBox[{"#", ",", + RowBox[{"{", + RowBox[{"2", ",", "K"}], "}"}]}], "]"}], "&"}], "/@", + RowBox[{"integerCompositions", "[", + RowBox[{"\[FormalR]", ",", + RowBox[{"2", "K"}]}], "]"}]}], ",", + RowBox[{"{", + RowBox[{"\[FormalR]", ",", "0", ",", "r"}], "}"}]}], "]"}]}]}], + ";"}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{"matIC", "::", "usage"}], "=", + "\"\\""}], ";"}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{"matIC", "=", + RowBox[{"edgIC", "//", "edg2mat"}]}], ";"}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{"matICdim", "=", + RowBox[{"Dimensions", "[", + RowBox[{"matIC", ",", "2"}], "]"}]}], ";"}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{"ClearAll", "[", "loc", "]"}], ";", + RowBox[{ + RowBox[{"loc", "::", "usage"}], "=", + "\"\\""}], ";", + RowBox[{ + RowBox[{"loc", "::", "usage", "::", "ChineseSimplified"}], "=", + "\"\<\:5728 \ +\!\(\*Cell[\"matIC\",ExpressionUUID->\"f9c59498-c2df-441e-bfcd-d428861ac95b\"]\ +\) \:4e2d\:67e5\:627e\:4e00\:4e2a\:591a\:91cd\:6307\:6807\>\""}], ";"}], + "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{"loc", "[", "vecponent_", "]"}], ":=", + RowBox[{ + RowBox[{"loc", "[", "vecponent", "]"}], "=", + RowBox[{"FirstPosition", "[", + RowBox[{"matIC", ",", "vecponent", ",", + RowBox[{"Missing", "[", "\"\\"", "]"}], ",", + RowBox[{"{", "2", "}"}]}], "]"}]}]}], ";"}]}]}]], "Input", + CellGroupingRules->{"GroupTogetherGrouping", 10001.}, + InitializationCell->True] +}]], + +Cell[CellGroupData[{ + +Cell["Misc", "Subsubsection"], + +Cell[BoxData[{ + RowBox[{ + RowBox[{ + RowBox[{"matX", "::", "usage"}], "=", + "\"\\"e638f67f-5d65-4182-8cf8-09e82d577ffe\"]\ +\)\>\""}], ";", + RowBox[{ + RowBox[{"matX", "::", "usage", "::", "ChineseSimplified"}], "=", + "\"\<\!\(\*Cell[\"matIC\",ExpressionUUID->\"4695cc3c-2d18-4885-a35f-\ +1bcaf9f9d706\"]\) \:7684\:5f62\:5f0f\:8868\:793a\>\""}], + ";"}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{"matX", "[", "]"}], "=", + RowBox[{"Map", "[", + RowBox[{ + RowBox[{ + RowBox[{"Superscript", "[", + RowBox[{ + RowBox[{"Style", "[", + RowBox[{"\[FormalX]", ",", "Larger"}], "]"}], ",", + RowBox[{"Style", "[", + RowBox[{ + RowBox[{"MatrixForm", "[", + RowBox[{"#", ",", + RowBox[{"TableSpacing", "\[Rule]", + RowBox[{"{", + RowBox[{"0", ",", "0"}], "}"}]}]}], "]"}], ",", "Smaller"}], + "]"}]}], "]"}], "&"}], ",", "matIC", ",", + RowBox[{"{", "2", "}"}]}], "]"}]}], ";"}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{"matX", "[", + RowBox[{"s_", ":", + RowBox[{"Except", "[", "All", "]"}]}], "]"}], ":=", + RowBox[{ + RowBox[{"matX", "[", "s", "]"}], "=", + RowBox[{"Map", "[", + RowBox[{ + RowBox[{ + RowBox[{"Subsuperscript", "[", + RowBox[{ + RowBox[{"Style", "[", + RowBox[{"\[FormalX]", ",", "Larger"}], "]"}], ",", "s", ",", + RowBox[{"Style", "[", + RowBox[{ + RowBox[{"MatrixForm", "[", + RowBox[{"#", ",", + RowBox[{"TableSpacing", "\[Rule]", + RowBox[{"{", + RowBox[{"0", ",", "0"}], "}"}]}]}], "]"}], ",", "Smaller"}], + "]"}]}], "]"}], "&"}], ",", "matIC", ",", + RowBox[{"{", "2", "}"}]}], "]"}]}]}], ";"}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{"matX", "[", "All", "]"}], "=", + RowBox[{"Table", "[", + RowBox[{ + RowBox[{"matX", "[", "k", "]"}], ",", + RowBox[{"{", + RowBox[{"k", ",", "1", ",", + SuperscriptBox["2", "K"]}], "}"}]}], "]"}]}], ";"}]}], "Input", + InitializationCell->True] +}]] +}]], + +Cell[CellGroupData[{ + +Cell["Known moments", "Subsection"], + +Cell[TextData[{ + "In the semi-definite optimisation procedure, ", + Cell[BoxData[ + FormBox[ + StyleBox[ + RowBox[{ + RowBox[{"m", "(", + StyleBox["\[Beta]", + FontWeight->"Bold"], ")"}], " ", "=", " ", + RowBox[{ + RowBox[{"\[DoubleStruckCapitalE]", "[", Cell[TextData[Cell[BoxData[ + FormBox[ + SuperscriptBox[ + StyleBox["X", + FontWeight->"Bold"], + StyleBox["\[Beta]", + FontWeight->"Bold"]], TraditionalForm]],ExpressionUUID-> + "9193c70f-ee14-462e-95f4-12faba39350e"]],ExpressionUUID-> + "d60c0cf6-3d5a-4373-9ee4-0da051d4cdbe"], "]"}], "=", + RowBox[{"\[DoubleStruckCapitalE]", "[", Cell[TextData[Cell[BoxData[ + FormBox[ + SuperscriptBox[ + RowBox[{"(", + RowBox[{ + StyleBox["S", + FontWeight->"Bold"], "-", + StyleBox["A", + FontWeight->"Bold"]}], ")"}], + StyleBox["\[Beta]", + FontWeight->"Bold"]], TraditionalForm]],ExpressionUUID-> + "d53a3a45-d868-437f-8521-617f6cd6c588"]],ExpressionUUID-> + "cf1a464e-dc64-4e30-8cb3-936aed773204"], "]"}]}]}], + FontSize->12], TraditionalForm]], "InlineFormula",ExpressionUUID-> + "9d4f3c05-aab0-4be2-8664-b78c887e00c4"], + ", the moments of the increments to the per-queue waiting times must be \ +known. The current version of our code uses the moments of the service time \ +and arrival time respectively to calculate these quantities." +}], "Text"], + +Cell[BoxData[{ + RowBox[{ + RowBox[{ + RowBox[{"\[Lambda]", "::", "usage"}], "=", "\"\\""}], + ";"}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{"\[Mu]", "::", "usage"}], "=", "\"\\""}], + ";"}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{"\[Lambda]", "=", ".5"}], ";", + RowBox[{"\[Mu]", "=", "1"}], ";"}]}], "Input", + InitializationCell->True], + +Cell[CellGroupData[{ + +Cell["Arrival", "Subsubsection"], + +Cell[BoxData[{ + RowBox[{ + RowBox[{"Clear", "[", + RowBox[{ + "M", ",", "inprobs", ",", "D0", ",", "D1", ",", "ArrivalPi", ",", + "ArrivalMoment", ",", "ArrivalMoment"}], "]"}], "\[IndentingNewLine]", + RowBox[{"(*", + RowBox[{ + "The", " ", "whole", " ", "MAP", " ", "feature", " ", "is", " ", + "currently", " ", "suspended"}], "*)"}]}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{"M", "::", "usage"}], "=", + "\"\\""}], + ";"}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{"M", "=", "2"}], ";"}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{"inprobs", "::", "usage"}], "=", + "\"\\""}], ";"}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{"inprobs", "=", + FractionBox[ + RowBox[{"Table", "[", + RowBox[{"1", ",", "K"}], "]"}], "K"]}], ";"}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{"D0", "::", "usage"}], "=", + "\"\\""}], + ";"}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{"D1", "::", "usage"}], "=", + "\"\\""}], ";"}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{"D0", "=", + RowBox[{"(", GridBox[{ + { + RowBox[{"-", "2"}], "0"}, + {"0", + RowBox[{ + RowBox[{"-", "1"}], "/", "2"}]} + }], ")"}]}], ";", + RowBox[{"D1", "=", + RowBox[{"(", GridBox[{ + { + RowBox[{"3", "/", "5"}], + RowBox[{"7", "/", "5"}]}, + { + RowBox[{"7", "/", "20"}], + RowBox[{"3", "/", "20"}]} + }], ")"}]}], ";"}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{"ArrivalPi", "=", + RowBox[{"Normalize", "[", + RowBox[{ + RowBox[{"First", "@", + RowBox[{"NullSpace", "[", + RowBox[{"D0", "+", "D1"}], "]"}]}], ",", "Total"}], "]"}]}], ";"}], + "\[IndentingNewLine]"}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{ + RowBox[{"ArrivalMoment", "::", "usage"}], "=", + "\"\\"524f825d-3170-455f-acad-\ +77fd43ed275b\"],FontSlant->\"Italic\"], \"]\"}], \ +TraditionalForm]],ExpressionUUID->\"8990b7d6-703a-438b-812a-5aff2e15e916\"]],\ +ExpressionUUID->\"03a8b042-e4ec-4772-866c-cb8b8283d9fa\"]\)\>\""}], ";"}], + RowBox[{"(*", " ", + RowBox[{"or", " ", Cell[TextData[Cell[BoxData[ + FormBox[ + SuperscriptBox[ + RowBox[{"ArrivalMoment", "[", "]"}], + StyleBox[Cell[ + "integer",ExpressionUUID->"15dd358f-ad74-41fb-a0a5-1680737c3f84"], + FontSlant->"Italic"]], TraditionalForm]],ExpressionUUID-> + "cddb2e89-fa1d-4677-956f-b4639ca16c9f"]],ExpressionUUID-> + "eb7fb9fd-2a83-4ebe-9647-50c1a0f44f1c"], "\"\<;\>"}], "*)"}], + "\[IndentingNewLine]", + RowBox[{"(*", + RowBox[{ + RowBox[{"ArrivalMoment", "/:", + RowBox[{"Power", "[", + RowBox[{"ArrivalMoment", ",", "k_Integer"}], "]"}], ":=", + RowBox[{"ArrivalMoment", "[", "k", "]"}]}], ";"}], "*)"}], + "\[IndentingNewLine]", + RowBox[{"(*", + RowBox[{ + RowBox[{"ArrivalMoment", "/:", + RowBox[{"Power", "[", + RowBox[{ + RowBox[{"ArrivalMoment", "[", "]"}], ",", "k_Integer"}], "]"}], ":=", + RowBox[{"ArrivalMoment", "[", "k", "]"}]}], ";"}], "*)"}], + "\[IndentingNewLine]", + RowBox[{"(*", + RowBox[{ + RowBox[{ + RowBox[{"ArrivalMoment", "[", "k_Integer", "]"}], ":=", + RowBox[{ + RowBox[{"ArrivalMoment", "[", "k", "]"}], "=", + RowBox[{ + RowBox[{"(", + RowBox[{"M", "!"}], ")"}], "*", + RowBox[{"ArrivalPi", ".", + RowBox[{"MatrixPower", "[", + RowBox[{ + RowBox[{"-", "D0"}], ",", + RowBox[{"-", "k"}], ",", + RowBox[{"Table", "[", + RowBox[{"1", ",", "M"}], "]"}]}], "]"}]}]}]}]}], ";"}], + RowBox[{"(*", "suspended", "*)"}], "*)"}]}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{ + RowBox[{"ArrivalMoment", "[", "k_Integer", "]"}], ":=", + RowBox[{ + RowBox[{"ArrivalMoment", "[", "k", "]"}], "=", + RowBox[{"Moment", "[", + RowBox[{ + RowBox[{"PoissonDistribution", "[", + RowBox[{"1", "/", "\[Lambda]"}], "]"}], ",", "k"}], "]"}]}]}], ";"}], + "\[IndentingNewLine]"}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{ + RowBox[{"ArrivalMoment", "::", "usage"}], "=", + "\"\\""}], ";"}], + RowBox[{"(*", "unused", "*)"}]}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{"ArrivalMoments", "[", "\[Beta]_List", "]"}], ":=", + RowBox[{ + RowBox[{"ArrivalMoment", "[", "\[Beta]", "]"}], "=", + RowBox[{"MapThread", "[", + RowBox[{ + RowBox[{ + RowBox[{ + SuperscriptBox["#2", "#1"], + RowBox[{"ArrivalMoment", "[", "#1", "]"}]}], "&"}], ",", + RowBox[{"{", + RowBox[{"\[Beta]", ",", "inprobs"}], "}"}]}], "]"}]}]}], + ";"}]}], "Input", + CellGroupingRules->{"GroupTogetherGrouping", 10000.}, + InitializationCell->True, + CellChangeTimes->{{3.814354147217802*^9, 3.8143541925808816`*^9}, { + 3.8143542364420433`*^9, 3.814354268589903*^9}, {3.814354302000815*^9, + 3.814354484514713*^9}, {3.8143545416935205`*^9, 3.814354541813964*^9}, { + 3.814354711811903*^9, 3.8143547217012334`*^9}, 3.81435517231498*^9, + 3.8143553341665645`*^9, {3.8143554226568813`*^9, 3.814355626943615*^9}, { + 3.8143557308065777`*^9, 3.814355781870577*^9}, {3.8143560649920087`*^9, + 3.8143560854756804`*^9}, {3.814399643721156*^9, 3.8143996671351104`*^9}, + 3.814408503824012*^9, 3.814408697862784*^9, {3.8184821544156275`*^9, + 3.8184821788606253`*^9}, 3.8184851541654778`*^9, {3.821571675963249*^9, + 3.82157169475276*^9}, {3.821572098593541*^9, 3.8215721046059585`*^9}, { + 3.8216055623780327`*^9, 3.8216056086333075`*^9}, {3.8216748352155304`*^9, + 3.8216748415791063`*^9}, {3.821674878656392*^9, 3.821674901547779*^9}, { + 3.8216764157642665`*^9, 3.8216764733022003`*^9}, {3.8216765072526317`*^9, + 3.8216765779145975`*^9}, {3.821676629903329*^9, 3.821676672625868*^9}, { + 3.821679166032086*^9, 3.8216793556741595`*^9}, {3.8216794023356795`*^9, + 3.8216794576824226`*^9}, 3.8216797839553375`*^9, {3.8216798788120594`*^9, + 3.8216799679949865`*^9}, 3.8216800088471823`*^9, 3.821699807985315*^9, { + 3.82169984389784*^9, 3.821699853641487*^9}, {3.8217014677978044`*^9, + 3.821701530190349*^9}, {3.821701593626543*^9, 3.8217015943369093`*^9}, { + 3.822478048621821*^9, 3.8224780497127504`*^9}, {3.8228116647089396`*^9, + 3.8228116827422295`*^9}, 3.8228117191344805`*^9, 3.822811759039522*^9, { + 3.8228736017750387`*^9, 3.822873602011322*^9}, {3.82287380109065*^9, + 3.8228738292712927`*^9}, {3.822873920945613*^9, 3.8228739249783573`*^9}, { + 3.8228740228210173`*^9, 3.8228740337520847`*^9}, {3.822874066878928*^9, + 3.822874067043927*^9}, 3.8228741487611322`*^9, {3.822888732149809*^9, + 3.8228887415826797`*^9}, {3.8228889103299212`*^9, 3.822889093385957*^9}}, + CellLabel->"In[25]:=",ExpressionUUID->"60055039-185b-4603-8de7-d9c6e20e2f5f"] +}, Open ]], + +Cell[CellGroupData[{ + +Cell["Service", "Subsubsection", + CellChangeTimes->{{3.814352040520709*^9, 3.8143520681261554`*^9}, { + 3.8216766401278114`*^9, 3.8216766414390364`*^9}, {3.8216793430802083`*^9, + 3.821679344423665*^9}},ExpressionUUID->"0de55b95-a8fa-421f-b258-\ +5c3b36e7ef2d"], + +Cell[BoxData[{ + RowBox[{"Clear", "[", + RowBox[{"outprobs", ",", "ServiceMoment", ",", "ServiceMoments"}], + "]"}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{"outprobs", "::", "usage"}], "=", + "\"\\""}], ";"}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{"outprobs", "=", + FractionBox[ + RowBox[{"Table", "[", + RowBox[{"1", ",", "K"}], "]"}], "K"]}], ";"}], + "\[IndentingNewLine]"}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{ + RowBox[{"ServiceMoment", "::", "usage"}], "=", + "\"\\"ae20adc6-ca96-49b4-a29b-\ +8afc63e8c8a8\"],FontSlant->\"Italic\"], \"]\"}], \ +TraditionalForm]],ExpressionUUID->\"ce2f02f1-9895-44f0-9382-eaa9f30562e7\"]],\ +ExpressionUUID->\"39c0edb1-9e34-4b42-9414-620c753d6590\"]\)\>\""}], ";"}], + RowBox[{"(*", " ", + RowBox[{"or", " ", Cell[TextData[Cell[BoxData[ + FormBox[ + SuperscriptBox[ + RowBox[{"ServiceMoment", "[", "]"}], + StyleBox[Cell[ + "integer",ExpressionUUID->"7ddb47e0-c3a5-4902-95c2-4aa977d10e0f"], + FontSlant->"Italic"]], TraditionalForm]],ExpressionUUID-> + "24ce4245-3667-420c-a00a-3fd574c237fe"]],ExpressionUUID-> + "4d9ed55c-c07a-4665-809f-a6f3ef733a24"], "\"\<;\>"}], "*)"}], + "\[IndentingNewLine]", + RowBox[{"(*", + RowBox[{ + RowBox[{"ServiceMoment", "/:", + RowBox[{"Power", "[", + RowBox[{"ServiceMoment", ",", "k_Integer"}], "]"}], ":=", + RowBox[{"ServiceMoment", "[", "k", "]"}]}], ";"}], "*)"}], + "\[IndentingNewLine]", + RowBox[{"(*", + RowBox[{ + RowBox[{"ServiceMoment", "/:", + RowBox[{"Power", "[", + RowBox[{ + RowBox[{"ServiceMoment", "[", "]"}], ",", "k_Integer"}], "]"}], ":=", + RowBox[{"ServiceMoment", "[", "k", "]"}]}], ";"}], + "*)"}]}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{ + RowBox[{"ServiceMoment", "[", "k_Integer", "]"}], ":=", + RowBox[{ + RowBox[{"ServiceMoment", "[", "k", "]"}], "=", + RowBox[{"Moment", "[", + RowBox[{ + RowBox[{"PoissonDistribution", "[", + RowBox[{"1", "/", "\[Mu]"}], "]"}], ",", "k"}], "]"}]}]}], ";"}], + "\[IndentingNewLine]"}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{ + RowBox[{"ServiceMoments", "::", "usage"}], "=", + "\"\\""}], ";"}], + RowBox[{"(*", "unused", "*)"}]}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{"ServiceMoments", "[", "\[Beta]_List", "]"}], ":=", + RowBox[{ + RowBox[{"ServiceMoments", "[", "\[Beta]", "]"}], "=", + RowBox[{"MapThread", "[", + RowBox[{ + RowBox[{ + RowBox[{ + SuperscriptBox["#2", "#1"], + RowBox[{"ServiceMoment", "[", "#1", "]"}]}], "&"}], ",", + RowBox[{"{", + RowBox[{"\[Beta]", ",", "outprobs"}], "}"}]}], "]"}]}]}], + ";"}]}], "Input", + CellGroupingRules->{"GroupTogetherGrouping", 10000.}, + InitializationCell->True] +}]], + +Cell[CellGroupData[{ + +Cell["Increment", "Subsubsection"], + +Cell[CellGroupData[{ + +Cell[BoxData[{ + RowBox[{ + RowBox[{"Clear", "[", "m", "]"}], "\[IndentingNewLine]", + RowBox[{"(*", + RowBox[{ + RowBox[{ + RowBox[{"m", "[", "\[Beta]_List", "]"}], ":=", + RowBox[{ + RowBox[{"m", "[", "\[Beta]", "]"}], "=", + RowBox[{"Times", "@@", + RowBox[{"MapThread", "[", + RowBox[{ + RowBox[{ + RowBox[{ + SuperscriptBox["#2", "#1"], + RowBox[{"ArrivalMoment", "[", "#1", "]"}]}], "&"}], ",", + RowBox[{"{", + RowBox[{"\[Beta]", ",", "inprob"}], "}"}]}], "]"}]}]}]}], ";"}], + RowBox[{"(*", "WRONG", "*)"}], "*)"}]}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{"m", "[", "\[Beta]_List", "]"}], ":=", + RowBox[{ + RowBox[{"m", "[", "\[Beta]", "]"}], "=", + RowBox[{ + UnderoverscriptBox["\[Product]", + RowBox[{"\[FormalK]", "=", "1"}], "K"], + RowBox[{"(", + RowBox[{ + UnderoverscriptBox["\[Sum]", + RowBox[{"\[FormalL]", "=", "1"}], "K"], + RowBox[{"(", + RowBox[{ + RowBox[{"Binomial", "[", + RowBox[{ + RowBox[{ + "\[Beta]", "\[LeftDoubleBracket]", "\[FormalK]", + "\[RightDoubleBracket]"}], ",", "\[FormalL]"}], "]"}], + SuperscriptBox[ + RowBox[{"(", + RowBox[{"-", "1"}], ")"}], "\[FormalL]"], + SuperscriptBox[ + RowBox[{ + "outprobs", "\[LeftDoubleBracket]", "\[FormalK]", + "\[RightDoubleBracket]"}], + RowBox[{ + RowBox[{ + "\[Beta]", "\[LeftDoubleBracket]", "\[FormalK]", + "\[RightDoubleBracket]"}], "-", "\[FormalL]"}]], + RowBox[{"ServiceMoment", "[", + RowBox[{ + RowBox[{ + "\[Beta]", "\[LeftDoubleBracket]", "\[FormalK]", + "\[RightDoubleBracket]"}], "-", "\[FormalL]"}], "]"}], + SuperscriptBox[ + RowBox[{ + "inprobs", "\[LeftDoubleBracket]", "\[FormalK]", + "\[RightDoubleBracket]"}], "\[FormalL]"], + RowBox[{"ArrivalMoment", "[", "\[FormalL]", "]"}]}], ")"}]}], + ")"}]}]}]}], ";"}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{"(*", + RowBox[{ + RowBox[{ + RowBox[{"m", "[", "\[Beta]_List", "]"}], ":=", + RowBox[{ + RowBox[{"m", "[", "\[Beta]", "]"}], "=", + RowBox[{ + UnderoverscriptBox["\[Product]", + RowBox[{"\[FormalK]", "=", "1"}], "K"], + RowBox[{"(", + RowBox[{ + UnderoverscriptBox["\[Sum]", + RowBox[{"\[FormalL]", "=", "1"}], "K"], + RowBox[{"(", + RowBox[{ + RowBox[{"Binomial", "[", + RowBox[{ + RowBox[{ + "\[Beta]", "\[LeftDoubleBracket]", "\[FormalK]", + "\[RightDoubleBracket]"}], ",", "\[FormalL]"}], "]"}], + SuperscriptBox[ + RowBox[{"(", + RowBox[{ + RowBox[{ + "outprobs", "\[LeftDoubleBracket]", "\[FormalK]", + "\[RightDoubleBracket]"}], " ", + RowBox[{"ServiceMoment", "[", "]"}]}], ")"}], + RowBox[{ + RowBox[{ + "\[Beta]", "\[LeftDoubleBracket]", "\[FormalK]", + "\[RightDoubleBracket]"}], "-", "\[FormalL]"}]], + SuperscriptBox[ + RowBox[{"(", + RowBox[{ + RowBox[{"-", + RowBox[{ + "inprobs", "\[LeftDoubleBracket]", "\[FormalK]", + "\[RightDoubleBracket]"}]}], " ", + RowBox[{"ArrivalMoment", "[", "]"}]}], ")"}], "\[FormalL]"]}], + ")"}]}], ")"}]}]}]}], ";"}], "*)"}], + RowBox[{ + RowBox[{ + RowBox[{"m", "::", "usage"}], "=", + "\"\\"Italic\"]],ExpressionUUID->\"\ +6956a59a-9e16-4220-a37f-8b369610efa0\"]\); the generally true form from the \ +arrival and service moments.\>\""}], ";", + RowBox[{ + RowBox[{"m", "::", "usage", "::", "ChineseSimplified"}], "=", + "\"\<\!\(\*Cell[TextData[StyleBox[\"X\",FontSlant->\"Italic\"]],\ +ExpressionUUID->\"3826e130-d0a4-4639-b889-fffb8e7570c6\"]\) \ +\:7684\:5404\:9636\:77e9; \:4ece\:5230\:8fbe\:8fc7\:7a0b\:548c\:670d\:52a1\ +\:8fc7\:7a0b\:7684\:5404\:9636\:77e9\:5f97\:5230\:7684\:666e\:904d\:6210\:7acb\ +\:7684\:5f62\:5f0f.\>\""}], ";"}]}]}], "Input", + CellGroupingRules->{"GroupTogetherGrouping", 10000.}, + InitializationCell->True], + +Cell[BoxData[{ + RowBox[{"Clear", "[", "m", "]"}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{"m", "[", "\[Beta]_List", "]"}], ":=", + RowBox[{ + RowBox[{"m", "[", "\[Beta]", "]"}], "=", + RowBox[{"Times", "@@", + RowBox[{"MapThread", "[", + RowBox[{ + RowBox[{ + RowBox[{"Expectation", "[", + RowBox[{ + SuperscriptBox[ + RowBox[{"(", + RowBox[{ + RowBox[{"#3", "\[FormalS]"}], "-", + RowBox[{"#2", "\[FormalA]"}]}], ")"}], "#1"], ",", + RowBox[{"{", + RowBox[{ + RowBox[{"\[FormalS]", "\[Distributed]", + RowBox[{"NormalDistribution", "[", + RowBox[{ + RowBox[{"1", "/", "4"}], ",", + SqrtBox[ + RowBox[{"1", "/", "8"}]]}], "]"}]}], ",", + RowBox[{"\[FormalA]", "\[Distributed]", + RowBox[{"NormalDistribution", "[", + RowBox[{ + RowBox[{"1", "/", "2"}], ",", + SqrtBox[ + RowBox[{"1", "/", "8"}]]}], "]"}]}]}], "}"}]}], "]"}], "&"}], + ",", + RowBox[{"{", + RowBox[{"\[Beta]", ",", "inprobs", ",", "outprobs"}], "}"}]}], + "]"}]}]}]}], ";", + RowBox[{ + RowBox[{"m", "::", "usage"}], "=", + "\"\\"Italic\"]],ExpressionUUID->\"\ +8be5f428-cee1-4abe-9522-fda28d2572d8\"]\); the one used in \!\(\*TemplateBox[{ +RowBox[{\"Bertsimas\", \" \", \"and\", \" \", \"Natarajan\", \" \", \ +\"2007\"}], { +URL[\"https://doi.org/10.1007/s11134-007-9028-7\"], None}, \ +\"https://doi.org/10.1007/s11134-007-9028-7\", \"HyperlinkActionNew\", \ +{\"HyperlinkActive\"}, BaseStyle -> {\"Hyperlink\"}, HyperlinkAction -> \"New\ +\"},\"HyperlinkTemplate\"]\).\>\""}], ";", + RowBox[{ + RowBox[{"m", "::", "usage", "::", "ChineseSimplified"}], "=", + "\"\<\!\(\*Cell[TextData[StyleBox[\"X\",FontSlant->\"Italic\"]],\ +ExpressionUUID->\"60e06b5b-d98e-4dd8-a16b-9b8496da7c49\"]\) \ +\:7684\:5404\:9636\:77e9; \!\(\*TemplateBox[{ +RowBox[{\"Bertsimas\", \" \", \"\:548c\", \" \", \"Natarajan\", \" \", \"2007\ +\"}], { +URL[\"https://doi.org/10.1007/s11134-007-9028-7\"], None}, \ +\"https://doi.org/10.1007/s11134-007-9028-7\", \"HyperlinkActionNew\", \ +{\"HyperlinkActive\"}, BaseStyle -> {\"Hyperlink\"}, HyperlinkAction -> \"New\ +\"},\"HyperlinkTemplate\"]\) \:4e2d\:4f7f\:7528\:7684\:5f62\:5f0f.\>\""}], + ";"}]}], "Input", + CellGroupingRules->{"GroupTogetherGrouping", 10000.}, + InitializationCell->True], + +Cell[BoxData[{ + RowBox[{"Clear", "[", "m", "]"}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{"m", "[", + RowBox[{"{", + RowBox[{"0", ".."}], "}"}], "]"}], ":=", "1"}], + ";"}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{"m", "[", + RowBox[{"{", "\[Beta]_Integer", "}"}], "]"}], ":=", + RowBox[{ + RowBox[{"m", "[", "\[Beta]", "]"}], "=", + SuperscriptBox["\[FormalM]", + RowBox[{"Style", "[", + RowBox[{"\[Beta]", ",", "Smaller"}], "]"}]]}]}], + ";"}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{"If", "[", + RowBox[{ + RowBox[{"K", ">", "1"}], ",", + RowBox[{ + RowBox[{"m", "[", "\[Beta]_List", "]"}], ":=", + RowBox[{ + RowBox[{"m", "[", "\[Beta]", "]"}], "=", + SuperscriptBox["\[FormalM]", + RowBox[{"Style", "[", + RowBox[{ + RowBox[{"TableForm", "[", + RowBox[{"\[Beta]", ",", + RowBox[{"TableSpacing", "\[Rule]", + RowBox[{"{", + RowBox[{"0", ",", "0"}], "}"}]}], ",", + RowBox[{"TableDirections", "\[Rule]", "Row"}]}], "]"}], ",", + "Smaller"}], "]"}]]}]}]}], "]"}], ";", + RowBox[{ + RowBox[{"m", "::", "usage"}], "=", + "\"\\"Italic\"]],ExpressionUUID->\"\ +ceabc312-249c-4a64-9716-39cfc44427ee\"]\); remained abstract.\>\""}], ";", + RowBox[{ + RowBox[{"m", "::", "usage", "::", "ChineseSimplified"}], "=", + "\"\<\!\(\*Cell[TextData[StyleBox[\"X\",FontSlant->\"Italic\"]],\ +ExpressionUUID->\"9e9e31a3-41cf-42ee-a3a2-2955105981bc\"]\) \ +\:7684\:5404\:9636\:77e9; \:4fdd\:7559\:62bd\:8c61\:5f62\:5f0f.\>\""}], + ";"}]}], "Input", + CellGroupingRules->{"GroupTogetherGrouping", 10000.}, + InitializationCell->True] +}]], + +Cell[BoxData[ + RowBox[{ + RowBox[{"m", "/:", + RowBox[{"Power", "[", + RowBox[{"m", ",", "\[Beta]_List"}], "]"}], ":=", + RowBox[{"m", "[", "\[Beta]", "]"}]}], ";"}]], "Input", + InitializationCell->True] +}]] +}]], + +Cell[CellGroupData[{ + +Cell["Constraints LHS", "Subsection"], + +Cell[BoxData[{ + RowBox[{ + RowBox[{ + RowBox[{"ConstraintMatView", "[", + RowBox[{"array_List", "|", "array_SparseArray"}], "]"}], ":=", + RowBox[{ + RowBox[{ + RowBox[{ + RowBox[{"If", "[", + RowBox[{ + RowBox[{ + RowBox[{"ArrayDepth", "@", "#"}], ">", "1"}], ",", + RowBox[{ + RowBox[{"Map", "[", + RowBox[{"Column", ",", "#", ",", + RowBox[{"{", + RowBox[{ + RowBox[{"ArrayDepth", "@", "#"}], "-", "1"}], "}"}]}], "]"}], + "&"}], ",", "Identity"}], "]"}], "@", + RowBox[{"Map", "[", + RowBox[{"Row", ",", "#", ",", + RowBox[{"{", + RowBox[{ + RowBox[{"ArrayDepth", "@", "#"}], "-", "1"}], "}"}]}], "]"}]}], + "&"}], "@", + RowBox[{"(", + RowBox[{ + RowBox[{ + RowBox[{"Map", "[", + RowBox[{"MatrixForm", ",", "#", ",", + RowBox[{"{", + RowBox[{ + RowBox[{"ArrayDepth", "@", "#"}], "-", "2"}], "}"}]}], "]"}], + "&"}], "@", + RowBox[{"Normal", "[", "array", "]"}]}], ")"}]}]}], ";", + RowBox[{ + RowBox[{"ConstraintMatView", "::", "usage"}], "=", + "\"\\""}], ";"}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{"ConstraintEqnView", "[", + RowBox[{"array_List", "|", "array_SparseArray"}], "]"}], ":=", + RowBox[{ + RowBox[{"If", "[", + RowBox[{ + RowBox[{ + RowBox[{"ArrayDepth", "@", "array"}], ">", "3"}], ",", + RowBox[{ + RowBox[{"Column", "[", + RowBox[{"Map", "[", + RowBox[{ + RowBox[{ + RowBox[{"(", + RowBox[{ + RowBox[{"Total", "[", + RowBox[{ + RowBox[{"Times", "[", + RowBox[{"#", ",", + RowBox[{"matX", "[", "All", "]"}]}], "]"}], ",", + RowBox[{"{", + RowBox[{"1", ",", "3"}], "}"}]}], "]"}], "\[Equal]", "0"}], + ")"}], "&"}], ",", "#", ",", + RowBox[{"{", + RowBox[{ + RowBox[{"ArrayDepth", "@", "array"}], "-", "3"}], "}"}]}], "]"}], + "]"}], "&"}], ",", + RowBox[{ + RowBox[{"(", + RowBox[{ + RowBox[{"Total", "[", + RowBox[{ + RowBox[{"Times", "[", + RowBox[{"#", ",", + RowBox[{"matX", "[", "All", "]"}]}], "]"}], ",", + RowBox[{"{", + RowBox[{"1", ",", "3"}], "}"}]}], "]"}], "\[Equal]", + RowBox[{"If", "[", + RowBox[{ + RowBox[{ + RowBox[{"ArrayDepth", "@", "array"}], ">", "3"}], ",", "0", ",", + "1"}], "]"}]}], ")"}], "&"}]}], "]"}], "@", + RowBox[{"Normal", "[", "array", "]"}]}]}], ";", + RowBox[{ + RowBox[{"ConstraintEqnView", "::", "usage"}], "=", + "\"\\""}], ";"}]}], "Input", + CellGroupingRules->{"GroupTogetherGrouping", 10000.}, + InitializationCell->True], + +Cell[CellGroupData[{ + +Cell["The constraint of independence; a list of 3-d arrays.", "ItemNumbered", + CellGroupingRules->{"GroupTogetherGrouping", 10002.}], + +Cell[BoxData[ + RowBox[{ + RowBox[{ + RowBox[{ + UnderoverscriptBox["\[Sum]", + RowBox[{ + StyleBox["s", + FontSlant->"Italic"], "=", "1"}], + SuperscriptBox["2", + StyleBox["K", + FontSlant->"Italic"]]], + SubsuperscriptBox[ + StyleBox["x", + FontSlant->"Italic"], + StyleBox["s", + FontSlant->"Italic"], + StyleBox[ + RowBox[{"\[Alpha]", "\[InvisibleComma]", "\[Beta]"}], + FontWeight->"Bold"]]}], "-", + RowBox[{ + SuperscriptBox[ + StyleBox["m", + FontSlant->"Italic"], + StyleBox["\[Beta]", + FontWeight->"Bold"]], + RowBox[{ + UnderoverscriptBox["\[Sum]", + RowBox[{ + StyleBox["s", + FontSlant->"Italic"], "=", "1"}], + SuperscriptBox["2", + StyleBox["K", + FontSlant->"Italic"]]], + SubsuperscriptBox[ + StyleBox["x", + FontSlant->"Italic"], + StyleBox["s", + FontSlant->"Italic"], + StyleBox[ + RowBox[{"\[Alpha]", "\[InvisibleComma]", "0"}], + FontWeight->"Bold"]]}]}]}], "\[Equal]", + "0"}]], "DisplayFormulaNumbered", + CellGroupingRules->{"GroupTogetherGrouping", 10002.}, + TextAlignment->-0.5], + +Cell[BoxData[ + RowBox[{ + RowBox[{"IndieA", "=", + RowBox[{ + RowBox[{ + RowBox[{"(", + RowBox[{ + RowBox[{"SparseArray", "/@", + RowBox[{"Map", "[", + RowBox[{ + RowBox[{"(", + RowBox[{"\[FormalY]", "\[Function]", + RowBox[{ + RowBox[{"SparseArray", "[", + RowBox[{ + RowBox[{"{", + RowBox[{ + RowBox[{"Prepend", "[", + RowBox[{ + RowBox[{"loc", "[", "\[FormalY]", "]"}], ",", "_"}], "]"}], + "\[RuleDelayed]", "1"}], "}"}], ",", + RowBox[{"Prepend", "[", + RowBox[{"matICdim", ",", + SuperscriptBox["2", "K"]}], "]"}]}], "]"}], "-", + RowBox[{"SparseArray", "[", + RowBox[{ + RowBox[{"{", + RowBox[{ + RowBox[{"Prepend", "[", + RowBox[{ + RowBox[{"loc", "[", + RowBox[{"\[FormalY]", "*", + RowBox[{"{", + RowBox[{"1", ",", "0"}], "}"}]}], "]"}], ",", "_"}], + "]"}], "\[RuleDelayed]", + RowBox[{"m", "[", + RowBox[{"\[FormalY]", "\[LeftDoubleBracket]", + RowBox[{"-", "1"}], "\[RightDoubleBracket]"}], "]"}]}], + "}"}], ",", + RowBox[{"Prepend", "[", + RowBox[{"matICdim", ",", + SuperscriptBox["2", "K"]}], "]"}]}], "]"}]}]}], ")"}], ",", + RowBox[{"DeleteDuplicates", "[", + RowBox[{"Flatten", "[", + RowBox[{"#", ",", "1"}], "]"}], "]"}]}], "]"}]}], "/.", + RowBox[{"(", + RowBox[{ + RowBox[{"SparseArray", "[", + RowBox[{ + RowBox[{"{", + RowBox[{"_", "\[RuleDelayed]", "0"}], "}"}], ",", + RowBox[{"Prepend", "[", + RowBox[{"matICdim", ",", + SuperscriptBox["2", "K"]}], "]"}]}], "]"}], "\[Rule]", + "Nothing"}], ")"}]}], ")"}], "&"}], "@", "matIC"}]}], ";"}]], "Input", + CellGroupingRules->{"GroupTogetherGrouping", 10002.}, + InitializationCell->True] +}]], + +Cell[CellGroupData[{ + +Cell["The constraint of combinatorics; a list of 3-d arrays.", "ItemNumbered", + CellGroupingRules->{"GroupTogetherGrouping", 10001.}], + +Cell[BoxData[ + RowBox[{ + RowBox[{ + RowBox[{ + UnderoverscriptBox["\[Sum]", + RowBox[{ + StyleBox["s", + FontSlant->"Italic"], "=", "1"}], + SuperscriptBox["2", + StyleBox["K", + FontSlant->"Italic"]]], + SubsuperscriptBox[ + StyleBox["x", + FontSlant->"Italic"], + StyleBox["s", + FontSlant->"Italic"], + StyleBox[ + RowBox[{"\[Alpha]", "\[InvisibleComma]", "0"}], + FontWeight->"Bold"]]}], "-", + RowBox[{ + UnderoverscriptBox["\[Sum]", + RowBox[{ + StyleBox["s", + FontSlant->"Italic"], "=", "1"}], + SuperscriptBox["2", + StyleBox["K", + FontSlant->"Italic"]]], + RowBox[{ + UnderscriptBox["\[Sum]", + RowBox[{ + RowBox[{"\[LeftBracketingBar]", + StyleBox["\[Gamma]", + FontWeight->"Bold"], "\[RightBracketingBar]"}], "\[LessEqual]", + RowBox[{"\[LeftBracketingBar]", + StyleBox["\[Alpha]", + FontWeight->"Bold"], "\[RightBracketingBar]"}]}]], + RowBox[{ + SubsuperscriptBox[ + StyleBox["g", + FontSlant->"Italic"], + RowBox[{ + StyleBox["k", + FontSlant->"Italic"], "\[InvisibleComma]", + StyleBox["\[Alpha]", + FontWeight->"Bold"]}], + StyleBox["\[Gamma]", + FontWeight->"Bold"]], + SubsuperscriptBox["x", "s", + StyleBox["\[Gamma]", + FontWeight->"Bold"]]}]}]}]}], "\[Equal]", + "0"}]], "DisplayFormulaNumbered", + CellGroupingRules->{"GroupTogetherGrouping", 10001.}, + TextAlignment->-0.5], + +Cell[BoxData[ + RowBox[{ + RowBox[{ + RowBox[{"CombieA", "=", + RowBox[{ + RowBox[{ + RowBox[{"-", + RowBox[{"(", + RowBox[{ + RowBox[{"SparseArray", "@", + RowBox[{"SparseArray", "[", + RowBox[{ + RowBox[{ + RowBox[{"Flatten", "[", + RowBox[{ + RowBox[{"Table", "[", + RowBox[{ + RowBox[{ + RowBox[{"CoefficientRules", "[", + RowBox[{ + RowBox[{"Times", "@@", + RowBox[{"(", + RowBox[{ + SuperscriptBox[ + RowBox[{"(", + RowBox[{"Table", "[", + RowBox[{ + RowBox[{ + RowBox[{"Indexed", "[", + RowBox[{"\[FormalW]", ",", "\[FormalK]"}], "]"}], "+", + RowBox[{"Indexed", "[", + RowBox[{"\[FormalX]", ",", "\[FormalK]"}], "]"}]}], ",", + RowBox[{"{", + RowBox[{"\[FormalK]", ",", "1", ",", "K"}], "}"}]}], + "]"}], ")"}], "#"], "/.", + RowBox[{"Thread", "[", + RowBox[{ + RowBox[{"Table", "[", + RowBox[{ + RowBox[{ + RowBox[{"Indexed", "[", + RowBox[{"\[FormalW]", ",", "\[FormalK]"}], "]"}], "+", + RowBox[{"Indexed", "[", + RowBox[{"\[FormalX]", ",", "\[FormalK]"}], "]"}]}], ",", + RowBox[{"{", + RowBox[{"\[FormalK]", ",", + RowBox[{"Position", "[", + RowBox[{ + RowBox[{"IntegerDigits", "[", + RowBox[{"\[FormalS]", ",", "2", ",", "K"}], "]"}], ",", + "0"}], "]"}]}], "}"}]}], "]"}], "\[Rule]", "0"}], "]"}]}], + ")"}]}], ",", + RowBox[{ + RowBox[{"Table", "[", + RowBox[{ + RowBox[{"Indexed", "[", + RowBox[{"\[FormalW]", ",", "\[FormalK]"}], "]"}], ",", + RowBox[{"{", + RowBox[{"\[FormalK]", ",", "1", ",", "K"}], "}"}]}], + "]"}], "~", "Join", "~", + RowBox[{"Table", "[", + RowBox[{ + RowBox[{"Indexed", "[", + RowBox[{"\[FormalX]", ",", "\[FormalK]"}], "]"}], ",", + RowBox[{"{", + RowBox[{"\[FormalK]", ",", "1", ",", "K"}], "}"}]}], + "]"}]}]}], "]"}], "/.", + RowBox[{"(", + RowBox[{ + RowBox[{"(", + RowBox[{"list_", "\[Rule]", "coef_"}], ")"}], + "\[RuleDelayed]", + RowBox[{"(", + RowBox[{ + RowBox[{"Prepend", "[", + RowBox[{ + RowBox[{"loc", "[", + RowBox[{"ArrayReshape", "[", + RowBox[{"list", ",", + RowBox[{"{", + RowBox[{"2", ",", "K"}], "}"}]}], "]"}], "]"}], ",", + RowBox[{"\[FormalS]", "+", "1"}]}], "]"}], "\[Rule]", + RowBox[{"If", "[", + RowBox[{ + RowBox[{ + RowBox[{"list", "\[LeftDoubleBracket]", + RowBox[{";;", "K"}], "\[RightDoubleBracket]"}], + "\[Equal]", "#"}], ",", + RowBox[{"coef", "-", "1"}], ",", "coef"}], "]"}]}], + ")"}]}], ")"}]}], ",", + RowBox[{"{", + RowBox[{"\[FormalS]", ",", "0", ",", + RowBox[{ + SuperscriptBox["2", "K"], "-", "1"}]}], "}"}]}], "]"}], + ",", "1"}], "]"}], "~", "Join", "~", + RowBox[{"{", + RowBox[{ + RowBox[{"Prepend", "[", + RowBox[{ + RowBox[{"loc", "[", + RowBox[{"{", + RowBox[{"#", ",", + RowBox[{"Table", "[", + RowBox[{"0", ",", "K"}], "]"}]}], "}"}], "]"}], ",", + "_"}], "]"}], "\[Rule]", + RowBox[{"-", "1"}]}], "}"}]}], ",", + RowBox[{"Prepend", "[", + RowBox[{"matICdim", ",", + SuperscriptBox["2", "K"]}], "]"}]}], "]"}]}], "/.", + RowBox[{"(", + RowBox[{ + RowBox[{"SparseArray", "[", + RowBox[{ + RowBox[{"{", + RowBox[{"_", "\[RuleDelayed]", "0"}], "}"}], ",", + RowBox[{"Prepend", "[", + RowBox[{"matICdim", ",", + SuperscriptBox["2", "K"]}], "]"}]}], "]"}], "\[Rule]", + "Nothing"}], ")"}]}], ")"}]}], "&"}], "/@", + RowBox[{"Rest", "[", "\[Alpha]IC", "]"}]}]}], ";"}], " "}]], "Input", + CellGroupingRules->{"GroupTogetherGrouping", 10001.}, + InitializationCell->True] +}]], + +Cell[CellGroupData[{ + +Cell["The constraint of unitisation; a list of 3-d arrays.", "ItemNumbered", + CellGroupingRules->{"GroupTogetherGrouping", 10002.}], + +Cell[BoxData[ + RowBox[{ + RowBox[{ + UnderoverscriptBox["\[Sum]", + RowBox[{ + StyleBox["s", + FontSlant->"Italic"], "=", "1"}], + SuperscriptBox["2", + StyleBox["K", + FontSlant->"Italic"]]], + SubsuperscriptBox[ + StyleBox["x", + FontSlant->"Italic"], + StyleBox["s", + FontSlant->"Italic"], + StyleBox[ + RowBox[{"0", "\[InvisibleComma]", "0"}], + FontWeight->"Bold"]]}], "\[Equal]", "1"}]], "DisplayFormulaNumbered", + CellGroupingRules->{"GroupTogetherGrouping", 10002.}, + TextAlignment->-0.5], + +Cell[BoxData[ + RowBox[{ + RowBox[{"UnieA", "=", + RowBox[{"SparseArray", "@", + RowBox[{"SparseArray", "[", + RowBox[{ + RowBox[{ + RowBox[{"Prepend", "[", + RowBox[{ + RowBox[{"loc", "[", + RowBox[{"ConstantArray", "[", + RowBox[{"0", ",", + RowBox[{"{", + RowBox[{"2", ",", "K"}], "}"}]}], "]"}], "]"}], ",", "_"}], + "]"}], "\[Rule]", "1"}], ",", + RowBox[{"Prepend", "[", + RowBox[{"matICdim", ",", + SuperscriptBox["2", "K"]}], "]"}]}], "]"}]}]}], ";"}]], "Input", + CellGroupingRules->{"GroupTogetherGrouping", 10002.}, + InitializationCell->True], + +Cell[TextData[{ + "Additional constraint due to coincident entries; ", + StyleBox["only one", + FontWeight->"Bold"], + " 3-d array." +}], "ItemNumbered", + CellGroupingRules->{"GroupTogetherGrouping", 10002.}], + +Cell[BoxData[ + RowBox[{ + RowBox[{"CoinA", "=", + RowBox[{ + RowBox[{ + RowBox[{ + RowBox[{"If", "[", + RowBox[{ + RowBox[{"#", "\[NotEqual]", + RowBox[{"{", "}"}]}], ",", "SparseArray", ",", "Identity"}], "]"}], + "@", + RowBox[{"Flatten", "[", + RowBox[{"#", ",", "1"}], "]"}]}], "&"}], "@", + RowBox[{"(", + RowBox[{ + RowBox[{"(", + RowBox[{"mat", "\[Function]", " ", + RowBox[{"If", "[", + RowBox[{ + RowBox[{ + RowBox[{"Length", "[", "mat", "]"}], ">", "2"}], ",", + RowBox[{ + RowBox[{ + RowBox[{"SparseArray", "[", + RowBox[{"#", ",", "matICdim"}], "]"}], "&"}], "/@", + RowBox[{"(", + RowBox[{ + RowBox[{ + RowBox[{"{", + RowBox[{ + RowBox[{ + RowBox[{ + "mat", "\[LeftDoubleBracket]", "1", + "\[RightDoubleBracket]"}], "\[Rule]", "1"}], ",", + RowBox[{"#", "\[Rule]", + RowBox[{"-", "1"}]}]}], "}"}], "&"}], "/@", + RowBox[{"mat", "\[LeftDoubleBracket]", + RowBox[{"2", ";;", + RowBox[{"Ceiling", "[", + RowBox[{ + RowBox[{"Length", "[", "mat", "]"}], "/", "2"}], "]"}]}], + "\[RightDoubleBracket]"}]}], ")"}]}], ",", "Nothing"}], "]"}]}], + ")"}], "/@", + RowBox[{"(", + RowBox[{ + RowBox[{ + RowBox[{"Position", "[", + RowBox[{"matIC", ",", "#", ",", "2"}], "]"}], "&"}], "/@", + RowBox[{"DeleteDuplicates", "[", + RowBox[{"Flatten", "[", + RowBox[{"matIC", ",", "1"}], "]"}], "]"}]}], ")"}]}], ")"}]}]}], + ";"}]], "Input", + CellGroupingRules->{"GroupTogetherGrouping", 10002.}, + InitializationCell->True] +}]], + +Cell[CellGroupData[{ + +Cell["Verification", "Subsubsection"], + +Cell[CellGroupData[{ + +Cell[BoxData[{"edgIC", "\[IndentingNewLine]", "\[Alpha]IC"}], "Input"] +}]], + +Cell[CellGroupData[{ + +Cell[BoxData[{ + RowBox[{ + RowBox[{"temp", "=", + RowBox[{"{", "2", "}"}]}], ";"}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{"Table", "[", + RowBox[{ + RowBox[{"Indexed", "[", + RowBox[{"\[FormalW]", ",", "k"}], "]"}], ",", + RowBox[{"{", + RowBox[{"k", ",", "1", ",", "K"}], "}"}]}], "]"}], "~", "Join", "~", + RowBox[{"Table", "[", + RowBox[{ + RowBox[{"Indexed", "[", + RowBox[{"\[FormalX]", ",", "k"}], "]"}], ",", + RowBox[{"{", + RowBox[{"k", ",", "1", ",", "K"}], "}"}]}], + "]"}]}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{"Times", "@@", + SuperscriptBox[ + RowBox[{"(", + RowBox[{"Table", "[", + RowBox[{ + RowBox[{ + RowBox[{"Indexed", "[", + RowBox[{"\[FormalW]", ",", "k"}], "]"}], "+", + RowBox[{"Indexed", "[", + RowBox[{"\[FormalX]", ",", "k"}], "]"}]}], ",", + RowBox[{"{", + RowBox[{"k", ",", "1", ",", "K"}], "}"}]}], "]"}], ")"}], "#"]}], + "&"}], "@", "temp"}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{"Table", "[", + RowBox[{ + RowBox[{"Thread", "[", + RowBox[{ + RowBox[{"Table", "[", + RowBox[{ + RowBox[{ + RowBox[{"Indexed", "[", + RowBox[{"\[FormalW]", ",", "k"}], "]"}], "+", + RowBox[{"Indexed", "[", + RowBox[{"\[FormalX]", ",", "k"}], "]"}]}], ",", + RowBox[{"{", + RowBox[{"k", ",", + RowBox[{"Position", "[", + RowBox[{ + RowBox[{"IntegerDigits", "[", + RowBox[{"s", ",", "2", ",", "K"}], "]"}], ",", "0"}], "]"}]}], + "}"}]}], "]"}], "\[Rule]", "0"}], "]"}], ",", + RowBox[{"{", + RowBox[{"s", ",", "0", ",", + RowBox[{ + SuperscriptBox["2", "K"], "-", "1"}]}], "}"}]}], "]"}], "&"}], "@", + "temp"}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{"Table", "[", + RowBox[{ + RowBox[{"Times", "@@", + RowBox[{"(", + RowBox[{ + SuperscriptBox[ + RowBox[{"(", + RowBox[{"Table", "[", + RowBox[{ + RowBox[{ + RowBox[{"Indexed", "[", + RowBox[{"\[FormalW]", ",", "k"}], "]"}], "+", + RowBox[{"Indexed", "[", + RowBox[{"\[FormalX]", ",", "k"}], "]"}]}], ",", + RowBox[{"{", + RowBox[{"k", ",", "1", ",", "K"}], "}"}]}], "]"}], ")"}], "#"], "/.", + RowBox[{"Thread", "[", + RowBox[{ + RowBox[{"Table", "[", + RowBox[{ + RowBox[{ + RowBox[{"Indexed", "[", + RowBox[{"\[FormalW]", ",", "k"}], "]"}], "+", + RowBox[{"Indexed", "[", + RowBox[{"\[FormalX]", ",", "k"}], "]"}]}], ",", + RowBox[{"{", + RowBox[{"k", ",", + RowBox[{"Position", "[", + RowBox[{ + RowBox[{"IntegerDigits", "[", + RowBox[{"s", ",", "2", ",", "K"}], "]"}], ",", "0"}], + "]"}]}], "}"}]}], "]"}], "\[Rule]", "0"}], "]"}]}], ")"}]}], + ",", + RowBox[{"{", + RowBox[{"s", ",", "0", ",", + RowBox[{ + SuperscriptBox["2", "K"], "-", "1"}]}], "}"}]}], "]"}], "&"}], "@", + "temp"}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{"Table", "[", + RowBox[{ + RowBox[{"CoefficientRules", "[", + RowBox[{ + RowBox[{"Times", "@@", + RowBox[{"(", + RowBox[{ + SuperscriptBox[ + RowBox[{"(", + RowBox[{"Table", "[", + RowBox[{ + RowBox[{ + RowBox[{"Indexed", "[", + RowBox[{"\[FormalW]", ",", "k"}], "]"}], "+", + RowBox[{"Indexed", "[", + RowBox[{"\[FormalX]", ",", "k"}], "]"}]}], ",", + RowBox[{"{", + RowBox[{"k", ",", "1", ",", "K"}], "}"}]}], "]"}], ")"}], "#"], + "/.", + RowBox[{"Thread", "[", + RowBox[{ + RowBox[{"Table", "[", + RowBox[{ + RowBox[{ + RowBox[{"Indexed", "[", + RowBox[{"\[FormalW]", ",", "k"}], "]"}], "+", + RowBox[{"Indexed", "[", + RowBox[{"\[FormalX]", ",", "k"}], "]"}]}], ",", + RowBox[{"{", + RowBox[{"k", ",", + RowBox[{"Position", "[", + RowBox[{ + RowBox[{"IntegerDigits", "[", + RowBox[{"s", ",", "2", ",", "K"}], "]"}], ",", "0"}], + "]"}]}], "}"}]}], "]"}], "\[Rule]", "0"}], "]"}]}], ")"}]}], + ",", + RowBox[{ + RowBox[{"Table", "[", + RowBox[{ + RowBox[{"Indexed", "[", + RowBox[{"\[FormalW]", ",", "k"}], "]"}], ",", + RowBox[{"{", + RowBox[{"k", ",", "1", ",", "K"}], "}"}]}], "]"}], "~", "Join", + "~", + RowBox[{"Table", "[", + RowBox[{ + RowBox[{"Indexed", "[", + RowBox[{"\[FormalX]", ",", "k"}], "]"}], ",", + RowBox[{"{", + RowBox[{"k", ",", "1", ",", "K"}], "}"}]}], "]"}]}]}], "]"}], ",", + RowBox[{"{", + RowBox[{"s", ",", "0", ",", + RowBox[{ + SuperscriptBox["2", "K"], "-", "1"}]}], "}"}]}], "]"}], "&"}], "@", + "temp"}], "\[IndentingNewLine]", + RowBox[{ + RowBox[{ + RowBox[{"(", + RowBox[{ + RowBox[{"Table", "[", + RowBox[{ + RowBox[{ + RowBox[{"CoefficientRules", "[", + RowBox[{ + RowBox[{"Times", "@@", + RowBox[{"(", + RowBox[{ + SuperscriptBox[ + RowBox[{"(", + RowBox[{"Table", "[", + RowBox[{ + RowBox[{ + RowBox[{"Indexed", "[", + RowBox[{"\[FormalW]", ",", "k"}], "]"}], "+", + RowBox[{"Indexed", "[", + RowBox[{"\[FormalX]", ",", "k"}], "]"}]}], ",", + RowBox[{"{", + RowBox[{"k", ",", "1", ",", "K"}], "}"}]}], "]"}], ")"}], + "#"], "/.", + RowBox[{"Thread", "[", + RowBox[{ + RowBox[{"Table", "[", + RowBox[{ + RowBox[{ + RowBox[{"Indexed", "[", + RowBox[{"\[FormalW]", ",", "k"}], "]"}], "+", + RowBox[{"Indexed", "[", + RowBox[{"\[FormalX]", ",", "k"}], "]"}]}], ",", + RowBox[{"{", + RowBox[{"k", ",", + RowBox[{"Position", "[", + RowBox[{ + RowBox[{"IntegerDigits", "[", + RowBox[{"s", ",", "2", ",", "K"}], "]"}], ",", "0"}], + "]"}]}], "}"}]}], "]"}], "\[Rule]", "0"}], "]"}]}], + ")"}]}], ",", + RowBox[{ + RowBox[{"Table", "[", + RowBox[{ + RowBox[{"Indexed", "[", + RowBox[{"\[FormalW]", ",", "k"}], "]"}], ",", + RowBox[{"{", + RowBox[{"k", ",", "1", ",", "K"}], "}"}]}], "]"}], "~", "Join", + "~", + RowBox[{"Table", "[", + RowBox[{ + RowBox[{"Indexed", "[", + RowBox[{"\[FormalX]", ",", "k"}], "]"}], ",", + RowBox[{"{", + RowBox[{"k", ",", "1", ",", "K"}], "}"}]}], "]"}]}]}], "]"}], "/.", + RowBox[{"(", + RowBox[{ + RowBox[{"(", + RowBox[{"list_", "\[Rule]", "coef_"}], ")"}], "\[RuleDelayed]", + RowBox[{"(", + RowBox[{ + RowBox[{"Prepend", "[", + RowBox[{ + RowBox[{"loc", "[", + RowBox[{"ArrayReshape", "[", + RowBox[{"list", ",", + RowBox[{"{", + RowBox[{"2", ",", "K"}], "}"}]}], "]"}], "]"}], ",", + RowBox[{"s", "+", "1"}]}], "]"}], "\[RuleDelayed]", + RowBox[{"If", "[", + RowBox[{ + RowBox[{ + RowBox[{"list", "\[LeftDoubleBracket]", + RowBox[{";;", "K"}], "\[RightDoubleBracket]"}], "\[Equal]", + "#"}], ",", + RowBox[{"coef", "-", "1"}], ",", "coef"}], "]"}]}], ")"}]}], + ")"}]}], ",", + RowBox[{"{", + RowBox[{"s", ",", "0", ",", + RowBox[{ + SuperscriptBox["2", "K"], "-", "1"}]}], "}"}]}], "]"}], "~", "Join", + "~", + RowBox[{"{", + RowBox[{ + RowBox[{"Prepend", "[", + RowBox[{ + RowBox[{"loc", "[", + RowBox[{"{", + RowBox[{"#", ",", + RowBox[{"Table", "[", + RowBox[{"0", ",", "K"}], "]"}]}], "}"}], "]"}], ",", "_"}], + "]"}], "\[Rule]", + RowBox[{"-", "1"}]}], "}"}]}], ")"}], "&"}], "@", + "temp"}], "\[IndentingNewLine]", + RowBox[{"Clear", "[", "temp", "]"}], "\[IndentingNewLine]"}], "Input"] +}]] +}]] +}]] +}]], + +Cell[CellGroupData[{ + +Cell["Results", "Section"], + +Cell[CellGroupData[{ + +Cell[BoxData[ + RowBox[{ + RowBox[{ + RowBox[{ + RowBox[{"SetOptions", "[", + RowBox[{"#", ",", " ", + RowBox[{"PageWidth", " ", "->", " ", "Infinity"}]}], "]"}], "&"}], "/@", + RowBox[{"{", + RowBox[{ + RowBox[{"CellObject", "[", "22833", "]"}], ",", " ", + RowBox[{"CellObject", "[", "90689", "]"}], ",", " ", + RowBox[{"CellObject", "[", "90705", "]"}], ",", " ", + RowBox[{"CellObject", "[", "91313", "]"}], ",", " ", + RowBox[{"CellObject", "[", "91121", "]"}]}], "\n", "}"}]}], + ";"}]], "Code", + CellGroupingRules->{"GroupTogetherGrouping", 10000.}], + +Cell[BoxData[{ + RowBox[{ + RowBox[{"matX", "[", "]"}], "//", "MatrixForm"}], "\[IndentingNewLine]", + RowBox[{"CombieA", "//", "ConstraintEqnView"}], "\[IndentingNewLine]", + RowBox[{"IndieA", "//", "ConstraintEqnView"}], "\[IndentingNewLine]", + RowBox[{"UnieA", "//", "ConstraintEqnView"}]}], "Input", + PageWidth:>DirectedInfinity[1], + ShowCellBracket->Automatic, + CellGroupingRules->{"GroupTogetherGrouping", 10000.}], + +Cell[BoxData[ + RowBox[{ + RowBox[{ + RowBox[{ + RowBox[{"SetOptions", "[", + RowBox[{"#", ",", " ", + RowBox[{"PageWidth", " ", "->", " ", "Infinity"}]}], "]"}], "&"}], "/@", + RowBox[{"{", + RowBox[{ + RowBox[{"CellObject", "[", "93505", "]"}], ",", " ", + RowBox[{"CellObject", "[", "94673", "]"}], ",", " ", + RowBox[{"CellObject", "[", "94145", "]"}], ",", " ", + RowBox[{"CellObject", "[", "94545", "]"}]}], "\n", "}"}]}], + ";"}]], "Code", + CellGroupingRules->{"GroupTogetherGrouping", 10000.}], + +Cell[BoxData[{ + RowBox[{"CombieA", "//", "ConstraintMatView"}], "\[IndentingNewLine]", + RowBox[{"IndieA", "//", "ConstraintMatView"}], "\[IndentingNewLine]", + RowBox[{"UnieA", "//", "ConstraintMatView"}]}], "Input", + PageWidth:>DirectedInfinity[1], + ShowCellBracket->Automatic, + CellGroupingRules->{"GroupTogetherGrouping", 10000.}, + InitializationCell->False] +}]] +}]] +}]] +}] +(* End of Notebook Content *) diff --git a/queue-sdp.wl b/queue-sdp.wl new file mode 120000 index 0000000..6520e6c --- /dev/null +++ b/queue-sdp.wl @@ -0,0 +1 @@ +QueueSDP.wl \ No newline at end of file