BookmarkSubscribeRSS Feed

A better way to FLIP (i.e, transpose/make wide) a dataset

Started ‎09-18-2020 by
Modified ‎03-23-2018 by
Views 10,503

This article is a little late as it re-presents a paper that was published, in 2013, by @Ksharp@Astounding, Joe Whitehurst and me. However, the macro presented was just updated yesterday, and the code can no longer be updated on sasCommunity.org.

 

The macro was designed to accomplish one task: to make a dataset (that might be either long or wide) wider and do so (1) faster than any other available methods, (2) require the least amount of user supplied code, (3) be easy to use for anyone who has used PROC TRANSPOSE, and (4) provide a resulting wide dataset that is most likely to meet a user's needs.

 

The macro runs up to 50 or more times faster than PROC TRANSPOSE and takes much less time and effort to prepare the code used to call the macro.

 

The only method that performs as fast is the one originally proposed (I think) by @data_null__, that uses PROC SUMMARY to transpose a dataset. However, that method doesn't provide the same variable naming capabilities as PROC TRANSPOSE, doesn't use ID values in variable names, and won't work if any by variable contains more than 100 values.

 

The code has been revised a number of times since its original publication as we test it with all examples that we see in posts on the forum and SAS-L and, as a result, include missing capabilities if we think they will add to the macros utility.

 

Here is the link to download the original paper and Powerpoint.

 

The most recent version of the macro is provided in the text box  below.

 

Art, CEO, AnalystFinder.com

 

/** The %transpose macro
  *
  * This program performs transpositions of SAS datasets very similar to those that
  * can be achieved with PROC TRANSPOSE, but in such a manner that is easier to use
  * when performing complex transpositions and runs significantly faster
  *
  * AUTHORS: Arthur Tabachneck, Xia Ke Shan, Robert Virgile and Joe Whitehurst
  * CREATED: January 20, 2013
  * MODIFIED: September 4, 2014
  * MODIFIED: September 15, 2017
  * MODIFIED: January 16, 2018
  * MODIFIED: February 1, 2018

  Parameter Descriptions:

  *libname_in* the parameter to which you can assign the name of the SAS library that
  contains the dataset you want to transpose. If left null, and the data parameter is
  only assigned a one-level filename, the macro will set this parameter to equal WORK

  *libname_out* the parameter to which you can assign the name of the SAS library
  where you want the transposed file written. If left null, and the out parameter only
  has a one-level filename assigned, the macro will set this parameter to equal WORK

  *data* the parameter to which you would assign the name of the file that you want
  to transpose.  Like with PROC TRANSPOSE, you can use either a one or two-level
  filename.  If you assign a two-level file name, the first level will take precedence
  over the value set in the libname_in parameter.  If you assign a one-level
  filename, the libname in the libname_in parameter will be used. Additionally, as
  with PROC TRANSPOSE, the data parameter will also accept data step options. Thus,
  for example, if you had a dataset called 'have' and want to limit the transposition
  to just the first 10 records, you could specify it as: data=have (obs=10). Any
  data step options accepted by a SAS data step can be included

  *out* the parameter to which you would assign the name of the transposed file that
  you want the macro to create.  Like with PROC TRANSPOSE, you can use either a one
  or two-level filename.  If you use assign a two-level file name, the first level
  will take precedence over the value set in the libname_out parameter.  If you use a
  one-level filename, the libname in the libname_out parameter will be used

  *by* the parameter to which you would assign the name of the data’s by variable
  or variables.  The by parameter is identical to the by statement used in PROC
  TRANSPOSE, namely the identification of the variable that the macro will use to
  form by groups, however one or more by variables must be specified.  By groups
  define the record level of the resulting transposed file

  *prefix* the parameter to which you would assign a string that you want each
  transposed variable to begin with

  *var* the parameter to which you would assign the name or names of the variables
  that you want the macro to transpose.  You can assign any combination of variable
  names or variable list(s) that you could assign to PROC TRANSPOSE’s var statement.
  If left null, all variables, all numeric variables, or all character variables
  (other than by, id and copy variables) will be assigned, dependent upon the value
  assigned to the autovars parameter

  *autovars* the parameter to which you would assign the types of variables you want
  automatically assigned to the var parameter in the event that the var parameter has
  a null value.  Possible values are: NUM, CHAR or ALL.  If left null, the macro code
  will set this parameter to equal NUM

  *id* the parameter to which you would assign the variable whose values you want
  concatenated with the var variable(s) selected.  Only one variable can be assigned
  
  *descendingid* the parameter that defines whether id values should be output in
  descending order. Possible values are YES or NO. If left null, the macro code will
  set this parameter to equal NO and id values will be output in ascending order

  *var_first* the parameter that defines whether var names should precede id values in
  the concatenated variable names resulting from a transposition. Possible values are
  YES or NO.  Concatenated variables names will be constructed as follows:
  prefix+(var or id)+delimiter+(var or id).  If left null, the macro code will set
  this parameter to equal YES

  *format* the parameter to which you would assign the format you want applied
  to the id variable in the event you don't want the variable’s actual format
  to be applied. If left null, and the variable doesn't have a format assigned,
  the macro code will create a format based on the variable's type and length

  *delimiter* the parameter to which you would assign the string you want
  assigned between the id values and var variable names in the variable name
  that will be assigned to the transposed variables the macro will create

  *copy* the parameter to which you would assign the name or names of any
  variables that you want the macro to copy rather than transpose
  
  *drop* the parameter to which you would assign the name(s)  of any variables
  you want dropped from the output.  Since only &by, &copy and transposed variables
  are kept, this parameter would only be used if you want to drop one or more of the
  &by variables

  *sort* the parameter to which you would indicate whether the input dataset
  must first be sorted before the data is transposed.  Possible values are:
  YES or NO. If left null, the macro code will set this parameter to equal NO
  and all datasteps that use a by statement will include the NOTSORTED option

  *sort_options* while the noequals option will be used for all sorts, you would use
  this parameter to specify any additional options you want used (e.g., presorted,
  force and/or tagsort

  *use_varname* the parameter you would use if you don't want the var names
  to be included in the transposed variable names.  Possible values are: YES or NO.
  If left null, the macro code will set this parameter to equal YES
  
  *suffix* the parameter to which you would assign the string you want
  assigned to the end of the transposed variables the macro will create
  

  *preloadfmt* If you want to predefine all possible id variable values, and the
  order in which those values will be assigned to the transposed variables, you can
  use this parameter to assign a one or two-level filename for a file you want the
  macro to use.  The file must contain a variable that has the same name as the data
  file's id variable, and a 2nd variable called 'order' that will reflect the desired
  order. The file must have one record for every id value the macro will find in the
  data, although it can also contain id values that aren't present in the data.
  Regarding the order variable, the value 1 must be assigned to the value you want
  furthest left, increasing by 1 for each remaining value, and the furthest right
  variable must be equal to the total number of id levels. If a two-level file name
  is specified, the first level will take precedence over the value set in the
  libname_in parameter. If a one-level filename is assigned, the libname in the
  libname_in parameter will be used (or 'work' if the libname_in parameter is null)

  Example:
  data order;
    input date date9. order;
    cards;
  31mar2013 1
  30jun2013 2
  30sep2013 3
  31dec2013 4
  ;

  *guessingrows* the parameter you would use to specify the maximum number of rows
  that will be read to determine the output ordering of the id variable’s values.
  If left null, the macro will set this parameter high enough to read all records

  *newid* the parameter you would use to specify the name you want to assign a
  new variable that will be created in the event that you don't specify an id
  variable.  If not declared, this parameter will be set to equal '_row'

  *convertid* is the parameter you would use to indicate that your ID variable
  contains any characters that aren't either alphanumeric or '_'.
  If not declared, this parameter will be set to equal 'NO'

*/

%macro transpose(libname_in=,
                 libname_out=,
                 data=,
                 out=,
                 by=,
                 prefix=,
                 var=,
                 autovars=,
                 id=,
                 descendingid=,
                 var_first=YES,
                 format=,
                 delimiter=,
                 copy=,
                 drop=,
                 sort=,
                 sort_options=,
                 use_varname=YES,
                 suffix=,
                 preloadfmt=,
                 guessingrows=,
                 newid=,
                 convertid=NO);

/*Check whether the data and out parameters contain one or two-level filenames*/
/*and, if needed, separate libname and data from data set options */
  %let lp=%sysfunc(findc(%superq(data),%str(%()));
  %if &lp. %then %do;
   %let rp=%sysfunc(findc(%superq(data),%str(%)),b));
/*for SAS*/
   %let dsoptions=%qsysfunc(substrn(%nrstr(%superq(data)),&lp+1,&rp-&lp-1));
   %let data=%sysfunc(substrn(%nrstr(%superq(data)),1,%eval(&lp-1)));
/*for WPS*/
/*     %let dsoptions=%qsysfunc(substrn(%nrquote(%superq(data)),&lp+1,&rp-&lp-1)); */
/*     %let data=%sysfunc(substrn(%nrquote(%superq(data)),1,%eval(&lp-1))); */
  %end;
  %else %let dsoptions=;

  %let lp=%sysfunc(findc(%superq(out),%str(%()));
  %if &lp. %then %do;
   %let rp=%sysfunc(findc(%superq(out),%str(%)),b));
/*for SAS*/
   %let odsoptions=%qsysfunc(substrn(%nrstr(%superq(out)),&lp+1,&rp-&lp-1));
   %let out=%sysfunc(substrn(%nrstr(%superq(out)),1,%eval(&lp-1)));
/*for WPS
   %let odsoptions=%qsysfunc(substrn(%nrquote(%superq(out)),&lp+1,&rp-&lp-1));
   %let out=%sysfunc(substrn(%nrquote(%superq(out)),1,%eval(&lp-1)));
*/
  %end;
  %else %let odsoptions=;

  %if %sysfunc(countw(&data.)) eq 2 %then %do;
    %let libname_in=%scan(&data.,1);
    %let data=%scan(&data.,2);
  %end;
  %else %if %length(&libname_in.) eq 0 %then %do;
    %let libname_in=work;
  %end;

  %if %sysfunc(countw(&out.)) eq 2 %then %do;
    %let libname_out=%scan(&out.,1);
    %let out=%scan(&out.,2);
  %end;
  %else %if %length(&libname_out.) eq 0 %then %do;
    %let libname_out=work;
  %end;

  %if %length(&newid.) eq 0 %then %do;
    %let newid=_row;
  %end;

  /*Create temporary file if there are dataset options*/
  %if %length(%unquote(&dsoptions.)) gt 2 %then %do;
    data _t_e_m_p;
      set &libname_in..&data. (%unquote(&dsoptions.));
    run;
    %let data=_t_e_m_p;
    %let libname_in=work;
  %end;

  /*obtain last by variable*/
  %if %length(&by.) gt 0 %then %do;
    %let lastby=%scan(&by.,-1);
  %end;
  %else %do;
    %let lastby=;
  %end;

