(*^ ::[ Information = "This is a Mathematica Notebook file. It contains ASCII text, and can be transferred by email, ftp, or other text-file transfer utility. It should be read or edited using a copy of Mathematica or MathReader. If you received this as email, use your mail application or copy/paste to save everything from the line containing (*^ down to the line containing ^*) into a plain text file. On some systems you may have to give the file a name ending with ".ma" to allow Mathematica to recognize it as a Notebook. The line below identifies what version of Mathematica created this file, but it can be opened using any other version as well."; FrontEndVersion = "X Window System Mathematica Notebook Front End Version 2.2"; X11StandardFontEncoding; fontset = title, inactive, noPageBreakBelow, noPageBreakInGroup, nohscroll, preserveAspect, groupLikeTitle, center, M7, bold, e8, 24, fontName, "times"; fontset = subtitle, inactive, noPageBreakBelow, noPageBreakInGroup, nohscroll, preserveAspect, groupLikeTitle, center, M7, bold, e6, 18, fontName, "times"; fontset = subsubtitle, inactive, noPageBreakBelow, noPageBreakInGroup, nohscroll, preserveAspect, groupLikeTitle, center, M7, italic, e6, 14, fontName, "times"; fontset = section, inactive, noPageBreakBelow, nohscroll, preserveAspect, groupLikeSection, grayBox, M22, bold, a20, 18, fontName, "times"; fontset = subsection, inactive, noPageBreakBelow, nohscroll, preserveAspect, groupLikeSection, blackBox, M19, bold, a15, 14, fontName, "times"; fontset = subsubsection, inactive, noPageBreakBelow, nohscroll, preserveAspect, groupLikeSection, whiteBox, M18, bold, a12, 12, fontName, "times"; fontset = text, inactive, nohscroll, noKeepOnOnePage, preserveAspect, M7, 12, fontName, "times"; fontset = smalltext, inactive, nohscroll, noKeepOnOnePage, preserveAspect, M7, 10, fontName, "times"; fontset = input, noPageBreakInGroup, nowordwrap, preserveAspect, groupLikeInput, M42, N23, bold, 12, fontName, "courier"; fontset = output, output, inactive, noPageBreakInGroup, nowordwrap, preserveAspect, groupLikeOutput, M42, N23, L-5, 12, fontName, "courier"; fontset = message, inactive, noPageBreakInGroup, nowordwrap, preserveAspect, groupLikeOutput, M42, N23, 12, fontName, "courier"; fontset = print, inactive, noPageBreakInGroup, nowordwrap, preserveAspect, groupLikeOutput, M42, N23, 12, fontName, "courier"; fontset = info, inactive, noPageBreakInGroup, nowordwrap, preserveAspect, groupLikeOutput, M42, N23, 12, fontName, "courier"; fontset = postscript, PostScript, formatAsPostScript, output, inactive, noPageBreakInGroup, nowordwrap, preserveAspect, groupLikeGraphics, M7, l34, w282, h287, 12, fontName, "courier"; fontset = name, inactive, noPageBreakInGroup, nohscroll, preserveAspect, M7, italic, B65535, 10, fontName, "times"; fontset = header, inactive, nohscroll, noKeepOnOnePage, preserveAspect, M7, italic, 12, fontName, "times"; fontset = leftheader, 12, fontName, "times"; fontset = footer, inactive, nohscroll, noKeepOnOnePage, preserveAspect, center, M7, italic, 12, fontName, "times"; fontset = leftfooter, 12, fontName, "times"; fontset = help, inactive, nohscroll, noKeepOnOnePage, preserveAspect, M7, 12, fontName, "times"; fontset = clipboard, inactive, nohscroll, noKeepOnOnePage, preserveAspect, M7, 12, fontName, "times"; fontset = completions, inactive, nohscroll, noKeepOnOnePage, preserveAspect, M7, 12, fontName, "courier"; fontset = special1, inactive, nohscroll, noKeepOnOnePage, preserveAspect, M7, 12, fontName, "times"; fontset = special2, inactive, nohscroll, noKeepOnOnePage, preserveAspect, M7, 12, fontName, "times"; fontset = special3, inactive, nohscroll, noKeepOnOnePage, preserveAspect, M7, 12, fontName, "times"; fontset = special4, inactive, nohscroll, noKeepOnOnePage, preserveAspect, M7, 12, fontName, "times"; fontset = special5, inactive, nohscroll, noKeepOnOnePage, preserveAspect, M7, 12, fontName, "times";currentKernel; ] :[font = title; inactive; preserveAspect; fontSize = 12] A Carcinogenesis Model at the Nucleotide Level :[font = subsubtitle; inactive; preserveAspect; fontSize = 12] Qi Zheng National Center for Toxicological Research U.S. Food and Drug Administration :[font = section; inactive; preserveAspect; fontSize = 12] Introduction :[font = text; inactive; preserveAspect] Rapid and accelerating advances in biomedical cancer research have led a dramatic increase in the amount of attention given to mathematical modeling of carcinogenesis. The advent of comprehensive symbolic computation systems like Mathematica has facilitated research in the area. A cancer model that describes mutational events at the nucleotide level has been proposed recently by Q. Zheng, D. Gaylor and W. Lutz (American Statistical Association 1995 Proceedings of the Biometrics Section, pp. 349-354). The computational aspects of this model (both symbolic and numerical) which were appreciably more complex than those of the traditional two-stage model were investigated using Mathematica and reported by this author at the Tenth International Conference on Mathematical and Computer Modelling and Scientific Computing in Boston on July 6, 1995 (see "Combining Symbolic and Numerical computing in Carcinogenesis Modeling" in the Proceedings of the Tenth International Conference) . The present notebook is based on the results presented at the Conference and focuses on computational aspects. For biological and modeling aspects, the interested reader should consult the two aforementioned references. :[font = input; preserveAspect] SetOptions["stdout",PageWidth->70]; :[font = section; inactive; preserveAspect; fontSize = 12] Cumulants and the Cumulant Generating Function :[font = subsection; inactive; preserveAspect; fontSize = 12] How to Derive Differential Equations :[font = text; inactive; preserveAspect] The model is essentially a four-compartment stochastic process. The joint cumulants of the process provide valuable statistical information. To solve for these cumulants, first derive a system of ordinary differential equations (ODE) that the cumulants of up to a given order must satisfy. Such ODEs may be derived from a partial differential equation (PDE) that the cumulant generating function (cgf) satisfies. The K[ ] function defined below produces symbolically the cgf for the model truncated at a specified order ord. Each term k[i1,i2,i3,i4][t] represents a cumulant function of order i1+i2+i3+i4. :[font = input; preserveAspect] K[ord_]:=Select[ Sum[k[i1,i2,i3,i4][t] x1^i1 x2^i2 x3^i3 x4^i4 /(i1! i2! i3! i4!), {i1,0,ord},{i2,0,ord},{i3,0,ord},{i4,0,ord}]/.k[0,0,0,0][t]->0, ((Exponent[#,x1]+Exponent[#,x2]+Exponent[#,x3]+ Exponent[#,x4])<=ord)&]; :[font = text; inactive; preserveAspect] The right hand side of the aforementioned PDE should also be expanded to the same given order. :[font = input; preserveAspect] RHS[ord_]:=Select[ Expand[(b Sum[x1^i/i!,{i,1,ord}]+ a Sum[(-x1+x2)^i/i!,{i,1,ord}]+ d1 Sum[(-x1)^i/i!,{i,1,ord}]) D[K[ord],x1]+ (p1 Sum[(x1-x2)^i/i!,{i,1,ord}]+p2 Sum[(x1-x2+x3)^i/i!,{i,1,ord}]+ d2 Sum[(-x2)^i/i!,{i,1,ord}]) D[K[ord],x2]+ (p3 Sum[(-x3+x4)^i/i!,{i,1,ord}]+ u Sum[x4^i/i!,{i,1,ord}]+ d3 Sum[(-x3)^i/i!,{i,1,ord}]) D[K[ord],x3]+ v Sum[x1^i/i!,{i,1,ord}] ] , ((Exponent[#,x1]+Exponent[#,x2]+Exponent[#,x3]+Exponent[#,x4])<=ord)&] :[font = text; inactive; preserveAspect] By equating coefficients of the left hand side of the PDE (which is simply D[K,t]) with those of the right hand side, a system of ODEs results. :[font = input; preserveAspect] odeForCumulants[ord_]:=List@@LogicalExpand[ Series[D[K[ord],t],{x1,0,ord},{x2,0,ord},{x3,0,ord}, {x4,0,ord}]==Series[RHS[ord], {x1,0,ord},{x2,0,ord},{x3,0,ord},{x4,0,ord}]]; :[font = subsection; inactive; preserveAspect; fontSize = 12] The Mean and Variance-Covariance Functions :[font = text; inactive; preserveAspect] The first and second order cumulants are the best known and the most widely used. The first order cumulants are referred to as means or expectations, while the second order cumulants are called variances (or covariances). One can easily obtain an ODE system for these cumulants. :[font = input; preserveAspect; startGroup] odeOrderTwo=odeForCumulants[2]; odeOrderTwo[[5]] :[font = output; output; inactive; preserveAspect; endGroup] -(d3*k[0, 0, 1, 0][t])/2 - (p3*k[0, 0, 1, 0][t])/2 + d3*k[0, 0, 2, 0][t] + p3*k[0, 0, 2, 0][t] - (p2*k[0, 1, 0, 0][t])/2 - p2*k[0, 1, 1, 0][t] + Derivative[1][k[0, 0, 2, 0]][t]/2 == 0 ;[o] -(d3 k[0, 0, 1, 0][t]) p3 k[0, 0, 1, 0][t] ---------------------- - ------------------- + 2 2 d3 k[0, 0, 2, 0][t] + p3 k[0, 0, 2, 0][t] - p2 k[0, 1, 0, 0][t] ------------------- - p2 k[0, 1, 1, 0][t] + 2 (k[0, 0, 2, 0])'[t] ------------------- == 0 2 :[font = text; inactive; preserveAspect] As one may readily see from the above output, the resulting ODEs are not yet in a form pleasing to the human eye. Further symbolic processing is needed to render the equations to a "canonical" form. First, fractions should be eliminated. Because the equations are in the form lhs==0, one only needs to process the left hand sides of these equations. :[font = input; preserveAspect; startGroup] odeOrderTwo=(Numerator[Together[#]])&/@(First/@odeOrderTwo); odeOrderTwo[[5]] :[font = output; output; inactive; preserveAspect; endGroup] -(d3*k[0, 0, 1, 0][t]) - p3*k[0, 0, 1, 0][t] + 2*d3*k[0, 0, 2, 0][t] + 2*p3*k[0, 0, 2, 0][t] - p2*k[0, 1, 0, 0][t] - 2*p2*k[0, 1, 1, 0][t] + Derivative[1][k[0, 0, 2, 0]][t] ;[o] -(d3 k[0, 0, 1, 0][t]) - p3 k[0, 0, 1, 0][t] + 2 d3 k[0, 0, 2, 0][t] + 2 p3 k[0, 0, 2, 0][t] - p2 k[0, 1, 0, 0][t] - 2 p2 k[0, 1, 1, 0][t] + (k[0, 0, 2, 0])'[t] :[font = text; inactive; preserveAspect] Secondly, collect coefficients for each cumulant . :[font = input; preserveAspect; startGroup] rule1=(a_ k[i__][t_]+ b_ k[i__][t_]):>(a+b) k[i][t]; odeOrderTwo=odeOrderTwo//.rule1; odeOrderTwo[[5]] :[font = output; output; inactive; preserveAspect; endGroup] (-d3 - p3)*k[0, 0, 1, 0][t] + (2*d3 + 2*p3)*k[0, 0, 2, 0][t] - p2*k[0, 1, 0, 0][t] - 2*p2*k[0, 1, 1, 0][t] + Derivative[1][k[0, 0, 2, 0]][t] ;[o] (-d3 - p3) k[0, 0, 1, 0][t] + (2 d3 + 2 p3) k[0, 0, 2, 0][t] - p2 k[0, 1, 0, 0][t] - 2 p2 k[0, 1, 1, 0][t] + (k[0, 0, 2, 0])'[t] :[font = text; inactive; preserveAspect] Thirdly, after locating the derivative term in each expression, translate these expressions back to ODEs. :[font = input; preserveAspect; startGroup] posOfDerivative=Flatten[(Position[#,_. k[__]'[_]])&/@odeOrderTwo]; odeOrderTwo=MapThread[(#[[#2]]==-Drop[#,{#2}])&, {odeOrderTwo,posOfDerivative}]; odeOrderTwo[[5]] :[font = output; output; inactive; preserveAspect; endGroup] Derivative[1][k[0, 0, 2, 0]][t] == -((-d3 - p3)*k[0, 0, 1, 0][t]) - (2*d3 + 2*p3)*k[0, 0, 2, 0][t] + p2*k[0, 1, 0, 0][t] + 2*p2*k[0, 1, 1, 0][t] ;[o] (k[0, 0, 2, 0])'[t] == -((-d3 - p3) k[0, 0, 1, 0][t]) - (2 d3 + 2 p3) k[0, 0, 2, 0][t] + p2 k[0, 1, 0, 0][t] + 2 p2 k[0, 1, 1, 0][t] :[font = text; inactive; preserveAspect; startGroup] Further simplification and sorting transform the ODEs into textbook format. At this point, one may rename these cumulants with more common notation (e.g., m stands for mean, etc.). :[font = input; preserveAspect; startGroup] rule2={k[1,0,0,0]->m1,k[0,1,0,0]->m2, k[0,0,1,0]->m3,k[0,0,0,1]->m4,k[2,0,0,0]->v11, k[1,1,0,0]->v12,k[1,0,1,0]->v13,k[1,0,0,1]->v14, k[0,2,0,0]->v22,k[0,1,1,0]->v23,k[0,1,0,1]->v24, k[0,0,2,0]->v33,k[0,0,1,1]->v34,k[0,0,0,2]->v44}; TableForm[Sort[Simplify[odeOrderTwo//.rule2]]] :[font = output; output; inactive; preserveAspect; endGroup; endGroup] TableForm[{Derivative[1][m1][t] == v - (a - b + d1)*m1[t] + (p1 + p2)*m2[t], Derivative[1][m2][t] == a*m1[t] - (d2 + p1 + p2)*m2[t], Derivative[1][m3][t] == p2*m2[t] - (d3 + p3)*m3[t], Derivative[1][m4][t] == (p3 + u)*m3[t], Derivative[1][v11][t] == v + (a + b + d1)*m1[t] + (p1 + p2)*m2[t] - 2*(a - b + d1)*v11[t] + 2*(p1 + p2)*v12[t], Derivative[1][v12][t] == -(a*m1[t]) - (p1 + p2)*m2[t] + a*v11[t] - (a - b + d1 + d2 + p1 + p2)*v12[t] + (p1 + p2)*v22[t], Derivative[1][v13][t] == p2*m2[t] + p2*v12[t] - (a - b + d1 + d3 + p3)*v13[t] + (p1 + p2)*v23[t], Derivative[1][v14][t] == (p3 + u)*v13[t] - (a - b + d1)*v14[t] + (p1 + p2)*v24[t]\ , Derivative[1][v22][t] == a*m1[t] + (d2 + p1 + p2)*m2[t] + 2*a*v12[t] - 2*(d2 + p1 + p2)*v22[t], Derivative[1][v23][t] == -(p2*m2[t]) + a*v13[t] + p2*v22[t] - (d2 + d3 + p1 + p2 + p3)*v23[t], Derivative[1][v24][t] == a*v14[t] + (p3 + u)*v23[t] - (d2 + p1 + p2)*v24[t], Derivative[1][v33][t] == p2*m2[t] + (d3 + p3)*m3[t] + 2*p2*v23[t] - 2*(d3 + p3)*v33[t], Derivative[1][v34][t] == -(p3*m3[t]) + p2*v24[t] + (p3 + u)*v33[t] - (d3 + p3)*v34[t], Derivative[1][v44][t] == (p3 + u)*(m3[t] + 2*v34[t])}] ;[o] m1'[t] == v - (a - b + d1) m1[t] + (p1 + p2) m2[t] m2'[t] == a m1[t] - (d2 + p1 + p2) m2[t] m3'[t] == p2 m2[t] - (d3 + p3) m3[t] m4'[t] == (p3 + u) m3[t] v11'[t] == v + (a + b + d1) m1[t] + (p1 + p2) m2[t] - 2 (a - b + d1) v11[t] + 2 (p1 + p2) v12[t] v12'[t] == -(a m1[t]) - (p1 + p2) m2[t] + a v11[t] - (a - b + d1 + d2 + p1 + p2) v12[t] + (p1 + p2) v22[t] v13'[t] == p2 m2[t] + p2 v12[t] - (a - b + d1 + d3 + p3) v13[t] + (p1 + p2) v23[t] v14'[t] == (p3 + u) v13[t] - (a - b + d1) v14[t] + (p1 + p2) v24[t] v22'[t] == a m1[t] + (d2 + p1 + p2) m2[t] + 2 a v12[t] - 2 (d2 + p1 + p2) v22[t] v23'[t] == -(p2 m2[t]) + a v13[t] + p2 v22[t] - (d2 + d3 + p1 + p2 + p3) v23[t] v24'[t] == a v14[t] + (p3 + u) v23[t] - (d2 + p1 + p2) v24[t] v33'[t] == p2 m2[t] + (d3 + p3) m3[t] + 2 p2 v23[t] - 2 (d3 + p3) v33[t] v34'[t] == -(p3 m3[t]) + p2 v24[t] + (p3 + u) v33[t] - (d3 + p3) v34[t] v44'[t] == (p3 + u) (m3[t] + 2 v34[t]) :[font = subsection; inactive; preserveAspect; fontSize = 12] How to Obtain Numerical Solutions :[font = text; inactive; preserveAspect] There are 34 cumulants of order up to 3. To numerically solve and plot them require additional symbolic manipulation. For the present purpose, one needs these ODEs in their "raw" form. :[font = input; preserveAspect] odeOrderThree=odeForCumulants[3]//.rule1; :[font = text; inactive; preserveAspect] Now specify numerical values for the cell kinetic parameters. :[font = input; preserveAspect] odeOrderThree=odeOrderThree//.{v->0.03,b->0.0019,d1->0.0015, d2->0.0016,d3->0.0017,a->0.0005, p1->0.0005,p2->0.0005,p3->0.0005,u->0.0000003}; :[font = text; inactive; preserveAspect] In addition to creating a list of equation names, determine and attach the initial conditions to the original ODE list. :[font = input; preserveAspect] odeNames=Table[If[i1+i2+i3+i4<=3,k[i1,i2,i3,i4],{}], {i1,0,3},{i2,0,3},{i3,0,3},{i4,0,3}]//Flatten//Rest; initial=Table[If[i1+i2+i3+i4<=3,k[i1,i2,i3,i4][0]==0,{}], {i1,0,3},{i2,0,3},{i3,0,3},{i4,0,3}]//Flatten//Rest; odeWithInit=Join[odeOrderThree,initial]; :[font = text; inactive; preserveAspect] Note that the NDSolve function in Mathematica Version 2.2 does not always behave correctly when the functions have indexed names, like k[2,0,0,1]. When computing numerical values, NDSolve sometimes also computes numerical values for the indices, after which it is no longer able to recognize the functions. This limitation of NDSolve has been corrected for Version 3 of Mathematica. However, there are several simple ways to deal with this problem in Version 2.2. One of the easiest ways is to use the NProtectedAll attribute to protect the function indices from numerical computation. The NProtectedAll attribute was added to Mathematica after the manual was printed, and so is not included in the manual. The name NProtectedAll has been changed to NHoldAll for Version 3. :[font = input; preserveAspect] SetAttributes[k, NProtectedAll]; odeSoln=NDSolve[odeWithInit,odeNames,{t,0,5000}]; :[font = text; inactive; preserveAspect; startGroup] To have a feeling of the shapes of these cumulant functions, one can plot a few of them . :[font = input; preserveAspect; startGroup] pic=(Plot[Evaluate[#[t]/.odeSoln],{t,0,5000}, Frame->True,PlotRange->All,PlotLabel->ToString[#], DisplayFunction->Identity ] )&/@odeNames[[Range[27,34]]]; Show[GraphicsArray[Partition[pic,2]]] :[font = postscript; PostScript; formatAsPostScript; output; inactive; preserveAspect; pictureLeft = 25; pictureWidth = 531; pictureHeight = 672] %! %%Creator: Mathematica %%AspectRatio: 1.2655 MathPictureStart %% Graphics /Courier findfont 10 scalefont setfont % Scaling calculations 0.0238095 0.47619 0.0301309 0.47619 [ [ 0 0 0 0 ] [ 1 1.2655 0 0 ] ] MathScale % Start of Graphics 1 setlinecap 1 setlinejoin newpath [ ] 0 setdash 0 g p P 0 0 m 1 0 L 1 1.2655 L 0 1.2655 L closepath clip newpath p p % Start of sub-graphic p 0.0238095 0.0301309 0.477324 0.310418 MathSubStart %% Graphics /Courier findfont 10 scalefont setfont % Scaling calculations 0.0238095 0.000190476 0.0147151 8.62191e-05 [ [(0)] .02381 0 0 2 Msboxa [(1000)] .21429 0 0 2 Msboxa [(2000)] .40476 0 0 2 Msboxa [(3000)] .59524 0 0 2 Msboxa [(4000)] .78571 0 0 2 Msboxa [(5000)] .97619 0 0 2 Msboxa [(0)] -0.0125 .01472 1 0 Msboxa [(1000)] -0.0125 .10093 1 0 Msboxa [(2000)] -0.0125 .18715 1 0 Msboxa [(3000)] -0.0125 .27337 1 0 Msboxa [(4000)] -0.0125 .35959 1 0 Msboxa [(5000)] -0.0125 .44581 1 0 Msboxa [(6000)] -0.0125 .53203 1 0 Msboxa [(k[2, 1, 0, 0])] .5 .61803 0 -2 Msboxa [ -0.001 -0.001 0 0 ] [ 1.001 .61903 0 0 ] ] MathScale % Start of Graphics 1 setlinecap 1 setlinejoin newpath [ ] 0 setdash p p .002 w .02381 0 m .02381 .00625 L s P [(0)] .02381 0 0 2 Mshowa p .002 w .21429 0 m .21429 .00625 L s P [(1000)] .21429 0 0 2 Mshowa p .002 w .40476 0 m .40476 .00625 L s P [(2000)] .40476 0 0 2 Mshowa p .002 w .59524 0 m .59524 .00625 L s P [(3000)] .59524 0 0 2 Mshowa p .002 w .78571 0 m .78571 .00625 L s P [(4000)] .78571 0 0 2 Mshowa p .002 w .97619 0 m .97619 .00625 L s P [(5000)] .97619 0 0 2 Mshowa p .001 w .0619 0 m .0619 .00375 L s P p .001 w .1 0 m .1 .00375 L s P p .001 w .1381 0 m .1381 .00375 L s P p .001 w .17619 0 m .17619 .00375 L s P p .001 w .25238 0 m .25238 .00375 L s P p .001 w .29048 0 m .29048 .00375 L s P p .001 w .32857 0 m .32857 .00375 L s P p .001 w .36667 0 m .36667 .00375 L s P p .001 w .44286 0 m .44286 .00375 L s P p .001 w .48095 0 m .48095 .00375 L s P p .001 w .51905 0 m .51905 .00375 L s P p .001 w .55714 0 m .55714 .00375 L s P p .001 w .63333 0 m .63333 .00375 L s P p .001 w .67143 0 m .67143 .00375 L s P p .001 w .70952 0 m .70952 .00375 L s P p .001 w .74762 0 m .74762 .00375 L s P p .001 w .82381 0 m .82381 .00375 L s P p .001 w .8619 0 m .8619 .00375 L s P p .001 w .9 0 m .9 .00375 L s P p .001 w .9381 0 m .9381 .00375 L s P p .002 w 0 0 m 1 0 L s P p .002 w 0 .01472 m .00625 .01472 L s P [(0)] -0.0125 .01472 1 0 Mshowa p .002 w 0 .10093 m .00625 .10093 L s P [(1000)] -0.0125 .10093 1 0 Mshowa p .002 w 0 .18715 m .00625 .18715 L s P [(2000)] -0.0125 .18715 1 0 Mshowa p .002 w 0 .27337 m .00625 .27337 L s P [(3000)] -0.0125 .27337 1 0 Mshowa p .002 w 0 .35959 m .00625 .35959 L s P [(4000)] -0.0125 .35959 1 0 Mshowa p .002 w 0 .44581 m .00625 .44581 L s P [(5000)] -0.0125 .44581 1 0 Mshowa p .002 w 0 .53203 m .00625 .53203 L s P [(6000)] -0.0125 .53203 1 0 Mshowa p .001 w 0 .03196 m .00375 .03196 L s P p .001 w 0 .0492 m .00375 .0492 L s P p .001 w 0 .06645 m .00375 .06645 L s P p .001 w 0 .08369 m .00375 .08369 L s P p .001 w 0 .11818 m .00375 .11818 L s P p .001 w 0 .13542 m .00375 .13542 L s P p .001 w 0 .15267 m .00375 .15267 L s P p .001 w 0 .16991 m .00375 .16991 L s P p .001 w 0 .2044 m .00375 .2044 L s P p .001 w 0 .22164 m .00375 .22164 L s P p .001 w 0 .23888 m .00375 .23888 L s P p .001 w 0 .25613 m .00375 .25613 L s P p .001 w 0 .29062 m .00375 .29062 L s P p .001 w 0 .30786 m .00375 .30786 L s P p .001 w 0 .3251 m .00375 .3251 L s P p .001 w 0 .34235 m .00375 .34235 L s P p .001 w 0 .37684 m .00375 .37684 L s P p .001 w 0 .39408 m .00375 .39408 L s P p .001 w 0 .41132 m .00375 .41132 L s P p .001 w 0 .42857 m .00375 .42857 L s P p .001 w 0 .46305 m .00375 .46305 L s P p .001 w 0 .4803 m .00375 .4803 L s P p .001 w 0 .49754 m .00375 .49754 L s P p .001 w 0 .51479 m .00375 .51479 L s P p .001 w 0 .54927 m .00375 .54927 L s P p .001 w 0 .56652 m .00375 .56652 L s P p .001 w 0 .58376 m .00375 .58376 L s P p .001 w 0 .601 m .00375 .601 L s P p .002 w 0 0 m 0 .61803 L s P P p p .002 w .02381 .61178 m .02381 .61803 L s P p .002 w .21429 .61178 m .21429 .61803 L s P p .002 w .40476 .61178 m .40476 .61803 L s P p .002 w .59524 .61178 m .59524 .61803 L s P p .002 w .78571 .61178 m .78571 .61803 L s P p .002 w .97619 .61178 m .97619 .61803 L s P p .001 w .0619 .61428 m .0619 .61803 L s P p .001 w .1 .61428 m .1 .61803 L s P p .001 w .1381 .61428 m .1381 .61803 L s P p .001 w .17619 .61428 m .17619 .61803 L s P p .001 w .25238 .61428 m .25238 .61803 L s P p .001 w .29048 .61428 m .29048 .61803 L s P p .001 w .32857 .61428 m .32857 .61803 L s P p .001 w .36667 .61428 m .36667 .61803 L s P p .001 w .44286 .61428 m .44286 .61803 L s P p .001 w .48095 .61428 m .48095 .61803 L s P p .001 w .51905 .61428 m .51905 .61803 L s P p .001 w .55714 .61428 m .55714 .61803 L s P p .001 w .63333 .61428 m .63333 .61803 L s P p .001 w .67143 .61428 m .67143 .61803 L s P p .001 w .70952 .61428 m .70952 .61803 L s P p .001 w .74762 .61428 m .74762 .61803 L s P p .001 w .82381 .61428 m .82381 .61803 L s P p .001 w .8619 .61428 m .8619 .61803 L s P p .001 w .9 .61428 m .9 .61803 L s P p .001 w .9381 .61428 m .9381 .61803 L s P p .002 w 0 .61803 m 1 .61803 L s P [(k[2, 1, 0, 0])] .5 .61803 0 -2 Mshowa p .002 w .99375 .01472 m 1 .01472 L s P p .002 w .99375 .10093 m 1 .10093 L s P p .002 w .99375 .18715 m 1 .18715 L s P p .002 w .99375 .27337 m 1 .27337 L s P p .002 w .99375 .35959 m 1 .35959 L s P p .002 w .99375 .44581 m 1 .44581 L s P p .002 w .99375 .53203 m 1 .53203 L s P p .001 w .99625 .03196 m 1 .03196 L s P p .001 w .99625 .0492 m 1 .0492 L s P p .001 w .99625 .06645 m 1 .06645 L s P p .001 w .99625 .08369 m 1 .08369 L s P p .001 w .99625 .11818 m 1 .11818 L s P p .001 w .99625 .13542 m 1 .13542 L s P p .001 w .99625 .15267 m 1 .15267 L s P p .001 w .99625 .16991 m 1 .16991 L s P p .001 w .99625 .2044 m 1 .2044 L s P p .001 w .99625 .22164 m 1 .22164 L s P p .001 w .99625 .23888 m 1 .23888 L s P p .001 w .99625 .25613 m 1 .25613 L s P p .001 w .99625 .29062 m 1 .29062 L s P p .001 w .99625 .30786 m 1 .30786 L s P p .001 w .99625 .3251 m 1 .3251 L s P p .001 w .99625 .34235 m 1 .34235 L s P p .001 w .99625 .37684 m 1 .37684 L s P p .001 w .99625 .39408 m 1 .39408 L s P p .001 w .99625 .41132 m 1 .41132 L s P p .001 w .99625 .42857 m 1 .42857 L s P p .001 w .99625 .46305 m 1 .46305 L s P p .001 w .99625 .4803 m 1 .4803 L s P p .001 w .99625 .49754 m 1 .49754 L s P p .001 w .99625 .51479 m 1 .51479 L s P p .001 w .99625 .54927 m 1 .54927 L s P p .001 w .99625 .56652 m 1 .56652 L s P p .001 w .99625 .58376 m 1 .58376 L s P p .001 w .99625 .601 m 1 .601 L s P p .002 w 1 0 m 1 .61803 L s P P p P p p p .004 w .02381 .01472 m .02505 .01472 L .02629 .01472 L .02753 .01472 L .02877 .01472 L .03001 .01472 L .03125 .01472 L .03249 .01472 L .03373 .01472 L .03497 .01472 L .03621 .01472 L .03869 .01472 L .03993 .01472 L .04117 .01472 L .04365 .01472 L .04613 .01472 L .04861 .01472 L .05357 .01472 L .05605 .01472 L .05853 .01472 L .06349 .01473 L .06845 .01473 L .07341 .01474 L .08333 .01476 L .08829 .01477 L .09325 .01479 L .10317 .01483 L .1131 .01489 L .12302 .01496 L .13294 .01505 L .14286 .01517 L .1627 .01548 L .18254 .01591 L .20238 .0165 L .22222 .01726 L .24206 .01822 L .2619 .01942 L .30159 .02264 L .34127 .02716 L .38095 .03327 L .42063 .04128 L .46032 .05152 L .5 .06435 L .53968 .08017 L .57937 .0994 L .61905 .12251 L .65873 .15 L .69841 .18241 L .7381 .22035 L .77778 .26444 L Mistroke .81746 .31537 L .85714 .3739 L .89683 .44081 L .93651 .51697 L .97619 .60332 L Mfstroke P P P 0 0 m 1 0 L 1 .61803 L 0 .61803 L closepath clip newpath MathSubEnd P % End of sub-graphic % Start of sub-graphic p 0.522676 0.0301309 0.97619 0.310418 MathSubStart %% Graphics /Courier findfont 10 scalefont setfont % Scaling calculations 0.0238095 0.000190476 0.0147151 1.29527e-05 [ [(0)] .02381 0 0 2 Msboxa [(1000)] .21429 0 0 2 Msboxa [(2000)] .40476 0 0 2 Msboxa [(3000)] .59524 0 0 2 Msboxa [(4000)] .78571 0 0 2 Msboxa [(5000)] .97619 0 0 2 Msboxa [(0)] -0.0125 .01472 1 0 Msboxa [(10000)] -0.0125 .14424 1 0 Msboxa [(20000)] -0.0125 .27377 1 0 Msboxa [(30000)] -0.0125 .4033 1 0 Msboxa [(40000)] -0.0125 .53282 1 0 Msboxa [(k[3, 0, 0, 0])] .5 .61803 0 -2 Msboxa [ -0.001 -0.001 0 0 ] [ 1.001 .61903 0 0 ] ] MathScale % Start of Graphics 1 setlinecap 1 setlinejoin newpath [ ] 0 setdash p p .002 w .02381 0 m .02381 .00625 L s P [(0)] .02381 0 0 2 Mshowa p .002 w .21429 0 m .21429 .00625 L s P [(1000)] .21429 0 0 2 Mshowa p .002 w .40476 0 m .40476 .00625 L s P [(2000)] .40476 0 0 2 Mshowa p .002 w .59524 0 m .59524 .00625 L s P [(3000)] .59524 0 0 2 Mshowa p .002 w .78571 0 m .78571 .00625 L s P [(4000)] .78571 0 0 2 Mshowa p .002 w .97619 0 m .97619 .00625 L s P [(5000)] .97619 0 0 2 Mshowa p .001 w .0619 0 m .0619 .00375 L s P p .001 w .1 0 m .1 .00375 L s P p .001 w .1381 0 m .1381 .00375 L s P p .001 w .17619 0 m .17619 .00375 L s P p .001 w .25238 0 m .25238 .00375 L s P p .001 w .29048 0 m .29048 .00375 L s P p .001 w .32857 0 m .32857 .00375 L s P p .001 w .36667 0 m .36667 .00375 L s P p .001 w .44286 0 m .44286 .00375 L s P p .001 w .48095 0 m .48095 .00375 L s P p .001 w .51905 0 m .51905 .00375 L s P p .001 w .55714 0 m .55714 .00375 L s P p .001 w .63333 0 m .63333 .00375 L s P p .001 w .67143 0 m .67143 .00375 L s P p .001 w .70952 0 m .70952 .00375 L s P p .001 w .74762 0 m .74762 .00375 L s P p .001 w .82381 0 m .82381 .00375 L s P p .001 w .8619 0 m .8619 .00375 L s P p .001 w .9 0 m .9 .00375 L s P p .001 w .9381 0 m .9381 .00375 L s P p .002 w 0 0 m 1 0 L s P p .002 w 0 .01472 m .00625 .01472 L s P [(0)] -0.0125 .01472 1 0 Mshowa p .002 w 0 .14424 m .00625 .14424 L s P [(10000)] -0.0125 .14424 1 0 Mshowa p .002 w 0 .27377 m .00625 .27377 L s P [(20000)] -0.0125 .27377 1 0 Mshowa p .002 w 0 .4033 m .00625 .4033 L s P [(30000)] -0.0125 .4033 1 0 Mshowa p .002 w 0 .53282 m .00625 .53282 L s P [(40000)] -0.0125 .53282 1 0 Mshowa p .001 w 0 .04062 m .00375 .04062 L s P p .001 w 0 .06653 m .00375 .06653 L s P p .001 w 0 .09243 m .00375 .09243 L s P p .001 w 0 .11834 m .00375 .11834 L s P p .001 w 0 .17015 m .00375 .17015 L s P p .001 w 0 .19605 m .00375 .19605 L s P p .001 w 0 .22196 m .00375 .22196 L s P p .001 w 0 .24786 m .00375 .24786 L s P p .001 w 0 .29967 m .00375 .29967 L s P p .001 w 0 .32558 m .00375 .32558 L s P p .001 w 0 .35149 m .00375 .35149 L s P p .001 w 0 .37739 m .00375 .37739 L s P p .001 w 0 .4292 m .00375 .4292 L s P p .001 w 0 .45511 m .00375 .45511 L s P p .001 w 0 .48101 m .00375 .48101 L s P p .001 w 0 .50692 m .00375 .50692 L s P p .001 w 0 .55873 m .00375 .55873 L s P p .001 w 0 .58463 m .00375 .58463 L s P p .001 w 0 .61054 m .00375 .61054 L s P p .002 w 0 0 m 0 .61803 L s P P p p .002 w .02381 .61178 m .02381 .61803 L s P p .002 w .21429 .61178 m .21429 .61803 L s P p .002 w .40476 .61178 m .40476 .61803 L s P p .002 w .59524 .61178 m .59524 .61803 L s P p .002 w .78571 .61178 m .78571 .61803 L s P p .002 w .97619 .61178 m .97619 .61803 L s P p .001 w .0619 .61428 m .0619 .61803 L s P p .001 w .1 .61428 m .1 .61803 L s P p .001 w .1381 .61428 m .1381 .61803 L s P p .001 w .17619 .61428 m .17619 .61803 L s P p .001 w .25238 .61428 m .25238 .61803 L s P p .001 w .29048 .61428 m .29048 .61803 L s P p .001 w .32857 .61428 m .32857 .61803 L s P p .001 w .36667 .61428 m .36667 .61803 L s P p .001 w .44286 .61428 m .44286 .61803 L s P p .001 w .48095 .61428 m .48095 .61803 L s P p .001 w .51905 .61428 m .51905 .61803 L s P p .001 w .55714 .61428 m .55714 .61803 L s P p .001 w .63333 .61428 m .63333 .61803 L s P p .001 w .67143 .61428 m .67143 .61803 L s P p .001 w .70952 .61428 m .70952 .61803 L s P p .001 w .74762 .61428 m .74762 .61803 L s P p .001 w .82381 .61428 m .82381 .61803 L s P p .001 w .8619 .61428 m .8619 .61803 L s P p .001 w .9 .61428 m .9 .61803 L s P p .001 w .9381 .61428 m .9381 .61803 L s P p .002 w 0 .61803 m 1 .61803 L s P [(k[3, 0, 0, 0])] .5 .61803 0 -2 Mshowa p .002 w .99375 .01472 m 1 .01472 L s P p .002 w .99375 .14424 m 1 .14424 L s P p .002 w .99375 .27377 m 1 .27377 L s P p .002 w .99375 .4033 m 1 .4033 L s P p .002 w .99375 .53282 m 1 .53282 L s P p .001 w .99625 .04062 m 1 .04062 L s P p .001 w .99625 .06653 m 1 .06653 L s P p .001 w .99625 .09243 m 1 .09243 L s P p .001 w .99625 .11834 m 1 .11834 L s P p .001 w .99625 .17015 m 1 .17015 L s P p .001 w .99625 .19605 m 1 .19605 L s P p .001 w .99625 .22196 m 1 .22196 L s P p .001 w .99625 .24786 m 1 .24786 L s P p .001 w .99625 .29967 m 1 .29967 L s P p .001 w .99625 .32558 m 1 .32558 L s P p .001 w .99625 .35149 m 1 .35149 L s P p .001 w .99625 .37739 m 1 .37739 L s P p .001 w .99625 .4292 m 1 .4292 L s P p .001 w .99625 .45511 m 1 .45511 L s P p .001 w .99625 .48101 m 1 .48101 L s P p .001 w .99625 .50692 m 1 .50692 L s P p .001 w .99625 .55873 m 1 .55873 L s P p .001 w .99625 .58463 m 1 .58463 L s P p .001 w .99625 .61054 m 1 .61054 L s P p .002 w 1 0 m 1 .61803 L s P P p P p p p .004 w .02381 .01472 m .02877 .01473 L .03373 .01474 L .04365 .01478 L .05357 .01484 L .06349 .01491 L .07341 .01501 L .08333 .01513 L .10317 .01545 L .12302 .01588 L .14286 .01646 L .1627 .01719 L .18254 .0181 L .22222 .02055 L .2619 .02398 L .30159 .02861 L .34127 .03466 L .38095 .04236 L .42063 .05199 L .46032 .06382 L .5 .07818 L .53968 .09539 L .57937 .11584 L .61905 .13991 L .65873 .16803 L .69841 .20068 L .7381 .23835 L .77778 .28159 L .81746 .33097 L .85714 .38714 L .89683 .45075 L .93651 .52255 L .97619 .60332 L s P P P 0 0 m 1 0 L 1 .61803 L 0 .61803 L closepath clip newpath MathSubEnd P % End of sub-graphic P p % Start of sub-graphic p 0.0238095 0.338447 0.477324 0.618735 MathSubStart %% Graphics /Courier findfont 10 scalefont setfont % Scaling calculations 0.0238095 0.000190476 0.0147151 0.000554492 [ [(0)] .02381 0 0 2 Msboxa [(1000)] .21429 0 0 2 Msboxa [(2000)] .40476 0 0 2 Msboxa [(3000)] .59524 0 0 2 Msboxa [(4000)] .78571 0 0 2 Msboxa [(5000)] .97619 0 0 2 Msboxa [(0)] -0.0125 .01472 1 0 Msboxa [(200)] -0.0125 .12561 1 0 Msboxa [(400)] -0.0125 .23651 1 0 Msboxa [(600)] -0.0125 .34741 1 0 Msboxa [(800)] -0.0125 .45831 1 0 Msboxa [(1000)] -0.0125 .56921 1 0 Msboxa [(k[2, 0, 0, 1])] .5 .61803 0 -2 Msboxa [ -0.001 -0.001 0 0 ] [ 1.001 .61903 0 0 ] ] MathScale % Start of Graphics 1 setlinecap 1 setlinejoin newpath [ ] 0 setdash p p .002 w .02381 0 m .02381 .00625 L s P [(0)] .02381 0 0 2 Mshowa p .002 w .21429 0 m .21429 .00625 L s P [(1000)] .21429 0 0 2 Mshowa p .002 w .40476 0 m .40476 .00625 L s P [(2000)] .40476 0 0 2 Mshowa p .002 w .59524 0 m .59524 .00625 L s P [(3000)] .59524 0 0 2 Mshowa p .002 w .78571 0 m .78571 .00625 L s P [(4000)] .78571 0 0 2 Mshowa p .002 w .97619 0 m .97619 .00625 L s P [(5000)] .97619 0 0 2 Mshowa p .001 w .0619 0 m .0619 .00375 L s P p .001 w .1 0 m .1 .00375 L s P p .001 w .1381 0 m .1381 .00375 L s P p .001 w .17619 0 m .17619 .00375 L s P p .001 w .25238 0 m .25238 .00375 L s P p .001 w .29048 0 m .29048 .00375 L s P p .001 w .32857 0 m .32857 .00375 L s P p .001 w .36667 0 m .36667 .00375 L s P p .001 w .44286 0 m .44286 .00375 L s P p .001 w .48095 0 m .48095 .00375 L s P p .001 w .51905 0 m .51905 .00375 L s P p .001 w .55714 0 m .55714 .00375 L s P p .001 w .63333 0 m .63333 .00375 L s P p .001 w .67143 0 m .67143 .00375 L s P p .001 w .70952 0 m .70952 .00375 L s P p .001 w .74762 0 m .74762 .00375 L s P p .001 w .82381 0 m .82381 .00375 L s P p .001 w .8619 0 m .8619 .00375 L s P p .001 w .9 0 m .9 .00375 L s P p .001 w .9381 0 m .9381 .00375 L s P p .002 w 0 0 m 1 0 L s P p .002 w 0 .01472 m .00625 .01472 L s P [(0)] -0.0125 .01472 1 0 Mshowa p .002 w 0 .12561 m .00625 .12561 L s P [(200)] -0.0125 .12561 1 0 Mshowa p .002 w 0 .23651 m .00625 .23651 L s P [(400)] -0.0125 .23651 1 0 Mshowa p .002 w 0 .34741 m .00625 .34741 L s P [(600)] -0.0125 .34741 1 0 Mshowa p .002 w 0 .45831 m .00625 .45831 L s P [(800)] -0.0125 .45831 1 0 Mshowa p .002 w 0 .56921 m .00625 .56921 L s P [(1000)] -0.0125 .56921 1 0 Mshowa p .001 w 0 .03689 m .00375 .03689 L s P p .001 w 0 .05907 m .00375 .05907 L s P p .001 w 0 .08125 m .00375 .08125 L s P p .001 w 0 .10343 m .00375 .10343 L s P p .001 w 0 .14779 m .00375 .14779 L s P p .001 w 0 .16997 m .00375 .16997 L s P p .001 w 0 .19215 m .00375 .19215 L s P p .001 w 0 .21433 m .00375 .21433 L s P p .001 w 0 .25869 m .00375 .25869 L s P p .001 w 0 .28087 m .00375 .28087 L s P p .001 w 0 .30305 m .00375 .30305 L s P p .001 w 0 .32523 m .00375 .32523 L s P p .001 w 0 .36959 m .00375 .36959 L s P p .001 w 0 .39177 m .00375 .39177 L s P p .001 w 0 .41395 m .00375 .41395 L s P p .001 w 0 .43613 m .00375 .43613 L s P p .001 w 0 .48049 m .00375 .48049 L s P p .001 w 0 .50267 m .00375 .50267 L s P p .001 w 0 .52485 m .00375 .52485 L s P p .001 w 0 .54703 m .00375 .54703 L s P p .001 w 0 .59139 m .00375 .59139 L s P p .001 w 0 .61357 m .00375 .61357 L s P p .002 w 0 0 m 0 .61803 L s P P p p .002 w .02381 .61178 m .02381 .61803 L s P p .002 w .21429 .61178 m .21429 .61803 L s P p .002 w .40476 .61178 m .40476 .61803 L s P p .002 w .59524 .61178 m .59524 .61803 L s P p .002 w .78571 .61178 m .78571 .61803 L s P p .002 w .97619 .61178 m .97619 .61803 L s P p .001 w .0619 .61428 m .0619 .61803 L s P p .001 w .1 .61428 m .1 .61803 L s P p .001 w .1381 .61428 m .1381 .61803 L s P p .001 w .17619 .61428 m .17619 .61803 L s P p .001 w .25238 .61428 m .25238 .61803 L s P p .001 w .29048 .61428 m .29048 .61803 L s P p .001 w .32857 .61428 m .32857 .61803 L s P p .001 w .36667 .61428 m .36667 .61803 L s P p .001 w .44286 .61428 m .44286 .61803 L s P p .001 w .48095 .61428 m .48095 .61803 L s P p .001 w .51905 .61428 m .51905 .61803 L s P p .001 w .55714 .61428 m .55714 .61803 L s P p .001 w .63333 .61428 m .63333 .61803 L s P p .001 w .67143 .61428 m .67143 .61803 L s P p .001 w .70952 .61428 m .70952 .61803 L s P p .001 w .74762 .61428 m .74762 .61803 L s P p .001 w .82381 .61428 m .82381 .61803 L s P p .001 w .8619 .61428 m .8619 .61803 L s P p .001 w .9 .61428 m .9 .61803 L s P p .001 w .9381 .61428 m .9381 .61803 L s P p .002 w 0 .61803 m 1 .61803 L s P [(k[2, 0, 0, 1])] .5 .61803 0 -2 Mshowa p .002 w .99375 .01472 m 1 .01472 L s P p .002 w .99375 .12561 m 1 .12561 L s P p .002 w .99375 .23651 m 1 .23651 L s P p .002 w .99375 .34741 m 1 .34741 L s P p .002 w .99375 .45831 m 1 .45831 L s P p .002 w .99375 .56921 m 1 .56921 L s P p .001 w .99625 .03689 m 1 .03689 L s P p .001 w .99625 .05907 m 1 .05907 L s P p .001 w .99625 .08125 m 1 .08125 L s P p .001 w .99625 .10343 m 1 .10343 L s P p .001 w .99625 .14779 m 1 .14779 L s P p .001 w .99625 .16997 m 1 .16997 L s P p .001 w .99625 .19215 m 1 .19215 L s P p .001 w .99625 .21433 m 1 .21433 L s P p .001 w .99625 .25869 m 1 .25869 L s P p .001 w .99625 .28087 m 1 .28087 L s P p .001 w .99625 .30305 m 1 .30305 L s P p .001 w .99625 .32523 m 1 .32523 L s P p .001 w .99625 .36959 m 1 .36959 L s P p .001 w .99625 .39177 m 1 .39177 L s P p .001 w .99625 .41395 m 1 .41395 L s P p .001 w .99625 .43613 m 1 .43613 L s P p .001 w .99625 .48049 m 1 .48049 L s P p .001 w .99625 .50267 m 1 .50267 L s P p .001 w .99625 .52485 m 1 .52485 L s P p .001 w .99625 .54703 m 1 .54703 L s P p .001 w .99625 .59139 m 1 .59139 L s P p .001 w .99625 .61357 m 1 .61357 L s P p .002 w 1 0 m 1 .61803 L s P P p P p p p .004 w .02381 .01472 m .02505 .01472 L .02629 .01472 L .02753 .01472 L .02877 .01472 L .03001 .01472 L .03125 .01472 L .03249 .01472 L .03373 .01472 L .03497 .01472 L .03621 .01472 L .03745 .01472 L .03869 .01472 L .03993 .01472 L .04117 .01472 L .04241 .01472 L .04365 .01472 L .04613 .01472 L .04737 .01472 L .04861 .01472 L .05109 .01472 L .05357 .01472 L .05605 .01472 L .05853 .01472 L .06101 .01472 L .06349 .01472 L .06845 .01472 L .07093 .01472 L .07341 .01472 L .07837 .01472 L .08333 .01472 L .08829 .01472 L .09325 .01472 L .09821 .01472 L .10317 .01472 L .1131 .01472 L .11806 .01473 L .12302 .01473 L .13294 .01474 L .14286 .01475 L .15278 .01477 L .1627 .01479 L .17262 .01481 L .18254 .01485 L .20238 .01494 L .2123 .015 L .22222 .01508 L .24206 .01528 L .2619 .01557 L .28175 .01595 L Mistroke .30159 .01646 L .32143 .01712 L .34127 .01797 L .36111 .01903 L .38095 .02035 L .42063 .02392 L .44048 .02628 L .46032 .0291 L .5 .03634 L .53968 .04621 L .57937 .05935 L .61905 .07653 L .65873 .09861 L .69841 .12659 L .7381 .1616 L .77778 .20492 L .81746 .25799 L .85714 .32245 L .89683 .40009 L .93651 .49297 L .97619 .60332 L Mfstroke P P P 0 0 m 1 0 L 1 .61803 L 0 .61803 L closepath clip newpath MathSubEnd P % End of sub-graphic % Start of sub-graphic p 0.522676 0.338447 0.97619 0.618735 MathSubStart %% Graphics /Courier findfont 10 scalefont setfont % Scaling calculations 0.0238095 0.000190476 0.0147151 0.000418944 [ [(0)] .02381 0 0 2 Msboxa [(1000)] .21429 0 0 2 Msboxa [(2000)] .40476 0 0 2 Msboxa [(3000)] .59524 0 0 2 Msboxa [(4000)] .78571 0 0 2 Msboxa [(5000)] .97619 0 0 2 Msboxa [(0)] -0.0125 .01472 1 0 Msboxa [(200)] -0.0125 .0985 1 0 Msboxa [(400)] -0.0125 .18229 1 0 Msboxa [(600)] -0.0125 .26608 1 0 Msboxa [(800)] -0.0125 .34987 1 0 Msboxa [(1000)] -0.0125 .43366 1 0 Msboxa [(1200)] -0.0125 .51745 1 0 Msboxa [(1400)] -0.0125 .60124 1 0 Msboxa [(k[2, 0, 1, 0])] .5 .61803 0 -2 Msboxa [ -0.001 -0.001 0 0 ] [ 1.001 .61903 0 0 ] ] MathScale % Start of Graphics 1 setlinecap 1 setlinejoin newpath [ ] 0 setdash p p .002 w .02381 0 m .02381 .00625 L s P [(0)] .02381 0 0 2 Mshowa p .002 w .21429 0 m .21429 .00625 L s P [(1000)] .21429 0 0 2 Mshowa p .002 w .40476 0 m .40476 .00625 L s P [(2000)] .40476 0 0 2 Mshowa p .002 w .59524 0 m .59524 .00625 L s P [(3000)] .59524 0 0 2 Mshowa p .002 w .78571 0 m .78571 .00625 L s P [(4000)] .78571 0 0 2 Mshowa p .002 w .97619 0 m .97619 .00625 L s P [(5000)] .97619 0 0 2 Mshowa p .001 w .0619 0 m .0619 .00375 L s P p .001 w .1 0 m .1 .00375 L s P p .001 w .1381 0 m .1381 .00375 L s P p .001 w .17619 0 m .17619 .00375 L s P p .001 w .25238 0 m .25238 .00375 L s P p .001 w .29048 0 m .29048 .00375 L s P p .001 w .32857 0 m .32857 .00375 L s P p .001 w .36667 0 m .36667 .00375 L s P p .001 w .44286 0 m .44286 .00375 L s P p .001 w .48095 0 m .48095 .00375 L s P p .001 w .51905 0 m .51905 .00375 L s P p .001 w .55714 0 m .55714 .00375 L s P p .001 w .63333 0 m .63333 .00375 L s P p .001 w .67143 0 m .67143 .00375 L s P p .001 w .70952 0 m .70952 .00375 L s P p .001 w .74762 0 m .74762 .00375 L s P p .001 w .82381 0 m .82381 .00375 L s P p .001 w .8619 0 m .8619 .00375 L s P p .001 w .9 0 m .9 .00375 L s P p .001 w .9381 0 m .9381 .00375 L s P p .002 w 0 0 m 1 0 L s P p .002 w 0 .01472 m .00625 .01472 L s P [(0)] -0.0125 .01472 1 0 Mshowa p .002 w 0 .0985 m .00625 .0985 L s P [(200)] -0.0125 .0985 1 0 Mshowa p .002 w 0 .18229 m .00625 .18229 L s P [(400)] -0.0125 .18229 1 0 Mshowa p .002 w 0 .26608 m .00625 .26608 L s P [(600)] -0.0125 .26608 1 0 Mshowa p .002 w 0 .34987 m .00625 .34987 L s P [(800)] -0.0125 .34987 1 0 Mshowa p .002 w 0 .43366 m .00625 .43366 L s P [(1000)] -0.0125 .43366 1 0 Mshowa p .002 w 0 .51745 m .00625 .51745 L s P [(1200)] -0.0125 .51745 1 0 Mshowa p .002 w 0 .60124 m .00625 .60124 L s P [(1400)] -0.0125 .60124 1 0 Mshowa p .001 w 0 .03147 m .00375 .03147 L s P p .001 w 0 .04823 m .00375 .04823 L s P p .001 w 0 .06499 m .00375 .06499 L s P p .001 w 0 .08175 m .00375 .08175 L s P p .001 w 0 .11526 m .00375 .11526 L s P p .001 w 0 .13202 m .00375 .13202 L s P p .001 w 0 .14878 m .00375 .14878 L s P p .001 w 0 .16553 m .00375 .16553 L s P p .001 w 0 .19905 m .00375 .19905 L s P p .001 w 0 .21581 m .00375 .21581 L s P p .001 w 0 .23257 m .00375 .23257 L s P p .001 w 0 .24932 m .00375 .24932 L s P p .001 w 0 .28284 m .00375 .28284 L s P p .001 w 0 .2996 m .00375 .2996 L s P p .001 w 0 .31635 m .00375 .31635 L s P p .001 w 0 .33311 m .00375 .33311 L s P p .001 w 0 .36663 m .00375 .36663 L s P p .001 w 0 .38339 m .00375 .38339 L s P p .001 w 0 .40014 m .00375 .40014 L s P p .001 w 0 .4169 m .00375 .4169 L s P p .001 w 0 .45042 m .00375 .45042 L s P p .001 w 0 .46717 m .00375 .46717 L s P p .001 w 0 .48393 m .00375 .48393 L s P p .001 w 0 .50069 m .00375 .50069 L s P p .001 w 0 .53421 m .00375 .53421 L s P p .001 w 0 .55096 m .00375 .55096 L s P p .001 w 0 .56772 m .00375 .56772 L s P p .001 w 0 .58448 m .00375 .58448 L s P p .001 w 0 .61799 m .00375 .61799 L s P p .002 w 0 0 m 0 .61803 L s P P p p .002 w .02381 .61178 m .02381 .61803 L s P p .002 w .21429 .61178 m .21429 .61803 L s P p .002 w .40476 .61178 m .40476 .61803 L s P p .002 w .59524 .61178 m .59524 .61803 L s P p .002 w .78571 .61178 m .78571 .61803 L s P p .002 w .97619 .61178 m .97619 .61803 L s P p .001 w .0619 .61428 m .0619 .61803 L s P p .001 w .1 .61428 m .1 .61803 L s P p .001 w .1381 .61428 m .1381 .61803 L s P p .001 w .17619 .61428 m .17619 .61803 L s P p .001 w .25238 .61428 m .25238 .61803 L s P p .001 w .29048 .61428 m .29048 .61803 L s P p .001 w .32857 .61428 m .32857 .61803 L s P p .001 w .36667 .61428 m .36667 .61803 L s P p .001 w .44286 .61428 m .44286 .61803 L s P p .001 w .48095 .61428 m .48095 .61803 L s P p .001 w .51905 .61428 m .51905 .61803 L s P p .001 w .55714 .61428 m .55714 .61803 L s P p .001 w .63333 .61428 m .63333 .61803 L s P p .001 w .67143 .61428 m .67143 .61803 L s P p .001 w .70952 .61428 m .70952 .61803 L s P p .001 w .74762 .61428 m .74762 .61803 L s P p .001 w .82381 .61428 m .82381 .61803 L s P p .001 w .8619 .61428 m .8619 .61803 L s P p .001 w .9 .61428 m .9 .61803 L s P p .001 w .9381 .61428 m .9381 .61803 L s P p .002 w 0 .61803 m 1 .61803 L s P [(k[2, 0, 1, 0])] .5 .61803 0 -2 Mshowa p .002 w .99375 .01472 m 1 .01472 L s P p .002 w .99375 .0985 m 1 .0985 L s P p .002 w .99375 .18229 m 1 .18229 L s P p .002 w .99375 .26608 m 1 .26608 L s P p .002 w .99375 .34987 m 1 .34987 L s P p .002 w .99375 .43366 m 1 .43366 L s P p .002 w .99375 .51745 m 1 .51745 L s P p .002 w .99375 .60124 m 1 .60124 L s P p .001 w .99625 .03147 m 1 .03147 L s P p .001 w .99625 .04823 m 1 .04823 L s P p .001 w .99625 .06499 m 1 .06499 L s P p .001 w .99625 .08175 m 1 .08175 L s P p .001 w .99625 .11526 m 1 .11526 L s P p .001 w .99625 .13202 m 1 .13202 L s P p .001 w .99625 .14878 m 1 .14878 L s P p .001 w .99625 .16553 m 1 .16553 L s P p .001 w .99625 .19905 m 1 .19905 L s P p .001 w .99625 .21581 m 1 .21581 L s P p .001 w .99625 .23257 m 1 .23257 L s P p .001 w .99625 .24932 m 1 .24932 L s P p .001 w .99625 .28284 m 1 .28284 L s P p .001 w .99625 .2996 m 1 .2996 L s P p .001 w .99625 .31635 m 1 .31635 L s P p .001 w .99625 .33311 m 1 .33311 L s P p .001 w .99625 .36663 m 1 .36663 L s P p .001 w .99625 .38339 m 1 .38339 L s P p .001 w .99625 .40014 m 1 .40014 L s P p .001 w .99625 .4169 m 1 .4169 L s P p .001 w .99625 .45042 m 1 .45042 L s P p .001 w .99625 .46717 m 1 .46717 L s P p .001 w .99625 .48393 m 1 .48393 L s P p .001 w .99625 .50069 m 1 .50069 L s P p .001 w .99625 .53421 m 1 .53421 L s P p .001 w .99625 .55096 m 1 .55096 L s P p .001 w .99625 .56772 m 1 .56772 L s P p .001 w .99625 .58448 m 1 .58448 L s P p .001 w .99625 .61799 m 1 .61799 L s P p .002 w 1 0 m 1 .61803 L s P P p P p p p .004 w .02381 .01472 m .02505 .01472 L .02629 .01472 L .02753 .01472 L .02877 .01472 L .03001 .01472 L .03125 .01472 L .03249 .01472 L .03373 .01472 L .03497 .01472 L .03621 .01472 L .03869 .01472 L .03993 .01472 L .04117 .01472 L .04365 .01472 L .04613 .01472 L .04861 .01472 L .05357 .01472 L .05605 .01472 L .05853 .01472 L .06349 .01472 L .06845 .01473 L .07341 .01473 L .07837 .01474 L .08333 .01474 L .08829 .01475 L .09325 .01476 L .10317 .01479 L .1131 .01483 L .12302 .01488 L .13294 .01495 L .14286 .01504 L .15278 .01514 L .1627 .01527 L .18254 .01561 L .20238 .01608 L .22222 .0167 L .24206 .01751 L .2619 .01853 L .28175 .0198 L .30159 .02134 L .34127 .02541 L .38095 .03102 L .42063 .03851 L .46032 .04821 L .5 .06053 L .53968 .07585 L .57937 .09465 L .61905 .1174 L .65873 .14464 L Mistroke .69841 .17693 L .7381 .2149 L .77778 .25921 L .81746 .31058 L .85714 .36981 L .89683 .43772 L .93651 .51523 L .97619 .60332 L Mfstroke P P P 0 0 m 1 0 L 1 .61803 L 0 .61803 L closepath clip newpath MathSubEnd P % End of sub-graphic P p % Start of sub-graphic p 0.0238095 0.646763 0.477324 0.927051 MathSubStart %% Graphics /Courier findfont 10 scalefont setfont % Scaling calculations 0.0238095 0.000190476 0.0147151 0.000417429 [ [(0)] .02381 0 0 2 Msboxa [(1000)] .21429 0 0 2 Msboxa [(2000)] .40476 0 0 2 Msboxa [(3000)] .59524 0 0 2 Msboxa [(4000)] .78571 0 0 2 Msboxa [(5000)] .97619 0 0 2 Msboxa [(0)] -0.0125 .01472 1 0 Msboxa [(200)] -0.0125 .0982 1 0 Msboxa [(400)] -0.0125 .18169 1 0 Msboxa [(600)] -0.0125 .26517 1 0 Msboxa [(800)] -0.0125 .34866 1 0 Msboxa [(1000)] -0.0125 .43214 1 0 Msboxa [(1200)] -0.0125 .51563 1 0 Msboxa [(1400)] -0.0125 .59912 1 0 Msboxa [(k[1, 2, 0, 0])] .5 .61803 0 -2 Msboxa [ -0.001 -0.001 0 0 ] [ 1.001 .61903 0 0 ] ] MathScale % Start of Graphics 1 setlinecap 1 setlinejoin newpath [ ] 0 setdash p p .002 w .02381 0 m .02381 .00625 L s P [(0)] .02381 0 0 2 Mshowa p .002 w .21429 0 m .21429 .00625 L s P [(1000)] .21429 0 0 2 Mshowa p .002 w .40476 0 m .40476 .00625 L s P [(2000)] .40476 0 0 2 Mshowa p .002 w .59524 0 m .59524 .00625 L s P [(3000)] .59524 0 0 2 Mshowa p .002 w .78571 0 m .78571 .00625 L s P [(4000)] .78571 0 0 2 Mshowa p .002 w .97619 0 m .97619 .00625 L s P [(5000)] .97619 0 0 2 Mshowa p .001 w .0619 0 m .0619 .00375 L s P p .001 w .1 0 m .1 .00375 L s P p .001 w .1381 0 m .1381 .00375 L s P p .001 w .17619 0 m .17619 .00375 L s P p .001 w .25238 0 m .25238 .00375 L s P p .001 w .29048 0 m .29048 .00375 L s P p .001 w .32857 0 m .32857 .00375 L s P p .001 w .36667 0 m .36667 .00375 L s P p .001 w .44286 0 m .44286 .00375 L s P p .001 w .48095 0 m .48095 .00375 L s P p .001 w .51905 0 m .51905 .00375 L s P p .001 w .55714 0 m .55714 .00375 L s P p .001 w .63333 0 m .63333 .00375 L s P p .001 w .67143 0 m .67143 .00375 L s P p .001 w .70952 0 m .70952 .00375 L s P p .001 w .74762 0 m .74762 .00375 L s P p .001 w .82381 0 m .82381 .00375 L s P p .001 w .8619 0 m .8619 .00375 L s P p .001 w .9 0 m .9 .00375 L s P p .001 w .9381 0 m .9381 .00375 L s P p .002 w 0 0 m 1 0 L s P p .002 w 0 .01472 m .00625 .01472 L s P [(0)] -0.0125 .01472 1 0 Mshowa p .002 w 0 .0982 m .00625 .0982 L s P [(200)] -0.0125 .0982 1 0 Mshowa p .002 w 0 .18169 m .00625 .18169 L s P [(400)] -0.0125 .18169 1 0 Mshowa p .002 w 0 .26517 m .00625 .26517 L s P [(600)] -0.0125 .26517 1 0 Mshowa p .002 w 0 .34866 m .00625 .34866 L s P [(800)] -0.0125 .34866 1 0 Mshowa p .002 w 0 .43214 m .00625 .43214 L s P [(1000)] -0.0125 .43214 1 0 Mshowa p .002 w 0 .51563 m .00625 .51563 L s P [(1200)] -0.0125 .51563 1 0 Mshowa p .002 w 0 .59912 m .00625 .59912 L s P [(1400)] -0.0125 .59912 1 0 Mshowa p .001 w 0 .03141 m .00375 .03141 L s P p .001 w 0 .04811 m .00375 .04811 L s P p .001 w 0 .06481 m .00375 .06481 L s P p .001 w 0 .0815 m .00375 .0815 L s P p .001 w 0 .1149 m .00375 .1149 L s P p .001 w 0 .1316 m .00375 .1316 L s P p .001 w 0 .14829 m .00375 .14829 L s P p .001 w 0 .16499 m .00375 .16499 L s P p .001 w 0 .19838 m .00375 .19838 L s P p .001 w 0 .21508 m .00375 .21508 L s P p .001 w 0 .23178 m .00375 .23178 L s P p .001 w 0 .24848 m .00375 .24848 L s P p .001 w 0 .28187 m .00375 .28187 L s P p .001 w 0 .29857 m .00375 .29857 L s P p .001 w 0 .31526 m .00375 .31526 L s P p .001 w 0 .33196 m .00375 .33196 L s P p .001 w 0 .36536 m .00375 .36536 L s P p .001 w 0 .38205 m .00375 .38205 L s P p .001 w 0 .39875 m .00375 .39875 L s P p .001 w 0 .41545 m .00375 .41545 L s P p .001 w 0 .44884 m .00375 .44884 L s P p .001 w 0 .46554 m .00375 .46554 L s P p .001 w 0 .48224 m .00375 .48224 L s P p .001 w 0 .49893 m .00375 .49893 L s P p .001 w 0 .53233 m .00375 .53233 L s P p .001 w 0 .54902 m .00375 .54902 L s P p .001 w 0 .56572 m .00375 .56572 L s P p .001 w 0 .58242 m .00375 .58242 L s P p .001 w 0 .61581 m .00375 .61581 L s P p .002 w 0 0 m 0 .61803 L s P P p p .002 w .02381 .61178 m .02381 .61803 L s P p .002 w .21429 .61178 m .21429 .61803 L s P p .002 w .40476 .61178 m .40476 .61803 L s P p .002 w .59524 .61178 m .59524 .61803 L s P p .002 w .78571 .61178 m .78571 .61803 L s P p .002 w .97619 .61178 m .97619 .61803 L s P p .001 w .0619 .61428 m .0619 .61803 L s P p .001 w .1 .61428 m .1 .61803 L s P p .001 w .1381 .61428 m .1381 .61803 L s P p .001 w .17619 .61428 m .17619 .61803 L s P p .001 w .25238 .61428 m .25238 .61803 L s P p .001 w .29048 .61428 m .29048 .61803 L s P p .001 w .32857 .61428 m .32857 .61803 L s P p .001 w .36667 .61428 m .36667 .61803 L s P p .001 w .44286 .61428 m .44286 .61803 L s P p .001 w .48095 .61428 m .48095 .61803 L s P p .001 w .51905 .61428 m .51905 .61803 L s P p .001 w .55714 .61428 m .55714 .61803 L s P p .001 w .63333 .61428 m .63333 .61803 L s P p .001 w .67143 .61428 m .67143 .61803 L s P p .001 w .70952 .61428 m .70952 .61803 L s P p .001 w .74762 .61428 m .74762 .61803 L s P p .001 w .82381 .61428 m .82381 .61803 L s P p .001 w .8619 .61428 m .8619 .61803 L s P p .001 w .9 .61428 m .9 .61803 L s P p .001 w .9381 .61428 m .9381 .61803 L s P p .002 w 0 .61803 m 1 .61803 L s P [(k[1, 2, 0, 0])] .5 .61803 0 -2 Mshowa p .002 w .99375 .01472 m 1 .01472 L s P p .002 w .99375 .0982 m 1 .0982 L s P p .002 w .99375 .18169 m 1 .18169 L s P p .002 w .99375 .26517 m 1 .26517 L s P p .002 w .99375 .34866 m 1 .34866 L s P p .002 w .99375 .43214 m 1 .43214 L s P p .002 w .99375 .51563 m 1 .51563 L s P p .002 w .99375 .59912 m 1 .59912 L s P p .001 w .99625 .03141 m 1 .03141 L s P p .001 w .99625 .04811 m 1 .04811 L s P p .001 w .99625 .06481 m 1 .06481 L s P p .001 w .99625 .0815 m 1 .0815 L s P p .001 w .99625 .1149 m 1 .1149 L s P p .001 w .99625 .1316 m 1 .1316 L s P p .001 w .99625 .14829 m 1 .14829 L s P p .001 w .99625 .16499 m 1 .16499 L s P p .001 w .99625 .19838 m 1 .19838 L s P p .001 w .99625 .21508 m 1 .21508 L s P p .001 w .99625 .23178 m 1 .23178 L s P p .001 w .99625 .24848 m 1 .24848 L s P p .001 w .99625 .28187 m 1 .28187 L s P p .001 w .99625 .29857 m 1 .29857 L s P p .001 w .99625 .31526 m 1 .31526 L s P p .001 w .99625 .33196 m 1 .33196 L s P p .001 w .99625 .36536 m 1 .36536 L s P p .001 w .99625 .38205 m 1 .38205 L s P p .001 w .99625 .39875 m 1 .39875 L s P p .001 w .99625 .41545 m 1 .41545 L s P p .001 w .99625 .44884 m 1 .44884 L s P p .001 w .99625 .46554 m 1 .46554 L s P p .001 w .99625 .48224 m 1 .48224 L s P p .001 w .99625 .49893 m 1 .49893 L s P p .001 w .99625 .53233 m 1 .53233 L s P p .001 w .99625 .54902 m 1 .54902 L s P p .001 w .99625 .56572 m 1 .56572 L s P p .001 w .99625 .58242 m 1 .58242 L s P p .001 w .99625 .61581 m 1 .61581 L s P p .002 w 1 0 m 1 .61803 L s P P p P p p p .004 w .02381 .01472 m .02505 .01472 L .02629 .01472 L .02753 .01472 L .02877 .01472 L .03001 .01472 L .03125 .01472 L .03249 .01472 L .03373 .01472 L .03497 .01472 L .03621 .01472 L .03869 .01472 L .04117 .01472 L .04365 .01472 L .04613 .01472 L .04861 .01472 L .05357 .01473 L .05853 .01474 L .06349 .01475 L .06845 .01476 L .07341 .01478 L .08333 .01482 L .09325 .01488 L .10317 .01495 L .1131 .01505 L .12302 .01517 L .14286 .0155 L .1627 .01595 L .18254 .01655 L .20238 .01733 L .22222 .01831 L .24206 .01951 L .2619 .02097 L .30159 .02475 L .34127 .02992 L .38095 .03672 L .42063 .04545 L .46032 .05641 L .5 .06996 L .53968 .08645 L .57937 .10628 L .61905 .12989 L .65873 .15774 L .69841 .19034 L .7381 .22823 L .77778 .27201 L .81746 .32232 L .85714 .37983 L .89683 .4453 L .93651 .51951 L Mistroke .97619 .60332 L Mfstroke P P P 0 0 m 1 0 L 1 .61803 L 0 .61803 L closepath clip newpath MathSubEnd P % End of sub-graphic % Start of sub-graphic p 0.522676 0.646763 0.97619 0.927051 MathSubStart %% Graphics /Courier findfont 10 scalefont setfont % Scaling calculations 0.0238095 0.000190476 0.0147151 0.000288348 [ [(0)] .02381 0 0 2 Msboxa [(1000)] .21429 0 0 2 Msboxa [(2000)] .40476 0 0 2 Msboxa [(3000)] .59524 0 0 2 Msboxa [(4000)] .78571 0 0 2 Msboxa [(5000)] .97619 0 0 2 Msboxa [(0)] -0.0125 .01472 1 0 Msboxa [(500)] -0.0125 .15889 1 0 Msboxa [(1000)] -0.0125 .30306 1 0 Msboxa [(1500)] -0.0125 .44724 1 0 Msboxa [(2000)] -0.0125 .59141 1 0 Msboxa [(k[2, 0, 0, 0])] .5 .61803 0 -2 Msboxa [ -0.001 -0.001 0 0 ] [ 1.001 .61903 0 0 ] ] MathScale % Start of Graphics 1 setlinecap 1 setlinejoin newpath [ ] 0 setdash p p .002 w .02381 0 m .02381 .00625 L s P [(0)] .02381 0 0 2 Mshowa p .002 w .21429 0 m .21429 .00625 L s P [(1000)] .21429 0 0 2 Mshowa p .002 w .40476 0 m .40476 .00625 L s P [(2000)] .40476 0 0 2 Mshowa p .002 w .59524 0 m .59524 .00625 L s P [(3000)] .59524 0 0 2 Mshowa p .002 w .78571 0 m .78571 .00625 L s P [(4000)] .78571 0 0 2 Mshowa p .002 w .97619 0 m .97619 .00625 L s P [(5000)] .97619 0 0 2 Mshowa p .001 w .0619 0 m .0619 .00375 L s P p .001 w .1 0 m .1 .00375 L s P p .001 w .1381 0 m .1381 .00375 L s P p .001 w .17619 0 m .17619 .00375 L s P p .001 w .25238 0 m .25238 .00375 L s P p .001 w .29048 0 m .29048 .00375 L s P p .001 w .32857 0 m .32857 .00375 L s P p .001 w .36667 0 m .36667 .00375 L s P p .001 w .44286 0 m .44286 .00375 L s P p .001 w .48095 0 m .48095 .00375 L s P p .001 w .51905 0 m .51905 .00375 L s P p .001 w .55714 0 m .55714 .00375 L s P p .001 w .63333 0 m .63333 .00375 L s P p .001 w .67143 0 m .67143 .00375 L s P p .001 w .70952 0 m .70952 .00375 L s P p .001 w .74762 0 m .74762 .00375 L s P p .001 w .82381 0 m .82381 .00375 L s P p .001 w .8619 0 m .8619 .00375 L s P p .001 w .9 0 m .9 .00375 L s P p .001 w .9381 0 m .9381 .00375 L s P p .002 w 0 0 m 1 0 L s P p .002 w 0 .01472 m .00625 .01472 L s P [(0)] -0.0125 .01472 1 0 Mshowa p .002 w 0 .15889 m .00625 .15889 L s P [(500)] -0.0125 .15889 1 0 Mshowa p .002 w 0 .30306 m .00625 .30306 L s P [(1000)] -0.0125 .30306 1 0 Mshowa p .002 w 0 .44724 m .00625 .44724 L s P [(1500)] -0.0125 .44724 1 0 Mshowa p .002 w 0 .59141 m .00625 .59141 L s P [(2000)] -0.0125 .59141 1 0 Mshowa p .001 w 0 .04355 m .00375 .04355 L s P p .001 w 0 .07238 m .00375 .07238 L s P p .001 w 0 .10122 m .00375 .10122 L s P p .001 w 0 .13005 m .00375 .13005 L s P p .001 w 0 .18772 m .00375 .18772 L s P p .001 w 0 .21656 m .00375 .21656 L s P p .001 w 0 .24539 m .00375 .24539 L s P p .001 w 0 .27423 m .00375 .27423 L s P p .001 w 0 .3319 m .00375 .3319 L s P p .001 w 0 .36073 m .00375 .36073 L s P p .001 w 0 .38957 m .00375 .38957 L s P p .001 w 0 .4184 m .00375 .4184 L s P p .001 w 0 .47607 m .00375 .47607 L s P p .001 w 0 .50491 m .00375 .50491 L s P p .001 w 0 .53374 m .00375 .53374 L s P p .001 w 0 .56258 m .00375 .56258 L s P p .002 w 0 0 m 0 .61803 L s P P p p .002 w .02381 .61178 m .02381 .61803 L s P p .002 w .21429 .61178 m .21429 .61803 L s P p .002 w .40476 .61178 m .40476 .61803 L s P p .002 w .59524 .61178 m .59524 .61803 L s P p .002 w .78571 .61178 m .78571 .61803 L s P p .002 w .97619 .61178 m .97619 .61803 L s P p .001 w .0619 .61428 m .0619 .61803 L s P p .001 w .1 .61428 m .1 .61803 L s P p .001 w .1381 .61428 m .1381 .61803 L s P p .001 w .17619 .61428 m .17619 .61803 L s P p .001 w .25238 .61428 m .25238 .61803 L s P p .001 w .29048 .61428 m .29048 .61803 L s P p .001 w .32857 .61428 m .32857 .61803 L s P p .001 w .36667 .61428 m .36667 .61803 L s P p .001 w .44286 .61428 m .44286 .61803 L s P p .001 w .48095 .61428 m .48095 .61803 L s P p .001 w .51905 .61428 m .51905 .61803 L s P p .001 w .55714 .61428 m .55714 .61803 L s P p .001 w .63333 .61428 m .63333 .61803 L s P p .001 w .67143 .61428 m .67143 .61803 L s P p .001 w .70952 .61428 m .70952 .61803 L s P p .001 w .74762 .61428 m .74762 .61803 L s P p .001 w .82381 .61428 m .82381 .61803 L s P p .001 w .8619 .61428 m .8619 .61803 L s P p .001 w .9 .61428 m .9 .61803 L s P p .001 w .9381 .61428 m .9381 .61803 L s P p .002 w 0 .61803 m 1 .61803 L s P [(k[2, 0, 0, 0])] .5 .61803 0 -2 Mshowa p .002 w .99375 .01472 m 1 .01472 L s P p .002 w .99375 .15889 m 1 .15889 L s P p .002 w .99375 .30306 m 1 .30306 L s P p .002 w .99375 .44724 m 1 .44724 L s P p .002 w .99375 .59141 m 1 .59141 L s P p .001 w .99625 .04355 m 1 .04355 L s P p .001 w .99625 .07238 m 1 .07238 L s P p .001 w .99625 .10122 m 1 .10122 L s P p .001 w .99625 .13005 m 1 .13005 L s P p .001 w .99625 .18772 m 1 .18772 L s P p .001 w .99625 .21656 m 1 .21656 L s P p .001 w .99625 .24539 m 1 .24539 L s P p .001 w .99625 .27423 m 1 .27423 L s P p .001 w .99625 .3319 m 1 .3319 L s P p .001 w .99625 .36073 m 1 .36073 L s P p .001 w .99625 .38957 m 1 .38957 L s P p .001 w .99625 .4184 m 1 .4184 L s P p .001 w .99625 .47607 m 1 .47607 L s P p .001 w .99625 .50491 m 1 .50491 L s P p .001 w .99625 .53374 m 1 .53374 L s P p .001 w .99625 .56258 m 1 .56258 L s P p .002 w 1 0 m 1 .61803 L s P P p P p p p .004 w .02381 .01472 m .04365 .01579 L .06349 .01721 L .10317 .02107 L .14286 .02633 L .18254 .03303 L .22222 .04123 L .2619 .051 L .30159 .06242 L .34127 .07556 L .38095 .09052 L .42063 .10737 L .46032 .12622 L .5 .14717 L .53968 .17031 L .57937 .19574 L .61905 .22359 L .65873 .25397 L .69841 .28699 L .7381 .32278 L .77778 .36147 L .81746 .40319 L .85714 .44809 L .89683 .49631 L .93651 .548 L .97619 .60332 L s P P P 0 0 m 1 0 L 1 .61803 L 0 .61803 L closepath clip newpath MathSubEnd P % End of sub-graphic P p % Start of sub-graphic p 0.0238095 0.95508 0.477324 1.23537 MathSubStart %% Graphics /Courier findfont 10 scalefont setfont % Scaling calculations 0.0238095 0.000190476 0.0147151 0.00335167 [ [(0)] .02381 0 0 2 Msboxa [(1000)] .21429 0 0 2 Msboxa [(2000)] .40476 0 0 2 Msboxa [(3000)] .59524 0 0 2 Msboxa [(4000)] .78571 0 0 2 Msboxa [(5000)] .97619 0 0 2 Msboxa [(0)] -0.0125 .01472 1 0 Msboxa [(25)] -0.0125 .09851 1 0 Msboxa [(50)] -0.0125 .1823 1 0 Msboxa [(75)] -0.0125 .26609 1 0 Msboxa [(100)] -0.0125 .34988 1 0 Msboxa [(125)] -0.0125 .43367 1 0 Msboxa [(150)] -0.0125 .51747 1 0 Msboxa [(175)] -0.0125 .60126 1 0 Msboxa [(k[1, 1, 0, 1])] .5 .61803 0 -2 Msboxa [ -0.001 -0.001 0 0 ] [ 1.001 .61903 0 0 ] ] MathScale % Start of Graphics 1 setlinecap 1 setlinejoin newpath [ ] 0 setdash p p .002 w .02381 0 m .02381 .00625 L s P [(0)] .02381 0 0 2 Mshowa p .002 w .21429 0 m .21429 .00625 L s P [(1000)] .21429 0 0 2 Mshowa p .002 w .40476 0 m .40476 .00625 L s P [(2000)] .40476 0 0 2 Mshowa p .002 w .59524 0 m .59524 .00625 L s P [(3000)] .59524 0 0 2 Mshowa p .002 w .78571 0 m .78571 .00625 L s P [(4000)] .78571 0 0 2 Mshowa p .002 w .97619 0 m .97619 .00625 L s P [(5000)] .97619 0 0 2 Mshowa p .001 w .0619 0 m .0619 .00375 L s P p .001 w .1 0 m .1 .00375 L s P p .001 w .1381 0 m .1381 .00375 L s P p .001 w .17619 0 m .17619 .00375 L s P p .001 w .25238 0 m .25238 .00375 L s P p .001 w .29048 0 m .29048 .00375 L s P p .001 w .32857 0 m .32857 .00375 L s P p .001 w .36667 0 m .36667 .00375 L s P p .001 w .44286 0 m .44286 .00375 L s P p .001 w .48095 0 m .48095 .00375 L s P p .001 w .51905 0 m .51905 .00375 L s P p .001 w .55714 0 m .55714 .00375 L s P p .001 w .63333 0 m .63333 .00375 L s P p .001 w .67143 0 m .67143 .00375 L s P p .001 w .70952 0 m .70952 .00375 L s P p .001 w .74762 0 m .74762 .00375 L s P p .001 w .82381 0 m .82381 .00375 L s P p .001 w .8619 0 m .8619 .00375 L s P p .001 w .9 0 m .9 .00375 L s P p .001 w .9381 0 m .9381 .00375 L s P p .002 w 0 0 m 1 0 L s P p .002 w 0 .01472 m .00625 .01472 L s P [(0)] -0.0125 .01472 1 0 Mshowa p .002 w 0 .09851 m .00625 .09851 L s P [(25)] -0.0125 .09851 1 0 Mshowa p .002 w 0 .1823 m .00625 .1823 L s P [(50)] -0.0125 .1823 1 0 Mshowa p .002 w 0 .26609 m .00625 .26609 L s P [(75)] -0.0125 .26609 1 0 Mshowa p .002 w 0 .34988 m .00625 .34988 L s P [(100)] -0.0125 .34988 1 0 Mshowa p .002 w 0 .43367 m .00625 .43367 L s P [(125)] -0.0125 .43367 1 0 Mshowa p .002 w 0 .51747 m .00625 .51747 L s P [(150)] -0.0125 .51747 1 0 Mshowa p .002 w 0 .60126 m .00625 .60126 L s P [(175)] -0.0125 .60126 1 0 Mshowa p .001 w 0 .03147 m .00375 .03147 L s P p .001 w 0 .04823 m .00375 .04823 L s P p .001 w 0 .06499 m .00375 .06499 L s P p .001 w 0 .08175 m .00375 .08175 L s P p .001 w 0 .11527 m .00375 .11527 L s P p .001 w 0 .13202 m .00375 .13202 L s P p .001 w 0 .14878 m .00375 .14878 L s P p .001 w 0 .16554 m .00375 .16554 L s P p .001 w 0 .19906 m .00375 .19906 L s P p .001 w 0 .21582 m .00375 .21582 L s P p .001 w 0 .23257 m .00375 .23257 L s P p .001 w 0 .24933 m .00375 .24933 L s P p .001 w 0 .28285 m .00375 .28285 L s P p .001 w 0 .29961 m .00375 .29961 L s P p .001 w 0 .31637 m .00375 .31637 L s P p .001 w 0 .33312 m .00375 .33312 L s P p .001 w 0 .36664 m .00375 .36664 L s P p .001 w 0 .3834 m .00375 .3834 L s P p .001 w 0 .40016 m .00375 .40016 L s P p .001 w 0 .41692 m .00375 .41692 L s P p .001 w 0 .45043 m .00375 .45043 L s P p .001 w 0 .46719 m .00375 .46719 L s P p .001 w 0 .48395 m .00375 .48395 L s P p .001 w 0 .50071 m .00375 .50071 L s P p .001 w 0 .53422 m .00375 .53422 L s P p .001 w 0 .55098 m .00375 .55098 L s P p .001 w 0 .56774 m .00375 .56774 L s P p .001 w 0 .5845 m .00375 .5845 L s P p .001 w 0 .61802 m .00375 .61802 L s P p .002 w 0 0 m 0 .61803 L s P P p p .002 w .02381 .61178 m .02381 .61803 L s P p .002 w .21429 .61178 m .21429 .61803 L s P p .002 w .40476 .61178 m .40476 .61803 L s P p .002 w .59524 .61178 m .59524 .61803 L s P p .002 w .78571 .61178 m .78571 .61803 L s P p .002 w .97619 .61178 m .97619 .61803 L s P p .001 w .0619 .61428 m .0619 .61803 L s P p .001 w .1 .61428 m .1 .61803 L s P p .001 w .1381 .61428 m .1381 .61803 L s P p .001 w .17619 .61428 m .17619 .61803 L s P p .001 w .25238 .61428 m .25238 .61803 L s P p .001 w .29048 .61428 m .29048 .61803 L s P p .001 w .32857 .61428 m .32857 .61803 L s P p .001 w .36667 .61428 m .36667 .61803 L s P p .001 w .44286 .61428 m .44286 .61803 L s P p .001 w .48095 .61428 m .48095 .61803 L s P p .001 w .51905 .61428 m .51905 .61803 L s P p .001 w .55714 .61428 m .55714 .61803 L s P p .001 w .63333 .61428 m .63333 .61803 L s P p .001 w .67143 .61428 m .67143 .61803 L s P p .001 w .70952 .61428 m .70952 .61803 L s P p .001 w .74762 .61428 m .74762 .61803 L s P p .001 w .82381 .61428 m .82381 .61803 L s P p .001 w .8619 .61428 m .8619 .61803 L s P p .001 w .9 .61428 m .9 .61803 L s P p .001 w .9381 .61428 m .9381 .61803 L s P p .002 w 0 .61803 m 1 .61803 L s P [(k[1, 1, 0, 1])] .5 .61803 0 -2 Mshowa p .002 w .99375 .01472 m 1 .01472 L s P p .002 w .99375 .09851 m 1 .09851 L s P p .002 w .99375 .1823 m 1 .1823 L s P p .002 w .99375 .26609 m 1 .26609 L s P p .002 w .99375 .34988 m 1 .34988 L s P p .002 w .99375 .43367 m 1 .43367 L s P p .002 w .99375 .51747 m 1 .51747 L s P p .002 w .99375 .60126 m 1 .60126 L s P p .001 w .99625 .03147 m 1 .03147 L s P p .001 w .99625 .04823 m 1 .04823 L s P p .001 w .99625 .06499 m 1 .06499 L s P p .001 w .99625 .08175 m 1 .08175 L s P p .001 w .99625 .11527 m 1 .11527 L s P p .001 w .99625 .13202 m 1 .13202 L s P p .001 w .99625 .14878 m 1 .14878 L s P p .001 w .99625 .16554 m 1 .16554 L s P p .001 w .99625 .19906 m 1 .19906 L s P p .001 w .99625 .21582 m 1 .21582 L s P p .001 w .99625 .23257 m 1 .23257 L s P p .001 w .99625 .24933 m 1 .24933 L s P p .001 w .99625 .28285 m 1 .28285 L s P p .001 w .99625 .29961 m 1 .29961 L s P p .001 w .99625 .31637 m 1 .31637 L s P p .001 w .99625 .33312 m 1 .33312 L s P p .001 w .99625 .36664 m 1 .36664 L s P p .001 w .99625 .3834 m 1 .3834 L s P p .001 w .99625 .40016 m 1 .40016 L s P p .001 w .99625 .41692 m 1 .41692 L s P p .001 w .99625 .45043 m 1 .45043 L s P p .001 w .99625 .46719 m 1 .46719 L s P p .001 w .99625 .48395 m 1 .48395 L s P p .001 w .99625 .50071 m 1 .50071 L s P p .001 w .99625 .53422 m 1 .53422 L s P p .001 w .99625 .55098 m 1 .55098 L s P p .001 w .99625 .56774 m 1 .56774 L s P p .001 w .99625 .5845 m 1 .5845 L s P p .001 w .99625 .61802 m 1 .61802 L s P p .002 w 1 0 m 1 .61803 L s P P p P p p p .004 w .02381 .01472 m .02505 .01472 L .02629 .01472 L .02753 .01472 L .02877 .01472 L .03001 .01472 L .03125 .01472 L .03249 .01472 L .03373 .01472 L .03497 .01472 L .03621 .01472 L .03745 .01472 L .03869 .01472 L .03993 .01472 L .04117 .01472 L .04241 .01472 L .04365 .01472 L .04489 .01472 L .04613 .01472 L .04737 .01472 L .04861 .01472 L .04985 .01472 L .05109 .01472 L .05357 .01472 L .05481 .01472 L .05605 .01472 L .05853 .01472 L .06101 .01472 L .06349 .01472 L .06597 .01472 L .06845 .01472 L .07093 .01472 L .07341 .01472 L .07589 .01472 L .07837 .01472 L .08333 .01472 L .08581 .01472 L .08829 .01472 L .09325 .01472 L .09821 .01472 L .10317 .01472 L .10813 .01472 L .1131 .01472 L .11806 .01472 L .12302 .01472 L .12798 .01472 L .13294 .01472 L .14286 .01473 L .14782 .01473 L .15278 .01473 L Mistroke .1627 .01474 L .17262 .01476 L .18254 .01477 L .19246 .0148 L .20238 .01483 L .2123 .01486 L .22222 .01491 L .23214 .01497 L .24206 .01504 L .2619 .01524 L .28175 .01551 L .30159 .01589 L .32143 .01639 L .34127 .01706 L .36111 .01792 L .38095 .01901 L .42063 .02206 L .44048 .02412 L .46032 .02661 L .5 .03314 L .53968 .04224 L .57937 .05458 L .61905 .07096 L .65873 .09229 L .69841 .11963 L .7381 .15419 L .77778 .19734 L .81746 .25062 L .85714 .31578 L .89683 .39478 L .93651 .48981 L .97619 .60332 L Mfstroke P P P 0 0 m 1 0 L 1 .61803 L 0 .61803 L closepath clip newpath MathSubEnd P % End of sub-graphic % Start of sub-graphic p 0.522676 0.95508 0.97619 1.23537 MathSubStart %% Graphics /Courier findfont 10 scalefont setfont % Scaling calculations 0.0238095 0.000190476 0.0147151 0.00260383 [ [(0)] .02381 0 0 2 Msboxa [(1000)] .21429 0 0 2 Msboxa [(2000)] .40476 0 0 2 Msboxa [(3000)] .59524 0 0 2 Msboxa [(4000)] .78571 0 0 2 Msboxa [(5000)] .97619 0 0 2 Msboxa [(0)] -0.0125 .01472 1 0 Msboxa [(50)] -0.0125 .14491 1 0 Msboxa [(100)] -0.0125 .2751 1 0 Msboxa [(150)] -0.0125 .40529 1 0 Msboxa [(200)] -0.0125 .53548 1 0 Msboxa [(k[1, 1, 1, 0])] .5 .61803 0 -2 Msboxa [ -0.001 -0.001 0 0 ] [ 1.001 .61903 0 0 ] ] MathScale % Start of Graphics 1 setlinecap 1 setlinejoin newpath [ ] 0 setdash p p .002 w .02381 0 m .02381 .00625 L s P [(0)] .02381 0 0 2 Mshowa p .002 w .21429 0 m .21429 .00625 L s P [(1000)] .21429 0 0 2 Mshowa p .002 w .40476 0 m .40476 .00625 L s P [(2000)] .40476 0 0 2 Mshowa p .002 w .59524 0 m .59524 .00625 L s P [(3000)] .59524 0 0 2 Mshowa p .002 w .78571 0 m .78571 .00625 L s P [(4000)] .78571 0 0 2 Mshowa p .002 w .97619 0 m .97619 .00625 L s P [(5000)] .97619 0 0 2 Mshowa p .001 w .0619 0 m .0619 .00375 L s P p .001 w .1 0 m .1 .00375 L s P p .001 w .1381 0 m .1381 .00375 L s P p .001 w .17619 0 m .17619 .00375 L s P p .001 w .25238 0 m .25238 .00375 L s P p .001 w .29048 0 m .29048 .00375 L s P p .001 w .32857 0 m .32857 .00375 L s P p .001 w .36667 0 m .36667 .00375 L s P p .001 w .44286 0 m .44286 .00375 L s P p .001 w .48095 0 m .48095 .00375 L s P p .001 w .51905 0 m .51905 .00375 L s P p .001 w .55714 0 m .55714 .00375 L s P p .001 w .63333 0 m .63333 .00375 L s P p .001 w .67143 0 m .67143 .00375 L s P p .001 w .70952 0 m .70952 .00375 L s P p .001 w .74762 0 m .74762 .00375 L s P p .001 w .82381 0 m .82381 .00375 L s P p .001 w .8619 0 m .8619 .00375 L s P p .001 w .9 0 m .9 .00375 L s P p .001 w .9381 0 m .9381 .00375 L s P p .002 w 0 0 m 1 0 L s P p .002 w 0 .01472 m .00625 .01472 L s P [(0)] -0.0125 .01472 1 0 Mshowa p .002 w 0 .14491 m .00625 .14491 L s P [(50)] -0.0125 .14491 1 0 Mshowa p .002 w 0 .2751 m .00625 .2751 L s P [(100)] -0.0125 .2751 1 0 Mshowa p .002 w 0 .40529 m .00625 .40529 L s P [(150)] -0.0125 .40529 1 0 Mshowa p .002 w 0 .53548 m .00625 .53548 L s P [(200)] -0.0125 .53548 1 0 Mshowa p .001 w 0 .04075 m .00375 .04075 L s P p .001 w 0 .06679 m .00375 .06679 L s P p .001 w 0 .09283 m .00375 .09283 L s P p .001 w 0 .11887 m .00375 .11887 L s P p .001 w 0 .17094 m .00375 .17094 L s P p .001 w 0 .19698 m .00375 .19698 L s P p .001 w 0 .22302 m .00375 .22302 L s P p .001 w 0 .24906 m .00375 .24906 L s P p .001 w 0 .30114 m .00375 .30114 L s P p .001 w 0 .32717 m .00375 .32717 L s P p .001 w 0 .35321 m .00375 .35321 L s P p .001 w 0 .37925 m .00375 .37925 L s P p .001 w 0 .43133 m .00375 .43133 L s P p .001 w 0 .45737 m .00375 .45737 L s P p .001 w 0 .4834 m .00375 .4834 L s P p .001 w 0 .50944 m .00375 .50944 L s P p .001 w 0 .56152 m .00375 .56152 L s P p .001 w 0 .58756 m .00375 .58756 L s P p .001 w 0 .6136 m .00375 .6136 L s P p .002 w 0 0 m 0 .61803 L s P P p p .002 w .02381 .61178 m .02381 .61803 L s P p .002 w .21429 .61178 m .21429 .61803 L s P p .002 w .40476 .61178 m .40476 .61803 L s P p .002 w .59524 .61178 m .59524 .61803 L s P p .002 w .78571 .61178 m .78571 .61803 L s P p .002 w .97619 .61178 m .97619 .61803 L s P p .001 w .0619 .61428 m .0619 .61803 L s P p .001 w .1 .61428 m .1 .61803 L s P p .001 w .1381 .61428 m .1381 .61803 L s P p .001 w .17619 .61428 m .17619 .61803 L s P p .001 w .25238 .61428 m .25238 .61803 L s P p .001 w .29048 .61428 m .29048 .61803 L s P p .001 w .32857 .61428 m .32857 .61803 L s P p .001 w .36667 .61428 m .36667 .61803 L s P p .001 w .44286 .61428 m .44286 .61803 L s P p .001 w .48095 .61428 m .48095 .61803 L s P p .001 w .51905 .61428 m .51905 .61803 L s P p .001 w .55714 .61428 m .55714 .61803 L s P p .001 w .63333 .61428 m .63333 .61803 L s P p .001 w .67143 .61428 m .67143 .61803 L s P p .001 w .70952 .61428 m .70952 .61803 L s P p .001 w .74762 .61428 m .74762 .61803 L s P p .001 w .82381 .61428 m .82381 .61803 L s P p .001 w .8619 .61428 m .8619 .61803 L s P p .001 w .9 .61428 m .9 .61803 L s P p .001 w .9381 .61428 m .9381 .61803 L s P p .002 w 0 .61803 m 1 .61803 L s P [(k[1, 1, 1, 0])] .5 .61803 0 -2 Mshowa p .002 w .99375 .01472 m 1 .01472 L s P p .002 w .99375 .14491 m 1 .14491 L s P p .002 w .99375 .2751 m 1 .2751 L s P p .002 w .99375 .40529 m 1 .40529 L s P p .002 w .99375 .53548 m 1 .53548 L s P p .001 w .99625 .04075 m 1 .04075 L s P p .001 w .99625 .06679 m 1 .06679 L s P p .001 w .99625 .09283 m 1 .09283 L s P p .001 w .99625 .11887 m 1 .11887 L s P p .001 w .99625 .17094 m 1 .17094 L s P p .001 w .99625 .19698 m 1 .19698 L s P p .001 w .99625 .22302 m 1 .22302 L s P p .001 w .99625 .24906 m 1 .24906 L s P p .001 w .99625 .30114 m 1 .30114 L s P p .001 w .99625 .32717 m 1 .32717 L s P p .001 w .99625 .35321 m 1 .35321 L s P p .001 w .99625 .37925 m 1 .37925 L s P p .001 w .99625 .43133 m 1 .43133 L s P p .001 w .99625 .45737 m 1 .45737 L s P p .001 w .99625 .4834 m 1 .4834 L s P p .001 w .99625 .50944 m 1 .50944 L s P p .001 w .99625 .56152 m 1 .56152 L s P p .001 w .99625 .58756 m 1 .58756 L s P p .001 w .99625 .6136 m 1 .6136 L s P p .002 w 1 0 m 1 .61803 L s P P p P p p p .004 w .02381 .01472 m .02505 .01472 L .02629 .01472 L .02753 .01472 L .02877 .01472 L .03001 .01472 L .03125 .01472 L .03249 .01472 L .03373 .01472 L .03497 .01472 L .03621 .01472 L .03745 .01472 L .03869 .01472 L .03993 .01472 L .04117 .01472 L .04241 .01472 L .04365 .01472 L .04613 .01472 L .04737 .01472 L .04861 .01472 L .04985 .01472 L .05109 .01472 L .05357 .01472 L .05605 .01472 L .05853 .01472 L .06101 .01472 L .06349 .01472 L .06597 .01472 L .06845 .01472 L .07093 .01472 L .07341 .01472 L .07837 .01472 L .08333 .01472 L .08829 .01472 L .09325 .01472 L .09821 .01473 L .10317 .01473 L .1131 .01474 L .11806 .01475 L .12302 .01476 L .13294 .01478 L .14286 .01482 L .15278 .01486 L .1627 .01492 L .17262 .015 L .18254 .0151 L .20238 .01536 L .2123 .01553 L .22222 .01574 L .24206 .01626 L Mistroke .2619 .01695 L .28175 .01786 L .30159 .01901 L .32143 .02043 L .34127 .02218 L .38095 .02679 L .42063 .0332 L .46032 .04178 L .5 .05296 L .53968 .0672 L .57937 .085 L .61905 .10689 L .65873 .13346 L .69841 .16536 L .7381 .20326 L .77778 .24793 L .81746 .30016 L .85714 .36083 L .89683 .43089 L .93651 .51135 L .97619 .60332 L Mfstroke P P P 0 0 m 1 0 L 1 .61803 L 0 .61803 L closepath clip newpath MathSubEnd P % End of sub-graphic P P % End of Graphics MathPictureEnd :[font = output; output; inactive; preserveAspect; endGroup; endGroup] GraphicsArray["<<>>"] ;[o] -GraphicsArray- :[font = section; inactive; preserveAspect; fontSize = 12] Survival and Hazard Functions :[font = text; inactive; preserveAspect] The survival and hazard functions play a key role in carcinogenesis modeling. They help answer a variety of questions arising from quantitative cancer research. This section briefly demonstrates computing and plotting of these two important functions. The survival function is computed using the characteristic method from standard partial differential equation  theory. :[font = input; preserveAspect] Survival[a_,b_,d1_,d2_,d3_,p1_,p2_,p3_,u_,v_,t0_]:=Module[ {ode,init,odeSoln,z1,z2,z3,t}, ode={z1'[t]==-b[t] z1[t]^2+(a[t]+b[t]+d1[t]) z1[t]-a[t] z2[t]-d1[t], z2'[t]==-p2[t] z1[t] z3[t]-p1[t] z1[t]+(p1[t]+p2[t]+d2[t]) z2[t]-d2[t], z3'[t]==(u[t]+p3[t]+d3[t]) z3[t]-d3[t]}; init={z1[t0]==z2[t0]==z3[t0]==1}; odeSoln=NDSolve[Join[ode,init],{z1,z2,z3},{t,0,t0},MaxSteps->3000]; NIntegrate[Evaluate[v[t] (z1[t]-1) /.odeSoln[[1]] ],{t,0,t0}, MaxRecursion->10]//Exp]; :[font = text; inactive; preserveAspect] Note that this approach allows the cell kinetic parameters to be time-dependent. The following example computes the survival probabilities using a linear function for one of the model parameters. :[font = input; preserveAspect] survivalList=Table[ {i,Survival[0.0005&,0.0019&,0.0015&,0.0016&,0.0017&,0.0005&, 0.0005&,0.0005&,0.0000003&,0.03 (1+0.0000015 #) &,i]}, {i,0,6000,100}]; :[font = input; preserveAspect; startGroup] ListPlot[survivalList,PlotJoined->True,Frame->True, PlotLabel->FontForm["A Survival Curve",{"Palatino-Bold",18}], FrameLabel->{"Time ", "Survival Probability"}] :[font = postscript; PostScript; formatAsPostScript; output; inactive; preserveAspect; pictureLeft = 100; pictureWidth = 413.25; pictureHeight = 255.375] %! %%Creator: Mathematica %%AspectRatio: .61803 MathPictureStart %% Graphics /Courier findfont 10 scalefont setfont % Scaling calculations 0.0238095 0.00015873 0.0147151 0.588604 [ [(0)] .02381 0 0 2 0 Minner Mrotsboxa [(1000)] .18254 0 0 2 0 Minner Mrotsboxa [(2000)] .34127 0 0 2 0 Minner Mrotsboxa [(3000)] .5 0 0 2 0 Minner Mrotsboxa [(4000)] .65873 0 0 2 0 Minner Mrotsboxa [(5000)] .81746 0 0 2 0 Minner Mrotsboxa [(6000)] .97619 0 0 2 0 Minner Mrotsboxa [(Time )] .5 0 0 2 0 0 -1 Mouter Mrotsboxa [(0)] -0.0125 .01472 1 0 0 Minner Mrotsboxa [(0.2)] -0.0125 .13244 1 0 0 Minner Mrotsboxa [(0.4)] -0.0125 .25016 1 0 0 Minner Mrotsboxa [(0.6)] -0.0125 .36788 1 0 0 Minner Mrotsboxa [(0.8)] -0.0125 .4856 1 0 0 Minner Mrotsboxa [(1)] -0.0125 .60332 1 0 0 Minner Mrotsboxa [(Survival Probability)] -0.0125 .30902 1 0 90 -1 0 Mouter Mrotsboxa p /Palatino-Bold findfont 18 scalefont setfont [(A Survival Curve)] .5 .61803 0 -2 Msboxa P [ -0.001 -0.001 0 0 ] [ 1.001 .61903 0 0 ] ] MathScale % Start of Graphics 1 setlinecap 1 setlinejoin newpath [ ] 0 setdash 0 g p p .002 w .02381 0 m .02381 .00625 L s P [(0)] .02381 0 0 2 0 Minner Mrotshowa p .002 w .18254 0 m .18254 .00625 L s P [(1000)] .18254 0 0 2 0 Minner Mrotshowa p .002 w .34127 0 m .34127 .00625 L s P [(2000)] .34127 0 0 2 0 Minner Mrotshowa p .002 w .5 0 m .5 .00625 L s P [(3000)] .5 0 0 2 0 Minner Mrotshowa p .002 w .65873 0 m .65873 .00625 L s P [(4000)] .65873 0 0 2 0 Minner Mrotshowa p .002 w .81746 0 m .81746 .00625 L s P [(5000)] .81746 0 0 2 0 Minner Mrotshowa p .002 w .97619 0 m .97619 .00625 L s P [(6000)] .97619 0 0 2 0 Minner Mrotshowa p .001 w .05556 0 m .05556 .00375 L s P p .001 w .0873 0 m .0873 .00375 L s P p .001 w .11905 0 m .11905 .00375 L s P p .001 w .15079 0 m .15079 .00375 L s P p .001 w .21429 0 m .21429 .00375 L s P p .001 w .24603 0 m .24603 .00375 L s P p .001 w .27778 0 m .27778 .00375 L s P p .001 w .30952 0 m .30952 .00375 L s P p .001 w .37302 0 m .37302 .00375 L s P p .001 w .40476 0 m .40476 .00375 L s P p .001 w .43651 0 m .43651 .00375 L s P p .001 w .46825 0 m .46825 .00375 L s P p .001 w .53175 0 m .53175 .00375 L s P p .001 w .56349 0 m .56349 .00375 L s P p .001 w .59524 0 m .59524 .00375 L s P p .001 w .62698 0 m .62698 .00375 L s P p .001 w .69048 0 m .69048 .00375 L s P p .001 w .72222 0 m .72222 .00375 L s P p .001 w .75397 0 m .75397 .00375 L s P p .001 w .78571 0 m .78571 .00375 L s P p .001 w .84921 0 m .84921 .00375 L s P p .001 w .88095 0 m .88095 .00375 L s P p .001 w .9127 0 m .9127 .00375 L s P p .001 w .94444 0 m .94444 .00375 L s P [(Time )] .5 0 0 2 0 0 -1 Mouter Mrotshowa p .002 w 0 0 m 1 0 L s P p .002 w 0 .01472 m .00625 .01472 L s P [(0)] -0.0125 .01472 1 0 0 Minner Mrotshowa p .002 w 0 .13244 m .00625 .13244 L s P [(0.2)] -0.0125 .13244 1 0 0 Minner Mrotshowa p .002 w 0 .25016 m .00625 .25016 L s P [(0.4)] -0.0125 .25016 1 0 0 Minner Mrotshowa p .002 w 0 .36788 m .00625 .36788 L s P [(0.6)] -0.0125 .36788 1 0 0 Minner Mrotshowa p .002 w 0 .4856 m .00625 .4856 L s P [(0.8)] -0.0125 .4856 1 0 0 Minner Mrotshowa p .002 w 0 .60332 m .00625 .60332 L s P [(1)] -0.0125 .60332 1 0 0 Minner Mrotshowa p .001 w 0 .03826 m .00375 .03826 L s P p .001 w 0 .0618 m .00375 .0618 L s P p .001 w 0 .08535 m .00375 .08535 L s P p .001 w 0 .10889 m .00375 .10889 L s P p .001 w 0 .15598 m .00375 .15598 L s P p .001 w 0 .17952 m .00375 .17952 L s P p .001 w 0 .20307 m .00375 .20307 L s P p .001 w 0 .22661 m .00375 .22661 L s P p .001 w 0 .2737 m .00375 .2737 L s P p .001 w 0 .29724 m .00375 .29724 L s P p .001 w 0 .32079 m .00375 .32079 L s P p .001 w 0 .34433 m .00375 .34433 L s P p .001 w 0 .39142 m .00375 .39142 L s P p .001 w 0 .41497 m .00375 .41497 L s P p .001 w 0 .43851 m .00375 .43851 L s P p .001 w 0 .46205 m .00375 .46205 L s P p .001 w 0 .50914 m .00375 .50914 L s P p .001 w 0 .53269 m .00375 .53269 L s P p .001 w 0 .55623 m .00375 .55623 L s P p .001 w 0 .57977 m .00375 .57977 L s P [(Survival Probability)] -0.0125 .30902 1 0 90 -1 0 Mouter Mrotshowa p .002 w 0 0 m 0 .61803 L s P P p p .002 w .02381 .61178 m .02381 .61803 L s P p .002 w .18254 .61178 m .18254 .61803 L s P p .002 w .34127 .61178 m .34127 .61803 L s P p .002 w .5 .61178 m .5 .61803 L s P p .002 w .65873 .61178 m .65873 .61803 L s P p .002 w .81746 .61178 m .81746 .61803 L s P p .002 w .97619 .61178 m .97619 .61803 L s P p .001 w .05556 .61428 m .05556 .61803 L s P p .001 w .0873 .61428 m .0873 .61803 L s P p .001 w .11905 .61428 m .11905 .61803 L s P p .001 w .15079 .61428 m .15079 .61803 L s P p .001 w .21429 .61428 m .21429 .61803 L s P p .001 w .24603 .61428 m .24603 .61803 L s P p .001 w .27778 .61428 m .27778 .61803 L s P p .001 w .30952 .61428 m .30952 .61803 L s P p .001 w .37302 .61428 m .37302 .61803 L s P p .001 w .40476 .61428 m .40476 .61803 L s P p .001 w .43651 .61428 m .43651 .61803 L s P p .001 w .46825 .61428 m .46825 .61803 L s P p .001 w .53175 .61428 m .53175 .61803 L s P p .001 w .56349 .61428 m .56349 .61803 L s P p .001 w .59524 .61428 m .59524 .61803 L s P p .001 w .62698 .61428 m .62698 .61803 L s P p .001 w .69048 .61428 m .69048 .61803 L s P p .001 w .72222 .61428 m .72222 .61803 L s P p .001 w .75397 .61428 m .75397 .61803 L s P p .001 w .78571 .61428 m .78571 .61803 L s P p .001 w .84921 .61428 m .84921 .61803 L s P p .001 w .88095 .61428 m .88095 .61803 L s P p .001 w .9127 .61428 m .9127 .61803 L s P p .001 w .94444 .61428 m .94444 .61803 L s P p .002 w 0 .61803 m 1 .61803 L s P p /Palatino-Bold findfont 18 scalefont setfont [(A Survival Curve)] .5 .61803 0 -2 Mshowa P p .002 w .99375 .01472 m 1 .01472 L s P p .002 w .99375 .13244 m 1 .13244 L s P p .002 w .99375 .25016 m 1 .25016 L s P p .002 w .99375 .36788 m 1 .36788 L s P p .002 w .99375 .4856 m 1 .4856 L s P p .002 w .99375 .60332 m 1 .60332 L s P p .001 w .99625 .03826 m 1 .03826 L s P p .001 w .99625 .0618 m 1 .0618 L s P p .001 w .99625 .08535 m 1 .08535 L s P p .001 w .99625 .10889 m 1 .10889 L s P p .001 w .99625 .15598 m 1 .15598 L s P p .001 w .99625 .17952 m 1 .17952 L s P p .001 w .99625 .20307 m 1 .20307 L s P p .001 w .99625 .22661 m 1 .22661 L s P p .001 w .99625 .2737 m 1 .2737 L s P p .001 w .99625 .29724 m 1 .29724 L s P p .001 w .99625 .32079 m 1 .32079 L s P p .001 w .99625 .34433 m 1 .34433 L s P p .001 w .99625 .39142 m 1 .39142 L s P p .001 w .99625 .41497 m 1 .41497 L s P p .001 w .99625 .43851 m 1 .43851 L s P p .001 w .99625 .46205 m 1 .46205 L s P p .001 w .99625 .50914 m 1 .50914 L s P p .001 w .99625 .53269 m 1 .53269 L s P p .001 w .99625 .55623 m 1 .55623 L s P p .001 w .99625 .57977 m 1 .57977 L s P p .002 w 1 0 m 1 .61803 L s P P p P 0 0 m 1 0 L 1 .61803 L 0 .61803 L closepath clip newpath .004 w .02381 .60332 m .03968 .60331 L .05556 .6032 L .07143 .60276 L .0873 .6017 L .10317 .59969 L .11905 .59643 L .13492 .59162 L .15079 .585 L .16667 .5764 L .18254 .56566 L .19841 .55272 L .21429 .5376 L .23016 .52034 L .24603 .50109 L .2619 .48003 L .27778 .45739 L .29365 .43343 L .30952 .40846 L .3254 .38279 L .34127 .35673 L .35714 .33059 L .37302 .30469 L .38889 .27929 L .40476 .25464 L .42063 .23096 L .43651 .20844 L .45238 .18721 L .46825 .16738 L .48413 .14902 L .5 .13217 L .51587 .11682 L .53175 .10296 L .54762 .09054 L .56349 .07949 L .57937 .06974 L .59524 .06119 L .61111 .05376 L .62698 .04733 L .64286 .04182 L .65873 .03712 L .6746 .03314 L .69048 .02978 L .70635 .02698 L .72222 .02465 L .7381 .02272 L .75397 .02114 L .76984 .01984 L .78571 .01879 L .80159 .01794 L Mistroke .81746 .01725 L .83333 .0167 L .84921 .01627 L .86508 .01592 L .88095 .01565 L .89683 .01544 L .9127 .01527 L .92857 .01514 L .94444 .01504 L .96032 .01496 L .97619 .0149 L Mfstroke % End of Graphics MathPictureEnd :[font = output; output; inactive; preserveAspect; endGroup] Graphics["<<>>"] ;[o] -Graphics- :[font = text; inactive; preserveAspect] The hazard function is computed by first creating an interpolation function object so that derivatives of the survival function may be computed. :[font = input; preserveAspect] interpObj=Interpolation[survivalList,InterpolationOrder->5]; dsurvival=Table[Evaluate[interpObj'[t]],{t,0,6000,100}]; :[font = text; inactive; preserveAspect] From the definition of the hazard function, one can easily compute and plot the hazard function. :[font = input; preserveAspect; startGroup] hazardList=-dsurvival/(#[[2]]&/@survivalList); ListPlot[hazardList,PlotJoined->True,Frame->True, FrameLabel->{"Time * 100","Hazard Rate"}, PlotLabel->FontForm["A Hazard Curve",{"Palatino-Bold",18}]] :[font = postscript; PostScript; formatAsPostScript; output; inactive; preserveAspect; pictureLeft = 100; pictureWidth = 453; pictureHeight = 280] %! %%Creator: Mathematica %%AspectRatio: .61803 MathPictureStart %% Graphics /Courier findfont 10 scalefont setfont % Scaling calculations 0.0238095 0.0156128 0.0147151 210.461 [ [(0)] .02381 0 0 2 0 Minner Mrotsboxa [(10)] .17994 0 0 2 0 Minner Mrotsboxa [(20)] .33607 0 0 2 0 Minner Mrotsboxa [(30)] .49219 0 0 2 0 Minner Mrotsboxa [(40)] .64832 0 0 2 0 Minner Mrotsboxa [(50)] .80445 0 0 2 0 Minner Mrotsboxa [(60)] .96058 0 0 2 0 Minner Mrotsboxa [(Time * 100)] .5 0 0 2 0 0 -1 Mouter Mrotsboxa [(0)] -0.0125 .01472 1 0 0 Minner Mrotsboxa [(0.0005)] -0.0125 .11995 1 0 0 Minner Mrotsboxa [(0.001)] -0.0125 .22518 1 0 0 Minner Mrotsboxa [(0.0015)] -0.0125 .33041 1 0 0 Minner Mrotsboxa [(0.002)] -0.0125 .43564 1 0 0 Minner Mrotsboxa [(0.0025)] -0.0125 .54087 1 0 0 Minner Mrotsboxa [(Hazard Rate)] -0.0125 .30902 1 0 90 -1 0 Mouter Mrotsboxa p /Palatino-Bold findfont 18 scalefont setfont [(A Hazard Curve)] .5 .61803 0 -2 Msboxa P [ -0.001 -0.001 0 0 ] [ 1.001 .61903 0 0 ] ] MathScale % Start of Graphics 1 setlinecap 1 setlinejoin newpath [ ] 0 setdash 0 g p p .002 w .02381 0 m .02381 .00625 L s P [(0)] .02381 0 0 2 0 Minner Mrotshowa p .002 w .17994 0 m .17994 .00625 L s P [(10)] .17994 0 0 2 0 Minner Mrotshowa p .002 w .33607 0 m .33607 .00625 L s P [(20)] .33607 0 0 2 0 Minner Mrotshowa p .002 w .49219 0 m .49219 .00625 L s P [(30)] .49219 0 0 2 0 Minner Mrotshowa p .002 w .64832 0 m .64832 .00625 L s P [(40)] .64832 0 0 2 0 Minner Mrotshowa p .002 w .80445 0 m .80445 .00625 L s P [(50)] .80445 0 0 2 0 Minner Mrotshowa p .002 w .96058 0 m .96058 .00625 L s P [(60)] .96058 0 0 2 0 Minner Mrotshowa p .001 w .05504 0 m .05504 .00375 L s P p .001 w .08626 0 m .08626 .00375 L s P p .001 w .11749 0 m .11749 .00375 L s P p .001 w .14871 0 m .14871 .00375 L s P p .001 w .21116 0 m .21116 .00375 L s P p .001 w .24239 0 m .24239 .00375 L s P p .001 w .27361 0 m .27361 .00375 L s P p .001 w .30484 0 m .30484 .00375 L s P p .001 w .36729 0 m .36729 .00375 L s P p .001 w .39852 0 m .39852 .00375 L s P p .001 w .42974 0 m .42974 .00375 L s P p .001 w .46097 0 m .46097 .00375 L s P p .001 w .52342 0 m .52342 .00375 L s P p .001 w .55464 0 m .55464 .00375 L s P p .001 w .58587 0 m .58587 .00375 L s P p .001 w .6171 0 m .6171 .00375 L s P p .001 w .67955 0 m .67955 .00375 L s P p .001 w .71077 0 m .71077 .00375 L s P p .001 w .742 0 m .742 .00375 L s P p .001 w .77322 0 m .77322 .00375 L s P p .001 w .83568 0 m .83568 .00375 L s P p .001 w .8669 0 m .8669 .00375 L s P p .001 w .89813 0 m .89813 .00375 L s P p .001 w .92935 0 m .92935 .00375 L s P p .001 w .9918 0 m .9918 .00375 L s P [(Time * 100)] .5 0 0 2 0 0 -1 Mouter Mrotshowa p .002 w 0 0 m 1 0 L s P p .002 w 0 .01472 m .00625 .01472 L s P [(0)] -0.0125 .01472 1 0 0 Minner Mrotshowa p .002 w 0 .11995 m .00625 .11995 L s P [(0.0005)] -0.0125 .11995 1 0 0 Minner Mrotshowa p .002 w 0 .22518 m .00625 .22518 L s P [(0.001)] -0.0125 .22518 1 0 0 Minner Mrotshowa p .002 w 0 .33041 m .00625 .33041 L s P [(0.0015)] -0.0125 .33041 1 0 0 Minner Mrotshowa p .002 w 0 .43564 m .00625 .43564 L s P [(0.002)] -0.0125 .43564 1 0 0 Minner Mrotshowa p .002 w 0 .54087 m .00625 .54087 L s P [(0.0025)] -0.0125 .54087 1 0 0 Minner Mrotshowa p .001 w 0 .03576 m .00375 .03576 L s P p .001 w 0 .05681 m .00375 .05681 L s P p .001 w 0 .07785 m .00375 .07785 L s P p .001 w 0 .0989 m .00375 .0989 L s P p .001 w 0 .14099 m .00375 .14099 L s P p .001 w 0 .16204 m .00375 .16204 L s P p .001 w 0 .18308 m .00375 .18308 L s P p .001 w 0 .20413 m .00375 .20413 L s P p .001 w 0 .24622 m .00375 .24622 L s P p .001 w 0 .26727 m .00375 .26727 L s P p .001 w 0 .28831 m .00375 .28831 L s P p .001 w 0 .30936 m .00375 .30936 L s P p .001 w 0 .35145 m .00375 .35145 L s P p .001 w 0 .3725 m .00375 .3725 L s P p .001 w 0 .39354 m .00375 .39354 L s P p .001 w 0 .41459 m .00375 .41459 L s P p .001 w 0 .45668 m .00375 .45668 L s P p .001 w 0 .47773 m .00375 .47773 L s P p .001 w 0 .49878 m .00375 .49878 L s P p .001 w 0 .51982 m .00375 .51982 L s P p .001 w 0 .56191 m .00375 .56191 L s P p .001 w 0 .58296 m .00375 .58296 L s P p .001 w 0 .60401 m .00375 .60401 L s P [(Hazard Rate)] -0.0125 .30902 1 0 90 -1 0 Mouter Mrotshowa p .002 w 0 0 m 0 .61803 L s P P p p .002 w .02381 .61178 m .02381 .61803 L s P p .002 w .17994 .61178 m .17994 .61803 L s P p .002 w .33607 .61178 m .33607 .61803 L s P p .002 w .49219 .61178 m .49219 .61803 L s P p .002 w .64832 .61178 m .64832 .61803 L s P p .002 w .80445 .61178 m .80445 .61803 L s P p .002 w .96058 .61178 m .96058 .61803 L s P p .001 w .05504 .61428 m .05504 .61803 L s P p .001 w .08626 .61428 m .08626 .61803 L s P p .001 w .11749 .61428 m .11749 .61803 L s P p .001 w .14871 .61428 m .14871 .61803 L s P p .001 w .21116 .61428 m .21116 .61803 L s P p .001 w .24239 .61428 m .24239 .61803 L s P p .001 w .27361 .61428 m .27361 .61803 L s P p .001 w .30484 .61428 m .30484 .61803 L s P p .001 w .36729 .61428 m .36729 .61803 L s P p .001 w .39852 .61428 m .39852 .61803 L s P p .001 w .42974 .61428 m .42974 .61803 L s P p .001 w .46097 .61428 m .46097 .61803 L s P p .001 w .52342 .61428 m .52342 .61803 L s P p .001 w .55464 .61428 m .55464 .61803 L s P p .001 w .58587 .61428 m .58587 .61803 L s P p .001 w .6171 .61428 m .6171 .61803 L s P p .001 w .67955 .61428 m .67955 .61803 L s P p .001 w .71077 .61428 m .71077 .61803 L s P p .001 w .742 .61428 m .742 .61803 L s P p .001 w .77322 .61428 m .77322 .61803 L s P p .001 w .83568 .61428 m .83568 .61803 L s P p .001 w .8669 .61428 m .8669 .61803 L s P p .001 w .89813 .61428 m .89813 .61803 L s P p .001 w .92935 .61428 m .92935 .61803 L s P p .001 w .9918 .61428 m .9918 .61803 L s P p .002 w 0 .61803 m 1 .61803 L s P p /Palatino-Bold findfont 18 scalefont setfont [(A Hazard Curve)] .5 .61803 0 -2 Mshowa P p .002 w .99375 .01472 m 1 .01472 L s P p .002 w .99375 .11995 m 1 .11995 L s P p .002 w .99375 .22518 m 1 .22518 L s P p .002 w .99375 .33041 m 1 .33041 L s P p .002 w .99375 .43564 m 1 .43564 L s P p .002 w .99375 .54087 m 1 .54087 L s P p .001 w .99625 .03576 m 1 .03576 L s P p .001 w .99625 .05681 m 1 .05681 L s P p .001 w .99625 .07785 m 1 .07785 L s P p .001 w .99625 .0989 m 1 .0989 L s P p .001 w .99625 .14099 m 1 .14099 L s P p .001 w .99625 .16204 m 1 .16204 L s P p .001 w .99625 .18308 m 1 .18308 L s P p .001 w .99625 .20413 m 1 .20413 L s P p .001 w .99625 .24622 m 1 .24622 L s P p .001 w .99625 .26727 m 1 .26727 L s P p .001 w .99625 .28831 m 1 .28831 L s P p .001 w .99625 .30936 m 1 .30936 L s P p .001 w .99625 .35145 m 1 .35145 L s P p .001 w .99625 .3725 m 1 .3725 L s P p .001 w .99625 .39354 m 1 .39354 L s P p .001 w .99625 .41459 m 1 .41459 L s P p .001 w .99625 .45668 m 1 .45668 L s P p .001 w .99625 .47773 m 1 .47773 L s P p .001 w .99625 .49878 m 1 .49878 L s P p .001 w .99625 .51982 m 1 .51982 L s P p .001 w .99625 .56191 m 1 .56191 L s P p .001 w .99625 .58296 m 1 .58296 L s P p .001 w .99625 .60401 m 1 .60401 L s P p .002 w 1 0 m 1 .61803 L s P P p P 0 0 m 1 0 L 1 .61803 L 0 .61803 L closepath clip newpath .004 w .03942 .01473 m .05504 .01483 L .07065 .01554 L .08626 .01721 L .10187 .02001 L .11749 .024 L .1331 .02916 L .14871 .03542 L .16432 .0427 L .17994 .0509 L .19555 .05991 L .21116 .06962 L .22678 .07994 L .24239 .09079 L .258 .10208 L .27361 .11375 L .28923 .12571 L .30484 .13793 L .32045 .15035 L .33607 .16293 L .35168 .17562 L .36729 .1884 L .3829 .20123 L .39852 .21409 L .41413 .22695 L .42974 .2398 L .44536 .25261 L .46097 .26537 L .47658 .27806 L .49219 .29067 L .50781 .30319 L .52342 .31561 L .53903 .3279 L .55464 .34008 L .57026 .35212 L .58587 .36401 L .60148 .37576 L .6171 .38736 L .63271 .39879 L .64832 .41006 L .66393 .42115 L .67955 .43207 L .69516 .44281 L .71077 .45337 L .72639 .46374 L .742 .47392 L .75761 .48391 L .77322 .4937 L .78884 .5033 L .80445 .51271 L Mistroke .82006 .52192 L .83568 .53093 L .85129 .53974 L .8669 .54836 L .88251 .55678 L .89813 .56501 L .91374 .57304 L .92935 .58088 L .94496 .58852 L .96058 .59597 L .97619 .60332 L Mfstroke % End of Graphics MathPictureEnd :[font = output; output; inactive; preserveAspect; endGroup] Graphics["<<>>"] ;[o] -Graphics- :[font = section; inactive; preserveAspect; fontSize = 12; startGroup] Acknowledgments :[font = text; inactive; preserveAspect; endGroup] Part of this work was performed while the author was visiting Wolfram Research, Inc.. During this visit, Tom Issaevitch and David Withoff of Wolfram Research made several valuable and specific coding suggestions, which led to more elegant and efficient code in the present notebook. I am indebted to S.R. Sipcic at Boston University College of Engineering for kindly inviting me to present part of this work to the Tenth International Conference on Mathematical and Computer Modeling and Scientific Computing. Partial support provided by Wolfram Research during the visit is gratefully acknowledged. This work was also supported by an appointment to the Postgraduate Research Program at the National Center for Toxicological Research administered by the Oak Ridge Institute for Science and Education through an interagency agreement between the U.S. Department of Energy and the Food and Drug Administration. ^*)