(* The package MultipleLogListPlot in the initialization cell is my latest version of an extension of the standard package MultipleListPlot to logarithmic plotting with colored symbols and colored error bars. It works for me as a package. You should have only to save it as a package and use it for your own work. Anyone accustomed to MultipleListPlot should find it straightforward and "transparent" . The package is not protected, so the user is responsible for his or her own safety. The code is written in Mathematica 4.2. the new features are: (1)Logarithmic tick marks that include minor ticks. (2) Built in functions that give you an algorithmic way to locate Legend corners by specifying "physical" coordinates for any particular graph. These functions are {LogLogCorner[{data__List},x_,y_,a_:0.612],LinearLogCorner[args],LogLinearCorner[args],LinearCorner[args]}. Data is any number of lists of data to be plotted, enclosed in curly brackets. X and y are the physical coordinates where you want to put the lower left hand corner of the Legend box. "a" is the aspect ratio of the graphic, and must match the AspectRatio specified in the graphic. It defaults to the standard aspect ratio. Note that it is essential that the data lists used as input to these functions be specified as a list of lists, rather than a sequence as is done in the main plotting functions. In general, you are very much encouraged to use the ImageSize option when using the Legend corner functions. (3) I have speeded up the whole process when data lists with no error bars are processed, so that theoretical curves don't take nearly as long to process as they did in the original version.. (4). The axis origin is now automatically located at the Floor of the absolute minimum of the input data, or at 0 if the data on an axis falls below zero. There are no warning messages except the standard messages from MultipleListPlot. This is for friendly users only. John W. Taylor *) BeginPackage[ "MultipleLogListPlot`",{"Graphics`MultipleListPlot`", "Utilities`FilterOptions`"}]; MultipleLogListPlot::"usage"= "MultipleLogListPlot contains a suite of functions which remove most of \ the drudgery of preparing linear data for plotting in multiple log log, \ linear log and log linear plots with colored plot points and error bars using \ MultipleListPlot. In addition, there is a function MultipleLinearPlot to \ make the package complete. Error bars should be input in one of the forms \ {{x,y},{xerror,yerror}} , {{x,y},yerr} , {{x,y},{{-negyerror,posyerror}}} and \ {{x,y},{{-negxerror,posxerror},{-negyerror,posyerror}}} and are automatically \ prepared in the last form for each of the four functions MultipleLogLogPlot, \ MultipleLinearLogPlot, MultipleLogLinearPlot and MultipleLinearPlot. Note \ that the ErrorBar designator should not be used in the input data. This is \ handled inside the Package. A suite of functions: FullMultipleLogGrid,TightMultipleLogGrid, \ LooseMultipleLogGrid and ScantMultipleLogGrid, FullMultipleLogTicks, \ TightMultipleLogTicks,LooseMultipleLogTicks and ScantMultipleLogTicks provide \ logarithmic spacings for the GridLines and Ticks options in \ MultipleLogListPlot. For log linear and linear log plots, the linear grid \ lines and Ticks must be supplied by the user as lists,or specified as \ Automatic. MultipleListPlot requires that if the GridLines option is called, \ both axes must be specified. The default options for GridLines and Tick marks \ are calculated from the spans of the data and are designed to keep the graphs \ from getting too cluttered. A second suite of functions provides colored symbols ranging through \ red,orange, yellow, green, blue and black, with associated shapes: colorpoint \ (actually a very small \ hexagon),colortriangle[s],colordiamond[s],colorpentagon[s ],colorhexagon[s] \ and colorstar[s]. Each of these functions except colorpoint requires an \ arguement[s] which specifies the radius of the symbol. Appropriate values of \ s are in the range 0.01 to 0.02. The SymbolShape->None option may also be \ used. Along with these are a set of functions \ {RedBar,OrangeBar,YellowBar,GreenBar,BlueBar,BlackBar,RedSerif,OrangeSerif,\ YellowSerif,GreenSerif,BlueSerif,BlackSerif} to make colored error bars with \ and without Serifs. Using the colored error bars requires the user to insert \ the command ErrorBarFunction\[Rule]{RedBar,GreenSerif,.....etc. Finally, the options \ {LogLogCorner,LinearLogCorner,LogLinearCorner,LinearCorner} permit location \ of the LegendPosition at the physical coordinates specified. This is an \ approximation, but a pretty good one."; MultipleLogLogPlot::"usage"= "MultipleLogLogPlot[List1,List2,,,Listn,options] accepts data in lists in \ any of the three forms {{x,y}},{{x,y},yerror},{{x,y},{xerror,yerror}} and \ passes it for plotting data in log log coordinates using MultipleListPlot \ with all its options."; MultipleLinearLogPlot::"usage"= "MultipleLinearLogPlot[List1,List2,,,Listn,options] accepts data in lists \ in any of the three forms {{x,y}},{{x,y},yerror},{{x,y},{xerror,yerror}} and \ passes it for plotting data in linear log coordinates using MultipleListPlot \ with all its options."; MultipleLogLinearPlot::"usage"= "MultipleLogLinearplot[List1,List2,,,Listn,options] accepts data in lists \ in any of the three forms {{x,y}},{{x,y},yerror},{{x,y},{xerror,yerror}} and \ passes it for plotting data in linear log coordinates using MultipleListPlot \ with all its options. The options for MultipleLogListPlot \ are:{AxesOrigin,ColorOutput,FrameLabel,GridLines,PlotRange,PlotStyle,Prolog,\ DisplayFunction,ErrorBarFunctionSymbolShape,SymbolStyle,LegendSize,\ LegendTextDirection,LegendTextOffset,LegendLabel,LegendLabelSpace,\ LegendOrientation,LegendSpacing,LegendBorder,LegendBorderSpace}"; MultipleLinearPlot::"usage"= "MultipleLinearplot[List1,List2,,,Listn,options] accepts data in lists in \ any of the three forms {{x,y}},{{x,y},yerror},{{x,y},{xerror,yerror}} and \ passes it for plotting data in linear coordinates using MultipleListPlot with \ all its options."; TightMultipleLogGrid::"usage"= "TightMultipleLogGrid[a,b] generates logarithmically spaced gridlines at \ {1,1.5,2,3,4,5,6,7,8,9,10} and multiples of 10^n for n from a through b."; FullMultipleLogGrid::"usage"= "TightMultipleLogGrid[a,b] generates logarithmically spaced gridlines at \ {1,1.1,1.2,1.3,1.4,1.5,1.6,1.7,1.8,1.9,2,2.5,3,3.5,4,4.5,5,5.5,6,6.5,7,7.5,8,\ 8.5,9,9.5,10} and multiples of 10^n for n from a through b. It is included \ for cases where one or at most 1.5 logarighmic cycles are to be plotted."; LooseMultipleLogGrid::"usage"= "LooseMultipleLogGrid[a,b] generates logarithmically spaced gridlines at \ {1,1.5,2,5,10} and multiples of 10^n for n from a through b."; ScantMultipleLogGrid::"usage"= "ScantMultipleLogGrid[a,b] should be used when the data span many orders \ of magnitude so that the only appropriate GridLines are the powers of ten."; FullMultipleLogTicks::"usage"= "FullMultipleLogTicks[a,b] generates logarithmically spaced ticks at \ {1,1.5,2,3,4,5,6,7,8,9,10} and multiples of 10^n for n from a through b."; TightMultipleLogTicks::"usage"= "TightMultipleLogTicks[a,b] generates logarithmically spaced ticks at \ {1,1.5,2,3,4,5,7,10} and multiples of 10^n for n from a through b."; LooseMultipleLogTicks::"usage"= "LooseMultipleLogTicks[a,b] generates logarithmically spaced ticks at \ {1,2,5,10} and multiples of 10^n for n from a through b."; ScantMultipleLogTicks::"usage"= "ScantMultipleLogTicks should be used when the data span many orders of \ magnitude so that the only appropriate GridLines are the powers of ten."; colortriangle::"usage"= "colortriangle[s_] is a triangle of scaled size s for use in the \ ColorSymbol functions."; colordiamond::"usage"= "colordiamond[s_] is a diamond of scaled size s for use in the \ ColorSymbol functions."; colorpentagon::"usage"= "colorpentagon[s_] is a pentagon of scaled size s for use in the \ ColorSymbol functions."; colorhexagon::"usage"= "colorhexagon[s_] is a hexagon of scaled size s for use in the \ ColorSymbol functions."; coloroctagon::"usage"= "coloroctagon[s_] is a diamond of scaled size s for use in the \ ColorSymbol functions."; colorstar::"usage"= "colorstar[s_] is a star of scaled size s for use in the ColorSymbol \ functions."; colorpoint::"usage"= "colorpoint is a hexagon of scaled size 0.002 used to maka a small point \ in the ColorSymbol functions."; RedSymbol::"usage"= "RedSymbol[symbolshape], colors the symbol which is its arguement red."; OrangeSymbol::"usage"= "OrangeSymbol[symbolshape], colors the symbol which is its arguement \ orange."; YellowSymbol::"usage"= "YellowSymbol[symbolshape], colors the symbol which is its arguement \ yellow."; GreenSymbol::"usage"= "GreenSymbol[symbolshape], colors the symbol which is its arguement \ green."; BlueSymbol::"usage"= "BlueSymbol[symbolshape], colors the symbol which is its arguement \ blue."; BlackSymbol::"usage"= "BlackSymbol[symbolshape], leaves the symbol which is its arguement \ black."; ColorSymbol::"usage"= "ColorSymbol[a_,b_,c_,symbolshape], colors the symbol which is its \ arguement according to the RGBColor code inserted."; HuedSymbol::"usage"= "HuedSymbol[e_,symbolshape], colors the symbol which is its arguement \ according to the Hue specified by e."; RedBar::"usage"= "The option ErrorBarFunction->RedBar in MultipleListPlot produces red \ errorbars."; RedSerif::"usage"= "The option ErrorBarFunction->RedSerif in MultipleListPlot produces red \ errorbars with serifs."; OrangeBar::"usage"= "The option ErrorBarFunction->OrangeBar in MultipleListPlot produces \ orange errorbars."; OrangeSerif::"usage"= "The option ErrorBarFunction->OrangeBar in MultipleListPlot produces \ orange errorbars with serifs."; YellowBar::"usage"= "The option ErrorBarFunction->YellowBar in MultipleListPlot produces \ yellow errorbars."; YellowSerif::"usage"= "The option ErrorBarFunction->YellowBar in MultipleListPlot produces \ yellow errorbars with serifs."; GreenBar::"usage"= "The option ErrorBarFunction->GreenBar in MultipleListPlot produces green \ errorbars."; GreenSerif::"usage"= "The option ErrorBarFunction->GreenBar in MultipleListPlot produces green \ errorbars with serifs."; BlueBar::"usage"= "The option ErrorBarFunction->BlueBar in MultipleListPlot produces blue \ errorbars."; BlueSerif::"usage"= "The option ErrorBarFunction->BlueBar in MultipleListPlot produces blue \ errorbars with serifs."; BlackBar::"usage"= "The option ErrorBarFunction->BlackBar in MultipleListPlot produces black \ errorbars."; BlackSerif::"usage"= "The option ErrorBarFunction->BlackBar in MultipleListPlot produces black \ errorbars with serifs."; LogLogCorner::"usage"= "LogLogCorner[{data_List},x_,y_,a_] locates the Legend in a LogLogPlot."; LinearLogCorner::"usage"= "LinearLogCorner[{data_List},x_,y_,a_] locates the Legend in a \ LinearLogPlot."; LogLinearCorner::"usage"= "LogLinearCorner[{data_List},x_,y_,a_] locates the Legend in a \ LogLinearPlot."; LinearCorner::"usage"= "LinearCorner[{data_List},x_,y_,a_] locates the Legend in a LinearPlot."; Begin["`Private`"]; Off[Min::nord]; improvedinputdata[datablock_]:= Module[{predecision,firstdecision,seconddecision,thirddecision, firstaction,secondaction,thirdaction,fourthaction,extradata}, predecision:= If[MatchQ[First[datablock],{{a_,b_},{{c_,d_},{e_,f_}}}]\[Equal]True, datablock,firstdecision[datablock]]; firstdecision[newblock_]:= If[MatchQ[First[newblock],{{a_,b_},{{c_,d_}}}]\[Equal]True, firstaction[newblock],seconddecision[newblock]]; seconddecision[secondblock_]:= If[MatchQ[First[secondblock],{{a_,b_},{c_,d_}}]\[Equal]True, secondaction[secondblock],thirddecision[secondblock]]; thirddecision[thirdblock_]:= If[MatchQ[First[thirdblock],{{a_,b_},c_}]\[Equal]True, thirdaction[thirdblock],fourthaction[thirdblock]]; extradata[list_]:=Table[{0,0},{i,1,Length[list]}]; firstaction[data_]:= Transpose[{Transpose[data][[1]], Transpose[{extradata[data], Transpose[Transpose[data][[2]]][[1]]}]}]; secondaction[data_]:=Module[{coords,deltaabciss,deltaord,totaldelta}, coords=Transpose[data][[1]]; deltaabciss:= Transpose[{-Transpose[Transpose[data][[2]]][[1]], Transpose[Transpose[data][[2]]][[1]]}]; deltaord:= Transpose[{-Transpose[Transpose[data][[2]]][[2]], Transpose[Transpose[data][[2]]][[2]]}]; totaldelta:=Transpose[{deltaabciss,deltaord}]; Transpose[{coords,totaldelta}]]; thirdaction[data_]:= Transpose[{Transpose[data][[1]], Transpose[{extradata[data], Transpose[{-Transpose[data][[2]],Transpose[data][[2]]}]}]}]; fourthaction[data_]:= Transpose[{data,Transpose[{extradata[data],extradata[data]}]}]; Table[predecision] ]; loglogoutput[inputdata__]:= Module[{datalist,setnumber,firstset,decisiondata,finalaction}, datalist:=inputdata; setnumber:=Count[datalist,_]; decisiondata[i_]:=datalist[[i]]; firstset= Table[If[MatchQ[First[decisiondata[i]],{{_,_},_}]\[Equal]True, finalaction[improvedinputdata[decisiondata[i]]], Log[10,decisiondata[i]]],{i,1,setnumber}]; finalaction[data_]:= Module[{coorddata,basedata,logerror,errorbar}, coorddata:=Log[10,Part[Transpose[data],1]]; basedata:=Part[Transpose[data],1]; logerror:= Chop[Log[10, Transpose[{1+ Transpose[Transpose[data][[2]]][[1]]/ Transpose[basedata][[1]], 1+Transpose[Transpose[data][[2]]][[2]]/ Transpose[basedata][[2]]}]]]; errorbar:= Table[ErrorBar[Apply[Sequence,Part[logerror,j]]],{j,1, Length[data]}]; Transpose[{coorddata,errorbar}] ]; Apply[Sequence,firstset] ]; MultipleLogLogPlot[inputdata__List,options___?OptionQ]:= MultipleListPlot[loglogoutput[Table[{inputdata}]], FilterOptions[MultipleListPlot,options], AxesOrigin\[Rule]loglogzero[Table[{inputdata}]], PlotRange\[Rule]loglogrange[Table[{inputdata}]], GridLines\[Rule]logloggrid[Table[{inputdata}]], Ticks\[Rule]loglogticks[Table[{inputdata}]]]; loglinearoutput[inputdata_] := Module[{setnumber, firstset,datalist, decisiondata, finalaction}, datalist:=inputdata; setnumber := Count[datalist, _]; decisiondata[i_] := datalist[[i]]; firstset= Table[If[MatchQ[First[decisiondata[i]],{{_,_},_}]\[Equal]True, finalaction[improvedinputdata[decisiondata[i]]], Transpose[{Log[10,Transpose[decisiondata[i]][[1]]], Transpose[decisiondata[i]][[2]]}]],{i,1,setnumber}]; finalaction[data_] := Module[{coorddata, linearbasedata, logbasedata, linearerror, logerrordata, logerror, totalerror, errorbar}, coorddata := Transpose[{Log[10, Transpose[Transpose[data][[1]]][[1]]], Transpose[Transpose[data][[1]]][[2]]}]; linearerror := Transpose[Transpose[data][[2]]][[2]]; logbasedata := Transpose[Transpose[data][[1]]][[1]]; logerrordata := Transpose[Transpose[data][[2]]][[1]]; logerror := Chop[Log[10, 1 + 1/logbasedata*Transpose[Transpose[improvedinputdata[ data]][[2]]][[1]]]]; totalerror := Transpose[{logerror, linearerror}]; errorbar = Table[ErrorBar[Sequence @@ totalerror[[j]]], {j, 1, Length[data]}]; Transpose[{coorddata, errorbar}]]; Sequence @@ firstset]; MultipleLogLinearPlot[inputdata__List,options___?OptionQ]:= MultipleListPlot[loglinearoutput[Table[{inputdata}]], FilterOptions[MultipleListPlot,options], PlotRange\[Rule]loglinearrange[Table[{inputdata}]], AxesOrigin\[Rule]loglinearref[Table[{inputdata}]], GridLines\[Rule]loglineargrid[Table[{inputdata}]], Ticks\[Rule]loglinearticks[Table[{inputdata}]]]; linearlogoutput[inputdata_]:= Module[{setnumber,firstset,decisiondata,finalaction}, setnumber:=Count[inputdata,_]; decisiondata[i_]:=improvedinputdata[Part[inputdata,i]]; firstset= Table[If[MatchQ[First[decisiondata[i]],{{_,_},_}]\[Equal]True, finalaction[improvedinputdata[decisiondata[i]]], Table[{decisiondata[i][[1]],Log[10,decisiondata[i][[2]]]}]],{i,1, setnumber}]; finalaction[data_]:= Module[{coorddata,linearbasedata,logbasedata,linearerror,logerrordata, logerror,totalerror,errorbar}, coorddata:= Transpose[{Part[Transpose[Part[Transpose[data],1]],1], Log[10,Part[Transpose[Part[Transpose[data],1]],2]]}]; linearerror:=Part[Transpose[Part[Transpose[data],2]],1]; logbasedata:=Part[Transpose[Part[Transpose[data],1]],2]; logerrordata:=Part[Transpose[Part[Transpose[data],2]],2]; logerror= Chop[Log[10, 1+Transpose[Transpose[improvedinputdata[data]][[2]]][[2]]/ logbasedata]]; totalerror=Transpose[{linearerror,logerror}]; errorbar= Table[ErrorBar[Apply[Sequence,Part[totalerror,j]]],{j,1, Length[data]}]; Transpose[{coorddata,errorbar}] ]; Apply[Sequence,firstset] ]; MultipleLinearLogPlot[inputdata__List,options___?OptionQ]:= MultipleListPlot[linearlogoutput[Table[{inputdata}]], FilterOptions[MultipleListPlot,options], AxesOrigin\[Rule]linearlogref[Table[{inputdata}]], PlotRange\[Rule]linearlogrange[Table[{inputdata}]], GridLines\[Rule]linearloggrid[Table[{inputdata}]], Ticks\[Rule]linearlogticks[Table[{inputdata}]]]; linearoutput[inputdata_]:= Module[{setnumber,firstset,decisiondata,finalaction}, setnumber:=Count[inputdata,_]; decisiondata[i_]:=improvedinputdata[Part[inputdata,i]]; firstset= Table[If[MatchQ[First[decisiondata[i]],{{_,_},_}]\[Equal]True, finalaction[improvedinputdata[decisiondata[i]]], decisiondata[i]],{i,1,setnumber}]; finalaction[data_]:= Module[{coorddata,basedata,errordata,logerror,errorbar}, coorddata:=Part[Transpose[data],1]; basedata:=Part[Transpose[data],1]; errordata:=Part[Transpose[data],2]; errorbar:= Table[ErrorBar[Apply[Sequence,Part[errordata,j]]],{j,1, Length[data]}]; Transpose[{coorddata,errorbar}] ]; Apply[Sequence,firstset] ]; MultipleLinearPlot[inputdata__List,options___?OptionQ]:= MultipleListPlot[linearoutput[Table[{inputdata}]], FilterOptions[MultipleListPlot,options], AxesOrigin\[Rule]linearref[Table[{inputdata}]], PlotRange\[Rule]linearrange[Table[{inputdata}]],GridLines\[Rule]Automatic, Ticks\[Rule]Automatic] TightMultipleLogGrid[a_,b_]:= Module[{tightgridgenerator,tightgridfullgenerator}, tightgridgenerator[n_]:=Table[N[Log[10,j 10^n]],{j,1,10}]; tightgridfullgenerator[n_]:= Prepend[tightgridgenerator[n],Log[10,1.5 10^n]]; Flatten[Table[N[tightgridfullgenerator[n]],{n,a,b}],1] ]; FullMultipleLogGrid[a_,b_]:=Module[{densegenerator,densefullgenerator}, densegenerator[n_]:=Table[N[Log[10,j 10^n]],{j,1,10}]; densefullgenerator[n_]:=Sort[Union[densegenerator[n], Flatten[Table[Log[10,(1+0.1*m)10^n],{m,1,9}],1], Flatten[Table[n+Log[10,(m+0.5)],{m,2,9}],1]]]; Flatten[Table[N[densefullgenerator[n]],{n,a,b}],1] ]; LooseMultipleLogGrid[a_,b_]:=Module[{generator}, generator[n_]:={Log[10,10^n],Log[10,2 10^n],Log[10,5 10^n], Log[10,10^(n+1)]}; Flatten[Table[N[generator[n]],{n,a,b}],1] ]; ScantMultipleLogGrid[a_,b_]:=Module[{generator}, generator[n_]:={Log[10,10^n],Log[10,10^(n+1)]}; Flatten[Table[N[generator[n]],{n,a,b}],1]]; generalticks[func1_,func2_]:= Module[{}, Join[Table[ Join[{Apply[Sequence,func1[[i]]],{0.01, 0.},{AbsoluteThickness[0.5]}}],{i,1,Length[func1]}], Table[Join[{Sequence[func2[[i]],""],{0.005,0.}}],{i,1, Length[func2]}]]]; fullticks[a_,b_]:=Module[{generator,fullgenerator,exfunc}, exfunc[n_]:="lO"^""<>ToString[n]<>""; generator[n_]:= If[n<0,Table[{Log[10,k 10^n],k},{k,2,9}], If[n>0,Table[{Log[10,k 10^n],k},{k,2,9}], Table[{Log[10,k 10^n],N[k 10^n]},{k,1,9}]]]; fullgenerator[n_]:= If[n<0,Insert[ Prepend[generator[n],{Log[10,10^n],exfunc[n]}],{Log[10,1.5 10^n], 1.5},2],If[n>0, Append[Prepend[ generator[n],{Log[10,1.5 10^n],1.5}],{Log[10,10^(n+1)], exfunc[n+1]}], Append[Insert[generator[n],{Log[10,1.5 10^n],N[1.5 10^n]}, 2],{Log[10,10^(n+1)],N[10^(n+1)]}]]]; Flatten[Table[fullgenerator[n],{n,a,b}],1] ]; tightticks[a_,b_]:=Module[{generator,fullgenerator,exfunc}, exfunc[n_]:="lO"^""<>ToString[n]<>""; generator[n_]:= If[n<-1,Table[{N[Log[10,k 10^n]],k},{k,2,7}], If[n>1,Table[{N[Log[10,k 10^n]],k},{k,2,7}], Table[{N[Log[10,k 10^n]],N[k 10^n]},{k,1,7}]]]; fullgenerator[n_]:= If[n<-1,Insert[ Prepend[generator[n],{N[Log[10,10^n]],exfunc[n]}],{N[ Log[10,1.5 10^n]],1.5},2], If[n>1,Append[ Prepend[generator[n],{Log[10,1.5 10^n],1.5}],{N[ Log[10,10^(n+1)]],exfunc[n+1]}], Append[Insert[generator[n],{N[Log[10,1.5 10^n]],N[1.5 10^n]}, 2],{N[Log[10,10^(n+1)]],N[10^(n+1)]}]]]; Flatten[Table[fullgenerator[n],{n,a,b}],1] ]; looseticks[a_,b_]:=Module[{generator,exfunc}, exfunc[n_]:="lO"^""<>ToString[n]<>""; generator[n_]:= If[n<-1,{{N[Log[10,10^n]],exfunc[n]},{N[Log[10,2 10^n]], 2},{N[Log[10,5 10^n]],5}}, If[n>1,{{N[Log[10,2 10^n]],2 },{N[Log[10,5 10^n]], 5},{N[Log[10,10^(n+1)]],exfunc[n+1]}},{{N[Log[10,10^n]], N[10^n]},{N[Log[10,2 10^n]],N[2 10^n]},{N[Log[10,5 10^n]], N[5 10^n]},{Log[10,10^(n+1)],N[ 10^(n+1)]}}]]; Flatten[Table[generator[n],{n,a,b}],1] ]; scantticks[a_,b_]:=Module[{generator,exfunc}, exfunc[n_]:="lO"^""<>ToString[n]<>""; generator[n_]:= If[n<-1,{{N[Log[10,10^n]],exfunc[n]}}, If[n>1,{{N[Log[10,10^(n+1)]],exfunc[n+1]}},{{N[Log[10,10^n]], N[10^n]},{N[Log[10,10^(n+1)]],N[10^(n+1)]}}]]; Flatten[Table[generator[n],{n,a,b}],1] ]; FullMultipleLogTicks[a_,b_]:= generalticks[fullticks[a,b],FullMultipleLogGrid[a,b]]; TightMultipleLogTicks[a_,b_]:= generalticks[tightticks[a,b],FullMultipleLogGrid[a,b]]; LooseMultipleLogTicks[a_,b_]:= generalticks[looseticks[a,b],TightMultipleLogGrid[a,b]]; ScantMultipleLogTicks[a_,b_]:= generalticks[scantticks[a,b],LooseMultipleLogGrid[a,b]]; loglogzero[inputdata_]:= Module[{setnumber,decisiondata,axesminset,finalaxesminaction}, setnumber=Count[inputdata,_]; decisiondata[i_]:=improvedinputdata[Part[inputdata,i]]; axesminset=Table[finalaxesminaction[decisiondata[i]],{i,1,setnumber}]; finalaxesminaction[data_]:= Log[10,{0.9*Min[Part[Transpose[Part[Transpose[data],1]],1]], 0.9*Min[Part[Transpose[Part[Transpose[data],1]],2]]}]; {Min[Part[Transpose[axesminset],1]],Min[Part[Transpose[axesminset],2]]} ]; loglinearzero[inputdata_]:= Module[{setnumber,decisiondata,axesminset,finalaxesminaction}, setnumber=Count[inputdata,_]; decisiondata[i_]:=improvedinputdata[Part[inputdata,i]]; axesminset=Table[finalaxesminaction[decisiondata[i]],{i,1,setnumber}]; finalaxesminaction[ data_]:={Log[10, 0.9*Min[Part[Transpose[Part[Transpose[data],1]],1]]], If[Min[Part[Transpose[Part[Transpose[data],1]],2]]>0, 0.9*Min[Part[Transpose[Part[Transpose[data],1]],2]], 1.1*Min[Part[Transpose[Part[Transpose[data],1]],2]]]}; {Min[Part[Transpose[axesminset],1]],Min[Part[Transpose[axesminset],2]]} ]; loglinearref[inputdata_]:={Part[loglinearzero[inputdata],1], If[Part[loglinearzero[inputdata],2]\[GreaterEqual]0, Part[loglinearzero[inputdata],2],0]}; linearlogzero[inputdata_]:= Module[{setnumber,decisiondata,axesminset,axesminaction}, setnumber=Count[inputdata,_]; decisiondata[i_]:=improvedinputdata[Part[inputdata,i]]; axesminset=Table[axesminaction[decisiondata[i]],{i,1,setnumber}]; axesminaction[data_]:= {If[Min[Part[Transpose[Part[Transpose[data],1]],1]]>0, 0.9 Min[Part[Transpose[Part[Transpose[data],1]],1]], 1.1 Min[Part[Transpose[Part[Transpose[data],1]],1]]], Log[10,0.9*Min[Part[Transpose[Part[Transpose[data],1]],2]]]}; {Min[Part[Transpose[axesminset],1]],Min[Part[Transpose[axesminset],2]]} ]; linearlogref[ inputdata_]:={If[Part[linearlogzero[inputdata],1]\[GreaterEqual]0, Part[linearlogzero[inputdata],1],0], Part[linearlogzero[inputdata],2]}; linearzero[inputdata_]:= Module[{setnumber,decisiondata,axesminset,finalaxesminaction}, setnumber=Count[inputdata,_]; decisiondata[i_]:=improvedinputdata[Part[inputdata,i]]; axesminset=Table[finalaxesminaction[decisiondata[i]],{i,1,setnumber}]; finalaxesminaction[ data_]:={If[Min[Part[Transpose[Part[Transpose[data],1]],1]]>0, 0.9*Min[Part[Transpose[Part[Transpose[data],1]],1]], 1.1*Min[Part[Transpose[Part[Transpose[data],1]],1]]], If[Min[Part[Transpose[Part[Transpose[data],1]],2]]>0, 0.9*Min[Part[Transpose[Part[Transpose[data],1]],2]], 1.1*Min[Part[Transpose[Part[Transpose[data],1]],2]]]}; {Min[Part[Transpose[axesminset],1]],Min[Part[Transpose[axesminset],2]]} ]; linearref[ inputdata_]:={If[Part[linearzero[inputdata],1]\[GreaterEqual]0, Part[linearzero[inputdata],1],0], If[Part[linearzero[inputdata],2]\[GreaterEqual]0, Part[linearzero[inputdata],2],0]}; loglogmax[inputdata_]:= Module[{setnumber,decisiondata,axesmaxset,axesmaxaction}, setnumber=Count[inputdata,_]; decisiondata[i_]:=improvedinputdata[Part[inputdata,i]]; axesmaxset=Table[axesmaxaction[decisiondata[i]],{i,1,setnumber}]; axesmaxaction[data_]:= Log[10,{1.2* Max[Part[Transpose[Part[Transpose[data],1]],1]], 1.2*Max[Part[Transpose[Part[Transpose[data],1]],2]]}]; {Max[Part[Transpose[axesmaxset],1]],Max[Part[Transpose[axesmaxset],2]]} ]; loglinearmax[inputdata_]:= Module[{setnumber,decisiondata,axesmaxset,axesmaxaction}, setnumber=Count[inputdata,_]; decisiondata[i_]:=improvedinputdata[Part[inputdata,i]]; axesmaxset=Table[axesmaxaction[decisiondata[i]],{i,1,setnumber}]; axesmaxaction[ data_]:={Log[10, 1.1* Max[Part[Transpose[Part[Transpose[data],1]],1]]], 1.1*Max[Part[Transpose[Part[Transpose[data],1]],2]]}; {Max[Part[Transpose[axesmaxset],1]],Max[Part[Transpose[axesmaxset],2]]} ]; linearlogmax[inputdata_]:= Module[{setnumber,decisiondata,axesmaxset,axesmaxaction}, setnumber=Count[inputdata,_]; decisiondata[i_]:=improvedinputdata[Part[inputdata,i]]; axesmaxset=Table[axesmaxaction[decisiondata[i]],{i,1,setnumber}]; axesmaxaction[ data_]:={1.1*Max[Part[Transpose[Part[Transpose[data],1]],1]], Log[10,1.1*Max[Part[Transpose[Part[Transpose[data],1]],2]]]}; {Max[Part[Transpose[axesmaxset],1]],Max[Part[Transpose[axesmaxset],2]]} ]; linearmax[inputdata_]:= Module[{setnumber,decisiondata,axesmaxset,axesmaxaction}, setnumber=Count[inputdata,_]; decisiondata[i_]:=improvedinputdata[Part[inputdata,i]]; axesmaxset=Table[axesmaxaction[decisiondata[i]],{i,1,setnumber}]; axesmaxaction[ data_]:={1.1* Max[Part[Transpose[Part[Transpose[data],1]],1]], 1.1*Max[Part[Transpose[Part[Transpose[data],1]],2]]}; {Max[Part[Transpose[axesmaxset],1]],Max[Part[Transpose[axesmaxset],2]]} ]; loglogrange[inputdata_]:= Table[{{Part[loglogzero[inputdata],1], Part[loglogmax[inputdata],1]},{Part[loglogzero[inputdata],2], Part[loglogmax[inputdata],2]}}]; linearlogrange[inputdata_]:= Table[{{Part[linearlogzero[inputdata],1], Part[linearlogmax[inputdata],1]},{Part[linearlogzero[inputdata],2], Part[linearlogmax[inputdata],2]}}]; loglinearrange[inputdata_]:= Table[{{Part[loglinearzero[inputdata],1], Part[loglinearmax[inputdata],1]},{Part[loglinearzero[inputdata],2], Part[loglinearmax[inputdata],2]}}] linearrange[inputdata_]:= Table[{{Part[linearzero[inputdata],1], Part[linearmax[inputdata],1]},{Part[linearzero[inputdata],2], Part[linearmax[inputdata],2]}}]; logloglengthfunc[inputdata_]:= Table[{Part[loglogmax[inputdata],1]-Part[loglogzero[inputdata],1], Part[loglogmax[inputdata],2]-Part[loglogzero[inputdata],2]}]; loglogcenterfunc[ inputdata_]:={0.5 Part[logloglengthfunc[inputdata],1]+ Part[loglogzero[inputdata],1], 0.5 Part[logloglengthfunc[inputdata],2]+Part[loglogzero[inputdata],2]}; LogLogCenter[inputdata___List]:=loglogcenterfunc[Table[{inputdata}]]; LogLogLength[inputdata___List]:=0.6 logloglengthfunc[Table[{inputdata}]]; linearloglengthfunc[inputdata_]:= Table[{Part[linearlogmax[inputdata],1]-Part[linearlogzero[inputdata],1], Part[linearlogmax[inputdata],2]-Part[linearlogzero[inputdata],2]}]; linearlogcenterfunc[ inputdata_]:={0.5 Part[linearloglengthfunc[inputdata],1]+ Part[linearlogzero[inputdata],1], 0.5 Part[linearloglengthfunc[inputdata],2]+ Part[linearlogzero[inputdata],2]}; LinearLogCenter[inputdata___List]:=linearlogcenterfunc[Table[{inputdata}]]; LinearLogLength[inputdata___List]:= 0.6linearloglengthfunc[Table[{inputdata}]]; loglinearlengthfunc[inputdata_]:= Table[{Part[loglinearmax[inputdata],1]-Part[loglinearzero[inputdata],1], Part[loglinearmax[inputdata],2]-Part[loglinearzero[inputdata],2]}]; loglinearcenterfunc[ inputdata_]:={0.5 Part[loglinearlengthfunc[inputdata],1]+ Part[loglinearzero[inputdata],1], 0.5 Part[loglinearlengthfunc[inputdata],2]+ Part[loglinearzero[inputdata],2]}; LogLinearCenter[inputdata___List]:=loglinearcenterfunc[Table[{inputdata}]]; LogLinearLength[inputdata___List]:= 0.6 loglinearlengthfunc[Table[{inputdata}]]; linearlengthfunc[inputdata_]:= Table[{Part[linearmax[inputdata],1]-Part[linearzero[inputdata],1], Part[linearmax[inputdata],2]-Part[linearzero[inputdata],2]}]; linearcenterfunc[ inputdata_]:={0.5 Part[linearlengthfunc[inputdata],1]+ Part[linearzero[inputdata],1], 0.5 Part[linearlengthfunc[inputdata],2]+Part[linearzero[inputdata],2]}; LinearCenter[inputdata___List]:=linearcenterfunc[Table[{inputdata}]]; LinearLength[inputdata___List]:=0.6 linearlengthfunc[Table[{inputdata}]]; LogLogCorner[{data__List},x_,y_,a_:0.612]:= Module[{halflength,halfheight,K,L,corner}, halflength:=LogLogLength[Apply[Sequence,{data}]][[1]]; halfheight:=LogLogLength[Apply[Sequence,{data}]][[2]]; K:=If[a<=1,1,1/a]; L:=If[a<=1,a,1]; corner={K (Log[10,x]-LogLogCenter[Apply[Sequence,{data}]][[1]])/ halflength, L (Log[10,y]-LogLogCenter[Apply[Sequence,{data}]][[2]])/ halfheight}]; LinearLogCorner[{data__List},x_,y_,a_:0.612]:= Module[{halflength,halfheight,K,L,corner}, halflength:=LinearLogLength[Apply[Sequence,{data}]][[1]]; halfheight:=LinearLogLength[Apply[Sequence,{data}]][[2]]; K:=If[a<=1,1,1/a]; L:=If[a<=1,a,1]; corner={K (x-LinearLogCenter[Apply[Sequence,{data}]][[1]])/halflength, L (Log[10,y]-LinearLogCenter[Apply[Sequence,{data}]][[2]])/ halfheight}]; LogLinearCorner[{data__List},x_,y_,a_:0.612]:= Module[{halflength,halfheight,K,L,corner}, halflength:=LogLinearLength[Apply[Sequence,{data}]][[1]]; halfheight:=LogLinearLength[Apply[Sequence,{data}]][[2]]; K:=If[a<=1,1,1/a]; L:=If[a<=1,a,1]; corner={K (Log[10,x]-LogLinearCenter[Apply[Sequence,{data}]][[1]])/ halflength, L (y-LogLinearCenter[Apply[Sequence,{data}]][[2]])/halfheight}]; LinearCorner[{data__List},x_,y_,a_:0.612]:= Module[{halflength,halfheight,K,L,corner}, halflength:=LinearLength[Apply[Sequence,{data}]][[1]]; halfheight:=LinearLength[Apply[Sequence,{data}]][[2]]; K:=If[a<=1,1,1/a]; L:=If[a<=1,a,1]; corner={K (x-LinearLogCenter[Apply[Sequence,{data}]][[1]])/halflength, L (y-LinearCenter[Apply[Sequence,{data}]][[2]])/halfheight}]; loglogticks[inputdata_]:= Module[{abclogbound,ordlogbound,abcdec,orddec,abcdiff,orddiff}, abclogbound={Floor[loglogrange[inputdata][[1]][[1]]], Ceiling[loglogrange[inputdata][[1]][[2]]]}; ordlogbound={Floor[loglogrange[inputdata][[2]][[1]]], Ceiling[loglogrange[inputdata][[2]][[2]]]}; abcdec[n_]:= If[n>3,ScantMultipleLogTicks[Apply[Sequence,abclogbound]], If[n>1.5,LooseMultipleLogTicks[Apply[Sequence,abclogbound]], If[n>1,TightMultipleLogTicks[Apply[Sequence,abclogbound]], FullMultipleLogTicks[Apply[Sequence,abclogbound]]]]]; orddec[n_]:= If[n>3,ScantMultipleLogTicks[Apply[Sequence,ordlogbound]], If[n>1.5,LooseMultipleLogTicks[Apply[Sequence,ordlogbound]], If[n>1,TightMultipleLogTicks[Apply[Sequence,ordlogbound]], FullMultipleLogTicks[Apply[Sequence,ordlogbound]]]]]; abcdiff= Abs[loglogrange[inputdata][[1]][[2]]- loglogrange[inputdata][[1]][[1]]]; orddiff= Abs[loglogrange[inputdata][[2]][[2]]- loglogrange[inputdata][[2]][[1]]]; Table[{abcdec[abcdiff],orddec[orddiff]}] ]; logloggrid[inputdata_]:= Module[{abclogbound,ordlogbound,abcdec,orddec,abcdiff,orddiff}, abclogbound={Floor[loglogrange[inputdata][[1]][[1]]], Ceiling[loglogrange[inputdata][[1]][[2]]]}; ordlogbound={Floor[loglogrange[inputdata][[2]][[1]]], Ceiling[loglogrange[inputdata][[2]][[2]]]}; abcdec[n_]:= If[n>3,ScantMultipleLogGrid[Apply[Sequence,abclogbound]], If[n>1.5,LooseMultipleLogGrid[Apply[Sequence,abclogbound]], If[n>1,TightMultipleLogGrid[Apply[Sequence,abclogbound]], FullMultipleLogGrid[Apply[Sequence,abclogbound]]]]]; orddec[n_]:= If[n>3,ScantMultipleLogGrid[Apply[Sequence,ordlogbound]], If[n>1.5,LooseMultipleLogGrid[Apply[Sequence,ordlogbound]], If[n>1,TightMultipleLogGrid[Apply[Sequence,ordlogbound]], FullMultipleLogGrid[Apply[Sequence,ordlogbound]]]]]; abcdiff= Abs[loglogrange[inputdata][[1]][[2]]- loglogrange[inputdata][[1]][[1]]]; orddiff= Abs[loglogrange[inputdata][[2]][[2]]- loglogrange[inputdata][[2]][[1]]]; Table[{abcdec[abcdiff],orddec[orddiff]}] ]; linearloggrid[inputdata_]:= Module[{ordlogbound,orddec,abcdiff,orddiff}, ordlogbound={Floor[linearlogrange[inputdata][[2]][[1]]], Ceiling[linearlogrange[inputdata][[2]][[2]]]}; orddec[n_]:= If[n>3,ScantMultipleLogGrid[Apply[Sequence,ordlogbound]], If[n>1.5,LooseMultipleLogGrid[Apply[Sequence,ordlogbound]], If[n>1,TightMultipleLogGrid[Apply[Sequence,ordlogbound]], FullMultipleLogGrid[Apply[Sequence,ordlogbound]]]]]; orddiff= Abs[loglogrange[inputdata][[2]][[2]]- loglogrange[inputdata][[2]][[1]]]; Table[{Automatic,orddec[orddiff]}]]; linearlogticks[inputdata_]:=Module[{ordlogbound,orddec,orddiff}, ordlogbound={Floor[loglogrange[inputdata][[2]][[1]]], Ceiling[loglogrange[inputdata][[2]][[2]]]}; orddec[n_]:= If[n>3,ScantMultipleLogTicks[Apply[Sequence,ordlogbound]], If[n>1.5,LooseMultipleLogTicks[Apply[Sequence,ordlogbound]], If[n>1,TightMultipleLogTicks[Apply[Sequence,ordlogbound]], FullMultipleLogTicks[Apply[Sequence,ordlogbound]]]]]; orddiff= Abs[linearlogrange[inputdata][[2]][[2]]- linearlogrange[inputdata][[2]][[1]]]; Table[{Automatic,orddec[orddiff]}] ]; loglineargrid[inputdata_]:=Module[{abclogbound,abcdec,abcdiff}, abclogbound={Floor[loglinearrange[inputdata][[1]][[1]]], Ceiling[loglinearrange[inputdata][[1]][[2]]]}; abcdec[n_]:= If[n>3,ScantMultipleLogGrid[Apply[Sequence,abclogbound]], If[n>1.5,LooseMultipleLogGrid[Apply[Sequence,abclogbound]], If[n>1,TightMultipleLogGrid[Apply[Sequence,abclogbound]], FullMultipleLogGrid[Apply[Sequence,abclogbound]]]]]; abcdiff= Abs[loglinearrange[inputdata][[1]][[2]]- loglinearrange[inputdata][[1]][[1]]]; Table[{abcdec[abcdiff],Automatic}] ]; loglinearticks[inputdata_]:=Module[{abclogbound,abcdec,abcdiff}, abclogbound={Floor[loglinearrange[inputdata][[1]][[1]]], Ceiling[loglinearrange[inputdata][[1]][[2]]]}; abcdec[n_]:= If[n>3,ScantMultipleLogTicks[Apply[Sequence,abclogbound]], If[n>1.5,LooseMultipleLogTicks[Apply[Sequence,abclogbound]], If[n>1,TightMultipleLogTicks[Apply[Sequence,abclogbound]], FullMultipleLogTicks[Apply[Sequence,abclogbound]]]]]; abcdiff= Abs[loglinearrange[inputdata][[1]][[2]]- loglinearrange[inputdata][[1]][[1]]]; Table[{abcdec[abcdiff],Automatic}] ]; colordiamond[s_]:=RegularPolygon[4,s]; colortriangle[s_]:=RegularPolygon[3,s]; colorpentagon[s_]:=RegularPolygon[5,s]; colorhexagon[s_]:=RegularPolygon[6,s]; coloroctagon[s_]:=RegularPolygon[8,s]; colorstar[s_]:=RegularPolygon[5,s,{0,0},0,2]; colorpoint:=RegularPolygon[6,0.002]; NewMakeSymbol[{a_,Line[x_]}]:= Module[{z,y},y=Line[(Scaled[#1,z]&)/@x]; y=y/.z\[Rule]#1; Evaluate[{a,y}]&]; ColorSymbol[e_,f_,g_,Line[x_]]:=NewMakeSymbol[{RGBColor[e,f,g],Line[x]}]; RedSymbol[Line[x_]]:=ColorSymbol[1,0,0,Line[x]]; OrangeSymbol[Line[x_]]:=ColorSymbol[1,0.5,0,Line[x]]; YellowSymbol[Line[x_]]:=ColorSymbol[1,1,0,Line[x]]; GreenSymbol[Line[x_]]:=ColorSymbol[0,1,0,Line[x]]; BlueSymbol[Line[x_]]:=ColorSymbol[0,0,1,Line[x]]; BlackSymbol[Line[x_]]:=ColorSymbol[0,0,0,Line[x]]; HuedSymbol[e_,Line[x_]]:=NewMakeSymbol[{Hue[e],Line[x]}]; gencolorbarfunc[pt_,e_,f_,g_, ErrorBar[{t_,s_},{u_,v_}]]:={RGBColor[e,f, g],{Line[{{pt[[1]]+Max[Abs[s]],pt[[2]]},{pt[[1]]-Max[Abs[t]], pt[[2]]}}]}, Line[{{pt[[1]],pt[[2]]-Max[Abs[u]]},{pt[[1]],pt[[2]]+Max[Abs[v]]}}], Line[{{pt[[1]],pt[[2]]+Max[Abs[v]]}, Offset[{2,0},{pt[[1]],pt[[2]]+Max[Abs[v]]}]}], Line[{{pt[[1]],pt[[2]]+Max[Abs[v]]}, Offset[{-2,0},{pt[[1]],pt[[2]]+Max[Abs[v]]}]}], Line[{{pt[[1]],pt[[2]]-Max[Abs[u]]}, Offset[{2,0},{pt[[1]],pt[[2]]-Max[Abs[u]]}]}], Line[{{pt[[1]],pt[[2]]-Max[Abs[u]]}, Offset[{-2,0},{pt[[1]],pt[[2]]-Max[Abs[u]]}]}], Line[{{pt[[1]]-Max[Abs[t]],pt[[2]]}, Offset[{0,2},{pt[[1]]-Max[Abs[t]],pt[[2]]}]}], Line[{{pt[[1]]-Max[Abs[t]],pt[[2]]}, Offset[{0,-2},{pt[[1]]-Max[Abs[t]],pt[[2]]}]}], Line[{{pt[[1]]+Max[Abs[s]],pt[[2]]}, Offset[{0,2},{pt[[1]]+Max[Abs[s]],pt[[2]]}]}], Line[{{pt[[1]]+Max[Abs[s]],pt[[2]]}, Offset[{0,-2},{pt[[1]]+Max[Abs[s]],pt[[2]]}]}]}; RedSerif[pt_,ErrorBar[{t_,s_},{u_,v_}]]:= gencolorbarfunc[pt,1,0,0,ErrorBar[{t,s},{u,v}]]; OrangeSerif[pt_,ErrorBar[{t_,s_},{u_,v_}]]:= gencolorbarfunc[pt,1,0.5,0,ErrorBar[{t,s},{u,v}]]; YellowSerif[pt_,ErrorBar[{t_,s_},{u_,v_}]]:= gencolorbarfunc[pt,1,1,0,ErrorBar[{t,s},{u,v}]]; GreenSerif[pt_,ErrorBar[{t_,s_},{u_,v_}]]:= gencolorbarfunc[pt,0,1,0,ErrorBar[{t,s},{u,v}]]; BlueSerif[pt_,ErrorBar[{t_,s_},{u_,v_}]]:= gencolorbarfunc[pt,0,0,1,ErrorBar[{t,s},{u,v}]]; BlackSerif[pt_,ErrorBar[{t_,s_},{u_,v_}]]:= gencolorbarfunc[pt,0,0,0,ErrorBar[{t,s},{u,v}]]; gennoseriffunc[pt_,e_,f_,g_, ErrorBar[{t_,s_},{u_,v_}]]:={RGBColor[e,f, g],{Line[{{pt[[1]]+Max[Abs[s]],pt[[2]]},{pt[[1]]-Max[Abs[t]], pt[[2]]}}]}, Line[{{pt[[1]],pt[[2]]-Max[Abs[u]]},{pt[[1]],pt[[2]]+Max[Abs[v]]}}]}; RedBar[pt_,ErrorBar[{t_,s_},{u_,v_}]]:= gennoseriffunc[pt,1,0,0,ErrorBar[{t,s},{u,v}]]; OrangeBar[pt_,ErrorBar[{t_,s_},{u_,v_}]]:= gennoseriffunc[pt,1,0.5,0,ErrorBar[{t,s},{u,v}]]; YellowBar[pt_,ErrorBar[{t_,s_},{u_,v_}]]:= gennoseriffunc[pt,1,1,0,ErrorBar[{t,s},{u,v}]]; GreenBar[pt_,ErrorBar[{t_,s_},{u_,v_}]]:= gennoseriffunc[pt,0,1,0,ErrorBar[{t,s},{u,v}]]; BlueBar[pt_,ErrorBar[{t_,s_},{u_,v_}]]:= gennoseriffunc[pt,0,0,1,ErrorBar[{t,s},{u,v}]]; BlackBar[pt_,ErrorBar[{t_,s_},{u_,v_}]]:= gennoseriffunc[pt,0,0,0,ErrorBar[{t,s},{u,v}]]; End[]; Attributes[MultipleLogLogPlot]={ReadProtected}; Attributes[MultipleLogLinearPlot]={ReadProtected}; Attributes[MultipleLinearLogPlot]={ReadProtected}; Attributes[MultipleLinearPlot]={ReadProtected}; Attributes[FullMultipleLogGrid]={ReadProtected}; Attributes[TightMultipleLogGrid]={ReadProtected}; Attributes[LooseMultipleLogGrid]={ReadProtected}; Attributes[ScantMultipleLogGrid]={ReadProtected}; Attributes[FullMultipleLogTicks]={ReadProtected}; Attributes[TightMultipleLogTicks]={ReadProtected}; Attributes[LooseMultipleLogTicks]={ReadProtected}; Attributes[ScantMultipleLogTicks]={ReadProtected}; Attributes[colortriangle]={ReadProtected}; Attributes[colordiamond]={ReadProtected}; Attributes[colorpentagon]={ReadProtected}; Attributes[colortriangle]={ReadProtected}; Attributes[colorhexagon]={ReadProtected}; Attributes[coloroctagon]={ReadProtected}; Attributes[colorstar]={ReadProtected}; Attributes[colorpoint]={ReadProtected}; Attributes[RedSymbol]={ReadProtected}; Attributes[OrangeSymbol]={ReadProtected}; Attributes[YellowSymbol]={ReadProtected}; Attributes[GreenSymbol]={ReadProtected}; Attributes[BlueSymbol]={ReadProtected}; Attributes[BlackSymbol]={ReadProtected}; Attributes[ColorSymbol]={ReadProtected}; Attributes[HuedSymbol]={ReadProtected}; Attributes[RedBar]={ReadProtected}; Attributes[OrangeBar]={ReadProtected}; Attributes[YellowBar]={ReadProtected}; Attributes[GreenBar]={ReadProtected}; Attributes[BlueBar]={ReadProtected}; Attributes[BlackBar]={ReadProtected}; Attributes[RedSerif]={ReadProtected}; Attributes[OrangeSerif]={ReadProtected}; Attributes[YellowSerif]={ReadProtected}; Attributes[GreenSerif]={ReadProtected}; Attributes[BlueSerif]={ReadProtected}; Attributes[BlackSerif]={ReadProtected}; Attributes[LogLogCorner]={ReadProtected}; Attributes[LinearLogCorner]={ReadProtected}; Attributes[LogLinearCorner]={ReadProtected}; Attributes[LinearCorner]={ReadProtected}; EndPackage[] Null