/*-------------------------------------------------------------------------------------*\ | PROGRAM NAME: | | scdm_data_qa_review-level1.sas | | | |---------------------------------------------------------------------------------------| | PURPOSE: | | The purpose of this program is to perform Level 1 data checks on all SCDM | | tables. | |---------------------------------------------------------------------------------------| | PROGRAM INPUT: | | see 00.0_scdm_data_qa_review_master_file.sas | | | | PROGRAM OUTPUT: | | see Workplan PDF | |---------------------------------------------------------------------------------------| | CONTACT: | | Sentinel Coordinating Center | | info@sentinelsystem.org | \*-------------------------------------------------------------------------------------*/ /*-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-; * PLEASE DO NOT EDIT BELOW WITHOUT CONTACTING THE SENTINEL OPERATIONS CENTER ; *-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-; /**/ * ---------------------- Macro: l1_variable ----------------------------------------------------- ; * Logic to confirm variables within table meet requirements existing, type, length and sort order ; * ----------------------------------------------------------------------------------------------- ; %macro l1_variable; %if &do_partitions and not %eval(&tabid in &tabid_exc) %then %let pn=1 ; /* use 1st partition as proxy for all partition */ %else %let pn= ; %* Collect table meta data - size, contents, total observations ; proc contents data=qadata.&&&tabid.table.&pn. out=l1_cont_temp noprint; run; %table_size (libin=QADATA, dsin=&&&tabid.table, libout=work, dsout=l1_size_temp); data dplocal.l1_cont_temp; length TABID $3 MEMNAME $32; set l1_cont_temp(rename=(memname=t_memname)); tabid=upcase("&tabid."); memname=PRXCHANGE('s/\d+$//', 1, trim(upcase(t_memname))) ; drop t_memname ; run; data dplocal.l1_cont_&tabid.; merge dplocal.l1_cont_temp l1_size_temp; by tabid memname; run; proc sql noprint; drop table dplocal.l1_cont_temp, l1_size_temp ; quit; %* Merge meta data to model l1 compliance lookup; proc sql noprint; create table dplocal.l1_scdm_comp_&tabid. as select upcase("&tabid.") as TabID length=3 , coalesce (a.variable,b.name) as var label="Variable Name" , a.varid label="SCDM Variable ID" , case when a.varid ne " " then "Y" else "N" end as MS_var label="Variable expected?" , case when length=. then "N" else "Y" end as DP_var label="Variable present?" , a.vartype as MS_type label="Expected variable type" , case when b.type=2 then 'C' when b.type=1 then 'N' else ' ' end as DP_type label="Actual variable type" length=1 , a.varlength as MS_length label="Expected variable length" length=3 , b.length as DP_length label="Actual variable length" length=3 , b.formatl as format_length label="Actual FORMATL value, if present" length=3 , . as req_length label="Required variable length" length=3 from infolder.lkp_all_l1 (where=(lowcase(tabid)=lowcase("&tabid."))) as a full join dplocal.l1_cont_&tabid. (keep=name type length formatl nobs) b on upcase(a.variable)=upcase(b.name) order by a.varid ; quit; %* Run query to collect table variable-value level counts; %do_l1_query ;; %* update metadata with required length result ; proc sql noprint; create table dplocal._l1_scdm_comp_&tabid. as select a.* , input(b.req_length,3.) as req_length from dplocal.l1_scdm_comp_&tabid.(drop=req_length) a left join dplocal.&tabid._l1_reqlen b on lowcase(a.var)=lowcase(b.var) order by a.varid ; drop table dplocal.l1_scdm_comp_&tabid.; quit; proc datasets lib=dplocal nolist; change _l1_scdm_comp_&tabid. = l1_scdm_comp_&tabid.; delete &tabid._l1_reqlen:; quit; %* Confirm correct table sort order ; %local sortVarList sortVarListSQL sortvarMiss sortOrderFlag; %local &tabid._sortOrderFlag_err &tabid._sortOrderFlag_count ; %let sortvarmiss=; %let &tabid._sortOrderFlag_err = 0; %let &tabid._sortOrderFlag_count = 0 ; proc sql noprint; select variable , quote(strip(lowcase(variable))) into :sortvarlist separated by " " , :sortvarlistsql separated by "," from infolder.lkp_all_l1 where lowcase(tabid) = lowcase("&tabid.") AND not missing(sortorder) order by sortorder; ; %* get any expected variables (MS_var=Y) missing from table (DP_var=N); select var into :sortvarmiss from dplocal.l1_scdm_comp_&tabid. where (MS_var="Y" AND MS_var ne DP_var) AND lowcase(var) in (&sortvarlistsql.) ; quit; %* if sort variables are present in table, then run the sort check ; %* otherwise, a 110 check will be flagged below to fail/abort processing; %if %length(&sortvarmiss.)=0 %then %do; %put ==> sortcheck: |table=&&&tabid.table.| |&=sortvarlist.| ; %put ==> Time now is %sysfunc(putn(%sysfunc(time()),timeampm12.)); %do p=1 %to &numpartitions; %if &do_partitions and not %eval(&tabid in &tabid_exc) %then %let pn=&p ; %else %do ; %let pn= ; %let p=&numpartitions ; %* end partition loop early ; %end ; %* redirect log output of sort test in temp log file to be parsed; filename sortlog "&dplocal.&tabid.&pn._sortchk.log"; proc printto log = sortlog new; run; proc sort data = qadata.&&&tabid.table.&pn(keep=&sortvarlist.) presorted out= _null_; by &sortvarlist.; run; %* output sort log; proc printto ; run; %* pull NOTES from temp log file to see if sort was verified ; data _null_; length lines $80; infile sortlog dlm='|'; input lines $; if lowcase(substr(lines,1,5)) = "note:"; if find(lowcase(lines),"input data set is not in sorted order") then call symputx('sortOrderFlag','1'); %* not sorted order ; else call symputx('sortOrderFlag','0'); %* in sorted order ; run; %* if sort order is verified then delete temp log output ; %if &sortOrderFlag. = 0 %then %do; %let rc=%sysfunc(fdelete(sortlog)); %let &tabid._sortOrderFlag_count=%eval(&&&tabid._sortOrderFlag_count + 1) ; %end; %else %do; %let &tabid._sortOrderFlag_err=%eval(&&&tabid._sortOrderFlag_err + &sortOrderFlag) ; %end ; %put |&tabid._sortOrderFlag_err=&&&tabid._sortOrderFlag_err| |&tabid._sortOrderFlag_count=&&&tabid._sortOrderFlag_count| ; %end; %* partition loop ; %put ==> Time now is %sysfunc(putn(%sysfunc(time()),timeampm12.)); %end; %*end condition sort var exists ; %* verify that the table meets uniq requirements ; %ds_nodupkey ; %* Evaluate metadata to define cases not meeting l1 requirement; data dplocal.temp_flag_&tabid._11x_00; length FlagID Variable $21 Value $8; set dplocal.l1_scdm_comp_&tabid. (where=(ms_var="Y")) end=last ; %* Exclude non-SCDM variables; retain FlagID Variable Value count; Variable=var; %* Flag missing variables ; if dp_type=' ' then do; flagid=strip(upcase("&tabid._1_"||varid||"_00-0_110")); count=99999; Value='NA'; output; end; %* Exclude missing SCDM variables from the remainder of the L1 checks; else do; %* ---- Compliance for variable type ; if ms_type ne dp_type then do; flagid=strip(upcase("&tabid._1_"||varid||"_00-0_112")); count=1; Value=dp_type; output; end; %* ---- Compliance for variable length ; %* Backwards compatibility for lab variable lengths in 8.0.0 ; %if &SCDMver=8.0.0 %then %do; if lowcase("&tabid.")= "lab" and VarID = "02" then ms_length = 10; if lowcase("&tabid.")= "lab" and VarID = "06" then ms_length = 6; %end; %* SHORT TERM FIX to be updated in future increments ; %* Provider table variable Specialty can have length of 2 or 10 ; if lowcase("&tabid.") = "pvd" and VarID = "02" then do; if dp_length not in (2,10) then do; flagid=strip(upcase("&tabid._1_"||varid||"_00-0_113")); count=99999; value=put(dp_length,3.); output; end; end; else do; if ms_length ne 0 and ms_length ne dp_length then do; flagid=strip(upcase("&tabid._1_"||varid||"_00-0_113")); count=99999; value=put(dp_length,3.); output; end; end; %* ---- Compliance for required length; if not missing(req_length) then do; if dp_length < req_length then do; flagid=strip(upcase("&tabid._1_"||varid||"_00-0_115")); count=99999; value=put(req_length, 3.); output; end; %* ---- Compliance for format length; if (format_length >0) AND (input(put(dp_length,ndigfmt.),3.) > format_length) then do; flagid=strip(upcase("&tabid._1_"||varid||"_00-0_116")); count=99999; value=put(format_length, 3.); output; end; end; %* end not missing(req_length) condition; end; %* ---- Compliance for sort order ; if last then do; if symgetn("&tabid._sortOrderFlag_err") >0 then do; flagid=strip(upcase("&tabid._1_00_00-0_102")); count=99999; variable = "NA"; value = "NA"; output; end; end; label variable=' '; keep flagid variable value count; run; %mend l1_variable; /* ---------------------- Macros utilized in do_l1_query ----------------------------------------- */ /* required length assessment logic */ %macro t_max(var) ; retain t_&var._max ; t_&var._max = max(t_&var._max, &var) ;; %mend; %macro reqlen(var); var="&var" ; if missing(t_&var._max) then req_length = '3' ; else req_length = put(t_&var._max,varlenf.) ;; %mend; /* missing and special missing counting logic */ %macro miss_spmiss(var); if &var in (.U, .S) then t_&var._spmiss+1 ; else if missing(&var) then t_&var._miss+1;; %mend; %macro miss(var); if missing(&var) then t_&var._miss+1;; %mend; %macro mvar_miss_spmiss(var); call symputx("&tabid._&var._spmiss", trim(put(t_&var._spmiss, 15.-l)), 'G' ) ; call symputx("&tabid._&var._miss", trim(put(t_&var._miss, 15.-l)), 'G' ) ;; t_nomiss = _n_ - t_&var._miss - t_&var._spmiss ; call symputx("&tabid._&var._nomiss", trim(put(t_nomiss, 15.-l)), 'G' ) ;; %mend; %macro mvar_miss(var); call symputx("&tabid._&var._spmiss", "0") ; call symputx("&tabid._&var._miss", trim(put(t_&var._miss, 15.-l)), 'G' ) ;; t_nomiss = _n_ - t_&var._miss ; call symputx("&tabid._&var._nomiss", trim(put(t_nomiss, 15.-l)), 'G' ) ;; %mend; /* logic for counting valid observations defined as populated */ /* valid observation defined as non-missing values & special missing if allowed per model */ %macro kcondition(var, varid, kcond) ; if ( &kcond ) then do ; t_&var._nobs+1 ; output dplocal._&varid._&tabid. ;; end; %mend ; %macro mvar_kcondition(var) ; call symputx("&tabid._&var._nobs", trim(put(t_&var._nobs, 15.-l)), 'G' ) ;; %mend; /* ---------------------- Macro: do_l1_query ----------------------------------------------------- */ /* Logic to create program per tabid with logic to count observations by select conditions and */ /* then run this program */ /* ----------------------------------------------------------------------------------------------- */ %macro do_l1_query ; %* Control macros to be populated by this macro; %global stmt_global stmt_dsout stmt_main stmt_eof ; %local i reqvarstr reqvarcnt reqvar; %* initialize program creation parameters that will be used to create program to missing; %let stmt_dsout= ; %let stmt_main= ; %let stmt_eof= ; %let stmt_global = ; %* identify variables already determined SCDM compliant; proc sql noprint; create table _t_l1query_lkp_&tabid. as select b.* from dplocal.l1_scdm_comp_&tabid. (where=(ms_var="Y")) as a left join infolder.lkp_all_l1 (where=(lowcase(tabid)=lowcase("&tabid."))) as b on a.var=b.variable where (upcase(a.dp_var)='Y') and (a.dp_length > .) and (a.ms_type = a.dp_type) order by b.varid ; ; create table _l1query_lkp_&tabid. as select *, monotonic ( ) as row from _t_l1query_lkp_&tabid. ; ; drop table _t_l1query_lkp_&tabid.; select count(*) into :varct from _l1query_lkp_&tabid. ; select quote(strip(lowcase(variable))) into :validvarlistsql separated by "," from _l1query_lkp_&tabid.; quit; %* select variables to evaluate for check 115/required length numeric to update program creation parameters; proc sql noprint; select variable1 into :reqvarstr separated by " " from infolder.lkp_all_flags where lowcase(TableID) = lowcase("&tabid.") AND checkID = "115" and lowcase(variable1) in (&validvarlistsql.); quit; %if %length(&reqvarstr. > 0) %then %do; %let stmt_dsout=&stmt_dsout dplocal.&tabid._l1_reqlen(keep=var req_length) ; %do i = 1 %to %sysfunc(countw(&reqvarstr.)); %let reqvar = %scan(&reqvarstr.,&i.); %let stmt_main=&stmt_main %nrstr(%t_max)(&reqvar) %str(;) ; %let stmt_eof=&stmt_eof %nrstr(%reqlen)(&reqvar) %str(;) output dplocal.&tabid._l1_reqlen %str(;) ; %end; %end ; %* select and process valid variables to update programming parameter values; %if &varct. > 0 %then %do j=1 %to &varct.; proc sql noprint; select varid , variable , vartype , case when lowcase(ValidValueType) = "special_missing" then cat(trim(variable), " > .") else cat("not missing(", trim(variable),")") end into :varid trimmed , :var trimmed , :vartype trimmed , :kcond trimmed from _l1query_lkp_&tabid. where row=&j. ; ;quit; %if "&vartype" = "N" %then %do ; %let stmt_main=&stmt_main %nrstr(%miss_spmiss)(&var) %str(;) ; %let stmt_eof=&stmt_eof %nrstr(%mvar_miss_spmiss)(&var) %str(;) ; %end ; %else %do ; %let stmt_main=&stmt_main %nrstr(%miss)(&var) %str(;) ; %let stmt_eof=&stmt_eof %nrstr(%mvar_miss)(&var) %str(;) ; %end ; %if &do_partitions and not %eval(&tabid in &tabid_exc) and %lowcase(&var) in &cross_varid and not %eval(%lowcase(&var) in &varname_exc) %then %do; %let stmt_dsout=&stmt_dsout dplocal._&varid._&tabid.(keep=&var pnum) ; %end ; %else %do; %let stmt_dsout=&stmt_dsout dplocal._&varid._&tabid.(keep=&var) ; %end; %let stmt_main=&stmt_main %nrstr(%kcondition)(&var, &varid, &kcond) %str(;) ; %let stmt_eof=&stmt_eof %nrstr(%mvar_kcondition)(&var) %str(;) ; %let stmt_global= &stmt_global ; %let stmt_global = &stmt_global &tabid._&var._nobs &tabid._&var._spmiss &tabid._&var._miss &tabid._&var._nomiss ; %end ; %* end j do loop; %* Apply fully populated programming parameters to create and run SAS program; %if &varct. > 0 %then %do; %global &tabid._nobs &stmt_global; data _null_; file "&msoc/gen_code_&tabid..sas" ; put "data &stmt_dsout ;" /; %if &do_partitions and not %eval(&tabid in &tabid_exc) %then %do ; put "set qadata.&&&tabid.table: end=eof nobs=t_rowcount INDSNAME=dsname ;" / " length pnum $ &pnum_length t_lag_dsname $41 ;" / ' retain pnum "0" t_lag_dsname "" ;' / " if t_lag_dsname ne dsname then do;" / " pnum=scan(trim(dsname),-1,,'kd') ;" / " t_lag_dsname=dsname ; " / " end;" ; %end; %else %do; put "set qadata.&&&tabid.table end=eof nobs=t_rowcount ;" ; %end ; put "retain var req_length;" ; put "length var $ 32 ;" // ; put "&stmt_main " ; put ";;" // ; put "if eof then do ;" ; put "call symputx('&tabid._nobs', trim(put(_n_, 15.-l)) ) ;" ; put "&stmt_eof ;" ; put "end;" ; put "run;" ; run; %include "&msoc/gen_code_&tabid..sas" ; %end; %* end varct conditional do statement; %mend do_l1_query; *** Flag 111 - variable not populated/all values set to missing ***; %macro l1_flags_111; %let flagid_111 = ; proc sql noprint; select flagid into :flagid_111 trimmed from infolder.lkp_all_flags where lowcase(tableid)=lowcase("&tabid.") and varid = "&varid." and checkid = "111"; quit; %if %length(&flagid_111.) > 0 and &&&tabid._&var._nobs = 0 %then %do; data dplocal.temp_flag_&tabid._111_&varid.; length FlagID Variable $ 21 Value $ 6; format count comma15.; FlagID = "&flagid_111." ; Variable = strip("&var."); Value = '_null_'; Count = 99999; run; %end; %* end do statement to create check 111 flag record; %mend l1_flags_111; *** Flag 120 - any value not populated/some values set to missing ***; %macro l1_flags_120; %let flagid_120 = ; proc sql noprint; select flagid into :flagid_120 trimmed from infolder.lkp_all_flags where lowcase(tableid)=lowcase("&tabid.") and varid = "&varid." and checkid = "120"; quit; %if %length(&flagid_120.) > 0 and &&&tabid._&var._miss. > 0 %then %do; data dplocal.temp_flag_&tabid._120_&varid.; length FlagID Variable $ 21 Value $ 6; format count comma15.; FlagID = "&flagid_120." ; Variable = strip("&var."); Value = '_null_'; Count = &&&tabid._&var._miss.; run; %end; %* end do statement to create check 111 flag record; %mend l1_flags_120; *** Flag 121 - value is not valid non-missing value ***; %macro l1_flags_121; %let flagid_121 = ; proc sql noprint; select flagid into :flagid_121 trimmed from infolder.lkp_all_flags where lowcase(tableid)=lowcase("&tabid.") and varid = "&varid." and checkid = "121"; select flagcondition into :condition from infolder.lkp_all_l1 where lowcase(tabid) = lowcase("&tabid.") and varid="&varid." ; quit; %if %length(&flagid_121.) > 0 %then %do; proc sql noprint; create table dplocal._temp_flag_&tabid._121_&varid. as select "&flagid_121." as FlagID length=21 , strip("&var.") as Variable length=21 , cats(&var.) as Value , count(*) as count from dplocal._&varid._&tabid. where &condition. group by Value; quit; %let recs=&sqlobs.; %* Reduce filesize of output file if threshold met ; %if &recs.>0 %then %do; %if %sysevalf(&recs. gt &maxobs.) %then %do; %let vallength=%eval(%length(&maxobs.)+4); data dplocal.temp_flag_&tabid._121_&varid.; length FlagID Variable $21 Value %str($&vallength.) count 8; FlagID="&flagid_121."; Variable=strip("&var."); Value="NA:>"||strip("&maxobs."); count=&recs.; run; %end; %else %do; proc sql noprint; select max(length(value)) into :maxlength trimmed from dplocal._temp_flag_&tabid._121_&varid. ; create table dplocal.temp_flag_&tabid._121_&varid. as select FlagID length=21 , Variable length=21 , %unquote(_value) as Value length=&maxlength. , count format=comma15. from dplocal._temp_flag_&tabid._121_&varid. (rename = (value = _value)) ; quit; %end; %end; %* end recs > 0 do statement; proc sql noprint; drop table dplocal._temp_flag_&tabid._121_&varid.; quit; %end; %* end flagID do statement; %mend l1_flags_121; *** Flag 122 - value includes leading space ***; %macro l1_flags_122; %let flagid_122 = ; proc sql noprint; select flagid into :flagid_122 trimmed from infolder.lkp_all_flags where lowcase(tableid)=lowcase("&tabid.") and varid = "&varid." and checkid = "122"; quit; %if %length(&flagid_122.) > 0 %then %do; proc sql noprint; create table dplocal._temp_flag_&tabid._122_&varid. as select "&flagid_122." as FlagID length=21 , strip("&var.") as Variable length=21 , &var. as Value , count(*) as count from dplocal._&varid._&tabid. where first(&var.)=' ' group by Value; quit; %let recs=&sqlobs.; %* Reduce filesize of output file if threshold met ; %if &recs.>0 %then %do; %if %sysevalf(&recs. gt &maxobs.) %then %do; %let vallength=%eval(%length(&maxobs.)+4); data dplocal.temp_flag_&tabid._122_&varid.; length FlagID Variable $21 Value %str($&vallength.) count 8; FlagID="&flagid_122."; Variable=strip("&var."); Value="NA:>"||strip("&maxobs."); count=&recs.; run; %end; %else %do; proc sql noprint; select max(length(value)) into :maxlength trimmed from dplocal._temp_flag_&tabid._122_&varid. ; create table dplocal.temp_flag_&tabid._122_&varid. as select FlagID length=21 , Variable length=21 , %unquote(_value) as Value length=&maxlength. , count format=comma15. from dplocal._temp_flag_&tabid._122_&varid. (rename = (value = _value)) ; quit; %end; %end; %* end recs > 0 do statement; proc sql noprint ; drop table dplocal._temp_flag_&tabid._122_&varid.; quit; %end; %* end flagID do statement; %mend l1_flags_122; *** Flag 124 - numeric variable value of 0 ***; %macro l1_flags_124; %let flagid_124 = ; proc sql noprint; select flagid into :flagid_124 trimmed from infolder.lkp_all_flags where lowcase(tableid)=lowcase("&tabid.") and varid = "&varid." and checkid = "124"; quit; %if %length(&flagid_124.) > 0 %then %do; proc sql noprint; create table dplocal.temp_flag_&tabid._124_&varid. as select "&flagid_124." as FlagID length=21 , strip("&var.") as Variable length=21 , "0" as Value length = 1 , count(*) as count format=comma15. from dplocal._&varid._&tabid. where &var.=0; quit; %end; %* end flagID do statement; %mend l1_flags_124; /* ---------------------- Macro: level_1 --------------------------------------------------------- */ /* Logic to conditionally execute all level 1 module checks */ /* ----------------------------------------------------------------------------------------------- */ %macro level_1; %let abort_qa=0; %local a b c; %local tabct varct; %local varid_list var_list; %local var varid ; %local retain_ds; %* evaluate variable-level checks for tables that exist; %* create nobs datasets; %let &tabid._memname = ; %* query table to get table and variable meta attributes, create 11x flags dataset; %l1_variable; proc sql noprint; select lowcase(PRXCHANGE ('s/\d+$//', 1, trim(upcase(memname)) )) as prefix , memtype into :&tabid._memname trimmed, :&tabid._memtype trimmed from dictionary.tables where libname = 'QADATA' and calculated prefix = "%lowcase(&&&tabid.table)"; quit; %if %length(&&&tabid._memname) = 0 %then %do; %put ==> The &&&tabid.table table does not exist. Aborting.; %abort; %end; %else %do; %if &&&tabid._nobs = 0 %then %do; %put ==> The &&&tabid.table table does not have any observations. Aborting.; %abort; %end; %end; data dplocal.nobs_&tabid.; TabID=upcase("&tabid."); MemType="&&&tabid._memtype"; Count_Obs=&&&tabid._nobs; format count_obs comma18.; run; %* create list of valid variables (variable name and varid) to further process in l1 checks; proc sql noprint; select varid , var into :varid_list separated by " " , :var_list separated by " " from dplocal.l1_scdm_comp_&tabid. where upcase(ms_var)="Y" and upcase(dp_var) = "Y" and upcase(ms_type) = upcase(dp_type) and ( (ms_length ne 0 and ms_length = dp_length) or (ms_length = 0 and ( ms_length <= req_length or missing(req_length) ) )); quit; %* evaluate variable value compliance; %do c=1 %to %sysfunc(countw(&varid_list.)); %let varid = %scan(&varid_list., &c.) ; %let var = %scan(&var_list., &c.) ; %* Update observation dataset with parameter values ; proc sql noprint; create table dplocal.temp_l1_recct_&varid. as select upcase("&tabid.") as TabID length=3 , "&varid" as VarID length=2 , "&var." as Variable length=21 , count_obs label= "Count of Table Records" format=comma18. , &&&tabid._&var._nomiss. as count_nomiss label="Non-Missing Value Count" format=comma18. , &&&tabid._&var._spmiss. as count_spmiss label="Special Missing Value Count" format=comma18. , &&&tabid._&var._miss. as count_null label="Null Value Count" format=comma18. from dplocal.nobs_&tabid. where lowcase(tabid)="&tabid."; quit; %l1_flags_111; %l1_flags_120; %if %sysfunc(exist(dplocal.temp_flag_&tabid._111_&varid.)) = 0 and %sysfunc(exist(dplocal.temp_flag_&tabid._120_&varid.)) = 0 %then %do; %l1_flags_121; %l1_flags_122; %l1_flags_124; %end; %* end do statement for executing checks 121, 122, 124; /** Check if current variable is included in the list of variables to retain */ %if not(&varid.=01 OR %sysfunc(indexw(&cross_varID., %lowcase(&var.))) > 0) %then %do; proc datasets lib=dplocal nolist nowarn nodetails; delete _&varid._&tabid.; quit; %end; %else %do; proc sort data=dplocal._&varid._&tabid. nodupkey ; by _all_ ; ;quit; %end; %end; %* end of loop c - by variable ; %if %lowcase(&tabid) eq dem %then %do ; data dplocal.patid2bdate ; set qadata.&&&tabid.table:(keep=patid birth_date) ; by patid ; ;run; %end; %* Combine Level 1 temporary datasets into one dataset for each table; %set_ds(libin=dplocal, dsin_prefix=temp_l1_recct_, libout=dplocal, dsout=l1_record_count_&tabid.); %set_ds_varlength (dsin_prefix=temp_flag_&tabid._, dsout=l1_tmp_flags_&tabid.); %* Consolidate like-named datasets to single dataset ; %set_ds (libin=dplocal, dsin_prefix=nobs_dup_, libout=&dplocalo, dsout=all_l2_nobs_dup_&tabid.); %set_ds (libin=dplocal, dsin_prefix=nobs_, libout=&dplocalo, dsout=all_l1_nobs_&tabid.); %set_ds (libin=dplocal, dsin_prefix=l1_record_count_, libout=&dplocalo, dsout=all_l1_record_count_&tabid.); %set_ds (libin=dplocal, dsin_prefix=l1_cont_, libout=&dplocalo, dsout=all_l1_cont_&tabid.); %set_ds (libin=dplocal, dsin_prefix=l1_scdm_comp_, libout=&dplocalo, dsout=all_l1_scdm_comp_&tabid.); %set_ds_varlength (dsin_prefix=l1_tmp_flags_, dsout=temp_flags); proc contents data=dplocal.temp_flags noprint out=proctemp (keep=nobs); run; %let temp_nobs=0; proc sql noprint; select distinct nobs into :temp_nobs trimmed from proctemp; quit; %* if flags defined, output to dataset; %if %eval(&temp_nobs. gt 0) %then %do; proc sql noprint; create table dplocalo.all_l1_flags_&tabid. as select b.flagid , b.flag_descr , b.flagtype , b.abortYN , b.variable1 , a.value , case when a.count=99999 then a.count else sum(a.count) end as count format=comma18. from dplocal.temp_flags (where=(count>0)) as a left join infolder.lkp_all_flags (where=(level='1' and lowcase(flagYN)='y')) as b on lowcase(a.flagid)=lowcase(b.flagid) group by b.flagid, b.flag_descr, b.flagtype, b.abortYN, b.variable1, a.value order by 3,4 desc,1; drop table dplocal.temp_flags; quit; proc sort data = dplocalo.all_l1_flags_&tabid nodupkey; by _all_; run; proc sql noprint; select count(*) into :abort_qa from dplocalo.all_l1_flags_&tabid (where=(lowcase(abortYN)='y')); quit; %end; %* end temp_obs do statement; proc datasets kill memtype=data lib=work nolist nowarn nodetails; quit; %* Evaluate flags dataset to determine if qa package should end due to L1 failure; %put ==> Abort_qa: &abort_qa.; %if &abort_qa. ne 0 %then %do; %let end_qa=1; proc datasets lib=dplocal nolist nowarn nodetails; delete _:; quit; data _null_; putlog 70*'!'; putlog 'ERR'"OR: The &module. module detected fatal L1 data flags"; putlog " that require the QA package to abort"; putlog 70*'!'; run; %end; %mend level_1; %level_1; *-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-; * END scdm-data-qa-review-level1.sas ; *-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-;