Changeset 26944 in main


Ignore:
Timestamp:
03/09/23 13:54:10 (11 days ago)
Author:
Maria Baron
Message:

birth count and rates modules

Location:
adopters/nj/trunk/src/main/ibisq/qModules3/birth
Files:
1 deleted
3 edited

Legend:

Unmodified
Added
Removed
  • adopters/nj/trunk/src/main/ibisq/qModules3/birth/Birth.cfg

    r26754 r26944  
    3333r sas 0
    3434r test 0
    35 r small_num 0
    36 r small_pop 20
     35#r small_num 0
     36#r small_pop 20
    3737#############################################################################
    3838#value name_sas name_html name_pop prompt type1 type2 length   
     
    7070## YEAR VARS       
    717121 bbthyear Year year Year num 0 4
     7221 bbthyear Year2020 year Year num 0 4
     7321 bbthyear YearBR year Year num 0 4
    727421 bbthyear YearGrp3 year Year num 3 4
     7521 bbthyear YearGrp3BR year Year num 3 4
    737621 bbthyear YearGrp5 year Year num 3 4
     7721 bbthyear YearGrp5BR year Year num 3 4
    7478
    7579## MOTHER CHARACTERISTICS ########################
  • adopters/nj/trunk/src/main/ibisq/qModules3/birth/BirthRate.def

    r26754 r26944  
    1 f label Birth&Rate
    2 f type rate
    3 f data_where dnjcnty=1
     1f label Birth&Fert&Rates
     2f type special
     3#f data_where dnjcnty=1
     4#f xml_out_map_file XMLRateBirth1K.map
     5#f out_detail lbl_not_used__see_xml_out_map_file
     6#f multiple 1000
     7#f pop_count pop
     8
     9--------BoNdArY--------
     101 script
     11OPTIONS MPRINT MLOGIC SYMBOLGEN NONUMBER NODATE PAGESIZE=4000;
     12OPTION SPOOL;
     13/*
     14        *this is to get the value of the last year for the YearGrp3Yrs dimension value.;
     15        proc freq data=tmp noprint; tables year / list out=years; run;
     16        proc print data=years; run;
     17        data lastyear; set years; by year; if first.year then YearGrp3Yrs=year; keep YearGrp3Yrs; run;
     18        proc print data=lastyear; run;
     19*/
     20 ************************** 1. TMP ******************************;
     21 * The dataset 'tmp' is the numerator dataset that has been read ;
     22 * in already by ibis-q. Any filters have already been applied.  ;
     23 * The proc summary counts deaths by cross1 and cross2.          ;
     24 * The variable "x" must be in the dataset, it is set equal to 1.;
     25 ****************************************************************;
     26        proc summary data=tmp;
     27                var x;
     28                class %cross1%
     29                ?cross2? %cross2%
     30                ;
     31                output out=tmp (drop=_TYPE_ _FREQ_) sum=count;
     32        proc sort data=tmp out=sorted; by %cross1%
     33                ?cross2? %cross2%
     34                ; run;
     35        proc print data=sorted noobs;
     36                title1 '---------------------------------';
     37                title2 '1. TMP - numerator dataset';
     38                run;
     39 
     40 *********************** 2. data_frame **************************;
     41 * df_%cross1%%cross2% is a dataset created by IBIS-Q.   ;
     42 * It consists of %cross1% and %cross2% (if the user specified   ;
     43 * %cross2%) and a variable named "count" that is set to "0".    ;
     44 * The results of the proc summary must be merged with the       ;
     45 * df_%cross1%%cross2% dataset.                          ;
     46 ****************************************************************;
     47        data frame;
     48                set df_%cross1%%cross2%;
     49                run;
     50        proc sort data=frame; by %cross1%
     51                ?cross2? %cross2%
     52                ; run;
     53        proc print data=frame noobs;
     54                title2 '2. Data Frame';
     55                run;
     56
     57        *set length so that values don't get truncated;
     58        *listing frame dataset first will retain all records in frame;
     59        data tmp;
     60                length count 8;
     61                merge frame sorted;
     62                by %cross1%
     63                   ?cross2? %cross2%
     64                ;
     65                run;
     66        proc print data=tmp noobs;
     67                title2 '2. tmp, after merged with frame';
     68                run;
     69
     70 *************** 3. Flag variable and popcross macro *************;
     71 * The flag variable checks the cross variables for presence of   ;
     72 * variables that are found in the population dataset. IBIS-q     ;
     73 * created popcross vars based on info from the .CFG file.        ;
     74 * The popcross macro will merge the numerator and denominator    ;
     75 * data, matching up the appropriate values of the cross vars.    ;
     76 *****************************************************************;
     77 * The Count measure does not need the population dataset. The    ;
     78 * following code, through the end of the macro, is used to       ;
     79 * compute the RSE for the data stability indicator and to check  ;
     80 * the numerator and denominator  counts for the cell suppression.;
     81 *****************************************************************;
     82        %let flag=0;
     83        ?popcross1? %let flag=1;
     84        ?popcross2? %let flag=1;
     85        ?popcross1? ?popcross2? %let flag=2;
     86
     87        %macro popcross;
     88
     89        %if &flag=0 %then %do;
     90                proc summary data=poptmp;
     91                        var pop;
     92                        output out=pop (drop=_TYPE_ _FREQ_) sum=pop;
     93                run;
     94                proc sql;
     95                        create table numbers as
     96                        select tmp.*, pop.*
     97                        from tmp, pop
     98                quit;
     99        %end;
     100
     101        %if &flag=1 %then %do;
     102                proc summary data=poptmp;
     103                        var pop;
     104                        class %popcross1% %popcross2%;
     105                        output out=pop (drop=_TYPE_ _FREQ_) sum=pop;
     106                run;
     107                proc sql;
     108                        create table numbers as
     109                        select tmp.*, pop.*
     110                        from tmp left join pop
     111                        on
     112                        ?popcross1? tmp.%cross1%=pop.%popcross1%;
     113                        ?popcross2? tmp.%cross2%=pop.%popcross2%; 
     114                quit;
     115        %end;
     116
     117        %if &flag=2 %then %do;
     118                proc summary data=poptmp;
     119                        var pop;
     120                        class %popcross1% %popcross2%  ;
     121                        output out=pop (drop=_TYPE_ _FREQ_) sum=pop;
     122                run;
     123                proc sql;
     124                        create table numbers as
     125                        select tmp.*, pop.*
     126                        from tmp left join pop
     127                        on
     128                        tmp.%cross1%=pop.%popcross1% and
     129                        tmp.%cross2%=pop.%popcross2%;
     130                quit;
     131        %end;
     132        %mend;
     133        %popcross;
     134        proc print data=numbers noobs;
     135        title2 '6. NUMBERS - tmp merged with pop dataset';
     136        run;
     137 ********************** 4. tmp, again ****************************;
     138 * Create the output variables for the IBIS xml/map file.         ;
     139 *****************************************************************;
     140        data rate;
     141                set numbers;
     142                        if count>0 then do;
     143                                rate=count/pop;
     144                                rateper=(rate*1000);
     145                        end;
     146                        if count<=0 then do;
     147                                rate=3/pop;
     148                                rateper=0;
     149                        end;
     150                stderr=sqrt(rate*(1-rate)/pop)*1000;
     151                t1=(rateper-(1.96*stderr));
     152                if (t1<0) then t1=0;
     153                LL=put(t1, 8.2);
     154                UL=put((rateper+(1.96*stderr)), 8.2);
     155                LL=compress(LL);
     156                UL=compress(UL);
     157                n=count;        *ibis-q needs a count variable named 'n';
     158
     159 *********************** 5. Red Flag *****************************;
     160 * redflag is the statistical stability indicator based on the    ;
     161 * relative standard error (RSE, or coefficient of variation).    ;
     162 * Redflag values created here are converted to images or special ;
     163 * characters in IBIS-View application XSLTfiles, for instance:   ;
     164 * (xslt\html\query\module\result\ResultPage.xslt, ...Values.xslt ;
     165 *****************************************************************;
     166/*              if count>0 then do;
     167                        rse=(stderr/rateper);
     168                        redflag=put('', $12.);
     169                        if rse>.3 then redflag=put('Unstable', $12.);
     170                        if rse>.5 then redflag=put('VeryUnstable', $12.);
     171                        if stderr=. then redflag=put('Unstable', $12.);
     172                end;
     173                *no variance, n=0, rse=div by zero;
     174                if count<=0 then redflag=put('Unstable', $12.);
     175        run;
     176*/
     177 ************* 6. New Mexico Small Numbers Rule ********************;
     178 * Suppress cells if the numerator in (1 2 3) AND the denominator   ;
     179 * is less than 20. For Counts, must run the crude rate code to     ;
     180 * capture the denominator, but only output the N. ZW’s program     ;
     181 * uses ".A" to identify cells for suppression. I have co-opted     ;
     182 * his method so I can use the NM logic for cell suppression instead;
     183 * of the standard IBIS logic. And I need to use ZW's program       ;
     184 * because it will suppress the table marginals that can be used to ;
     185 * calculate the suppressed cells. If this code is used, the .def   ;
     186 * file should have the "NM_" prefix. Needs suppressed_variabes     ;
     187 * code at the end of this file to work.                            ;
     188 *******************************************************************;
     189        data tmp;
     190                set rate;
     191                if  pop ne . and 0<=n<20 then do;
     192                        rateper = .A;
     193                        *n = .A;
     194                        *pop = .A;
     195                        *LL = .A;
     196                        *UL = .A;
     197                        LL = put('**', 8.0);
     198                        UL = put('**', 8.0);
     199                        redflag = put('Suppressed', $12.);
     200                                *Only one value attribute is allowed - so if suppressed, overwrite unstable;
     201                                *This also puts ** in record code column for suppressed rows, and adds footnote;
     202                end;
     203               
     204                *if pop=. then redflag=put('', $12.); *no value attribute for missing crossby values;
     205
     206                if pop eq . and n eq 0 then delete;  *deletes zero rows with no corresponding pop estimate, e.g. residence unknown;
     207               
     208                if pop eq . and n ne 0 then do; *no matching denominator value, e.g., Other Race;
     209                        rateper = put('.', 8.0);
     210                        LL = put('.', 8.0);
     211                        UL = put('.', 8.0);
     212                        redflag= put('NoPop', $12.);
     213                end;
     214
     215        proc print data=tmp noobs;  title2 '6. TMP - final dataset to pass to IBIS View app';
     216        run;
     217
     218--------BoNdArY--------
     219# definition for output file
     220f out_variable rateper
    4221f xml_out_map_file XMLRateBirth1K.map
    5 f out_detail lbl_not_used__see_xml_out_map_file
    6 f multiple 1000
    7 f pop_count pop
     222--------BoNdArY--------
     223f out_detail lbl_not_used__see_xml_out_map_file
     224  rateper 15.1
     225  LL 15.3
     226  UL 15.3
     227  n 15.0
     228  pop 15.0
     229  redflag 12.0
     230--------BoNdArY--------
     231#**************** 7. suppressed variables **************************;
     232# ZW’s CGI program must be told how many variables it will need to  ;
     233# suppress and which ones they are. NOTE: If the SAS code, above, is;
     234# commented out, these lines can be left in the .def file without   ;
     235# causing any problems. They will only be used if the SAS code,     ;
     236# above is active, OR if the small_num and small_pop parameters     ;
     237# are active in the .CFG file, and with non-zero values.            ;
     238#                                                                                                                                       ;
     239# MLB 3/8/23 NOTE: If I list all 5 below, UL and LL show as A           ;
     240# instead of **.  Only rateper gets converted to ** below.              ;
     241# LL and UL are assigned ** as needed above.                                            ;
     242#*******************************************************************;
     243--------BoNdArY--------
     2441 suppressed_variables 1
     245  rateper
     246--------BoNdArY--------
  • adopters/nj/trunk/src/main/ibisq/qModules3/birth/TotalFertRate.def

    r26754 r26944  
    11f label Total&Fertility&Rate
    22f type special
    3 f data_where dnjcnty=1
    4 #f data_where 15<=mage<=44
    5 f pop_where sex=2
    6 #&and&15<=age<=44
    7 #########################################
     3#############################################
     4# Since there's no data frame, zero and         #
     5# unknown rows don't show in the output.        #
     6#############################################
    87--------BoNdArY--------
    981 script
    10  data tmp;
    11         set tmp;
    12         if magegrp in (2 3) then agegrp_f=0;
    13         else if magegrp=4 then agegrp_f=1;
    14         else if magegrp=5 then agegrp_f=2;
    15         else if magegrp=6 then agegrp_f=3;
    16         else if magegrp=7 then agegrp_f=4;
    17         else if magegrp=8 then agegrp_f=5;
    18  run;
     9OPTIONS MPRINT MLOGIC MLOGICNEST SYMBOLGEN NONUMBER NODATE PAGESIZE=4000;
    1910
    20  data poptmp;
    21         set poptmp;
    22         if magegrp in (2 3) then agegrp_f=0;
    23         else if magegrp=4 then agegrp_f=1;
    24         else if magegrp=5 then agegrp_f=2;
    25         else if magegrp=6 then agegrp_f=3;
    26         else if magegrp=7 then agegrp_f=4;
    27         else if magegrp=8 then agegrp_f=5;
    28  run;
     11        data tmp;
     12                set tmp;
     13                mage=bmomage;
     14                if mage<10 then mage=10;
     15                if mage>44 then mage=45;
     16                agegrp_f=int((mage-10)/5);
     17        run;
     18        proc freq data=tmp; tables agegrp_f; title 'step 1'; run;
    2919
    30  proc summary data=tmp;
    31  var x;
    32  class agegrp_f %cross1% %cross2%;
    33  output out=tmp n=number;
    34  run;
    35  proc summary data=poptmp;
    36  var pop;
    37  class agegrp_f %popcross1% %popcross2%;
    38  output out=pop sum=popnum;
    39  run;
    40  proc sql;
    41  create table rate as
    42  select tmp.*, pop.*
    43  from tmp, pop
    44  where tmp.agegrp_f=pop.agegrp_f and tmp.agegrp_f^=.
    45 ?popcross1?     and tmp.%cross1%=pop.%popcross1%
    46 ?cross2? ?popcross2?    and tmp.%cross2%=pop.%popcross2%
    47         ;
    48  quit;
     20        data poptmp;
     21                set poptmp;
     22                if magegrp=1 then agegrp_f=0;                     *age <15;
     23                else if 2<=magegrp<=3 then agegrp_f=1;    *age 15-19;
     24                else if magegrp=4 then agegrp_f=2;                *age 20-24;
     25                else if magegrp=5 then agegrp_f=3;        *age 25-29;
     26                else if magegrp=6 then agegrp_f=4;        *age 30-34;
     27                else if magegrp=7 then agegrp_f=5;        *age 35-39;
     28                else if magegrp=8 then agegrp_f=6;        *age 40-44;
     29                else if 9<=magegrp<=10 then agegrp_f=7;   *age 45+;
     30        run;
     31        proc freq data=poptmp; tables agegrp_f; title 'step 2'; run;
    4932
    50  data tmp;
    51  set rate;
    52  rate=number/popnum;
    53  ?cross1? if (%cross1%=.) then %cross1%=-99;
    54  ?cross2? if (%cross2%=.) then %cross2%=-99;
    55  keep agegrp_f rate number popnum %cross1% %cross2%;
    56 run;
     33        proc summary data=tmp;
     34                var x;
     35                class agegrp_f %cross1% %cross2%;
     36                output out=tmp (drop=_TYPE_ _FREQ_) n=number;
     37        run;
     38        proc freq data=tmp; tables agegrp_f; title 'step 3'; run;
    5739
    58  proc summary data=tmp;
    59  var rate number popnum;
    60  class %cross1% %cross2%;
    61  output out=tmp sum(rate number popnum)=;
    62  run;
    63  
    64 data tmp;
    65  set tmp;
    66  ?cross1? if (%cross1%^=.);
    67  ?cross2? if (%cross2%^=.);
    68  ?cross1? if (%cross1%=-99) then %cross1%=.;
    69  ?cross2? if (%cross2%=-99) then %cross2%=.;
    70 proc print data=tmp;
    71 title 'before final';
    72 run;
     40        proc summary data=poptmp;
     41                var pop;
     42                class agegrp_f %popcross1% %popcross2%;
     43                output out=pop sum=popnum;
     44        run;
     45        proc freq data=pop; tables agegrp_f; title 'step 4'; run;
    7346
    74 data tmp;
    75   set tmp;
    76 stdev=1.96*sqrt(rate*(1-rate)/popnum);
    77  t1=(rate-stdev)*1000;
    78  if (t1<0) then t1=0;
    79  r1=put(t1, 8.2);
    80  r2=put((rate+stdev)*1000, 8.2);
    81  rate=rate*1000;
    82  r1=compress(r1);
    83  r2=compress(r2);
    84  ci=r1 || ' - ' || r2;
    85  rate=rate*5;
    86  r1=r1*5;
    87  r2=r2*5;
    88 n=number;
    89 proc print;
    90 title 'final';
    91 run;
     47        proc sql;
     48                create table rate as
     49                select tmp.*, pop.*
     50                from tmp, pop
     51                where tmp.agegrp_f=pop.agegrp_f and tmp.agegrp_f^=.
     52                ?popcross1?     and tmp.%cross1%=pop.%popcross1%
     53                ?cross2? ?popcross2?    and tmp.%cross2%=pop.%popcross2%
     54                ;
     55        quit;
     56        proc print data=rate; title 'step 5 - rate'; run;
     57
     58        data tmp;
     59                set rate;
     60                rate=(number/popnum);
     61                ?cross1? if (%cross1%=.) then %cross1%=-99;
     62                ?cross2? if (%cross2%=.) then %cross2%=-99;
     63                keep agegrp_f rate number popnum %cross1% %cross2%;
     64        run;
     65        proc print data=tmp; title 'step 6'; run;
     66
     67        proc summary data=tmp;
     68                var rate number popnum;
     69                class %cross1% %cross2%;
     70                output out=tmp sum(rate number popnum)=;
     71        run;
     72        proc print data=tmp; title 'step 7'; run;
     73         
     74        data tmp;
     75                set tmp;
     76                ?cross1? if (%cross1%^=.);
     77                ?cross2? if (%cross2%^=.);
     78                ?cross1? if (%cross1%=-99) then %cross1%=.;
     79                ?cross2? if (%cross2%=-99) then %cross2%=.;
     80        proc print data=tmp noobs; title 'step 8 - before final'; run;
     81
     82        data tmp;
     83                set tmp;
     84                stderr=sqrt(rate*(1-rate)/popnum)*1000;
     85                rateper=rate*1000;
     86                t1=(rateper-(1.96*stderr));
     87                if (t1<0) then t1=0;
     88                LL=put(t1, 8.2);
     89                UL=put((rateper+(1.96*stderr)), 8.2);
     90                LL=compress(LL);
     91                UL=compress(UL);
     92                n=number;
     93        proc print data=tmp noobs; title 'step 9'; run;
     94
     95 *********************** 5. Red Flag *****************************;
     96 * redflag is the statistical stability indicator based on the    ;
     97 * relative standard error (RSE, or coefficient of variation).    ;
     98 * Redflag values created here are converted to images or special ;
     99 * characters in IBIS-View application XSLTfiles, for instance:   ;
     100 * (xslt\html\query\module\result\ResultPage.xslt, ...Values.xslt ;
     101 *****************************************************************;
     102
     103/*              if count>0 then do;
     104                        rse=(stderr/rateper);
     105                        redflag=put('', $12.);
     106                        if rse>.3 then redflag=put('Unstable', $12.);
     107                        if rse>.5 then redflag=put('VeryUnstable', $12.);
     108                        if stderr=. then redflag=put('Unstable', $12.);
     109                end;
     110                *no variance, n=0, rse=div by zero;
     111                if count<=0 then redflag=put('Unstable', $12.);
     112                if popcount=. then redflag=put('', $12.); *no value attribute for missing crossby values;
     113*/
     114        data tmp;
     115                set tmp;
     116                rateper=rateper*5;
     117                LL=LL*5;
     118                UL=UL*5;
     119
     120                proc print data=tmp noobs; title 'step 10 - almost final';
     121                run;
     122
     123 ************* 6. New Mexico Small Numbers Rule *********************;
     124 * Suppress cells if the numerator in (1 2 3) AND the denominator    ;
     125 * is less than 20. For Counts, must run the crude rate code to      ;
     126 * capture the denominator, but only output the N. ZW’s program      ;
     127 * uses ".A" to identify cells for suppression. I have co-opted      ;
     128 * his method so I can use the NM logic for cell suppression instead ;
     129 * of the standard IBIS logic. And I need to use ZW's program        ;
     130 * because it will suppress the table marginals that can be used to  ;
     131 * calculate the suppressed cells. If this code is used, the .def    ;
     132 * file should have the "NM_" prefix. Needs suppressed_variabes      ;
     133 * code at the end of this file to work.                             ;
     134 ********************************************************************;
     135
     136        data tmp;
     137                set tmp;
     138                if  popnum ne . and 0<=n<20 then do;
     139                        rateper = .A;
     140                        *n = .A;
     141                        *pop = .A;
     142                        *LL = .A;
     143                        *UL = .A;
     144                        LL = put('**', 8.0);
     145                        UL = put('**', 8.0);
     146                        redflag = put('Suppressed', $12.);
     147                                *Only one value attribute is allowed - so if suppressed, overwrite unstable;
     148                                *This also puts ** in record code column for suppressed rows, and adds footnote;
     149                end;
     150               
     151                *if popnum=. then redflag=put('', $12.); *no value attribute for missing crossby values;
     152
     153                if popnum eq . and n eq 0 then delete;  *deletes zero rows with no corresponding pop estimate, e.g. residence unknown;
     154               
     155                if popnum eq . and n ne 0 then do;      *no matching denominator value, e.g., Other Race;
     156                        rateper = put('.', 8.0);
     157                        LL = put('.', 8.0);
     158                        UL = put('.', 8.0);
     159                        redflag= put('NoPop', $12.);
     160                end;
     161
     162        proc print data=tmp noobs;  title2 '6. TMP - final dataset to pass to IBIS View app';
     163        run;
    92164
    93165--------BoNdArY--------
     
    98170--------BoNdArY--------
    99171f out_detail lbl_not_used__see_xml_out_map_file
    100 rate 15.4
    101 r1 15.4
    102 r2 15.4
    103 n 15.0
    104 popnum 15.0
     172  rateper 15.1
     173  LL 15.3
     174  UL 15.3
     175  n 15.0
     176  popnum 15.0
     177  redflag 12.0
     178--------BoNdArY--------
     179--------BoNdArY--------
     1801 suppressed_variables 1
     181rateper
    105182--------BoNdArY--------
    106183
    107184
     185
Note: See TracChangeset for help on using the changeset viewer.