/*Create macro variable to contain a list of variables to be copied*/
 %let to_copy=;
  %if %length(&copy.) gt 0 %then %do;
    data t_e_m_p;
      set &libname_in..&data. (obs=1 keep=&copy.);
    run;

    proc sql noprint;
      select name
        into :to_copy separated by " "
          from dictionary.columns
            where libname="WORK" and
                  memname="T_E_M_P"
        ;
      quit;
  %end;

/*Populate var parameter in the event it has a null value*/
  %if %length(&var.) eq 0 %then %do;
    data t_e_m_p;
      set &libname_in..&data. (obs=1 drop=&by. &id. &copy.);
    run;

    proc sql noprint;
      select name
        into :var separated by " "
          from dictionary.columns
            where libname="WORK" and
                  memname="T_E_M_P"
        %if %sysfunc(upcase("&autovars.")) eq "CHAR" %then %do;
                  and type="char"
        %end;
        %else %if %sysfunc(upcase("&autovars.")) ne "ALL" %then %do;
                  and type="num"
        %end;
        ;
      quit;
  %end;
  
/*Initialize macro variables*/
  %let vars_char=;
  %let varlist_char=;
  %let vars_num=;
  %let varlist_num=;
  %let formats_char=;
  %let format_char=;
  %let formats_num=;
  %let format_num=;

  %let label_num=;
  %let label_char=;
  %let length_num=;
  %let length_char=;
  %let labels_num=;
  %let labels_char=;
  %let lengths_num=;
  %let lengths_char=;

/*Create file t_e_m_p to contain one record with all var variables*/
  data t_e_m_p;
    set &libname_in..&data. (obs=1 keep=&var.);
  run;

/*Create macro variables containing untransposed var names and formats*/
  proc sql noprint;
    select name, case
                   when missing(format) then " $"||strip(put(length,5.))||'.'
                   else strip(format)
                 end,
                 case
                   when missing(label) then strip(name)
                   else strip(label)
                 end,
                 " $"||strip(put(length,5.))
      into :vars_char separated by " ",
           :formats_char separated by "~",
           :labels_char separated by "~",
           :lengths_char separated by "~"
        from dictionary.columns
          where libname="WORK" and
                memname="T_E_M_P" and
                type="char"
    ;
    select name, case
                   when missing(format) then "best12."
                   else strip(format)
                 end,
                 case
                   when missing(label) then strip(name)
                   else strip(label)
                 end,
                 " "||strip(put(length,5.))
      into :vars_num separated by " ",
           :formats_num separated by "~",
           :labels_num separated by "~",
           :lengths_num separated by "~"
        from dictionary.columns
          where libname="WORK" and
                memname="T_E_M_P" and
                type="num"
    ;
    select name
      into :vars_all separated by " "
        from dictionary.columns
          where libname="WORK" and
                memname="T_E_M_P"
    ;
  quit;

/* If ID variable contains non-SAS name characters, translate them to '_' */
  %if %sysfunc(upcase("&convertid.")) eq "YES" %then %do;
    data t_e_m_p;
      set &libname_in..&data.;
      do _n_=1 to length(&id.);
        if notalnum(substr(&id.,_n_,1)) then substr(&id.,_n_,1)='_';
      end;
    run;
    %let data=t_e_m_p;
    %let libname_in=work;
  %end;

/*If sort parameter has a value of YES, create a sorted temporary data file*/
  %if %sysfunc(upcase("&sort.")) eq "YES" %then %do;
    %let notsorted=;
    proc sort data=&libname_in..&data.
                (keep=&by. &id. &vars_char. &vars_num. &to_copy.) 
                 out=t_e_m_p &sort_options. noequals;
      by &by.;
    run;
    %let data=t_e_m_p;
    %let libname_in=work;
  %end;
  %else %do;
    %let notsorted=notsorted;
  %end;

  /*if no id parameter is present, create one from &newid.*/
  %if %length(&id.) eq 0 %then %do;
    data t_e_m_p;
      set &libname_in..&data.;
      by &by. &notsorted.;
      if first.&lastby then &newid.=1;
      else &newid+1;
    run;
    %let id=&newid.;
    %let data=t_e_m_p;
    %let libname_in=work;
  %end;

/*Ensure guessingrows parameter contains a value*/
  %if %length(&guessingrows.) eq 0 %then %do;
    %let guessingrows=%sysfunc(constant(EXACTINT));
  %end;

/*Ensure a format is assigned to an id variable*/
  %if %length(&id.) gt 0 %then %do;
    proc sql noprint;
      select type,length,%sysfunc(strip(format))
        into :tr_macro_type, :tr_macro_len, :tr_macro_format
          from dictionary.columns
            where libname="%sysfunc(upcase(&libname_in.))" and
                  memname="%sysfunc(upcase(&data.))" and
                  upcase(name)="%sysfunc(upcase(&id.))"
        ;
    quit;

    %if %length(&format.) eq 0 %then %do;
      %let optsave=%sysfunc(getoption(missing),$quote.);
      options missing=.;
      %if %length(&tr_macro_format.) gt 0 %then %do;
        %let format=&tr_macro_format.;
      %end;
      %else %if "&tr_macro_type." eq "num " %then %do;
        %let format=%sysfunc(catt(best,&tr_macro_len.,%str(.)));
      %end;
      %else %do;
        %let format=%sysfunc(catt($,&tr_macro_len.,%str(.)));
      %end;
      options missing=&optsave;
    %end;
  %end;

/*Create macro variables containing ordered lists of the requested transposed variable
  names for character (varlist_char) and numeric (varlist_num) var variables */
  %if %length(&preloadfmt.) gt 0 %then %do;
    %if %sysfunc(countw(&preloadfmt.)) eq 1 %then %do;
      %let preloadfmt=&libname_in..&preloadfmt.;
    %end;
  %end;
  %else %do;
    proc freq data=&libname_in..&data. (obs=&guessingrows. keep=&id.) noprint;
      tables &id./out=_for_format (keep=&id.);
    run;
    %if %sysfunc(upcase("&descendingid.")) eq "YES" %then %do;
      proc sort data=_for_format;
        by descending &id;
      run;
    %end;
    data _for_format;
      set _for_format;
      order=_n_;
    run;
  %end;

  proc sql noprint;
  %do i=1 %to 2;
    %if &i. eq 1 %then %let i_type=char;
    %else %let i_type=num;
    %if %length(&&vars_&i_type.) gt 0 %then %do;
    select distinct
      %do j=1 %to 4;
        %if &j. eq 1 %then %let j_type=;
        %else %if &j. eq 2 %then %let j_type=label;
        %else  %if &j. eq 3 %then %let j_type=length;
        %else %let j_type=format;
        %do k=1 %to %sysfunc(countw(&&vars_&i_type.));
         "&j_type. "||cats("&prefix.",
          %if %sysfunc(upcase("&var_first.")) eq "NO" %then %do;
            put(&id.,&format),"&delimiter."
            %if %sysfunc(upcase("&use_varname.")) ne "NO" %then
            ,scan("&&vars_&i_type.",&k.);
            ,"&suffix."
          %end;
          %else %do;
            %if %sysfunc(upcase("&use_varname.")) ne "NO" %then
               scan("&&vars_&i_type.",&k.),;
            "&delimiter.",put(&id.,&format),"&suffix."
          %end;
          )
          %if &j. eq 2 %then
            ||cats("=",scan("&&labels_&i_type.",&k.,"~"),";");
          %else %if &j. eq 3 %then
            ||" "||cats(scan("&&lengths_&i_type.",&k.,"~"),";");
          %else %if &j. eq 4 %then
            ||" "||cats(scan("&&formats_&i_type.",&k.,"~"),";");
          %if &k. lt %sysfunc(countw(&&vars_&i_type.)) %then ||;
          %else ,;
        %end;
      %end;
      %if "&tr_macro_type." eq "num " %then &id. format=best12.;
        %else &id.;
        ,order
          into :varlist_&i_type. separated by " ",
               :label_&i_type. separated by " ",
               :length_&i_type. separated by " ",
               :format_&i_type. separated by " ",
               :idlist separated by " ",
               :idorder separated by " "
           %if %length(&preloadfmt.) gt 0 %then from &preloadfmt.;
           %else from _for_format;
               order by order
    ;
      %let num_numlabels=&sqlobs.;
    %end;
  %end;
  quit;

  proc sql noprint;
    select distinct
        %let j_type=;
        %do k=1 %to %sysfunc(countw(&&vars_all.));
      "&j_type. "||cats("&prefix.",
      
          %if %sysfunc(upcase("&var_first.")) eq "NO" %then %do;
          put(&id.,&format),"&delimiter.",
            %if %sysfunc(upcase("&use_varname.")) ne "NO" %then
          scan("&&vars_all.",&k.);
          ,"&suffix.")
          %end;
          %else %do;
            %if %sysfunc(upcase("&use_varname.")) ne "NO" %then
          scan("&&vars_all.",&k.),;
          "&delimiter.",put(&id.,&format),"&suffix.")
          %end;
          %if &k. lt %sysfunc(countw(&&vars_all.)) %then ||;
          %else ,;
        %end;
        order
          into :varlist_all separated by " ",
               :idorder separated by " "
           %if %length(&preloadfmt.) gt 0 %then from &preloadfmt.;
           %else from _for_format;
               order by order
    ;
  quit;

/*Create a format that will be used to assign values to the transposed variables*/
  data _for_format;
    %if %length(&preloadfmt.) gt 0 %then set &preloadfmt. (rename=(&id.=start)); 
    %else set _for_format  (rename=(&id.=start));
    ;
    %if "&tr_macro_type." eq "num " %then retain fmtname "labelfmt" type "N";
    %else retain fmtname "$labelfmt" type "C";
    ;
    label=
     %if %length(&preloadfmt.) eq 0 %then _n_-1;
     %else order-1;
     ;
  run;

  proc format cntlin = _for_format;
  run ;

