/*------------------------------------------------------------------------------ © Copyright 2011-2013 University of Manitoba This program is free software: you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation, either version 3 of the License, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program. If not, see . --------------------------------------------------------------------------------- Original Author: Mahmoud Azimaee Modified by: Say Hong Please direct questions and comments to info@cpe.umanitoba.ca This macro performs a trend analysis over a specified time range, the output will be saved in graphinc formats (.PNG) Add parameter xaxis_space to allow users to specify the interval of the xaxis label 21Oct2014 Macro Parameters: Ds = Name of dataset Startyr = Beginning year Endyr = Ending year Bydate = Date variable (must be SAS Date) bydatetime = Date time variable Byvar = Optional, if omitted the trend analysis will be run for all records in the dataset Byfmt = Optional, format for byvar if any Bymonth = Default value is N, if set to Y then trend analysis will be run by month instead of year (valid value is Y/N) Ytype = Default value is F, if set to C then trend analysis will be run by calendar year, otherwise trend analysis will be performed by fiscal year (valid value is F/C) memnum = Space separated list of cluster members xaxis_space = Allow users to speicfy the user define interval of the xaxis label -------------------------------------------------------------------------------*/ %macro dq_trend(ds=, startyr=, endyr=, bydate=, bydatetime=, byvar=_ALL_, byfmt=, bymonth=N, ytype=F, memnum=, xaxis_space=); %if &bydate ^= and &bydatetime ^= %then %do; %put WARNING: The dq_trend macro can not run for DATE and DATETIME variables simultaneously; %put WARNING: One of the BYDATE or BYDATETIME variable must be blank; %put WARNING: This macro stop without executing; %return; %end; %if &bydate = and &bydatetime = %then %do; %put WARNING: At least one of macro paramter bydate= or bydatetime= can not be blank; %put WARNING: This macro stop without executing; %return; %end; proc format; %if &bydate ^= %then %do; %if %upcase(&bymonth) = N %then %do; value byyr %if %upcase(&ytype) = F %then %do; %do i = &startyr %to &endyr - 1; "01apr&i"d - "31mar%eval(&i+1)"d = "&i/%eval(&i+1)" %end; %end; %else %if %upcase(&ytype) = C %then %do; %do i = &startyr %to &endyr; "01jan&i"d - "31dec&i"d = "&i" %end; %end; Other = 'Other Years' ; %end; %else %if %upcase(&bymonth) = Y %then %do; value monthly %if %upcase(&ytype) = F %then %do; %do yr = &startyr %to &endyr-1; "01Apr&yr"d - "01May&yr"d = "Apr&yr" "01May&yr"d - "01Jun&yr"d = "May&yr" "01Jun&yr"d - "01Jul&yr"d = "Jun&yr" "01Jul&yr"d - "01Aug&yr"d = "Jul&yr" "01Aug&yr"d - "01Sep&yr"d = "Aug&yr" "01Sep&yr"d - "01Oct&yr"d = "Sep&yr" "01Oct&yr"d - "01Nov&yr"d = "Oct&yr" "01Nov&yr"d - "01Dec&yr"d = "Nov&yr" "01Dec&yr"d - "01Jan%eval(&yr+1)"d = "Dec&yr" "01Jan%eval(&yr+1)"d - "01Feb%eval(&yr+1)"d = "Jan%eval(&yr+1)" "01Feb%eval(&yr+1)"d - "01Mar%eval(&yr+1)"d = "Feb%eval(&yr+1)" "01Mar%eval(&yr+1)"d - "01Apr%eval(&yr+1)"d = "Mar%eval(&yr+1)" %end; %end; %else %if %upcase(&ytype) = C %then %do; %do yr = &startyr %to &endyr; "01Jan&yr"d - "01Feb&yr"d = "Jan&yr" "01Feb&yr"d - "01Mar&yr"d = "Feb&yr" "01Mar&yr"d - "01Apr&yr"d = "Mar&yr" "01Apr&yr"d - "01May&yr"d = "Apr&yr" "01May&yr"d - "01Jun&yr"d = "May&yr" "01Jun&yr"d - "01Jul&yr"d = "Jun&yr" "01Jul&yr"d - "01Aug&yr"d = "Jul&yr" "01Aug&yr"d - "01Sep&yr"d = "Aug&yr" "01Sep&yr"d - "01Oct&yr"d = "Sep&yr" "01Oct&yr"d - "01Nov&yr"d = "Oct&yr" "01Nov&yr"d - "01Dec&yr"d = "Nov&yr" "01Dec&yr"d - "01Jan%eval(&yr+1)"d = "Dec&yr" %end; %end; other = 'Other Years' ; %end; %end; %if &bydatetime ^= %then %do; %if %upcase(&bymonth) = N %then %do; value byyr %if %upcase(&ytype) = F %then %do; %do i = &startyr %to &endyr - 1; "01apr&i.:0:0"dt - "31mar%eval(&i+1):23:59:59"dt = "&i/%eval(&i+1)" %end; %end; %else %if %upcase(&ytype) = C %then %do; %do i = &startyr %to &endyr; "01jan&i.:0:0"dt - "31dec&i.:23:59:59"dt = "&i" %end; %end; Other = 'Other Years' ; %end; %else %if %upcase(&bymonth) = Y %then %do; value monthly %if %upcase(&ytype) = F %then %do; %do yr = &startyr %to &endyr - 1; "01Apr&yr.:0:0"dt - "01May&yr.:0:0"dt = "Apr&yr" "01May&yr.:0:0"dt - "01Jun&yr.:0:0"dt = "May&yr" "01Jun&yr.:0:0"dt - "01Jul&yr.:0:0"dt = "Jun&yr" "01Jul&yr.:0:0"dt - "01Aug&yr.:0:0"dt = "Jul&yr" "01Aug&yr.:0:0"dt - "01Sep&yr.:0:0"dt = "Aug&yr" "01Sep&yr.:0:0"dt - "01Oct&yr.:0:0"dt = "Sep&yr" "01Oct&yr.:0:0"dt - "01Nov&yr.:0:0"dt = "Oct&yr" "01Nov&yr.:0:0"dt - "01Dec&yr.:0:0"dt = "Nov&yr" "01Dec&yr.:0:0"dt - "01Jan%eval(&yr+1):0:0"dt = "Dec&yr" "01Jan%eval(&yr+1):0:0"dt - "01Feb%eval(&yr+1):0:0"dt = "Jan%eval(&yr+1)" "01Feb%eval(&yr+1):0:0"dt - "01Mar%eval(&yr+1):0:0"dt = "Feb%eval(&yr+1)" "01Mar%eval(&yr+1):0:0"dt - "01Apr%eval(&yr+1):0:0"dt = "Mar%eval(&yr+1)" %end; %end; %else %if %upcase(&ytype) = C %then %do; %do yr = &startyr %to &endyr; "01Jan&yr.:0:0"dt - "01Feb&yr.:0:0"dt = "Jan&yr" "01Feb&yr.:0:0"dt - "01Mar&yr.:0:0"dt = "Feb&yr" "01Mar&yr.:0:0"dt - "01Apr&yr.:0:0"dt = "Mar&yr" "01Apr&yr.:0:0"dt - "01May&yr.:0:0"dt = "Apr&yr" "01May&yr.:0:0"dt - "01Jun&yr.:0:0"dt = "May&yr" "01Jun&yr.:0:0"dt - "01Jul&yr.:0:0"dt = "Jun&yr" "01Jul&yr.:0:0"dt - "01Aug&yr.:0:0"dt = "Jul&yr" "01Aug&yr.:0:0"dt - "01Sep&yr.:0:0"dt = "Aug&yr" "01Sep&yr.:0:0"dt - "01Oct&yr.:0:0"dt = "Sep&yr" "01Oct&yr.:0:0"dt - "01Nov&yr.:0:0"dt = "Oct&yr" "01Nov&yr.:0:0"dt - "01Dec&yr.:0:0"dt = "Nov&yr" "01Dec&yr.:0:0"dt - "01Jan%eval(&yr+1):0:0"dt = "Dec&yr" %end; %end; Other = 'Other Years' ; %end; %end; run; %if &memnum ^= %then %do; %let memn = %sysfunc(countw(&memnum)); %let cls = %scan(&ds, 2, .); %do i = 1 %to &memn; %let mem = %scan(&memnum, &i); data data&i; set &ds(memnum=&mem); run; %end; data &cls; set data1-data&memn; run; proc datasets nolist memtype=data lib=work; delete data1-data&memn; quit; %let ds = &cls; %end; %if &bydate = %then %let bydate = &bydatetime; data data_temp; length trend_by $64; %if %upcase(&byvar) = _ALL_ %then set &ds(keep=&bydate)%str(;); %else set &ds(keep=&bydate &byvar)%str(;); %if %upcase(&bymonth) = N %then yr=put(&bydate, byyr.)%str(;); %else %if %upcase(&bymonth) = Y %then yr=put(&bydate, monthly.)%str(;); %if %upcase(&byvar) = _ALL_ %then trend_by = "&byvar"%str(;); %else %if %upcase(&byvar) ^= _ALL_ %then %do; %if &byfmt= %then trend_by = &byvar%str(;); %else trend_by=put(&byvar, &byfmt..)%str(;); %end; run; proc freq data=Data_Temp noprint; table yr*trend_by / list out=trend_data sparse; run; data trend_data; set trend_data; by yr; if yr in ('Other Years', 'unknown' , '') then delete; else sup=0; if upcase(substr(yr,1,3))='JAN' then monthyr= substr(yr,4)||'01'; if upcase(substr(yr,1,3))='FEB' then monthyr= substr(yr,4)||'02'; if upcase(substr(yr,1,3))='MAR' then monthyr= substr(yr,4)||'03'; if upcase(substr(yr,1,3))='APR' then monthyr= substr(yr,4)||'04'; if upcase(substr(yr,1,3))='MAY' then monthyr= substr(yr,4)||'05'; if upcase(substr(yr,1,3))='JUN' then monthyr= substr(yr,4)||'06'; if upcase(substr(yr,1,3))='JUL' then monthyr= substr(yr,4)||'07'; if upcase(substr(yr,1,3))='AUG' then monthyr= substr(yr,4)||'08'; if upcase(substr(yr,1,3))='SEP' then monthyr= substr(yr,4)||'09'; if upcase(substr(yr,1,3))='OCT' then monthyr= substr(yr,4)||'10'; if upcase(substr(yr,1,3))='NOV' then monthyr= substr(yr,4)||'11'; if upcase(substr(yr,1,3))='DEC' then monthyr= substr(yr,4)||'12'; drop percent; run; proc sort data=trend_data; %if %upcase(&bymonth) = N %then by trend_by yr%str(;); %if %upcase(&bymonth) = Y %then by trend_by monthyr%str(;); run; *** Do the transformations; data trend_data; set trend_data; %if %upcase(&bymonth) = N %then by trend_by yr;; %if %upcase(&bymonth) = Y %then by trend_by monthyr;; %if %upcase(&bymonth) = N %then %do; retain firstyr; time=input(substr(yr,1,4),4.); count1=lag(count); if first.trend_by then firstyr=time; time=time - firstyr + 1; %end; %else %do; if first.trend_by then time=0; time + 1; %end; time2=time*time; logtime=log(time); sqrttime=sqrt(time); exptime=exp(time); inverstime=1/time; negexptime=exp(-time); run; *** Find the best Regression Model by Minimum RSME; proc reg data=trend_data outest=parms noprint; Linear: model COUNT=Time / EDF ; Quatratic: model COUNT=Time2 / EDF ; Exponential: model COUNT=exptime / EDF ; Logaritmic: model COUNT=logtime / EDF ; SQRT: model COUNT=sqrttime / EDF ; Inverse: model COUNT=inverstime / EDF ; Neg_Exponential: model COUNT=negexptime / EDF ; by trend_by; run; Proc means data=parms noprint; var _RMSE_ ; by trend_by; output out=RMSE (keep=trend_by RMSE) MIN=RMSE; run; data parms; merge parms RMSE; by trend_by; if _RMSE_ = RMSE; rename _RSQ_ = RSQ _MODEL_ = Model; keep trend_by _MODEL_ RMSE _RSQ_ ; run; data trend_data; merge trend_data parms; by trend_by; if time=1 then count1=.; if count=count1 & count ^in (0, 5.999) then same=1; else same=0; run; proc reg data=trend_data outest=parm_lin noprint; Linear: model COUNT=Time; by trend_by; output out=res_lin RSTUDENT=STR; format time time.; where model='Linear'; run; proc reg data=trend_data outest=parm_quad noprint; Quatratic: model COUNT=Time2; by trend_by; output out=res_quad RSTUDENT=STR; format time time.; where model='Quatratic'; run; proc reg data=trend_data outest=parm_exp noprint; Exponential: model COUNT=exptime; by trend_by; output out=res_exp RSTUDENT=STR; format time time.; where model='Exponential'; run; proc reg data=trend_data outest=parm_log noprint; Logaritmic: model COUNT=logtime ; by trend_by; output out=res_log RSTUDENT=STR; format time time.; where model='Logaritmic'; run; proc reg data=trend_data outest=parm_sqrt noprint; SQRT: model COUNT=sqrttime ; by trend_by; output out=res_sqrt RSTUDENT=STR; format time time.; where model='SQRT'; run; proc reg data=trend_data outest=parm_inv noprint; Inverse: model COUNT=inverstime ; by trend_by; output out=res_inv RSTUDENT=STR; format time time.; where model='Inverse'; run; proc reg data=trend_data outest=parm_neg noprint; Neg_Exponential: model COUNT=negexptime ; by trend_by; output out=res_neg RSTUDENT=STR; format time time.; where model='Neg_Exponential'; run; data parm_all; length _depvar_ $32; set parm_lin parm_quad parm_exp parm_log parm_sqrt parm_inv parm_neg; by trend_by; array beta{7} time time2 exptime logtime sqrttime inverstime negexptime; do i=1 to 7; if beta{i} ^=. then Beta1=beta{i}; end; keep trend_by intercept beta1; run; data parms; merge parms parm_all; by trend_by; run; data trend_data; merge trend_data parms; by trend_by; if Model='Linear' then yhat=intercept + beta1*time; if Model='Quatratic' then yhat=intercept + beta1*time2; if Model='Exponential' then yhat=intercept + beta1*exptime; if Model='Logaritmic' then yhat=intercept + beta1*logtime; if Model='SQRT' then yhat=intercept + beta1*sqrttime; if Model='Inverse' then yhat=intercept + beta1*inverstime; if Model='Neg_Exponential' then yhat=intercept + beta1*negexptime; run; data res_all; length COUNT 8. trend_by $ 64.; set %let dslist=res_lin res_quad res_exp res_log res_sqrt res_inv res_neg; %do i = 1 %to %sysfunc(countw(&dslist)); %let dsid = %sysfunc(open(%scan(&dslist, &i))); %let numobs = %sysfunc(attrn(&dsid, nlobs)); %let rc = %sysfunc(close(&dsid)); %if &numobs ^= 0 %then %scan(&dslist, &i); %end; ; by trend_by; if YR^=''; keep YR trend_by STR monthyr; run; proc freq data=trend_data noprint; table yr / list out=t; run; data _null_; if 0 then set t nobs=nobs; call symputx('n', nobs); stop; run; data t; set t; call symput('t',tinv(.95,%EVAL(&n-2-1))); run; data trend_data; length model2 $30 trend_by2 $64; merge trend_data res_all; %IF %upcase(&bymonth)=N %THEN by trend_by yr;; %IF %upcase(&bymonth)=Y %THEN by trend_by monthyr;; t=SYMGETN('t'); label t='t(.95,n-p-1)'; if (t < STR) | (STR < -t) then outlier=1; else outlier=0; if Model='Linear' then model2='Y=Beta0 + Beta1*X '; if Model='Quatratic' then model2='Y=Beta0 + Beta1*X^2 '; if Model='Exponential' then model2='Y=Beta0 + Beta1*exp(X) '; if Model='Logaritmic' then model2='Y=Beta0 + Beta1*log(X) '; if Model='SQRT' then model2='Y=Beta0 + Beta1*SQRT(X)'; if Model='Inverse' then model2='Y=Beta0 + Beta1*(1/X) '; if Model='Neg_Exponential' then model2='Y=Beta0 + Beta1*Exp(-X)'; if trend_by='_ALL_' then trend_by2='All Records'; else trend_by2=trend_by; if 0 < COUNT < 6 then do; COUNT=3; sup=1; end; Lable trend_by2='By Variable'; run; data graphlabel(keep=function xsys ysys xc y text color position size trend_by trend_by2); set trend_data; by trend_by2; * Define annotate variable attributes; length color function $8 text $30; retain function 'symbol' xsys ysys '2' color 'red' position '2' size 1.8; if outlier=1 then do; * Create a label; text = 'dot'; %IF %upcase(&bymonth)=N %THEN xc=yr;; %IF %upcase(&bymonth)=Y %THEN xc=monthyr;; y=count; output graphlabel; end; run; data graphlabel2(keep=function xsys ysys xc y text color position size trend_by trend_by2); set trend_data; %IF %upcase(&BYMONTH)=N %THEN by trend_by2 yr;; %IF %upcase(&BYMONTH)=Y %THEN by trend_by2 monthyr;; * Define annotate variable attributes; length color function $8 text $30; retain function 'label' xsys ysys '2' color 'vibg' position '6' size 1; %IF %upcase(&BYMONTH)=N %THEN if last.trend_by2 & last.yr then do;; %IF %upcase(&BYMONTH)=Y %THEN if last.trend_by2 & last.monthyr then do;; * Create a label; text = model2; %IF %upcase(&BYMONTH)=N %THEN xc=yr;; %IF %upcase(&BYMONTH)=Y %THEN xc=monthyr;; y=yhat; output graphlabel2; end; run; data graphlabel3(keep=function xsys ysys xc y text color position size trend_by trend_by2); set trend_data; %IF %upcase(&BYMONTH)=N %THEN by trend_by2 yr;; %IF %upcase(&BYMONTH)=Y %THEN by trend_by2 monthyr;; * Define annotate variable attributes; length color function $8 text $30; retain function 'symbol' xsys ysys '2' color 'green' position '2' size 2.2; if sup=1 then do; * Create a label; text = 'circle'; %IF %upcase(&BYMONTH)=N %THEN xc=yr;; %IF %upcase(&BYMONTH)=Y %THEN xc=monthyr;; y=count; output graphlabel3; end; run; data graphlabel4(keep=function xsys ysys xc y text color position size trend_by trend_by2); set trend_data; %IF %upcase(&BYMONTH)=N %THEN by trend_by2 yr;; %IF %upcase(&BYMONTH)=Y %THEN by trend_by2 monthyr;; * Define annotate variable attributes; length color function $8 text $30; retain function 'symbol' xsys ysys '2' color 'orange' position '2' size 1.8; if same=1 then do; * Create a label; text = 'dot'; %IF %upcase(&BYMONTH)=N %THEN xc=yr;; %IF %upcase(&BYMONTH)=Y %THEN xc=monthyr;; y=count; output graphlabel4; end; run; data graphlabel; set graphlabel graphlabel2 graphlabel3 graphlabel4; by trend_by2; run; /* Add to allow users to specify the interval of the xaxis tick mark label 21Oct2014*/ %if &xaxis_space ^= %then %do; proc sql noprint; select count (distinct yr) into :cntyr from trend_data; quit; %let tickmark =; %do i = 1 %to &cntyr %by &xaxis_space; %let tick = %str(t=&i); %do j = 1 %to &xaxis_space-1; %let n = %eval(&i + &j); %if &n <= &cntyr %then %let tick = &tick %str(t=&n ''); %end; %let tickmark = &tickmark &tick; %*%put &tick; %end; %end; /******/ goptions reset=all noborder cback=white htitle=12pt htext=9pt; SYMBOL1 i=join l=1 w=3 v=dot color='blue' h=1 pointlabel = none; SYMBOL2 i=join l=20 v=dot c=vibg h=.01 pointlabel=none ; title1 f=zapfb h=1.2 c=blue "Trend Analysis for Dataset: &DS"; %if %upcase(&byvar) = _ALL_ %then title2 f=zapfb h=1 "Date Variable: &BYDATE"%str(;); %else title2 f=zapfb h=1 "Date Variable: &BYDATE, By Variable: &BYVAR"%str(;); footnote1 justify=c f=zapfb height=.8 c=red box=1 bspace=0 bcolor=red ' ' justify=l c=black ' Significant outliers'; footnote2 justify=c f=zapfb height=.8 c=orange box=1 bspace=0 bcolor=orange ' ' justify=l c=black ' Identical Subsequent frequencies'; footnote3 justify=c f=zapfb height=.8 c=green box=1 bspace=0 bcolor=green ' ' justify=l c=black ' Suppressed small frequencies (between 0 to 6)'; /* Add to allow users to specify the interval of the xaxis tick mark label 21Oct2014*/ %if &xaxis_space ^= %then %do; %IF %upcase(&BYMONTH)=N %THEN axis1 minor=none value=(h=.9 angle=90 &tickmark) offset=(3,20) %if %upcase(&ytype) = F %then label=('Fiscal Year')%str(;); %else %if %upcase(&ytype) = C %then label = ('Calendar Year')%str(;); %IF %upcase(&BYMONTH)=Y %THEN axis1 minor=none value=( h=.9 &tickmark) offset=(3,20) label=('Month');; %end; /******/ %else %do; %IF %upcase(&BYMONTH)=N %THEN axis1 minor=none value=(h=.9 angle=90) offset=(3,20) %if %upcase(&ytype) = F %then label=('Fiscal Year')%str(;); %else %if %upcase(&ytype) = C %then label = ('Calendar Year')%str(;); %IF %upcase(&BYMONTH)=Y %THEN axis1 minor=none value=( h=.9 ) offset=(3,20) label=('Month');; %end; axis2 minor=none offset=(0,3) label=('Frequency' justify=right ); *** Plot on the Screen only; proc GPLOT data=trend_data; %IF %upcase(&BYMONTH)=N %THEN plot COUNT*yr yhat*yr / overlay frame haxis=axis1 vaxis=axis2 vzero cframe=gwh annotate=graphlabel;; %IF %upcase(&BYMONTH)=Y %THEN plot COUNT*monthyr yhat*monthyr / overlay frame haxis=axis1 vaxis=axis2 vzero cframe=gwh annotate=graphlabel;; by trend_by2; /* %IF &BYFMT ^='' %THEN %DO;*/ /* format trend_by2 &BYFMT;*/ /* %END;*/ run; quit; proc sql noprint; select distinct trend_by2 into :ngraph separated by ',' from trend_data; quit; %if %index(%quote(&ngraph), %str(,)) ^= 0 %then %let graph_name=&ngraph; %else %if %upcase(%sysfunc(compress(&ngraph))) = ALLRECORDS %then %let graph_name = &bydate; %let dsid = %sysfunc(open(trend_data)); %let varnum = %sysfunc(varnum(&dsid,trend_by2)); %let vartyp = %sysfunc(vartype(&dsid,&varnum)); /* variable type */ %let rc = %sysfunc(close(&dsid)); %if %substr(&dq_dir, %length(&dq_dir), 1) = \ %then %let dq_dir = %substr(&dq_dir, 1, %length(&dq_dir) - 1); *** Re-Plotting for output PNG format; goptions device=png gsfname=graphout; %do i = 1 %to %sysfunc(countw(%bquote(&ngraph), %str(,))); filename graphout "&DQ_Dir\trend_%scan(%bquote(&graph_name), &i, %str(,)).png"; %if %upcase(&byvar) ^= _ALL_ %then title3 f=zapfb h=1 "&byvar = %upcase(%scan(%bquote(&graph_name), &i, %str(,)))"%str(;); proc GPLOT data=trend_data; where %if &vartyp = C %then trend_by2 = "%scan(%bquote(&ngraph), &i, %str(,))"%str(;); %else %if &vartyp = N %then trend_by2 = %scan(%bquote(&ngraph), &i, %str(,))%str(;); %IF %upcase(&BYMONTH)=N %THEN %do; plot COUNT*yr yhat*yr / overlay frame haxis=axis1 vaxis=axis2 vzero cframe=gwh annotate=graphlabel(where=( %if &vartyp = C %then trend_by2 = "%scan(%bquote(&ngraph), &i, %str(,))"; %else %if &vartyp = N %then trend_by2 = %scan(%bquote(&ngraph), &i, %str(,));)); %end; %IF %upcase(&BYMONTH)=Y %THEN plot COUNT*monthyr yhat*monthyr / overlay frame haxis=axis1 vaxis=axis2 vzero cframe=gwh annotate=graphlabel;; /* by trend_by2;*/ /* %IF &BYFMT ^='' %THEN %DO;*/ /* format trend_by2 &BYFMT;*/ /* %END;*/ run; quit; %end; goptions reset=all; proc Datasets lib=work; delete data_temp graphlabel graphlabel2-graphlabel4 parms parm_all parm_lin parm_exp parm_inv parm_log parm_neg parm_quad parm_sqrt res_all res_exp res_inv res_lin res_log res_neg res_quad res_sqrt rmse t trend_data data_temp; quit; %mend dq_trend;