/*Create and run the datastep that does the transposition*/
   data &libname_out..&out.;
     set &libname_in..&data. (keep=&by. &id. 
       %do i=1 %to %sysfunc(countw("&vars_char."));  
         %scan(&vars_char.,&i.) 
       %end; 
       %do i=1 %to %sysfunc(countw("&vars_num."));  
         %scan(&vars_num.,&i.) 
       %end; 
       %do i=1 %to %sysfunc(countw("&to_copy."));  
         %scan(&to_copy.,&i.) 
       %end; 
/*       %unquote(&dsoptions.) */
       ); 
    by &by. &notsorted.;
    &format_char. &format_num. &label_char. &label_num. &length_char. &length_num.
  %if %length(&vars_char.) gt 0 %then %do;
    array want_char(*) $
    %do i=1 %to %eval(&num_numlabels.*%sysfunc(countw("&vars_char."))); 
      %scan(&varlist_char.,&i.)
    %end;
    ;
    array have_char(*) $ &vars_char.;
    retain want_char;
    if first.&lastby. then call missing(of want_char(*));
    ___nchar=put(&id.,labelfmt.)*dim(have_char);
    do ___i=1 to dim(have_char);
      want_char(___nchar+___i)=have_char(___i);
    end;
  %end;
  %if %length(&vars_num.) gt 0 %then %do;
    array want_num(*)
    %do i=1 %to %eval(&num_numlabels.*%sysfunc(countw("&vars_num."))); 
      %scan(&varlist_num.,&i.)
    %end;
    ;
    array have_num(*) &vars_num.;
    retain want_num;
    if first.&lastby. then call missing(of want_num(*));
    ___nnum=put(&id.,labelfmt.)*dim(have_num);
    do ___i=1 to dim(have_num);
      want_num(___nnum+___i)=have_num(___i);
    end;
  %end;
    drop &id. ___: &var. &drop.;
    if last.&lastby. then output;
  run;

  data &libname_out..&out.
    %if %length(%unquote(&odsoptions.)) gt 2 %then (&odsoptions.);;
    retain &by. &to_copy. &varlist_all.;
    set &libname_out..&out.;
  run;

/*Delete all temporary files*/
  %if %sysfunc(exist(work._t_e_m_p)) %then %do;
    proc delete data=work.t_e_m_p work._t_e_m_p work._for_format;
    run;
  %end;
  %else %do;
    proc delete data=work.t_e_m_p work._for_format;
    run;
  %end;
%mend transpose;
options NOQUOTELENMAX;

/****************Examples**********************
data have;
  attrib  col1 col2 col3 col4 format=$20.;
  infile datalines;
  input col1 $ col2 $ col3 $ col4 $;
datalines;
A 2014 N 0
A 2013 X 1
A 2012 N 0
A 2011 X 2
B 2013 X 5
B 2012 X 0
B 2011 N 1
B 2010 N 0
;

data order;
  informat col2 $20.;
  format col2 $20.;
  input col2 order;
  cards;
2014   1
2013   2
2011   3
2010   4
;

%transpose(data=have, out=want, by=col1, id=col2, delimiter=_,
 var=col2-col4, preloadfmt=order)

** or **

%transpose(data=have, out=want, by=col1, id=col2, delimiter=_,
 var=col2-col4, descendingid=yes)

data have;
  format idnum 4.;
  input idnum date var1 $;
  informat date date9.;
  format date yymon7.;
  cards;
1 01jan2001 SD
1 01feb2001 EF
1 01mar2001 HK
2 01jan2001 GH
2 01apr2001 MM
2 01may2001 JH
;

%transpose(data=have, out=want, by=idnum, var=var1,
 id=date, format=yymon7., delimiter=_,
 sort=yes, guessingrows=1000)

data have;
  format idnum 4.;
  input idnum date var1 $;
  informat date date9.;
  format date yymon7.;
  cards;
1 01jan2001 GH
1 01apr2001 MM
1 01may2001 JH
2 01jan2001 SD
2 01feb2001 EF
2 01mar2001 HK
;

%transpose(data=have, out=want, by=idnum, var=var1,
 id=date, format=yymon7., delimiter=_,
 sort=yes, guessingrows=1000)

data have (drop=months);
  format idnum 1.;
  informat date date9.;
  format date date9.;
  input date ind1-ind4 ;
  other=2;
  do idnum=1 to 2;
    date="31dec2010"d;
    do months=3 to 12 by 3;
      date=intnx('month',date,3);
      if not(months eq 9 and mod(idnum,2)) then output;
    end;
  end;
  cards;
01dec2010 1 2 3 4
;

%transpose(data=have, out=want, by=idnum, id=date, guessingrows=1000,
 format=qtr1., delimiter=_Qtr, var=ind1-ind4)

%transpose(data=have, out=want, by=idnum, id=date, guessingrows=1000,
 format=qtr1., prefix=Qtr, delimiter=_, var_first=no, var=ind1-ind4)

data have;
  informat name $5.;
  format name $5.;
  input year name height weight;
  cards;
2013 Richard 6.1 185
2013 Tom  5.8 163
2013 Harry 6.0 175
2014 Richard 6.1 180
2014 Tom  5.8 160
2014 Harry 6.0 195
;

data order;
  informat name $5.;
  format name $5.;
  input name order;
  cards;
Tom   1
Richard  2
Harry 3
;

%transpose(data=have, out=want, by=year, id=name, guessingrows=1000,
 delimiter=_, var=height weight, var_first=no, preloadfmt=order)

data have;
 format idnum 4. date date9.;
 input idnum date var1 var12 $;
 informat date date9.;
 cards;
1 31mar2013 1 SD
1 30jun2013 2 EF
1 30sep2013 3 HK
1 31dec2013 4 HL
2 31mar2013 5 GH
2 30jun2013 6 MM
2 30sep2013 7 JH
2 31dec2013 4 MS
;

%transpose(data=have, out=want, by=idnum, id=date, Guessingrows=1000,
 format=qtr1., delimiter=_Qtr, var=var1--var12)
 
DATA STEP1;
  INFILE CARDS MISSOVER;
  INPUT DATE$ UNIT$ AMT IND$;
  CARDS;
3/31/15 UNIT1 150 Y
3/31/16 UNIT1 200
4/30/16 UNIT1 300 Y
9/30/16 UNIT1 350 Y
12/31/16 UNIT1 400 Y
3/31/17 UNIT1 450 Y
4/30/17 UNIT1 500 Y
3/31/15 UNIT2 250
3/31/16 UNIT2 200 Y
4/30/16 UNIT2 400 Y
9/30/16 UNIT2 150 Y
12/31/16 UNIT2 200
3/31/17 UNIT2 450 Y
4/30/17 UNIT2 500 Y
3/31/15 UNIT3 550
3/31/16 UNIT3 200
4/30/16 UNIT3 300
9/30/16 UNIT3 350 Y
12/31/16 UNIT3 400 Y
3/31/17 UNIT3 450 Y
4/30/17 UNIT3 500 Y
;
RUN;

data order;
  input date $ order;
  cards;
3_31_15 1
3_31_16 2
4_30_16 3
9_30_16 4
12_31_16 5
3_31_17 6
4_30_17 7
;

%transpose(data=step1 (where=(IND='Y')), out=want, by=unit, id=date, var=amt, 
           prefix=_,use_varname=no,preloadfmt=order,convertid=yes)

%transpose(data=step1 (where=(IND='Y')), out=want, by=unit, id=date, var=amt, 
           delimiter=_,preloadfmt=order,convertid=yes)

 for development
 
data have;
  format idnum 4. date date9.
         var1 1.
         var12 $2.
  ;
  input idnum date var1 var12 $;
  informat date date9.;
  label var1="first variable"
        var12="last variable"
  ;
cards;
1 31mar2013 1 SD
1 30jun2013 2 EF
1 30sep2013 3 HK
1 31dec2013 4 HL
2 31mar2013 5 GH
2 30jun2013 6 MM
2 30sep2013 7 JH
2 31dec2013 4 MS
;

%transpose(data=have, out=want, by=idnum, id=date, Guessingrows=1000,
 format=qtr1., delimiter=_Qtr, var=var1--var12)
 
 ********************************************************************/

 

Comments

This is very useful.

There were a few things I disliked, so I started modifying it until I ended with a completely revamped version of this macro, which is more compact and legible imho, as it uses a few data steps rather than macro loops and macro variable lists. I also does input vetting and allows for multiple ID and BY variables.

My 2 cents. 🙂

/*****************************************************************************************

    Macro name          DS_WIDE
    ¯¯¯¯¯¯¯¯¯¯
    Description         Transform a data set by adding columns and removing rows  
    ¯¯¯¯¯¯¯¯¯¯¯           in a manner similar to what PROC TRANSPOSE does.
                        Much flexibility is given to order and name the columns. 

                        Run %ds_wide(help) or look below for a complete overview of the parameters, and for examples.

    Generates SAS code  Yes
    ¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯
    Calls other macros  No
    ¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯
    Inputs              One user-chosen table
    ¯¯¯¯¯¯
    Outputs             One user-chosen table
    ¯¯¯¯¯¯¯
*****************************************************************************************
Who              When        What
*****************************************************************************************
Various Authors              Initial version from 
                               https://communities.sas.com/t5/SAS-Communities-Library/A-better-way-to-FLIP-i-e-transpose-make-wide-a-dataset/ta-p/4336
C Graffeuille    2018-03-20  Complete rewrite V1
                              - Input parameters vetted and cleaned
                              - Data step driven rather then macro variable lists and loops
                              - Multiple ID variables accepted
                              - More options for column names and order
*****************************************************************************************/

%macro ds_wide(help
              ,libin           =WORK
              ,libout          =WORK
              ,dsin            =
              ,dsout           =
              ,by_vars         =
              ,tr_vars         =
              ,tr_auto         =ALL
              ,copy_vars       =
              ,colname_form    =< > <VAR_NAME> <_> <ID_VALUE> < >
              ,colname_order   =VAR_NAME*ID_VALUE
              ,colname_id_vars =
              ,colname_id_order=ASC
              ,colname_id_fmt  =
              ,colname_id_table=
              ,sort            =
              ,sort_options    = 
              ,debug           =N);

  %if %length(%superq(help)) | ^%length(%superq(dsin)) | ^%length(%superq(dsout)) %then %do;
    %local saveoptions;
    %let saveoptions=%sysfunc(getoption(symbolgen)) %sysfunc(getoption(mlogic)) %sysfunc(getoption(ps,keyword)) %sysfunc(getoption(ls,keyword)); 
    options nosymbolgen nomlogic ps=5000 ls=132;
    %put %nrstr(                                                                                                                             );
    %put %sysfunc(repeat(#,124)                                                                                                              );
    %put %nrstr(#       _____________________________                                                                                       #);
    %put %nrstr(#       Help screen for macro DS_WIDE                                                                                       #);
    %put %nrstr(#       ¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯                                                                                       #);
    %put %sysfunc(repeat(#,124)                                                                                                              );
    %put %nrstr(#                                                                                                                           #);
    %put %nrstr(#  This program performs transpositions of SAS datasets very similar to those that                                          #);
    %put %nrstr(#  can be achieved with PROC TRANSPOSE, but in such a manner that is easier to use                                          #);
    %put %nrstr(#  when performing complex transpositions and runs significantly faster.                                                    #);
    %put %nrstr(#                                                                                                                           #);
    %put %nrstr(# Parameters                                                                                                                #);
    %put %nrstr(# ¯¯¯¯¯¯¯¯¯¯                                                                                                                #);
    %put %nrstr(#   libin=            OPTL Input library. Ignored if a library is given in parameter DSIN=                                  #);
    %put %nrstr(#                          Default=WORK                                                                                     #);
    %put %nrstr(#                                                                                                                           #);
    %put %nrstr(#   libout=           OPTL Output library. Ignored if a library is given in parameter DSOUT=                                #);
    %put %nrstr(#                          Default=WORK                                                                                     #);
    %put %nrstr(#                                                                                                                           #);
    %put %nrstr(#   dsin=             REQD Input dataset name.                                                                              #);
    %put %nrstr(#                          Can contain the library name, in which case LIBIN= is ignored.                                   #);
    %put %nrstr(#                          Can contain data set options.                                                                    #);
    %put %nrstr(#                                                                                                                           #);
    %put %nrstr(#   dsout=            REQD Output dataset name.                                                                             #);
    %put %nrstr(#                          Can contain the library name, in which case LIBOUT= is ignored.                                  #);
    %put %nrstr(#                          Can contain data set options.                                                                    #);
    %put %nrstr(#                                                                                                                           #);
    %put %nrstr(#   by_vars=          REQD List of variable(s) used to form BY groups.                                                      #);
    %put %nrstr(#                          This parameter is identical to the BY statement used in PROC TRANSPOSE.                          #);
    %put %nrstr(#                          BY_VARS groups define the record level of the resulting transposed file                          #);
    %put %nrstr(#                                                                                                                           #);
    %put %nrstr(#   copy_vars=        OPTL List of variable(s) that are copied rather than transposed                                       #);
    %put %nrstr(#                            List syntax using dash and/or colon shortcuts can be used.                                     #);
    %put %nrstr(#                          This parameter is identical to the COPY statement used in PROC TRANSPOSE.                        #);
    %put %nrstr(#                                                                                                                           #);
    %put %nrstr(#   tr_vars=          OPTL List of variable(s) to transpose.                                                                #);
    %put %nrstr(#                          This parameter is identical to the VARS statement used in PROC TRANSPOSE.                        #);
    %put %nrstr(#                            List syntax using dash and/or colon shortcuts can be used.                                     #);
    %put %nrstr(#                          Default= Variable(s) defined by parameter TR_AUTO=.                                              #);
    %put %nrstr(#                                                                                                                           #);
    %put %nrstr(#   tr_auto=          OPTL This parameter automatically assigns variable names to the TR_VARS= parameter                    #);
    %put %nrstr(#                           provided the TR_VARS= parameter is missing.                                                     #);
    %put %nrstr(#                           BY_VARS, COPY_VARS and COLNAME_ID_VARS variables are never transposed.                          #);
    %put %nrstr(#                          Values = NUM, CHAR, ALL. Only the first letter is needed.                                        #);
    %put %nrstr(#                          Default= ALL                                                                                     #);
    %put %nrstr(#                                                                                                                           #);
    %put %nrstr(#   colname_form=     OPTL Defines the structure of the name of the transposed columns                                      #);
    %put %nrstr(#                          Format: <prefix> <VAR_NAME | ID_VALUE | NONE> <delimiter> <VAR_NAME | ID_VALUE | NONE> <suffix>  #);
    %put %nrstr(#                            prefix, delimiter, suffix are strings of your choice.                                          #);
    %put %nrstr(#                            VAR_NAME situates the name of the variable whose values populate the columnm                   #);
    %put %nrstr(#                            ID_VALUE situates the value of the COLNAME_ID_VARS variable(s) for this column                 #);
    %put %nrstr(#                            NONE can replace of VAR_NAME in order to omit it (only use if one variable is transposed)      #);
    %put %nrstr(#                          The 5 sets of angle brackets are needed. Some content can be empty. Spaces are ignored.          #);
    %put %nrstr(#                          Default=< > <VAR_NAME> <_> <ID_VALUE> < >                                                        #);
    %put %nrstr(#                                                                                                                           #);
    %put %nrstr(#   colname_order=    OPTL Defines the order of the transposed columns                                                      #);
    %put %nrstr(#                          The order can be: The first ID_VALUE for all the transposed columns, then the next ID_VALUE, etc #);
    %put %nrstr(#                                        or: The first colunm with all the ID_VALUEs, then the next column, etc             #);
    %put %nrstr(#                          Values=VAR_NAME*ID_VALUE or ID_VALUE*VAR_NAME. Only the first letter is needed.                  #);
    %put %nrstr(#                          Default=VAR_NAME*ID_VALUE                                                                        #);
    %put %nrstr(#                                                                                                                           #);
    %put %nrstr(#   colname_id_vars=  OPTL Variable(s) whose ID values are used to build the transposed column names.                       #);
    %put %nrstr(#                          Default=Ordinal count (i.e. row number, no variable used)                                        #);
    %put %nrstr(#                                                                                                                           #);
    %put %nrstr(#   colname_id_order= OPTL This parameter defines whether the COLNAME_ID_VARS values are used in descending order.          #);
    %put %nrstr(#                          Values =ASC, DESC. Only the first letter is needed.                                              #);
    %put %nrstr(#                          This parameter is ignored when a COLNAME_ID_TABLE is given.                                      #);
    %put %nrstr(#                          Default=ASC                                                                                      #);
    %put %nrstr(#                                                                                                                           #);
    %put %nrstr(#   colname_id_table= OPTL Defines the order and values of the COLNAME_ID_VARS part of the column names                     #);
    %put %nrstr(#                          This parameter contains a table name. That table contains the COLNAME_ID_VARS variable(s),       #);
    %put %nrstr(#                            in the order and with the values wanted.                                                       #);
    %put %nrstr(#                          COLNAME_ID_VARS values that do not appear in the table are not output.                           #);
    %put %nrstr(#                          Default=<ascending order of the COLNAME_ID_VARS variable(s)>                                     #);
    %put %nrstr(#                                                                                                                           #);
    %put %nrstr(#   colname_id_fmt=   OPTL Format to use for the COLNAME_ID_VARS variable(s).                                               #);
    %put %nrstr(#                          Default= Format already assigned to the COLNAME_ID_VARS variable(s).                             #);
    %put %nrstr(#                                                                                                                           #);
    %put %nrstr(#   sort=             OPTL Indicates whether the input dataset must be sorted before the data is transposed.                #);
    %put %nrstr(#                          Values =YES, NO.  Only the first letter is needed.                                               #);
    %put %nrstr(#                          Default=NO (No sorting, the data is read using the NOTSORTED option)                             #);
    %put %nrstr(#                                                                                                                           #);
    %put %nrstr(#   sort_options=     OPTL Options to use when sorting the input dataset. The NOEQUALS PRESORTED options are always used.   #);
    %put %nrstr(#                          Other options such as FORCE or TAGSORT can be added here.                                        #);
    %put %nrstr(#                                                                                                                           #);
    %put %nrstr(# Examples                                                                                                                  #);
    %put %nrstr(# ¯¯¯¯¯¯¯¯                                                                                                                  #);
    %put %nrstr(#                                                                                                                           #);
    %put %nrstr(# %ds_wide(help)                                                                                                            #);
    %put %nrstr(#    Displays this help screen                                                                                              #);
    %put %nrstr(#                                                                                                                           #);
    %put %nrstr(#                                                                                                                           #);
    %put %nrstr(# Example data                                                                                                              #);
    %put %nrstr(# ¯¯¯¯¯¯¯¯¯¯¯¯                                                                                                              #);
    %put %nrstr(#   data CLASS; format DATE date9.; set SASHELP.CLASS(in=A) SASHELP.CLASS; DATE=A+20000; run;                               #);
    %put %nrstr(#                                                                                                                           #);
    %put %nrstr(#                                                                                                                           #);
    %put %nrstr(# 1- Default options                                                                                                        #);
    %put %nrstr(# ¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯                                                                                                        #);
    %put %nrstr(# %ds_wide(dsin=CLASS(firstobs=2 obs=4), dsout=WANT1, by_vars=SEX, colname_id_vars=AGE)                                     #);
    %put %nrstr(#                                                                                                                           #);
    %put %nrstr(# Sex | DATE_13   | DATE_14   | Height_13 | Height_14 | Name_13 | Name_14 | Weight_13 | Weight_14                           #);
    %put %nrstr(# -----------------------------------------------------------------------------------------------                           #);
    %put %nrstr(# F   | 05OCT2014 | 05OCT2014 | 65.3      | 62.8      | Barbara | Carol   | 98        | 102.5                               #);
    %put %nrstr(#                                                                                                                           #);
    %put %nrstr(#                                                                                                                           #);
    %put %nrstr(# 2- Ask for sort, two BY variables                                                                                         #);
    %put %nrstr(# ¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯                                                                                         #);
    %put %nrstr(# %ds_wide(dsin=CLASS(where=(AGE=11)), dsout=WANT2, by_vars=SEX DATE, colname_id_vars=AGE, tr_auto=N, sort=Y)               #);
    %put %nrstr(#                                                                                                                           #);
    %put %nrstr(# Sex | DATE_13   | DATE_14   | Height_13 | Height_14 | Weight_13 | Weight_14                                               #);
    %put %nrstr(# ---------------------------------------------------------------------------                                               #);
    %put %nrstr(# F   | 05OCT2014 | 05OCT2014 | 56.5      | 62.8      | 84        | 102.5                                                   #);
    %put %nrstr(# M   | .         | 05OCT2014 | .         | 69        | .         | 112.5                                                   #);
    %put %nrstr(#                                                                                                                           #);
    %put %nrstr(#                                                                                                                           #);
    %put %nrstr(# 3- Two ID variables, colname_order is VAR_NAME*ID_VALUE, colname is <VAR_NAME>_<ID_VALUE> with ascending ID_VALUE         #);
    %put %nrstr(# ¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯         #);
    %put %nrstr(# %ds_wide%(dsin=CLASS(where=(AGE=11)), dsout=WANT3, by_vars=AGE, colname_id_vars=SEX DATE, colname_id_fmt=$1. date5.        #);
    %put %nrstr(#                    ,tr_vars=WEIGHT NAME, colname_order=v, colname_id_order=a, sort=Y%)                                     #);
    %put %nrstr(#                                                                                                                           #);
    %put %nrstr(# Age | Weight_F_04OCT | Weight_F_05OCT | Weight_M_04OCT | Weight_M_05OCT | Name_F_04OCT | Name_F_05OCT | Name_M_04OCT      #);
    %put %nrstr(# -------------------------------------------------------------------------------------------------------------------- 8><  #);
    %put %nrstr(# 11  | 50.5 |           50.5           | 85             | 85             | Joyce        | Joyce        | Thomas            #);
    %put %nrstr(#                                                                                                                           #);
    %put %nrstr(#                                                                                                                           #);
    %put %nrstr(# 4- Same data as above but column names and column order changed                                                           #);
    %put %nrstr(# ¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯                                                           #);
    %put %nrstr(# %ds_wide%(dsin=CLASS(where=(AGE=11)), dsout=WANT4, by_vars=AGE, colname_id_vars=SEX DATE, colname_id_fmt=$1. date5.        #);
    %put %nrstr(#       ,tr_vars=WEIGHT NAME, colname_order=i, colname_id_order=d, sort=Y, colname_form=<><ID_VALUE><><VAR_NAME><x>%)        #);
    %put %nrstr(#                                                                                                                           #);
    %put %nrstr(# Age | M_05OCTWeightX | M_05OCTNameX | M_04OCTWeightX | M_04OCTNameX | F_05OCTWeightX | F_05OCTNameX | F_04OCTWeightX      #);
    %put %nrstr(# -------------------------------------------------------------------------------------------------------------------- 8><  #);
    %put %nrstr(# 11  | 85             | Thomas       |             85 | Thomas       | 50.5           | Joyce         | 50.5               #);
    %put %nrstr(#                                                                                                                           #);
    %put %nrstr(#                                                                                                                           #);
    %put %nrstr(# 5- VAR_NAME omitted, ID_VALUEs (age) forced, a prefix is automatically added to make column name valid                    #);
    %put %nrstr(# ¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯                    #);
    %put %nrstr(# data VAL; do AGE=12,15,14; output; end; run;                                                                              #);
    %put %nrstr(# %ds_wide%(dsin=CLASS, dsout=WANT5, by_vars=SEX DATE, colname_id_vars=AGE , colname_id_table=VAL                            #);
    %put %nrstr(#                    ,tr_vars=WEIGHT , colname_order=i, colname_id_order=d, sort=Y, colname_form=<><ID_VALUE><><NONE><>%)    #);
    %put %nrstr(#                                                                                                                           #);
    %put %nrstr(# DATE      | Sex | _12 | _15   | _14                                                                                       #);
    %put %nrstr(# -------------------------------------                                                                                     #);
    %put %nrstr(# 04OCT2014 | F   | 77  | 112   | 90                                                                                        #);
    %put %nrstr(# 05OCT2014 | F   | 77  | 112.5 | 102.5                                                                                     #);
    %put %nrstr(# 04OCT2014 | M   | 128 | 133   | 112.5                                                                                     #);
    %put %nrstr(# 05OCT2014 | M   | 128 | 133   | 112.5                                                                                     #);
    %put %nrstr(#                                                                                                                           #);
    %put %nrstr(#                                                                                                                           #);
    %put %nrstr(# 6- No ID var, incremental ID is automatically created                                                                     #);
    %put %nrstr(# ¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯                                                                     #);
    %put %nrstr(# %ds_wide(dsin=CLASS(firstobs=2 obs=4), dsout=WANT6, by_vars=SEX, tr_vars=WEIGHT )                                         #);
    %put %nrstr(#                                                                                                                           #);
    %put %nrstr(# Sex | Weight_1 | Weight_2 | Weight_3                                                                                      #);
    %put %nrstr(# ------------------------------------                                                                                      #);
    %put %nrstr(# F   | 84       | 98       | 102.5                                                                                         #);
    %put %nrstr(#                                                                                                                           #);
    %put %sysfunc(repeat(#,124)                                                                                                              );
    %put %nrstr(                                                                                                                             );
    options &saveoptions. ;
    %return;
  %end;

  %*** INIT *********************************************;
  %macro _; %mend _;  
  %local random msg dsinopt dsoutopt notsorted colname_id_comma nb_id_vars i tmp;
  %local colname_prefix colname_part1 colname_sep colname_part2 colname_suffix;

  %let random=%scan(%sysfunc(ranuni(0))%sysfunc(time()),2); 

  %*** CLEAN INPUTS *********************************************;
  %let libin           =%sysfunc(putc(%sysfunc(prxchange(s/[^a-zA-Z0-9_]//   ,-1,%superq(libin  ))) ,$upcase32. ));
  %let libout          =%sysfunc(putc(%sysfunc(prxchange(s/[^a-zA-Z0-9_]//   ,-1,%superq(libout ))) ,$upcase32. ));

  %let tmp=%index(%superq(dsin),%str(%());
  %if &tmp. %then %do; 
    %let dsinopt         =%qsubstr(%superq(dsin), &tmp+1, %length(%superq(dsin))-&tmp.   -1);
    %let dsin            =%qsubstr(%superq(dsin), 1     ,  %index(%superq(dsin),%str(%())-1);
  %end;
  %let tmp=%index(%superq(dsout),%str(%());
  %if &tmp. %then %do; 
    %let dsoutopt         =%qsubstr(%superq(dsout), &tmp+1, %length(%superq(dsout))-&tmp.   -1);
    %let dsout            =%qsubstr(%superq(dsout), 1     ,  %index(%superq(dsout),%str(%())-1);
  %end;
  %let dsin            =%sysfunc(putc(%sysfunc(prxchange(s/[^a-zA-Z0-9_.]//   ,-1,%qscan(%superq(dsin ),1,%str(%()))) ,$upcase65.));
  %let dsout           =%sysfunc(putc(%sysfunc(prxchange(s/[^a-zA-Z0-9_.]//   ,-1,%qscan(%superq(dsout),1,%str(%()))) ,$upcase65.));

  %let by_vars         =%sysfunc(putc(%sysfunc(prxchange(s/[^a-zA-Z0-9_ ]//   ,-1,%superq(by_vars          ))) ,$upcase999.));
  %let tr_vars         =%sysfunc(putc(%sysfunc(prxchange(s/[^a-zA-Z0-9_ -:]// ,-1,%superq(tr_vars          ))) ,$upcase999.));
  %let tr_auto         =%sysfunc(putc(%sysfunc(prxchange(s/[^a-zA-Z]//        ,-1,%superq(tr_auto          ))) ,$upcase1.  ));
  %let copy_vars       =%sysfunc(putc(%sysfunc(prxchange(s/[^a-zA-Z0-9_ -:]// ,-1,%superq(copy_vars        ))) ,$upcase999.));
  %let colname_form    =%sysfunc(putc(%sysfunc(prxchange(s/[^a-zA-Z0-9_<>]//  ,-1,%superq(colname_form     ))) ,$upcase65. ));
  %let colname_order   =%sysfunc(putc(%sysfunc(prxchange(s/[^a-zA-Z*]//       ,-1,%superq(colname_order    ))) ,$upcase1.  ));
  %let colname_id_vars =%sysfunc(putc(%sysfunc(prxchange(s/[^a-zA-Z0-9_ ]//   ,-1,%superq(colname_id_vars  ))) ,$upcase999.));
  %let colname_id_order=%sysfunc(putc(%sysfunc(prxchange(s/[^adAD]//          ,-1,%superq(colname_id_order ))) ,$upcase1.  ));
  %let colname_id_fmt  =%sysfunc(putc(%sysfunc(prxchange(s/[^a-zA-Z0-9_.\$ ]//,-1,%superq(colname_id_fmt   ))) ,$upcase999.)); 
  %let colname_id_table=%sysfunc(putc(%sysfunc(prxchange(s/[^a-zA-Z0-9_.]//   ,-1,%superq(colname_id_table ))) ,$upcase65. )); 

  %let sort            =%sysfunc(putc(%sysfunc(prxchange(s/[^a-zA-Z]//        ,-1,%superq(sort             ))) ,$upcase1.  ));
  %let sort_options    =%sysfunc(putc(%sysfunc(prxchange(s/[^a-zA-Z]//        ,-1,%superq(sort_options     ))) ,$upcase65. ));
  %let debug           =%sysfunc(putc(%sysfunc(prxchange(s/[^a-zA-Z ]//       ,-1,%superq(debug            ))) ,$upcase1.  ));

  %*** VET INPUTS *********************************************;
  %if %length(%scan(&dsin.,2)) %then %do;
    %let libin=%scan(&dsin,1);
    %let dsin =%scan(&dsin,2);
  %end;
  %if ^%length(&libin.) %then %let libin=WORK;
  %if ^%sysfunc(exist(&libin..&dsin.)) %then %do; %let msg=Input data set &libin..&dsin not found.; %goto bye; %end;

  %if %length(%scan(&dsout.,2)) %then %do;
    %let libout=%scan(&dsout,1);
    %let dsout =%scan(&dsout,2);
  %end;
  %if ^%length(&libout.) %then %let libout=WORK;       
  %if %sysfunc(libref(&libout.)) %then %do; %let msg=Output library &libout not found.; %goto bye; %end;
  %if ^%sysfunc(nvalid(&dsout.)) %then %do; %let msg=Output data set name &dsout is invalid.; %goto bye; %end;

  %if ^%length(&by_vars.) %then %do; %let msg=BY parameter must be defined.; %goto bye; %end;

  %if %sysfunc(countw(&colname_id_fmt.%str( ))) ne %sysfunc(countw(&colname_id_vars.%str( ))) 
      %then %do; %let msg=There must be the same number of COLNAME_ID variables and formats (or no format).; %goto bye; %end;

  %if %sysfunc(prxmatch(/<\w*><(VAR_NAME|ID_VALUE|NONE)><\w*><(VAR_NAME|ID_VALUE|NONE)><\w*>/i,&colname_form)) ne 1 
      %then %do; %let msg=COLNAME_FORM must be in the form <prefix> <VAR_NAME|ID_VALUE|NONE> <separator> <VAR_NAME|ID_VALUE|NONE> <suffix>.; %goto bye; %end;

  %let colname_prefix =%scan(%sysfunc(prxchange(s/\U(<.*?>)(<.*?>)(<.*?>)(<.*?>)(<.*?>)\E/$1/,1,&colname_form)),1,<>) ; 
  %let colname_part1  =%scan(%sysfunc(prxchange(s/\U(<.*?>)(<.*?>)(<.*?>)(<.*?>)(<.*?>)\E/$2/,1,&colname_form)),1,<>) ; 
  %let colname_sep    =%scan(%sysfunc(prxchange(s/\U(<.*?>)(<.*?>)(<.*?>)(<.*?>)(<.*?>)\E/$3/,1,&colname_form)),1,<>) ; 
  %let colname_part2  =%scan(%sysfunc(prxchange(s/\U(<.*?>)(<.*?>)(<.*?>)(<.*?>)(<.*?>)\E/$4/,1,&colname_form)),1,<>) ; 
  %let colname_suffix =%scan(%sysfunc(prxchange(s/\U(<.*?>)(<.*?>)(<.*?>)(<.*?>)(<.*?>)\E/$5/,1,&colname_form)),1,<>) ; 
  %if       &colname_part1=VAR_NAME and &colname_part2=ID_VALUE %then %do; %let colname_part1=VARNAME_&random; %let colname_part2=IDVAL_&random  ; %end;
  %else %if &colname_part1=NONE     and &colname_part2=ID_VALUE %then %do; %let colname_part1=' '            ; %let colname_part2=IDVAL_&random  ; %end;
  %else %if &colname_part1=ID_VALUE and &colname_part2=VAR_NAME %then %do; %let colname_part1=IDVAL_&random  ; %let colname_part2=VARNAME_&random; %end;
  %else %if &colname_part1=ID_VALUE and &colname_part2=NONE     %then %do; %let colname_part1=IDVAL_&random  ; %let colname_part2=' '            ; %end;
  %else %do; %let msg=COLNAME_FORM must be in the form <prefix> <VAR_NAME|ID_VALUE|NONE> <separator> <VAR_NAME|ID_VALUE|NONE> <suffix>.; %goto bye; %end;

  %*Populate TR_VARS parameter in case it is empty;
  %if %length(&tr_vars.) eq 0 %then %do;
    data _&random._TRPOS_VAR1; set &libin..&dsin.( %unquote(&dsinopt) ) ; stop; run;
    proc contents data=_&random._TRPOS_VAR1 (drop=&by_vars. &colname_id_vars. &copy_vars. ) noprint out=_&random._TRPOS_VAR2;
    proc sql noprint;
      select upcase(NAME) into :tr_vars separated by ' ' from _&random._TRPOS_VAR2 
        %if "&tr_auto" eq "C" %then where TYPE=2;
        %if "&tr_auto" eq "N" %then where TYPE=1;
      ;
    quit;
  %end;
  %if ^%length(&tr_vars.) %then %do; %let msg=No variables to transpose.; %goto bye; %end;
  %if %sysfunc(countw(&tr_vars.))>1 & %index(&colname_form.,NONE) %then %do; 
     %let msg=Only one variable can be transposed when parameter COLNAME_FORM includes NONE.; %goto bye; %end;

  %*Sort table if requested;
  %if "&sort" eq "Y" %then %do;
    proc sort data=&libin..&dsin. ( %unquote(&dsinopt) ) 
              out =_&random._TRPOS_SORT(keep=&by_vars. &colname_id_vars. &tr_vars. &copy_vars.) &sort_options. noequals presorted;
      by &by_vars.;
    run;
    %let dsin =_&random._TRPOS_SORT;
    %let libin=WORK;
  %end;
  %else %do;
    %let notsorted=notsorted;
  %end;        
 
  %*Create temporary file if there are dataset options ;
  %if "&sort" ne "Y" %then %if %length(%superq(dsinopt)) %then %do;
    data _&random._OPTIONS (keep=&by_vars. &colname_id_vars. &tr_vars. &copy_vars.);
      set &libin..&dsin. (%unquote(&dsinopt));
    run;
    %let dsin =_&random._OPTIONS;
    %let libin=WORK;
  %end;
                   
  %* Expand the COPY_VARS variable names in case variable list syntax is used;
  %if %length(&copy_vars.) %then %do;
    proc contents data=&libin..&dsin.(keep=&copy_vars.) noprint out=_&random._TRPOS_COPY;
    proc sql noprint;
      select upcase(NAME) into :copy_vars separated by " " from _&random._TRPOS_COPY; 
    quit;           
  %end;

  %*If parameter COLNAME_ID_VARS is empty, create one that contains the row number in each by group;
  %if ^%length(&colname_id_vars.) %then %do;
    data _&random._TRPOS_ID;
      set &libin..&dsin.;
        %if %length(&by_vars.) %then %do;
      by &by_vars. &notsorted.;
      if first.%scan(&by_vars.,-1) then COLNAME_ID_&random.=1;
      else COLNAME_ID_&random.+1;
        %end;
        %else %do;
      COLNAME_ID_&random.=_N_;
        %end;
    run;
    %let colname_id_vars=COLNAME_ID_&random;
    %let dsin           =_&random._TRPOS_ID;
    %let libin          =WORK;
  %end;
  %let colname_id_comma=%sysfunc(translate(%sysfunc(strip(%superq(colname_id_vars))),%str(,),%str( )));
                                     
  %*If parameter COLNAME_ID_TABLE is empty, create a table;
  %if ^%length(&colname_id_table.) %then %do;
    proc sql;
      create table _&random._TRPOS_IDTAB as
      select unique &colname_id_comma.  
      from &libin..&dsin.                                           
      order by %if &colname_id_order.=A %then &colname_id_comma.;
               %else %sysfunc(prxchange(s/(\w)(%str(,| ))/$1 desc$2/,-1, %nrbquote(&colname_id_comma. ) ));
      ;
    quit;
    %let colname_id_table=_&random._TRPOS_IDTAB;
  %end;
  %*If parameter COLNAME_ID_TABLE is populated verify its contents;
  %else %do;
    proc contents data=&libin..&dsin.(keep=&colname_id_vars.) noprint out=_&random._TRPOS_ID1;
    proc sql noprint;
      select count(*) into :nb_id_vars from _&random._TRPOS_ID1 ;
    quit;
    %if %sysfunc(countw(&colname_id_vars)) ne &nb_id_vars %then %do; 
      %let msg=COLNAME_ID_VARS variables not found in table COLNAME_ID_TABLE.; %goto bye; %end;
  %end;

  %*If parameter COLNAME_ID_FMT is empty, fill it;
  %if ^%length(&colname_id_fmt.) %then %do;
    data _null_;
      set &colname_id_table.(obs=1);
      length VARNAME_&random. $32 FMT_&random. $999 ;
      do while (1);
        call vnext(VARNAME_&random.);
        if VARNAME_&random. = "VARNAME_&random" then leave;      
        FMT_&random.=catx(' ',FMT_&random.,vformatx(VARNAME_&random.));
      end;
      call symputx('colname_id_fmt',FMT_&random.);
    run;
  %end;

  %*Check that the col names are valid names when ID_VALUE comes first. If not force prefix to _;
  data _null_;
    set &colname_id_table.;
    length VARNAME_&random. $40;
    call vnext(VARNAME_&random.);  
    %* if the first element of column name is ID value, check the values of the first ID variable;
    %if       %substr(&colname_part1.,1,3)=IDV %then VARNAME_&random.=cats("&colname_prefix"            , vvaluex(VARNAME_&random.) );
    %* if the second element of column name is ID value and the first is NONE, check the values of the first ID variable;
    %else %if %substr(&colname_part1.,1,3)=' ' %then VARNAME_&random.=cats("&colname_prefix&colname_sep", vvaluex(VARNAME_&random.) );
    %* else check the names of the transposed variables, just in case and since we are here anyway... ;
    %else                                            VARNAME_&random.=cats("&colname_prefix", scan("&tr_vars",min(countw("&tr_vars"),_N_)));
    ;
    if not nvalid(VARNAME_&random.,'v7') then
      call symput('colname_prefix','_');    
  run;                   
                                         
  %*Declare all transposed variables in the correct order;
  %if &colname_order.=V %then %do; %*order is VAR_NAME*ID_VALUE;
    data _null_;
      %do i= 1 %to %sysfunc(countw(&tr_vars.));
        if 0 then set &libin..&dsin.(keep=%scan(&tr_vars.,&i.));
      %end;
      length VARNAME_&random. $32 TYPE_&random. $1 ;
      if _N_=1 then call execute("data _&random._ATTRIB; attrib ");
      if 0 then set &colname_id_table. nobs=NOBS;
      do while (1);
        call vnext(VARNAME_&random.,TYPE_&random.,LEN_&random.);
        if VARNAME_&random. = "VARNAME_&random." then leave;
        do OBS_&random.=1 to NOBS; 
          set &colname_id_table.(keep=&colname_id_vars.) point=OBS_&random.;
          IDVAL_&random.=catt(
            %do i=1 %to %sysfunc(countw(&colname_id_vars.));
              %if &i.>1 %then ,'_', ;
              put(%scan(&colname_id_vars.,&i.),%scan(&colname_id_fmt.,&i.,%str( )) -l)
            %end;
          );
          call execute(catt("&colname_prefix",&colname_part1.,"&colname_sep",&colname_part2.,"&colname_suffix"
                           , ' length=', ifc(TYPE_&random.='C','$',' '), LEN_&random.
                           , ' format=', vformatx(VARNAME_&random.)
                           , ' label =', quote(trim(vlabelx(VARNAME_&random.)))));
        end; 
      end;
      call execute('; call missing(of _ALL_); stop; run;');
      stop;
    run;
  %end;
  %else %do;  %*order is ID_VALUE*VAR_NAME;
    data _null_;
      %do i= 1 %to %sysfunc(countw(&tr_vars.));
        if 0 then set &libin..&dsin.(keep=%scan(&tr_vars.,&i.));
      %end;
      length VARNAME_&random. $32 TYPE_&random. $1 ;
      if _N_=1 then call execute("data _&random._ATTRIB; attrib ");
      set &colname_id_table.(keep=&colname_id_vars.) end=LASTOBS;
      VARNAME_&random.=' ';
      IDVAL_&random.=catt(
        %do i=1 %to %sysfunc(countw(&colname_id_vars.));
          %if &i.>1 %then ,'_', ;
          put(%scan(&colname_id_vars.,&i.),%scan(&colname_id_fmt.,&i.,%str( )) -l)
        %end;
      );
      do while (1);
        call vnext(VARNAME_&random.,TYPE_&random.,LEN_&random.);
        if VARNAME_&random. = "VARNAME_&random." then leave;    
        call execute(catt("&colname_prefix",&colname_part1.,"&colname_sep",&colname_part2.,"&colname_suffix"
                         , ' length=', ifc(TYPE_&random.='C','$',' '),LEN_&random.
                         , ' format=',vformatx(VARNAME_&random.)
                         , ' label=', quote(trim(vlabelx(VARNAME_&random.)))));
      end; 
      if LASTOBS then call execute('; call missing(of _ALL_); stop; run;');
    run;
  %end;     
                                         
  %*Final step: transpose the data set;
  data _null_;
    if 0 then set  &libin..&dsin.(keep= &tr_vars.);
    length VARNAME_&random. NEW_COL_&random. $32 ;
    if 0 then set &colname_id_table. nobs=NOBS;                      
    call execute("data &dsout (%unquote(%superq(dsoutopt))); if 0 then set &libin..&dsin(keep=&by_vars &copy_vars) _&random._ATTRIB;");
    call execute("set &libin..&dsin.; by &by_vars;  ");                   
    do OBS_&random.=1 to NOBS; 
      set &colname_id_table. point=OBS_&random.;  
      format &colname_id_vars.;
      VARNAME_&random.=' ';
      %if %length(&colname_id_fmt.)=0 %then %do;
        IDVAL_&random.=catx('_',&colname_id_comma.);
      %end;
      %else %do ;
        IDVAL_&random.=catt(
        %do i=1 %to %sysfunc(countw(&colname_id_vars.));
          %if &i.>1 %then ,'_', ;
          put(%scan(&colname_id_vars.,&i.),%scan(&colname_id_fmt.,&i.,%str( )) -l)
        %end;
        );
      %end;
      do while (1);
        call vnext(VARNAME_&random.);
        if VARNAME_&random. = "VARNAME_&random" then leave; 
        NEW_COL_&random.=catt("&colname_prefix",&colname_part1.,"&colname_sep",&colname_part2.,"&colname_suffix"); 
        call execute('retain '||NEW_COL_&random.||' ;');
        call execute('keep   '||NEW_COL_&random.||' ;');
        call execute(catt('if first.',scan("&by_vars",-1),' then call missing(',NEW_COL_&random.,' );'));
        call execute('if ');
        do J= 1 to countw("&colname_id_vars");
          IDVAR_&random.=scan("&colname_id_vars",J);
          if J>1 then call execute (' and ');
          call execute(catt(IDVAR_&random.,'=',ifc(vtypex(IDVAR_&random.)='C',quote(trim(vvaluex(IDVAR_&random.))),vvaluex(IDVAR_&random.))));
        end;
        call execute(' then '||catt(NEW_COL_&random.,'=',VARNAME_&random.,';'));
      end; 
    end; 
    call execute(catt('if last.',scan("&by_vars",-1)," then output; keep &by_vars &copy_vars; run;")); 
    stop;       
  run;
                                           

  %*************** TERM **************;

  %*Delete all temporary files;
  %if &debug. ne Y %then %do;
    proc datasets noprint; delete _&random:; run;
  %end;
                          
  %goto bottom;

  %bye:     
    %put %sysfunc(repeat(_,50));
    %put ;
    %put ERROR: Invalid call to macro &sysmacroname.;
    %put ERROR- &msg;
    %put ERROR- Macro &sysmacroname. has been stopped.;
    %put ;
    %put %sysfunc(repeat(¯,50));
                                                           
  %bottom:      

%mend ;

/*
%ds_wide()

data CLASS; format DATE date9.; set SASHELP.CLASS(in=A) SASHELP.CLASS; DATE=A+20000; run;        

%ds_wide(dsin=CLASS(firstobs=2 obs=3), dsout=WANT1, by_vars=SEX, tr_vars=WEIGHT );

%ds_wide(dsin=CLASS, dsout=WANT3, by_vars=SEX DATE, tr_vars=WEIGHT , sort=Y) 
 
%ds_wide(dsin=CLASS, dsout=WANT3, by_vars=SEX DATE, tr_vars=WEIGHT , sort=Y,colname_form=<><ID_VALUE><><VAR_NAME><x>)  
 
%ds_wide(dsin=CLASS, dsout=WANT3, by_vars=SEX DATE, tr_vars=WEIGHT , sort=Y,colname_form=<><NONE><z><ID_VALUE><x>)   
%ds_wide(dsin=CLASS, dsout=WANT3, by_vars=SEX DATE, tr_vars=WEIGHT , sort=Y,colname_form=<><VAR_NAME><><ID_VALUE><x>)   


 %ds_wide(dsin=CLASS(firstobs=2 obs=4), dsout=WANT1, by_vars=SEX, colname_id_vars=AGE)                                    
                                                                                                                          
 %ds_wide(dsin=CLASS(where=(AGE=11)), dsout=WANT2, by_vars=SEX DATE, colname_id_vars=AGE, tr_auto=N, sort=Y)              

 %ds_wide(dsin=CLASS(where=(AGE=11)), dsout=WANT3, by_vars=AGE, colname_id_vars=SEX DATE, colname_id_fmt=$1. date5.       
                    ,tr_vars=WEIGHT NAME, colname_order=v, colname_id_order=a, sort=Y)                                    
                                                                                                                          
 %ds_wide(dsin=CLASS(where=(AGE=11)), dsout=WANT3, by_vars=AGE, colname_id_vars=SEX DATE, colname_id_fmt=$1. date5.       
       ,tr_vars=WEIGHT NAME, colname_order=i, colname_id_order=d, sort=Y, colname_form=<><ID_VALUE><><VAR_NAME><x>)       

 data VAL; do AGE=12,15,14; output; end; run;
 %ds_wide(dsin=CLASS, dsout=WANT3, by_vars=SEX DATE, colname_id_vars=AGE , colname_id_table=VAL                           
                    ,tr_vars=WEIGHT , colname_order=i, colname_id_order=d, sort=Y, colname_form=<><ID_VALUE><><NONE><>)   

*/

 

 

 

 

 

@ChrisNZ: I'll have to test your code, but you're always welcome to improve any of my code.

 

The three reasons I publish papers are: (1) to provide others with a way to do things either faster or better than they can with existing SAS procs; (2) to encourage SAS developers to include additional capabilities in procs; and (3) to give others a base to improve upon the concepts.

 

I'm publishing two new papers at SGF this year, one dealing with making a wide file either long or less wide (i.e., untranspose), and the other incorporating a number of capabilities (regarding exporting to Excel) that I wish were available with PROC EXPORT. You're welcome to improve on either of those, as well as any of the SAS related papers I've published (see: http://www.sascommunity.org/wiki/Presentations:Art297_Papers_and_Presentations).

 

Art, CEO, AnalystFinder.com

 

All the bleeps make the posted code unusable...apparently **bleep** as a shortened form of Richard is forbidden.  Use the download instead. 

@tomrvincent: I copied @ChrisNZ's macro to notepad, then copied it from there to SAS. Didn't run into the problem you mentioned but, agree, that posting code in the 'insert code' box makes it easier.

 

@ChrisNZ: The two macros run at around the same speed. I compared them on a 3.5 million record data set.

I especially liked the concept of your colname_order parameter, but it needs some modification so that it works as intended. As is, it didn't output the results in the desired order.

 

I didn't like it that your macro converted the ID names to upper case, but that should be easy to fix.

 

Another thing I didn't like in your revision was your changing parameter names that have equivalents in PROC TRANSPOSE. When I'm mimicking a SAS proc, I try to make the option and parameter names as consistent as possible in order to lessen the learning curve for those already familiar with the proc.

 

Here is the code I ran:

data have (drop=months);
  format idnum 8.;
  informat date date9.;
  format date date9.;
  input date ind1-ind4 ;
  other=2;
  do idnum=1 to 1000000;
    date="31dec2010"d;
    do months=3 to 12 by 3;
      date=intnx('month',date,3);
      if not(months eq 9 and mod(idnum,2)) then output;
    end;
  end;
  cards;
01dec2010 1 2 3 4
;

%ds_wide(dsin=have, dsout=WANT1, by_vars=idnum, colname_id_vars=date ,                          
                    tr_vars=ind1-ind4 , colname_order=VAR_NAME*ID_VALUE,
                    colname_id_fmt=qtr1.,
                    colname_form=<><VAR_NAME><_Qtr><ID_VALUE><>) 

%transpose(data=have, out=want, by=idnum, id=date,
 format=qtr1., delimiter=_Qtr, var=ind1-ind4)

Art, CEO, AnalystFinder.com

 

@art297

 

I was referring to the examples.  The macro compiles just fine, but some of the examples have Tom, D i c k, and Harry...which the censor converts to:

 

data order;
  informat name $5.;
  format name $5.;
  input name order;
  cards;
Tom   1
**bleep**  2
Harry 3
;

 🙂 I guess I'm the only one who tried to run the examples from the original post! 🙂

@tomrvincent @art297 ah, the smut filter.  Next time we meet in person I can show you the list of words that it detects/converts.  It's enough to make any middle-schooler giggle.  

@tomrvincent: Ah, you're talking about my macro. That's the first paper I published on the community and had no idea that there was a smut filter. I just edited the file and changed %d %i %c %k to Richard

 

@ChrisHemedinger: I'd appreciate your sending those to me in the event we don't ever get to meet again in person. I had no idea there was such a filter in the background.

 

Art, CEO, AnalystFinder.com

 

It's fun to do a search for bleep and see where else it has struck.  One is a post that seems to be partially in Dutch, I think...don't know what it censored.  Some are people just posting 'oh, poop' or 'gosh darn it'...some are other old American fogies like me that use that 'Tom-Richard-Harry' construct. 🙂

I just did that search and interested how few results were found. One I have to test: rectum (i.e., %r %e %c tum) as I presume that is the word that was used in the test. Wonder why that is on the list (assuming that was the word).

 

Nope! Guess they used some other word.

 

here's the one I found that looks like Dutch...don't know if it was a naughty English word or a naughty Dutch word.

 

 

https://communities.sas.com/t5/Base-SAS-Programming/put-infile-data-into-a-sas-dataset/m-p/425750/hi...

 

 

merde  

 

Okay, now I know it doesn't censor French. 🙂

 

 

This is getting interesting! I did a search for the address shown in that post and it was from Denmark. The text of the address read:

**bleep**otvej

 

If the spam filter blocks it, I'll repost with the link to the site where I found it.

 

Art, CEO, AnalystFinder.com

 

@tomrvincent: Success! The post you pointed to included what looked like coordinates, so I check them with Google Maps.

 

Interestingly it brought me to the Herlev neighborhood of Copenhagen.

 

There I found a street spelled  %f %a %g %o %t %v %e %j without the percents. When I edited my last post to include that name I got the newfound bleep insertion.

 

@ChrisHemedinger: Seriously?

 

Finally, the following is one more test to see if the spam checker only looks at prefixes:

 

**bleep**oting, serfage, leafage and wharfage. All four contain %f %a and %g .. just curious!

 

so what about maku**bleep**a or Adamnan or association or ambassadors or a**bleep**ori or o**bleep**aoshi or **bleep**atedashinage or **bleep**epoke?

 

Interesting...I guess a SAS programming sumo wrestler who raised herons would be frustrated. 🙂

@art297

> The two macros run at around the same speed.

Yes the speeds should be similar, except if you for sort and have data set options and I combine these.

 

> I didn't like it that your macro converted the ID names to upper case, but that should be easy to fix.

 Indeed

 

> Another thing I didn't like in your revision was your changing parameter names that have equivalents in PROC TRANSPOSE.

That's easy to change as well. I prefer to have meaningful and coherent parameter names. Likewise for the name of the macro.

There is no right or wrong. With so many options for customisation, I aimed for self-explanatory and consistent parameter names.

 

> I especially liked the concept of your colname_order parameter, but it needs some modification so that it works as intended. As is, it didn't output the results in the desired order.

Yes I struggled with the requirement to support variable list syntax *and* keep transposed variable order as given by the user.

 

Updating this section of the macro makes this behaviour much closer to what I expect.

  %*Populate TR_VARS parameter in case it is empty;
  %if ^%length(&tr_vars.) %then %do;
    data _&random._TRPOS_VAR1; set &libin..&dsin.( %unquote(&dsinopt) ) ; stop; run;
    proc contents data=_&random._TRPOS_VAR1 (drop=&by_vars. &colname_id_vars. &copy_vars. ) noprint out=_&random._TRPOS_VAR2;
    proc sql noprint;
      select upcase(NAME) into :tr_vars separated by ' ' from _&random._TRPOS_VAR2 
        %if "&tr_auto" eq "C" %then where TYPE=2;
        %if "&tr_auto" eq "N" %then where TYPE=1;
      ;
    quit;
  %end;
  %* Expand the TR_VARS variable names in case variable list syntax is used, while keeping desired order;
  %else %do;
    %let tr_vars=%sysfunc(prxchange(s/( *(-+) *)/$2/,-1,&tr_vars.)); %*Remove spaces around dashes;
    data _&random._TRPOS_TR1;
      %do i= 1 %to %sysfunc(countw(&tr_vars.,%str( )));
        if 0 then set &libin..&dsin.(keep=%scan(&tr_vars.,&i.,%str( )));
      %end;
      stop;
    run;
    proc contents data=_&random._TRPOS_TR1 noprint out=_&random._TRPOS_TR2;
    proc sql noprint;
      select upcase(NAME) into :tr_vars separated by " " from _&random._TRPOS_TR2 order by VARNUM;
    quit;           
  %end;
  %if ^%length(&tr_vars.) %then %do; %let msg=No variables to transpose.; %goto bye; %end;
  %if %sysfunc(countw(&tr_vars.))>1 & %index(&colname_form.,NONE) %then %do; 
     %let msg=Only one variable can be transposed when parameter COLNAME_FORM includes NONE.; %goto bye; %end;

Using your data and the modiified code above:

 

%ds_wide(dsin=have, dsout=WANT1, by_vars=idnum, colname_id_vars=date ,                          
                    tr_vars=ind4 ind1-ind3 , colname_order=VAR_NAME*ID_VALUE,
                    colname_id_fmt=qtr1.,
                    colname_form=<><VAR_NAME><_Qtr><ID_VALUE><>)

%ds_wide(dsin=have, dsout=WANT2, by_vars=idnum, colname_id_vars=date ,                          
                    tr_vars=ind4 ind1-ind3 , colname_order=ID_VALUE*VAR_NAME,
                    colname_id_fmt=qtr1.,
                    colname_form=<><VAR_NAME><_Qtr><ID_VALUE><>)

 

 

Obs idnum ind4_QTR1 ind4_QTR2 ind4_QTR3 ind4_QTR4 ind1_QTR1 ind1_QTR2 ind1_QTR3 ind1_QTR4 ind2_QTR1 ind2_QTR2 ind2_QTR3 ind2_QTR4 ind3_QTR1 ind3_QTR2 ind3_QTR3 ind3_QTR4
1 1 4 4   4 1 1   1 2 2   2 3 3   3

 



Obs idnum ind4_QTR1 ind1_QTR1 ind2_QTR1 ind3_QTR1 ind4_QTR2 ind1_QTR2 ind2_QTR2 ind3_QTR2 ind4_QTR3 ind1_QTR3 ind2_QTR3 ind3_QTR3 ind4_QTR4 ind1_QTR4 ind2_QTR4 ind3_QTR4
1 1 4 1 2 3 4 1 2 3         4 1 2 3

 

 

 

 

 

@ChrisNZ: Yes, that appears to correct the ordering!

 

Would the following change have any adverse effect on the rest of your code?:

  %let colname_form    =%sysfunc(putc(%sysfunc(prxchange(s/[^a-zA-Z0-9_<>]//  ,-1,%superq(colname_form     ))) ,$65. ));

/*instead of*/

%*  %let colname_form    =%sysfunc(putc(%sysfunc(prxchange(s/[^a-zA-Z0-9_<>]//  ,-1,%superq(colname_form     ))) ,$upcase65. ));

The change kept the delimiter from being switched to upper case, but I don't know if your code requires any of the items in that list to be in upper case. Does it?

 

Regarding speed, I did a test that included a dataset option and a sort. Using a 7 million record file, DS_wide took 3.42 seconds and transpose took 3.45 seconds. I'd say those are quite comparable.

 

Art, CEO, AnalystFinder.com

 

 

 

@art297 Yes changing this line will do what you want.

 

Also replace these 5 lines as below and all will work as expected (the second and fourth values must be uppercased).

  %let colname_prefix =%scan(%sysfunc(prxchange(s/(<.*?>)(<.*?>)(<.*?>)(<.*?>)(<.*?>)/$1/    ,1,&colname_form)),1,<>) ; 
  %let colname_part1  =%scan(%sysfunc(prxchange(s/(<.*?>)(<.*?>)(<.*?>)(<.*?>)(<.*?>)/\U$2\E/,1,&colname_form)),1,<>) ; 
  %let colname_sep    =%scan(%sysfunc(prxchange(s/(<.*?>)(<.*?>)(<.*?>)(<.*?>)(<.*?>)/$3/    ,1,&colname_form)),1,<>) ; 
  %let colname_part2  =%scan(%sysfunc(prxchange(s/(<.*?>)(<.*?>)(<.*?>)(<.*?>)(<.*?>)/\U$4\E/,1,&colname_form)),1,<>) ; 
  %let colname_suffix =%scan(%sysfunc(prxchange(s/(<.*?>)(<.*?>)(<.*?>)(<.*?>)(<.*?>)/$5/    ,1,&colname_form)),1,<>) ; 

 

idnum ind4_Qtr1 ind4_Qtr2 ind4_Qtr3 ind4_Qtr4 ind1_Qtr1 ind1_Qtr2 ind1_Qtr3 ind1_Qtr4 ind2_Qtr1 ind2_Qtr2 ind2_Qtr3 ind2_Qtr4 ind3_Qtr1 ind3_Qtr2 ind3_Qtr3 ind3_Qtr4
1 4 4   4 1 1   1 2 2   2 3 3   3

 

As for speed. I would have expected visible gains by suppressing steps, but I didn't benchmark, and your test seems to show that there is nothing indeed.

 

 

 

 

@tomrvincent @art297 Forget my allusion to middle-school boys.  I think we have found our smut filter target audience.  I'm glad that it's provided so much entertainment 🙂

@ChrisHemedinger  Hey, I've kept the same interest/entertainment levels since I was 12....if it has poop/boogers/robots/monsters/spaceships/superheroes in it, I'm there. 🙂

Version history
Last update:
‎03-23-2018 01:31 PM
Updated by:
Contributors

sas-innovate-2024.png

Join us for SAS Innovate April 16-19 at the Aria in Las Vegas. Bring the team and save big with our group pricing for a limited time only.

Pre-conference courses and tutorials are filling up fast and are always a sellout. Register today to reserve your seat.

 

Register now!

Free course: Data Literacy Essentials

Data Literacy is for all, even absolute beginners. Jump on board with this free e-learning  and boost your career prospects.

Get Started

Article Tags