This page was created by the IDL library routine mk_html_help2.

Last modified: Thu Aug 6 12:53:14 2020.


Directory Listing of Routines


Routine Descriptions

SPD_CDAWLIB

[Next Routine] [List of Routines]
 NAME:
 spd_cdawlib

 PURPOSE:
 This procedure compiles all the files in this directory.
 These files were adapted (forked) from NASA's CDAWLib.
 They are needed by spdfCdawebChooser and spd_ui_spdfcdawebchooser.
 

 MODIFICATION HISTORY:

$LastChangedBy: nikos $
$LastChangedDate: 2018-02-25 14:58:49 -0800 (Sun, 25 Feb 2018) $
$LastChangedRevision: 24774 $
$URL: svn+ssh://thmsvn@ambrosia.ssl.berkeley.edu/repos/spdsoft/tags/spedas_4_0/external/spdfcdas/spd_cdawlib/spd_cdawlib.pro $

(See external/spdfcdas/spd_cdawlib/spd_cdawlib.pro)


SPD_CDAWLIB_BREAK_MYSTRING

[Previous Routine] [Next Routine] [List of Routines]
 NAME: BREAK_MYSTRING
 PURPOSE: 
       Convert a string into a string array given a delimiting character 
 CALLING SEQUENCE:
       out = break_mystring(instring)
 INPUTS:
       instring = input text string
 KEYWORD PARAMETERS:
       delimiter = character to parse by.  Default = ' '
 OUTPUTS:
       out = string array
 AUTHOR:
       Jason Mathews, NASA/GSFC/Code 633,  June, 1994
       mathews@nssdc.gsfc.nasa.gov    (301)286-6879
 MODIFICATION HISTORY:

Copyright 1996-2013 United States Government as represented by the 
Administrator of the National Aeronautics and Space Administration. 
All Rights Reserved.

(See external/spdfcdas/spd_cdawlib/spd_cdawlib_break_mystring.pro)


SPD_CDAWLIB_LIST_MYSTRUCT[1]

[Previous Routine] [Next Routine] [List of Routines]
 NAME:	spd_cdawlib_ffo_string - substitute for string()

 PURPOSE: allows override of free format I/O specifications 

 INPUT: format - a format specification, value - a value to be string'ed

 Examples: newstring = spd_cdawlib_ffo_string( 'F10.2', 354.9985 )
           newstring = spd_cdawlib_ffo_string( struct.format, struct.dat )

 NOTE: this function wraps the format string in parenthesis

 original version - JWJ 08/08/2000

UNCTION spd_cdawlib_ffo_string, format, value

 ; First, if format is defined, just use it against the value
 ; and return the result
 if strlen( format ) gt 0 then begin
   ; print, 'spd_cdawlib_ffo_string using given format: string( FORMAT = (' + format + '), value)'
   return, string( FORMAT = '(' + format + ')', value )
 endif

 ; Here's the original reason this function was developed.
 ; If the format is not defined and the data type
 ; is FLOAT, use F13.6 instead of the IDL 5.2 free format 
 ; specifier of G13.6 which is causes us particular problems
 if size( value, /type ) eq 4 then begin
   ; print, 'spd_cdawlib_ffo_string overriding free format for FLOAT type: string( FORMAT = (F13.6), value)'
   return, string( FORMAT = '(F13.6)', value )
 endif

 ; At last, if no particular rules were met for overriding the
 ; format specifcation, use the free format I/O
 ; print, 'spd_cdawlib_ffo_string doing free format I/O: string( value )'
 return, string( value )

nd ; spd_cdawlib_ffo_string

(See external/spdfcdas/spd_cdawlib/spd_cdawlib_list_mystruct.pro)


SPD_CDAWLIB_LIST_MYSTRUCT[2]

[Previous Routine] [Next Routine] [List of Routines]
 NAME: spd_cdawlib_delete.pro

 PURPOSE: Frees memory

 INPUT;  var   - any variable

RO spd_cdawlib_delete, var

    ptr=PTR_NEW(var)
   PTR_FREE, ptr
ar = 0B

nd

(See external/spdfcdas/spd_cdawlib/spd_cdawlib_list_mystruct.pro)


SPD_CDAWLIB_LIST_MYSTRUCT[2]

[Previous Routine] [Next Routine] [List of Routines]
 NAME: spd_cdawlib_reform_strc.pro

 PURPOSE: Reforms the data array from a (1,N) to a (N).

 astrc    -  Input structure

UNCTION spd_cdawlib_reform_strc, astrc
str=0
amest=tag_names(astrc)
s_tags=n_tags(astrc)

or k=0, ns_tags-1 do begin
  tagname=namest[k]
  names=tag_names(astrc.(k))
  ntags=n_tags(astrc.(k))
  mc=where((names eq 'VAR_NOTES'),nc)
  for j=0, ntags-1 do begin
     if(names[j] eq 'DAT') then begin
        asize=size(astrc.(k).dat)
        if(asize[0] gt 0) then newdata=reform(astrc.(k).dat) else $
                             newdata=astrc.(k).dat
        tempa=create_struct('DAT',newdata)
        tempb=create_struct(tempb,tempa)
     endif else begin
        str_p=astrc.(k).(j)
        if(j eq 0) then begin
           tempb=create_struct(names[j],str_p)
        endif else begin
           tempa=create_struct(names[j],str_p)
           tempb=create_struct(tempb,tempa)
        endelse
     endelse
  endfor  ; end j
  ; Add VAR_NOTES to each variable that does not have this attribute
  if(mc[0] lt 0) then begin
     tempa=create_struct('VAR_NOTES','')
     tempb=create_struct(tempb,tempa)
  endif
  ; Add each variable to the overall structure
  if(istr eq 0) then begin
     temp2=create_struct(namest[k],tempb)
     b=create_struct(temp2)
  endif else begin
     temp2=create_struct(namest[k],tempb)
     b=create_struct(b,temp2)
  endelse
  istr=istr+1
ndfor    ; end k

 Free Memory
pd_cdawlib_delete, tempa
pd_cdawlib_delete, tempb
pd_cdawlib_delete, temp2

eturn, b
nd

12/13/2006 - TJK moved parse_mydepend0 out of this file to its own
file (w/ same name so that it can be called by spd_cdawlib_read_mycdf.pro


(See external/spdfcdas/spd_cdawlib/spd_cdawlib_list_mystruct.pro)


SPD_CDAWLIB_LIST_MYSTRUCT[3]

[Previous Routine] [Next Routine] [List of Routines]
 NAME: spd_cdawlib_reform_mystruct.pro

 PURPOSE: Reforms the data array from a (i,j,k) to a (i*j,k) and (i,j,k,l) to a (i*j*k,l)

 astrc    -  Input structure

UNCTION spd_cdawlib_reform_mystruct, astrc

 CATCH, err
 IF err NE 0 THEN BEGIN
   CATCH, /CANCEL
   PRINT, !ERROR_STATE.MSG
   RETURN,-1
 ENDIF


str=0
amest=tag_names(astrc)
s_tags=n_tags(astrc)

or k=0, ns_tags-1 do begin
  sz=size(astrc.(k).dat)
  names=tag_names(astrc.(k))
  ntags=n_tags(astrc.(k))
  ;
  ;
  case sz[0] of
    3: begin
     tagname=namest[k]
     newsz=sz(1)*sz(2)
     newdata=reform(astrc.(k).dat,newsz,sz(3))
     astrc.(k).var_notes='ListImage'
     for j=0, ntags-1 do begin
        if(names[j] eq 'DAT') then begin
           tempa=create_struct('DAT',newdata)
           tempb=create_struct(tempb,tempa)
        endif else begin
           str_p=astrc.(tagname).(j)
           if(j eq 0) then begin
              tempb=create_struct(names[j],str_p)
           endif else begin
              tempa=create_struct(names[j],str_p)
              tempb=create_struct(tempb,tempa)
           endelse
        endelse
     endfor   ; end j
     temp2=create_struct(namest[k],tempb)
     b=create_struct(b,temp2)
    end
    4: begin
     tagname=namest[k]
     newsz=sz(1)*sz(2)*sz(3)
     newdata=reform(astrc.(k).dat,newsz,sz(4))
     astrc.(k).var_notes='ListImage3D'
     for j=0, ntags-1 do begin
        if(names[j] eq 'DAT') then begin
           tempa=create_struct('DAT',newdata)
           tempb=create_struct(tempb,tempa)
        endif else begin
           str_p=astrc.(tagname).(j)
           if(j eq 0) then begin
              tempb=create_struct(names[j],str_p)
           endif else begin
              tempa=create_struct(names[j],str_p)
              tempb=create_struct(tempb,tempa)
           endelse
        endelse
     endfor   ; end j
     temp2=create_struct(namest[k],tempb)
     b=create_struct(b,temp2)
     ;
    end
    else: begin
     if(istr eq 0) then begin
        b=create_struct(namest[k],astrc.(k))
     endif else begin
        temp=create_struct(namest[k],astrc.(k))
        b=create_struct(b,temp)
     endelse
    end
  endcase 
  istr=istr+1
ndfor

 Free Memory
pd_cdawlib_delete, tempa
pd_cdawlib_delete, tempb
pd_cdawlib_delete, temp

eturn, b
nd

(See external/spdfcdas/spd_cdawlib/spd_cdawlib_list_mystruct.pro)


SPD_CDAWLIB_LIST_MYSTRUCT[4]

[Previous Routine] [Next Routine] [List of Routines]
 NAME: spd_cdawlib_ord_mystruct.pro

 PURPOSE: Reorders the given structure so that the dimension of the data 
          variables is increasing w/ each entry. 

   astrc  -  Input structure
   vorder -  An array of the dimension of each variable in the structure

  RCJ 04/24/2008 Before the structure is reordered,
      look for vars w/ uncertainties associated w/ them, create
      and index and reorder the structure according to this index. 
      This will make var and uncertainty be listed side by side. 

UNCTION spd_cdawlib_ord_mystruct, astrc, vorder, is

len=n_elements(vorder)
max=max(vorder)
str=0
ames=tag_names(astrc)

 RCJ 04/24/2008
 Reorder names so that uncertainties go right next to their respective vars.
 Note: astrc is not being reordered!  only names!  So we also need 'order'

names=[names[0]]  ; Start w/ Epoch.
rder=0            ; Position of Epoch in astrc
or i=1,n_elements(names)-1 do begin
  q=where(nnames eq names[i])
  if q[0] eq -1 then begin  ;  Avoid repeating vars already listed
     nnames=[nnames,names[i]]
     q=where(names eq names[i])
     order=[order,q[0]]
     qq=where(tag_names(astrc.(i)) eq 'DELTA_PLUS_VAR')
     qqq=where(tag_names(astrc.(i)) eq 'DELTA_MINUS_VAR')
     if qq[0] ne -1 and qqq[0] ne -1 then begin
        if astrc.(i).delta_plus_var ne '' then begin
           q=where(names eq strupcase(astrc.(i).delta_plus_var))
    qq=where(nnames eq strupcase(astrc.(i).delta_plus_var))
    ;if q[0] ne -1 then begin  ; if, for whatever reason, this var is not
    if (q[0] ne -1 and qq[0] eq -1) then begin  ; if, for whatever reason, this var is not
       ;  included in the input structure, then skip it; or if it's already
       ; in nnames due to another var
              nnames=[nnames,strupcase(astrc.(i).delta_plus_var)]
              order=[order,q[0]]
    endif
        endif
        if astrc.(i).delta_minus_var ne '' and $
           astrc.(i).delta_minus_var ne astrc.(i).delta_plus_var then begin
           q=where(names eq strupcase(astrc.(i).delta_minus_var))
    qq=where(nnames eq strupcase(astrc.(i).delta_minus_var))
           ;if  q[0] ne -1 then begin  ; if, for whatever reason, this var is not
           if (q[0] ne -1 and qq[0] eq -1) then begin  ; if, for whatever reason, this var is not
       ;  included in the input structure, then skip it; or if it's already
       ; in nnames due to another var
       nnames=[nnames,strupcase(astrc.(i).delta_minus_var)]
              order=[order,q[0]]
    endif  
        endif
     endif
  endif      
ndfor

   Need to reorder vorder:
order=vorder(order)
 RCJ 07/10/2013  RBSP test revealed that 'names' should be ordered too:
ames=names(order)

or k=is, vmax do begin
  for i=0, vlen-1  do begin
     if(vorder[i] eq k) then begin
        if(istr eq 0) then begin
           bnew=create_struct(names[i],astrc.(i))
        endif else begin
           temp=create_struct(names[i],astrc.(order[i]))
           bnew=create_struct(bnew,temp)
        endelse
        istr=istr+1
     endif
  endfor   ; end i
ndfor   ; end k

 Free Memeory
pd_cdawlib_delete, temp

eturn, bnew
nd

(See external/spdfcdas/spd_cdawlib/spd_cdawlib_list_mystruct.pro)


SPD_CDAWLIB_LIST_MYSTRUCT[5]

[Previous Routine] [Next Routine] [List of Routines]
 NAME: spd_cdawlib_wrt_hybd_strct.pro

 PURPOSE: Prints ascii file of RV or NRV variables

UNCTION spd_cdawlib_wrt_hybd_strct, a, unit, convar, maxrecs, depend0, mega_num  

 Establish error handler
atch, error_status
f(error_status ne 0) then begin
  if(error_status eq -96) then $ 
         print, 'STATUS= This amount of data cannot be listed, please request a shorter time range' 
  if(error_status eq -133) then $ 
         print, 'STATUS= Incompatible variable types. Select variables separately' 
  if(error_status eq -124) then $ 
         print, 'STATUS= Temporary memory error. Please try again.'
  if(error_status eq -350) then $ ;  format has too many elements
         print, 'STATUS= Please select fewer variables.' $
         else print, 'STATUS= Data cannot be listed'
  print, 'ERROR=Error number: ',error_status,' in listing (spd_cdawlib_wrt_hybd_strct).'
  print, 'ERROR=Error Message: ', !ERR_STRING
  return, -1 
ndif

tatus=0
ames=strupcase(tag_names(a))
tags=n_tags(a)
lnk='# '


print,'convar = ',convar
ase convar of
  0 : begin
      ; Check MAXRECS
      if(n_elements(num_data) eq 0) then num_data=0 
      num_data=num_data+ntags
      if(num_data gt maxrecs) then begin
         dif_rec=num_data-maxrecs 
         text='# The maximum number of records allowed to be listed is '
         text1='# Your request has exceeded this maximum by '
         text2='# WARNING: Maxrecs exceeded in Global Attributes; No. Recs. = '
         printf, unit,text,maxrecs
         printf, unit, format='(a,i)',text1,dif_rec
         printf, unit, format='(a)',blnk
         status=1
      endif
      printf, unit, format='("#",14x,"************************************")'
      printf, unit, format='("#",14x,"*****    GLOBAL ATTRIBUTES    ******")'
      printf, unit, format='("#",14x,"************************************")'
      printf, unit, format='("#",14x)'
      for i=0L, ntags-1 do begin
         ;  RCJ 03/18/2014  Space below is arbitrarily defined so each global attr name will fit in that
  ;       space, and could be chopped if too long.
  ;       Needs to be increased if we find longer global attr name. You might need to make changes to spd_cdawlib_ex_prt too.
         ;var='                    '
         var='                              '
         var1=strtrim(names[i],2)
         strput,var,var1,0
         tstsz=size(a.(i))
         if(tstsz[0] eq 0) then begin
            var2=strtrim(a.(i),2)
     ; RCJ 03/18/2014  Clean var2 from carriage-returns, replace w/ blank space:
     var2=strjoin(strsplit(var2,string(10B),/extract),' ')
            slen=strlen(var2)
     ;print,'var2 = ',var2
     ;print,'slen = ',slen
            if(slen gt 80) then begin
               status=spd_cdawlib_ex_prt(unit,var,var2,slen,0) 
            endif else begin
               ;printf, unit, format='("#",5x,a,5x,a)', var, var2
               printf, unit, format='("#",5x,a,2x,a)', var, var2
            endelse
         endif else begin

            for k=0L, tstsz(1)-1 do begin
               var2=strtrim(a.(i)[k])
               slen=strlen(var2)
               if(slen gt 80) then begin
                  status=spd_cdawlib_ex_prt(unit,var,var2,slen,k) 
               endif else begin
                  if(k eq 0) then begin
                     ;printf, unit, format='("#",5x,a,5x,a)', var, var2
                     printf, unit, format='("#",5x,a,2x,a)', var, var2
                  endif else begin
                     ;printf, unit, format='("#",30x,a)', var2
                     printf, unit, format='("#",37x,a)', var2
                  endelse
               endelse
            endfor   ; end k
         endelse
      endfor   ; end i
      ;
      if(num_data gt maxrecs) then begin                                       
         dif_rec=num_data-maxrecs
         text='# The maximum number of records allowed to be listed is '
         text1='# Your request has exceeded this maximum by '
         text2='# WARNING: Maxrecs exceeded in Global Attributes; No. Recs. = '
         printf, unit, format='(a)',blnk
         printf, unit, text,maxrecs
         printf, unit, format='(a,i)',text1,dif_rec
         status=1
      endif
      ;
      printf, unit, format='("#",14x)'   ;'(15x)'
      if mega_num gt 1 then printf, unit,'# **************************************************************************************'
      if mega_num gt 1 then printf, unit,'# *********    There is more than one Epoch for the variables selected    **************'
      if mega_num gt 1 then printf, unit,'# *********    Please scroll down                                         **************'
      if mega_num gt 1 then printf, unit,'# **************************************************************************************'
      if mega_num gt 1 then printf, unit, format='("#",14x)'    ;'(15x)'
  end  ; end case 0
  ;
  ; Record Varying Variables 
  ;
  1 : begin

      ; Check MAXRECS
      if(n_elements(num_data) eq 0) then num_data=0
      ; Put in appropriate record count
      len=size(a.(0).dat)
      length=len(len[0]+2)
      num_data=length
      ; Check for maxrecs begin exceeded
      num_data=num_data+4
      if(num_data gt maxrecs) then begin
         dif_rec=num_data-maxrecs
         text='# The maximum number of records allowed to be listed is '
         text1='# Your request has exceeded this maximum by '
         printf, unit, text,maxrecs
         printf, unit, format='(a,i6)',text1,dif_rec
         printf, unit, format='(a)',blnk
         status=1
         length=maxrecs
      endif
      status=spd_cdawlib_list_header(a,unit,ntags)
      ;labels=strarr(ntags-3)
      ;units=strarr(ntags-3) 
      ; RCJ 05/12/2009   Append strings to 'labels' and 'units' instead of presetting the array sizes.
      ; Note that this first value is cut off the array after the array is populated. 
      labels=''
      units='' 
      ;
      inc=0
      for i=0L, ntags-5 do begin
         ;if (a.(i).var_type eq 'data') or (a.(i).var_type eq 'support_data') then begin
         if (a.(i).var_type eq 'data') or ((a.(i).var_type eq 'support_data') and (a.(i).cdfrecvary ne 'NOVARY')) then begin
            nvar=a.(i).fillval
            ;labels(i)=spd_cdawlib_label_search(a,1,i,0)
     labels=[labels,spd_cdawlib_label_search(a,1,i,0)]
            ;units(i)=a.(i).units
            ;units(i)=spd_cdawlib_unit_search(a,1,i,0)
     units=[units,spd_cdawlib_unit_search(a,1,i,0)]
            ; if 'EPOCH' or 'EPOCH92' etc.
            if(names[i] eq depend0) then begin
               temp=create_struct(names[i],a.(i).dateph[0])
            endif else begin
               if(nvar eq 0) then begin
                  temp=create_struct(names[i],a.(i).dat[0]) 
               endif else begin
                  temp=create_struct(names[i],a.(i).dat[0:nvar]) 
               endelse
            endelse
            if(inc eq 0) then begin
               b=temp
            endif else begin
               b=create_struct(b,temp)
            endelse
     inc=inc+1
  endif   
      endfor   ; end i
      labels=labels[1:*]
      units=units[1:*]
      ; Free Memory
      spd_cdawlib_delete, temp
      printf,unit,format=a.lform,labels
      printf,unit,format=a.uform,units   ;  if too many vars are requested, a.uform could be too long for idl and an error is generated.
      ;
      for j=0L, length-1 do begin
         inc=0
         for i=0L,ntags-5 do begin
            ;if (a.(i).var_type eq 'data') or (a.(i).var_type eq 'support_data') then begin
            if (a.(i).var_type eq 'data') or ((a.(i).var_type eq 'support_data') and (a.(i).cdfrecvary ne 'NOVARY')) then begin
               ; temporary patch until nvar included as a new variable attribute
               nvar=a.(i).fillval[0]
               ;nvar=nvar(0)
               ; if(names(i) eq 'EPOCH' or names(i) eq 'EPOCH92') then begin
               if(names[i] eq depend0) then begin
                  b.(inc)=a.(i).dateph[j]
	   inc=inc+1
               endif else begin
                  if(nvar eq 0) then begin
                     b.(inc)=a.(i).dat[j] 
                  endif else begin
                     b.(inc)=a.(i).dat[0:nvar]
                  endelse
	   inc=inc+1
               endelse
            endif		
         endfor   ; end i
         printf,unit,format=a.dform,b 
      endfor   ; end j   
      if(num_data gt maxrecs) then begin
         dif_rec=num_data-maxrecs
         text='The maximum number of records allowed to be listed is '
         text1='Your request has exceeded this maximum by '
         printf, unit, format='(a)',blnk
         printf, unit, text,maxrecs
         printf, unit, format='(a,i6)',text1,dif_rec
         status=1                                  
      endif
      ; Free Memory
      spd_cdawlib_delete, b
  end   ; end case 1
  ; 
  ; Non-Record Varying Variables 
  ;
  2 : begin
      ; Check MAXRECS
      if(n_elements(num_data) eq 0) then num_data=0
      ; Put in appropriate record count
      num_data=num_data+4    
      if(num_data gt maxrecs) then begin
         dif_rec=num_data-maxrecs
         text='The maximum number of records allowed to be listed is '
         text1='Your request has exceeded this maximum by '
         printf, unit, text,maxrecs
         printf, unit, format='(a,i6)',text1,dif_rec
         printf, unit, format='(a)',blnk
         status=1                                  
         length=maxrecs
      endif
      ;
      printf, unit, format='("#",14x,"************************************")'
      printf, unit, format='("#",14x,"**  NON-RECORD VARYING VARIABLES  **")'
      printf, unit, format='("#",14x,"************************************")'
      printf, unit, format='("#",14x)'
  end   ; end case 2
  ;
  ; 2-D Record Varying Variables 
  ;
  3 : begin
Put in a loop to determine the data sizes for each variable's data array
just once instead of doing this a million times below.  We can't
trust what's set in a.*.idlsize (at least for virtual variables)
      idlsizes = lonarr(ntags-4,10)
      for i = 0, ntags-5 do begin
          t_size = size(a.(i).dat)
          for j = 0, n_elements(t_size)-1 do begin
              idlsizes[i,j] = t_size[j]
          endfor
      endfor

      ; Check MAXRECS
      if(n_elements(num_data) eq 0) then num_data=0
      ; Put in appropriate record count
Use the computed sizes stored in idlsizes above
       len=size(a.(0).dat)
      len=idlsizes[0,*]
      length=len(len[0]+2)
      ; Check for maxrecs begin exceeded                 
      num_data=length
      num_data=num_data+4
      if(num_data gt maxrecs) then begin
         dif_rec=num_data-maxrecs
         text='# The maximum number of records allowed to be listed is '
         text1='# Your request has exceeded this maximum by '
         printf, unit, text,maxrecs
         printf, unit, format='(a,i6)',text1,dif_rec
         printf, unit, format='(a)',blnk
         status=1                                  
         length=maxrecs
      endif
      status=spd_cdawlib_list_header(a,unit,ntags)
      num=a.(0).fillval
      labels=strarr(num)
      units=strarr(num)
      dep1_values=''
      atags=tag_names(a)
      inc=0L 
      for i=0L, ntags-5 do begin
         ;if(a.(i).var_type eq 'data') or (a.(i).var_type eq 'support_data') then begin
         if (a.(i).var_type eq 'data') or ((a.(i).var_type eq 'support_data') and (a.(i).cdfrecvary ne 'NOVARY')) then begin
TJK replace w/ computed size above to improve performance
             st_sz=size(a.(i).dat)
             st_sz=idlsizes[i,*]
            if(st_sz[0] le 1) then begin
               ; Include condition where only 1 time selected w/ num_var 
               ;  length vector
               if(st_sz[0] eq 1 and st_sz[1] gt 1 and length eq 1) then begin
                  num_var=st_sz[1]
                  for k=0L, num_var-1 do begin
                     labels(inc)=spd_cdawlib_label_search(a,st_sz[0],i,k)
                     ;units(inc)=a.(i).units
	      units(inc)=spd_cdawlib_unit_search(a,st_sz[0],i,k)
                     ; temp=create_struct(labels(inc),a.(i).dat(k,0))
                     ; temp=create_struct(atags(i)+labels(inc),a.(i).dat(k,0))
	      unique = strtrim(string(inc), 2)
                     temp=create_struct(atags(i)+unique,a.(i).dat[k,0])
                     if(inc eq 0) then begin
                        b=temp
                     endif else begin
                        b=create_struct(b,temp)
                     endelse
                     inc=inc+1
                  endfor   ; end k
               endif else begin
                  ;print,'2', inc, size(labels)
                  labels(inc)=spd_cdawlib_label_search(a,st_sz[0],i,0)
	   ;print,'labels(inc) 1 = ',labels(inc)
                  ;units(inc)=a.(i).units
	   units(inc)=spd_cdawlib_unit_search(a,st_sz[0],i,0)
	   ;print,'units(inc) 1 = ',units(inc)
                  ; names(i) eq 'EPOCH' or 'EPOCH92' etc.
                  if(names(i) eq depend0) then begin
                     temp=create_struct(names(i),a.(i).dateph[0])
                  endif else begin
                     temp=create_struct(names(i),a.(i).dat[0])
                  endelse
                  if(inc eq 0) then begin
                     b=temp
                  endif else begin
                     b=create_struct(b,temp)
                  endelse
                  inc=inc+1
               endelse
            endif   ;  end st_sz[0] le 1
            ;
            if(st_sz[0] eq 2) then begin
               num_var=st_sz[1]
                  for k=0L, num_var-1 do begin
                     labels(inc)=spd_cdawlib_label_search(a,st_sz[0],i,k)
                     ;units(inc)=a.(i).units
	      units(inc)=spd_cdawlib_unit_search(a,st_sz[0],i,k)
                     ; temp=create_struct(labels(inc),a.(i).dat(k,0))
                     ;temp=create_struct(atags(i)+labels(inc),a.(i).dat(k,0))
	      unique = strtrim(string(inc), 2)
                     temp=create_struct(atags(i)+unique,a.(i).dat[k,0])
                     if(inc eq 0) then begin
                        b=temp
                     endif else begin
                        b=create_struct(b,temp)
	      endelse
	      ; RCJ 05/19/2003  Added the 'if endif else' above because
	      ; we got errors when inc=0: b was undefined.	 
                     ;b=create_struct(b,temp)
                     inc=inc+1
                  endfor
            endif   ; end if st_sz(0) eq 2
            dep1=spd_cdawlib_dependn_search(a,i,1)
            if (dep1[0] ne '') then begin
               depend1=a.(i).depend_1
               ; RCJ 05/16/2013  If alt_cdaweb_depend_1 exists, use it instead:
               q=where(tag_names(a.(i)) eq 'ALT_CDAWEB_DEPEND_1')
               if (q[0] ne -1) then if (a.(i).alt_cdaweb_depend_1 ne '') then depend1=a.(i).alt_cdaweb_depend_1
               dep1_units=a.(strtrim(depend1,2)).units
               dep1=['(@_'+dep1+'_'+dep1_units+')']
            endif   
            dep1_values=[dep1_values,dep1]
         endif   ; end a.(i).var_type
      endfor   ; end i
      ; Free Memory
      spd_cdawlib_delete, temp
      ;
      printf,unit,format=a.lform,labels
      ; listing depend_1 values if they exist. RCJ 04/01
      ;if (n_elements(dep1_values) gt 1) then begin
         dep1_values=dep1_values[1:*]
         q=where (dep1_values ne '') 
         if q[0] ne -1  then printf,unit,format=a.dpform,dep1_values
      ;endif 
      printf,unit,format=a.uform,units
      ;
do this computation once, instead of for each record
_ntags = ntags-5

      for j=0L, length-1 do begin
         inc=0L
         for i=0L,i_ntags do begin
            ;if(a.(i).var_type eq 'data') or (a.(i).var_type eq 'support_data') then begin
            if ((a.(i).var_type eq 'data') or (a.(i).var_type eq 'support_data') and (a.(i).cdfrecvary ne 'NOVARY'))  then begin
               ; 'EPOCH' or 'EPOCH92'
               if(names(i) eq depend0) then begin
                  b.(inc)=a.(i).dateph[j]
                  inc=inc+1
               endif else begin

TJK 8/24/2009 EXTREMEMLY poor performance 
                   st_sz=size(a.(i).dat)
instead, compute the sizes once above this big loop and reference 
the values here.  
                  st_sz = idlsizes[i,*]
                  if(st_sz[0] le 1) then begin
                    if(st_sz[0] eq 1 and st_sz[1] gt 1 and length eq 1) then begin
                        num_var=st_sz[1]
                        for k=0L,num_var-1 do begin
                           b.(inc)=a.(i).dat[k,j]
                           inc=inc+1
                        endfor
                     endif else begin
                        b.(inc)=a.(i).dat[j] 
                        inc=inc+1
                     endelse
                  endif   
                  if(st_sz[0] eq 2) then begin
                     num_var=st_sz[1]
	      ; RCJ 12/02/2003  Commented out this 'if num_var lt 20...'
	      ; It doesn't seem to make sense. Will test.
                     ;if(num_var lt 20) then begin
                        for k=0L,num_var-1 do begin
                           b.(inc)=a.(i).dat[k,j]
                           inc=inc+1
                        endfor
                     ;endif else begin
                        ;b.(inc)=a.(i).dat(*,j)
                        ;inc=inc+1  ; RTB added 1/21/99
                     ;endelse
                  endif
               endelse  ; end  (names(i) ne depend0)
            endif   ; end a.(i).var_type
         endfor   ; end i
         printf,unit,format=a.dform,b 
      endfor   ; end j
      ;
      if(num_data gt maxrecs) then begin
         dif_rec=num_data-maxrecs
         text='# The maximum number of records allowed to be listed is '
         text1='# Your request has exceeded this maximum by '
         printf, unit, format='(a)',blnk
         printf, unit, text,maxrecs
         printf, unit, format='(a,i6)',text1,dif_rec
         status=1                                  
         length=maxrecs
      endif
      ; Free Memory
      spd_cdawlib_delete, b
  end   ;   end case 3
  ;
  ; 3-D Record Varying Variables 
  ;
  4 : begin
      ; Check MAXRECS
      if(n_elements(num_data) eq 0) then num_data=0
      ; Put in appropriate record count
      len=size(a.(0).dat)
      length=len(len[0]+2)
      ; Check for maxrecs begin exceeded                 
      num_data=length
      num_data=num_data+4
      if(num_data gt maxrecs) then begin
         dif_rec=num_data-maxrecs
         text='# The maximum number of records allowed to be listed is '
         text1='# Your request has exceeded this maximum by '
         printf, unit, text,maxrecs
         printf, unit, format='(a,i6)',text1,dif_rec
         printf, unit, format='(a)',blnk
         ; printf, unit, ' '                                                     
         status=1                                  
         length=maxrecs
      endif
      ;
      printf, unit, format='("#",14x,"************************************")'
      printf, unit, format='("#",14x,"****  RECORD VARYING VARIABLES  ****")'
      printf, unit, format='("#",14x,"************************************")'
      printf, unit, format='("#",14x)'
      printf,unit, format='("# 1. ",a)', a.epoch.fieldnam
      printf,unit, format='("# 2. ",a)', a.index.catdesc
      printf,unit, format='("# 3. ",a)', a.qflag.catdesc
      printf,unit, format='("# 4. ",a)', a.position.fieldnam
      printf,unit, format='("# 5. ",a)', a.vel.fieldnam
      printf,unit,format='("#",14x)'
      ;
      num=7
      labels=strarr(num)
      units=strarr(num)
      inc=0
      ; Epoch
      eplabel='                       ' 
      strput,eplabel,a.epoch.fieldnam,0
      labels(inc)=eplabel
      units(inc)=a.epoch.units
      temp=create_struct('EPOCH',a.epoch.dateph[0])
      b=temp
      inc=inc+1
      ; Index     
      labels(inc)="Index" 
      units(inc)=''
      inc=inc+1
      ; Qflag
      labels(inc)=a.qflag.lablaxis
      units(inc)=a.qflag.units
      inc=inc+1
      ; Position     
      for k=0, 1 do begin
         if(k eq 0) then labels(inc)=" geo latitude"
         if(k eq 1) then labels(inc)="geo longitude"
         units(inc)=a.position.units
         inc=inc+1
      endfor
      for k=0, 1 do begin
         if(k eq 0) then labels(inc)=" geo east vel"
         if(k eq 1) then labels(inc)="geo north vel"
         units(inc)=a.vel.units
         inc=inc+1
      endfor
      ;
      farr=fltarr(180)
      in=0
      for l=0,29 do begin
         farr(in)=a.index.dat[0]
         in=in+1
         farr(in)=a.qflag.dat[l,0]
         in=in+1
         for k=0, 1 do begin
            farr(in)= a.position.dat[k,l,0]
            in=in+1
         endfor
         for k=0, 1 do begin
            farr(in)= a.vel.dat[k,l,0]
            in=in+1
         endfor
      endfor
      temp=create_struct('DATREC',farr)
      b=create_struct(b,temp)
      ;
      ; Free Memory
      spd_cdawlib_delete, temp 
      printf,unit,format=a.lform,labels
      printf,unit,format=a.uform,units
      ;
      for j=0L, length-1 do begin
         m=0
         b.epoch=a.epoch.dateph[j]
         for l=0,29 do begin
            b.datrec(m)=a.index.dat[l]
            m=m+1
            b.datrec(m)=a.qflag.dat[l,j]
            m=m+1
            for k=0,1 do begin
               b.datrec(m)=a.position.dat[k,l,j]
               m=m+1
            endfor
            for k=0,1 do begin
               b.datrec(m)=a.vel.dat[k,l,j]
               m=m+1
            endfor
         endfor   ; end l
         printf,unit,format=a.dform,b
      endfor   ; end j
      ;
      if(num_data gt maxrecs) then begin
         dif_rec=num_data-maxrecs
         text='# The maximum number of records allowed to be listed is '
         text1='# Your request has exceeded this maximum by '
         printf, unit, format='(a)',blnk
         printf, unit, text,maxrecs
         printf, unit, format='(a,i6)',text1,dif_rec
         status=1                                  
         length=maxrecs
      endif
      ; Free Memory
      spd_cdawlib_delete, b
  end   ;  end case 4
  ;
  ; Image Data and 3D data (only difference is 3D data will have depend_3)
  ;
  5: begin
      ; Check MAXRECS
      if(n_elements(num_data) eq 0) then num_data=0
      ; Put in appropriate record count
      len=size(a.(0).dat)
      length=len(len[0]+2)
      ; Check for maxrecs begin exceeded                 
      num_data=length
      num_data=num_data+4
      if(num_data gt maxrecs) then begin
         dif_rec=num_data-maxrecs
         text='# The maximum number of records allowed to be listed is '
         text1='# Your request has exceeded this maximum by '
         printf, unit, text,maxrecs
         printf, unit, format='(a,i6)',text1,dif_rec
         printf, unit, format='(a)',blnk
         ; printf, unit, ' '                                                     
         status=1                                  
         length=maxrecs
      endif
      status=spd_cdawlib_list_header(a,unit,ntags)
      num=a.(0).fillval
      final_labels=''
      final_units=''
      final_dep1_values=''
      final_dep2_values=''
      final_dep3_values=''
      atags=tag_names(a)
      inc=0L
      for i=0L, ntags-5 do begin
         if(a.(i).var_type eq 'data') or ((a.(i).var_type eq 'support_data') and (a.(i).cdfrecvary ne 'NOVARY')) then begin
            labels=''
            units=''
            dep1_values=''
            dep2_values=''
            dep3_values=''
            st_sz=size(a.(i).dat)
     ;print,'name = ',a.(i).varname
     ;print,'st_sz = ',st_sz
            if(st_sz[0] le 1) then begin
               ; get labels and units:
               labels=[labels,spd_cdawlib_label_search(a,st_sz[0],i,0)]
               ;units=[units,a.(i).units]
               units=[units,spd_cdawlib_unit_search(a,st_sz[0],i,0)]
               if(names(i) eq depend0) then begin
                  temp=create_struct(names(i),a.(i).dateph[0])
               endif else begin
                  temp=create_struct(names(i),a.(i).dat[0])
               endelse
               if(inc eq 0) then begin
                  b=temp
               endif else begin
                  b=create_struct(b,temp)
               endelse
               inc=inc+1L
            endif
            if(st_sz[0] eq 2) then begin
               ; get labels and units:
               num_var=st_sz[1]
               for k=0L, num_var-1 do begin
                  labels=[labels,spd_cdawlib_label_search(a,st_sz[0],i,k)]
                  units=[units,spd_cdawlib_unit_search(a,st_sz[0],i,k)]
	   unique = strtrim(string(inc), 2)
                  temp=create_struct(atags(i)+unique,a.(i).dat[k,0])
                  b=create_struct(b,temp)
                  inc=inc+1
               endfor
            endif   ; end st_sz(0) eq 2
            ; Free Memory
            spd_cdawlib_delete, temp
            ;
            labels=labels[1:*]
            final_labels=[final_labels,labels]
     ;help,final_labels
            units=units[1:*]
            final_units=[final_units,units]
            ;
            ; create array of depend_1 values, if they exist, to also be listed
            ; RCJ 07/2013
            ; exist test is done in spd_cdawlib_dependn_search, if does not exist
            ; return ''
            dep1=spd_cdawlib_dependn_search(a,i,1)
            if (dep1[0] ne '') then begin
               depend1=a.(i).depend_1
               ; RCJ 05/16/2013  If alt_cdaweb_depend_1 exists, use it instead:
               q=where(tag_names(a.(i)) eq 'ALT_CDAWEB_DEPEND_1')
               if (q[0] ne -1) then if (a.(i).alt_cdaweb_depend_1 ne '') then depend1=a.(i).alt_cdaweb_depend_1 
               dep1_units=a.(strtrim(depend1,2)).units
               dep1=['(@_'+dep1+'_'+dep1_units+')']
            endif 
            dep1_values=[dep1_values,dep1]
            ; create array of depend_2 and _3 values, if they exist, to also be listed
            ; RCJ 07/13
            ; exist test is done in spd_cdawlib_dependn_search, if does not exist
            ; return ''
            dep2=spd_cdawlib_dependn_search(a,i,2)
            if (dep2[0] ne '') then begin
               depend2=a.(i).depend_2
               ; RCJ 05/16/2013  If alt_cdaweb_depend_2 exists, use it instead:
               q=where(tag_names(a.(i)) eq 'ALT_CDAWEB_DEPEND_2')
               if (q[0] ne -1) then if (a.(i).alt_cdaweb_depend_2 ne '') then depend2=a.(i).alt_cdaweb_depend_2 
               dep2_units=a.(strtrim(depend2,2)).units
               dep2=['(@_'+dep2+'_'+dep2_units+')']
            endif 
            dep2_values=[dep2_values,dep2]
            dep3=spd_cdawlib_dependn_search(a,i,3)
            if (dep3[0] ne '') then begin
               depend3=a.(i).depend_3
               q=where(tag_names(a.(i)) eq 'ALT_CDAWEB_DEPEND_3')
               if (q[0] ne -1) then if (a.(i).alt_cdaweb_depend_3 ne '') then depend3=a.(i).alt_cdaweb_depend_3 
               dep3_units=a.(strtrim(depend3,2)).units
               dep3=['(@_'+dep3+'_'+dep3_units+')']
            endif 
            dep3_values=[dep3_values,dep3]
            ;
            ; listing depend_1 values if they exist. RCJ 06/01
            if (n_elements(dep1_values) gt 1) then begin
               tmp_dep1_values=dep1_values[1:*]
               while n_elements(dep1_values)-1 le n_elements(labels)-n_elements(tmp_dep1_values) do begin
                  dep1_values=[dep1_values,tmp_dep1_values]
               endwhile
               dep1_values=dep1_values[1:*]
               final_dep1_values=[final_dep1_values,dep1_values]
            endif    
            ; listing depend_2 values if they exist. RCJ 06/01
            if (n_elements(dep2_values) gt 1) then begin
               tmp_dep2_values=dep2_values[1:*]
               if n_elements(tmp_dep2_values) eq n_elements(labels) then begin
                  ;print,'SAME NUMBER OF ELEMENTS!!!!!!'
                  ; RCJ 07/01 If the initial depend_2 is 2D (now stretched into 1D)
                  ; we don't need to do what goes below:
               endif else begin
                  k=0
                  dep2_values=''
                  while n_elements(dep2_values)-1 le n_elements(labels)-n_elements(tmp_dep1_values) do begin
                     for kk=0L,n_elements(tmp_dep1_values)-1 do begin
                        dep2_values=[dep2_values,tmp_dep2_values[k]]
                     endfor   
                     k=k+1
                     if k ge n_elements(tmp_dep2_values) then k=0
                  endwhile
               endelse   
               if n_elements(dep2_values) gt 1 then dep2_values=dep2_values[1:*]
               final_dep2_values=[final_dep2_values,dep2_values]
            endif  
            ; listing depend_3 values if they exist. 
            if (n_elements(dep3_values) gt 1) then begin
               tmp_dep3_values=dep3_values[1:*]
               if n_elements(tmp_dep3_values) eq n_elements(labels) then begin
                  ;print,'SAME NUMBER OF ELEMENTS!!!!!!'
               endif else begin
                  k=0
                  dep3_values=''
                  while n_elements(dep3_values)-1 le (n_elements(labels)-(n_elements(tmp_dep2_values)*n_elements(tmp_dep1_values))) do begin
                     for kk=0L,(n_elements(tmp_dep2_values)*n_elements(tmp_dep1_values))-1 do begin
                        dep3_values=[dep3_values,tmp_dep3_values[k]]
                     endfor   
                     k=k+1
                     if k ge n_elements(tmp_dep3_values) then k=0
                  endwhile
               endelse 
               if n_elements(dep3_values) gt 1 then dep3_values=dep3_values[1:*]
               final_dep3_values=[final_dep3_values,dep3_values]
            endif  
            ;
            ;
         endif   ; end a.(i).var_type
         ;
      endfor   ; end i
      ;
      final_labels=final_labels[1:*]
      printf,unit,format=a.lform,final_labels            ; <----------------------- print final labels
      final_units=final_units[1:*]  ;  but cannot printf the units right now
                                    ;  If there are depend_1/_2 they come first.
      ; If there are labels with no corresponding dep1 values,
      ; then add spaces before the first element of the array.
      ; This works as long as the labels which *do not have* corresponding dep1 
      ; values come before the labels which *have* corresponding dep1 values. 
      ; If that condition is not true, the logic has to be reworked.  RCJ 07/01
      if n_elements(final_dep1_values) gt 1 then begin
         final_dep1_values=final_dep1_values[1:*]
         diff=n_elements(final_labels)-n_elements(final_dep1_values)
         for k=1L,diff do begin
            formt = "('" + strtrim(strlen(final_labels[k])+1,2)+"'x,a)"
            space=string("",format=formt)
            ;cmd='space=string("",format="('+strtrim(strlen(final_labels[k])+1,2)+'x,a)")
            final_dep1_values=[space,final_dep1_values]
         endfor
      ;printf,unit,format=a.dpform,final_dep1_values
         q=where (final_dep1_values ne '') 
         if q[0] ne -1 then printf,unit,format=a.dpform,final_dep1_values; <----------------------- print final dep1
      endif   
      ; same for dep2 values:
      if n_elements(final_dep2_values) gt 1 then begin
         final_dep2_values=final_dep2_values[1:*]
         diff=n_elements(final_labels)-n_elements(final_dep2_values)
         for k=1L,diff do begin
            formt = "('" + strtrim(strlen(final_labels[k])+1,2)+"'x,a)"
            space=string("",format=formt)
            ;cmd='space=string("",format="('+strtrim(strlen(final_labels[k])+1,2)+'x,a)")
            final_dep2_values=[space,final_dep2_values]
         endfor
      ;printf,unit,format=a.dpform,final_dep2_values
         q=where (final_dep2_values ne '') 
         if q[0] ne -1 then printf,unit,format=a.dpform,final_dep2_values; <----------------------- print final dep2
      endif  
      ; 
      ; same for dep3 values:
      if n_elements(final_dep3_values) gt 1 then begin
         final_dep3_values=final_dep3_values[1:*]
         diff=n_elements(final_labels)-n_elements(final_dep3_values)
         for k=1L,diff do begin
            formt = "('" + strtrim(strlen(final_labels[k])+1,2)+"'x,a)"
            space=string("",format=formt)
            ;cmd='space=string("",format="('+strtrim(strlen(final_labels[k])+1,2)+'x,a)")
            final_dep3_values=[space,final_dep3_values]
         endfor
         q=where (final_dep3_values ne '') 
         if q[0] ne -1 then printf,unit,format=a.dpform,final_dep3_values; <----------------------- print final dep3
      endif  
      ; 
      printf,unit,format=a.uform,final_units      ; <----------------------- print final units
      ;
     ;help,final_dep1_values,final_dep2_values,final_dep3_values,final_labels
     ;print,'** ',final_dep1_values
     ;print,'** ',final_dep2_values
     ;print,'** ',final_dep3_values
     ;print,'** ',final_labels
      for j=0L, length-1 do begin
         inc=0L
         for i=0L,ntags-5 do begin
            if (a.(i).var_type eq 'data') or ((a.(i).var_type eq 'support_data') and (a.(i).cdfrecvary ne 'NOVARY')) then begin
               ; if(names(i) eq 'EPOCH' or names(i) eq 'EPOCH92') then begin
               if(names(i) eq depend0) then begin
                  b.(inc)=a.(i).dateph[j]
                  inc=inc+1L
               endif else begin
                  st_sz=size(a.(i).dat)  
                  if(st_sz[0] eq 1) then begin
                     b.(inc)=a.(i).dat[j] 
                     inc=inc+1L
                  endif   
                  if(st_sz[0] eq 2) then begin
                     num_var=st_sz[1]
                     for k=0L,num_var-1 do begin
                        b.(inc)=a.(i).dat[k,j]
                        inc=inc+1L
                     endfor
                  endif
               endelse
            endif
         endfor   ; end i
         printf,unit,format=a.dform,b
      endfor   ; end j
      ; 
      if(num_data gt maxrecs) then begin
         dif_rec=num_data-maxrecs
         text='# The maximum number of records allowed to be listed is '
         text1='# Your request has exceeded this maximum by '
         printf, unit, format='(a)',blnk
         printf, unit,text,maxrecs
         printf, unit, format='(a,i6)',text1,dif_rec
         status=1                                  
         length=maxrecs
      endif
      ; Free Memory
      spd_cdawlib_delete, b   
  end   ; end case 5
  ;
  ;
  else : begin
         print, 'STATUS= A listing of these data cannot be generated. '
         print, "ERROR=Error: Invalid control variable; convar= ",convar
         close,1
         return, -1
  end 
ndcase   ; end case convar

eturn, status 
 
nd

(See external/spdfcdas/spd_cdawlib/spd_cdawlib_list_mystruct.pro)


SPD_CDAWLIB_LIST_MYSTRUCT[6]

[Previous Routine] [Next Routine] [List of Routines]
 NAME:  spd_cdawlib_form_bld.pro

 PURPOSE: Builds format statements 

 shft - 0= left justified field; 1= right justified field

UNCTION spd_cdawlib_form_bld, col_sz, label, units, dat_len, dep_col_sz, depend1_labels, $
  dep2_col_sz, depend2_labels, dep3_col_sz, depend3_labels,form, shft

 Use column size and to build label, unit and data format statements

axlength=max(strlen(depend1_labels)) > max(strlen(depend2_labels))  > max(strlen(depend3_labels)) > strlen(label) 
intab=fix(dep_col_sz-max(strlen(depend1_labels))) < fix(dep2_col_sz-max(strlen(depend2_labels))) < fix(dep3_col_sz-max(strlen(depend3_labels)))<fix(col_sz-strlen(label))

 depend1 and depend2 use the same format (depv) :
 depend1, depend2 and depend3 use the same format (depv) :
tab=strtrim(mintab,2)
fld=strtrim(maxlength,2)
f(shft eq 0) then begin
  if(ltab ne '0') then depv='A'+lfld+','+ltab+'X,1X,' else depv='A'+lfld+',1X,'
ndif else begin
  if(ltab ne '0') then depv=ltab+'X,A'+lfld+',1X,' else depv='A'+lfld+',1X,'
ndelse

f(shft eq 0) then begin
  if(ltab ne '0') then labv='A'+lfld+','+ltab+'X,1X,' else labv='A'+lfld+',1X,'
ndif else begin
  if(ltab ne '0') then labv=ltab+'X,A'+lfld+',1X,' else labv='A'+lfld+',1X,'
ndelse

ol_sz=maxlength > col_sz
tab=strtrim(fix(col_sz-strlen(units)),2)
fld=strtrim(strlen(units),2)
f(shft eq 0) then begin
  if(utab ne '0') then untv='A'+ufld+','+utab+'X,1X,' else untv='A'+ufld+',1X,'
ndif else begin
  if(utab ne '0') then untv=utab+'X,A'+ufld+',1X,' else untv='A'+ufld+',1X,'
ndelse

tab=strtrim(fix(col_sz-dat_len),2)
f(dtab ne '0') then datv=dtab+'X,'+form+',1X,' $
    else datv=form+',1X,'
form=create_struct('labv',labv,'untv',untv,'datv',datv,'depv',depv)

eturn, sform
nd

(See external/spdfcdas/spd_cdawlib/spd_cdawlib_list_mystruct.pro)


SPD_CDAWLIB_LIST_MYSTRUCT[7]

[Previous Routine] [Next Routine] [List of Routines]
 NAME:  spd_cdawlib_data_len.pro

 PURPOSE: Determines the length of the data field given FORMAT, FILLVAL 



UNCTION spd_cdawlib_data_len,format,fillval
                 
 Set input values if undefined 

tatus=0
if(n_elements(format) eq 0) then form='null' else form=strmid(format,0,1)
if(strlen(format) eq 0) then form='null' else begin
 RCJ 11/23/05   It has to be G format or fillvals will be ****          
f(strlen(format) eq 0) then format='G13.6' 
trip=0
c=0
ew_form='        '
var=''
var=0
or i=0L, strlen(format)-1 do begin   
  ch=strupcase(strmid(format,i,1))
  if(ch ne '(') and (ch ne 'A') and (ch ne 'F') and (ch ne 'P') and $
     (ch ne 'I') and (ch ne 'Z') and (ch ne 'G') and (ch ne 'E') then begin
     if(ivar eq 0) then nvar=nvar+ch
  endif
  if(ch eq 'A') or (ch eq 'F') or (ch eq 'I') or (ch eq 'Z') or (ch eq 'G') $
     or (ch eq 'E') then begin
     form=ch
     itrip=1
     ivar=1
  endif 
  if(ch eq 'P') then ch=''
  if(ch eq ',') or (ch eq ')') then itrip=0
  if(itrip eq 1) then begin
     strput,new_form,ch,nc
     nc=nc+1
  endif
ndfor   ; end i
ormat=strtrim(new_form,2)
ormlen=strlen(format)-1
endelse

ase form of
  'null' : begin
           status=-1
           return, status
  end
  ; RCJ 11/23/05  We are setting formats F,E,G to G13.6 (or wider)
  ;   to accomodate possible fillvals in the data
  'F' : begin
        dat_len = 13.6 > strmid(format,1,formlen)
        ;dat_len = strmid(dat_len,6,4)
 ; RCJ 10/29/2007  Generalizing line above. Same for E and G below.
        dat_len = strmid(dat_len,6,formlen > 4)
  end
  'E' : begin
        dat_len = 13.6 > strmid(format,1,formlen)
        ;dat_len = strmid(dat_len,6,4)
        dat_len = strmid(dat_len,6,formlen > 4)
  end
  'G' : begin
        dat_len = 13.6 > strmid(format,1,formlen)
        ;dat_len = strmid(dat_len,6,4)
        dat_len = strmid(dat_len,6,formlen > 4)
  end
  'I' : begin
        ;  Program caused arithmetic error: Floating illegal operand; where?
        if(n_elements(fillval) eq 0) then dat_len=strmid(format,1,formlen) else $
           dat_len=strlen(strtrim(string(fix(fillval)),2)) > strmid(format,1,3)
  end
  'A' : begin
        ;if(n_elements(fillval) eq 0) then dat_len=strmid(format,1,formlen) else $
        ;   dat_len=strlen(strtrim(fillval,2)) > strmid(format,1,3)       
        if(n_elements(fillval) eq 0) then dat_len=strmid(format,1,formlen) $
 else begin
    if size(fillval,/tname) eq 'DCOMPLEX' then $
    ; RCJ 11/2006  This is the case of epoch for themis data
           dat_len=strlen(strtrim(real_part(fillval),2)) > strmid(format,1,3) else $
           dat_len=strlen(strtrim(fillval,2)) > strmid(format,1,3) 
 endelse   
  end
  else : begin
         dat_len=0
  end
ndcase
 RCJ 11/23/05  It has to be G format or fillvals will be ****:
f(form eq 'F') or (form eq 'E') then form='G' 
f(nvar ne '') then begin
  format=nvar+form+strtrim(dat_len,2)
  dat_len=fix(nvar)*fix(dat_len)
  nvar=fix(nvar)-1
ndif else begin
  format=form+strtrim(dat_len,2)
  dat_len=fix(dat_len)
  nvar=0
ndelse
rm_st=create_struct('status',status, 'form',format, 'dat_len',dat_len, $
                     'nvar',nvar) 
eturn, frm_st

nd

unction spd_cdawlib_ep_conv, b, depd0, HANDLE=handle, sec_of_year=sec_of_year
 
atch, error_status
f(error_status ne 0) then begin
  if(error_status eq -78) then $ 
     print, 'STATUS=Available memory exceeded. Re-select time interval.'
  print, 'ERROR=Error number: ',error_status,' in listing (spd_cdawlib_ep_conv).'
  print, 'ERROR=Error Message: ', !ERR_STRING
  stop
ndif

agnames=tag_names(b)
1=spd_cdawlib_tagindex(depd0,tagnames)
f(n_elements(handle) eq 0) then handle=0

f(handle eq 0) then begin
  dat=b.(v1[0]).dat
  datsz=size(dat)
  if(datsz[0] gt 0) then dat=reform(dat) 
ndif else begin 
  tmp=b.(v1[0]).HANDLE
  handle_value, tmp, dat
  datsz=size(dat)
  if(datsz[0] gt 0) then dat=reform(dat) 
ndelse
en=size(dat)
TJK 10/1/2009 - put in code to check for Epoch 16 values (dcomplex)
if found, then print the extra time fields (micro, nano and pico)

poch_type = size(dat,/type)
ase epoch_type of
9: begin  ; complex
  ep16=1
  if keyword_set(sec_of_year) then b.(v1[0]).units="Year____Secs-of-year" else $  ;  e.g. 2001 4585746.000  <-  microsec precision
     b.(v1[0]).units="dd-mm-yyyy hh:mm:ss.mil.mic.nan.pic"
end
14: begin  ;  long64
  ep16=0
  if keyword_set(sec_of_year) then b.(v1[0]).units="Year____Secs-of-year" else $  ;  e.g. 2001 4585746.000  <-  microsec precision
     b.(v1[0]).units="dd-mm-yyyy hh:mm:ss.mil.mic" 
end
else: begin
   ep16=0
  if keyword_set(sec_of_year) then b.(v1[0]).units="Year____Secs-of-year" else $  ;  e.g. 2001 4585746.000  <-  microsec precision
      b.(v1[0]).units="dd-mm-yyyy hh:mm:ss.ms"
end
ndcase
if (epoch_type eq 9) then begin ; if dcomplex
    ep16 = 1 
    b.(v1(0)).units="dd-mm-yyyy hh:mm:ss.mil.mic.nan.pic"
endif else begin
     ep16 = 0
endelse

ength=long(len(len(0)+2))
at_eph=strarr(length)

or k=0L, length-1 do begin
  if keyword_set(sec_of_year) then begin
    CDF_EPOCH,dat[k], yr, mo, dy, hr, mn, sc, milli, micro, /break
    yr=long(yr) & mo=long(mo) & dy=long(dy) & hr=long(hr) & mn=long(mn)
    sc=long(sc) & hr=long(hr) 
    ical,yr,doy,mo,dy,/idoy
    doy=float(doy-1)  ;  if day=1 have to start from beginning of day, ie, not a whole day has passed at 00:05 of day 1, don't you agree?
    yrsec=double(sc)+double(mn)*60.+double(hr)*3600.+double(doy)*24.*3600.
    yrsec=yrsec+double(milli)/1000.+double(micro)/10^6.
    ;print,'date = ',yr, mo, dy, hr, mn,sc,milli, micro, yrmilli
  endif else begin
    if (ep16) then begin
     CDF_EPOCH16,dat[k], yr, mo, dy, hr, mn, sc, milli, micro, nano, pico, /break 
    endif else begin   
     if (size(dat[k],/type) eq 14) then begin
          CDF_EPOCH,dat[k], yr, mo, dy, hr, mn, sc, milli, micro, /break,/tointeger 
 endif else begin
          CDF_EPOCH,dat[k], yr, mo, dy, hr, mn, sc, milli, /break
 endelse
    endelse 
  endelse 
  if(dy lt 10) then dy= '0'+strtrim(dy,2) else dy=strtrim(dy,2)
  if(mo lt 10) then mo= '0'+strtrim(mo,2) else mo=strtrim(mo,2)
  if(hr lt 10) then hr= '0'+strtrim(hr,2) else hr=strtrim(hr,2)
  if(mn lt 10) then mn= '0'+strtrim(mn,2) else mn=strtrim(mn,2)
  if(sc lt 10) then sc= '0'+strtrim(sc,2) else sc=strtrim(sc,2)
  milli=strmid(strtrim(float(milli)/1000.,2),2,3)
  yr=strtrim(yr,2)
  if keyword_set(sec_of_year) then begin
    yrsec_str=string(yrsec,format='(f15.6)')
    dat_eph[k]=yr+' '+yrsec_str
  endif else begin
    if (ep16) then begin
      micro=strmid(strtrim(float(micro)/1000.,2),2,3)
      nano=strmid(strtrim(float(nano)/1000.,2),2,3)
      pico=strmid(strtrim(float(pico)/1000.,2),2,3)
      dat_eph[k]=dy+'-'+mo+'-'+yr+' '+hr+':'+mn+':'+sc+'.'+milli+'.'+micro+'.'+nano+'.'+pico   
    endif else begin
     if (size(dat[k],/type) eq 14) then begin
      micro=strmid(strtrim(float(micro)/1000.,2),2,3)
      dat_eph[k]=dy+'-'+mo+'-'+yr+' '+hr+':'+mn+':'+sc+'.'+milli +'.'+micro
     endif else begin   
      dat_eph[k]=dy+'-'+mo+'-'+yr+' '+hr+':'+mn+':'+sc+'.'+milli
     endelse   
    endelse
  endelse  
ndfor
ptmp=create_struct('DATEPH',dat_eph)
eturn, eptmp

nd 

+ 
 NAME:  spd_cdawlib_list_mystruct.pro

 PURPOSE:  Generates a list output for CDAWweb

 CALLING SEQUENCE:

 FUNCTION spd_cdawlib_list_mystruct, a,NOGATT=nogatt,NOVATT=novatt,NORV=norv,$
                         NONRV=nonrv,NO2DRV=no2drv,FILENAME=filename,$
                         TSTART=TSTART,TSTOP=TSTOP,MAXRECS=maxrecs
  
 VARIABLES:

 Input:

  a        - an IDL structure
 
 Keyword Parameters:

  nogatt   - Global attributes output: =0 (print), =1 (no print)
  novatt   - Variable attributes output: =0 (print), =1 (no print)
  norv     - Record varying output: =0 (print), =1 (no print) 
  nonrv    - Non record varying output: =0 (print), =1 (no print)
  no2drv   - 2D record varying output: =0 (print), =1 (no print)
  filename - Output filename 
  maxrecs  - Maximum record output

 REQUIRED PROCEDURES:

 HISTORY

 Initial version: 

         1.0  R. Baldwin  HSTX           2/9/96


Copyright 1996-2013 United States Government as represented by the 
Administrator of the National Aeronautics and Space Administration. 
All Rights Reserved.

(See external/spdfcdas/spd_cdawlib/spd_cdawlib_list_mystruct.pro)


SPD_CDAWLIB_PLOTMASTER

[Previous Routine] [Next Routine] [List of Routines]
 NAME: spd_cdawlib_plotmaster
 PURPOSE: To plot the data given in 1 to 10 anonymous structure of the type
          returned by the spd_cdawlib_read_mycdf function.  This function determines
          the plot type for each variable, and generates the plot.
 CALLING SEQUENCE:
       out = spd_cdawlib_plotmaster(a,[more_structures])
 INPUTS:
       a = structure returned by the spd_cdawlib_read_mycdf procedure.

 KEYWORD PARAMETERS:
   TSTART =  String of the form '1996/01/02 12:00:00' or a DOUBLE CDF_EPOCH
   time that is the desired start time of the plots. Data is clipped or
   padded to conform to this time. Default is the start time of the
   earliest data.

   TSTOP = String of the form '1996/01/02 12:00:00' or a DOUBLE
   CDF_EPOCH time that is the desired stop time of the plots. Data is
   clipped or padded to conform to this time. Default is the stop time of
   the latest data.

   GIF
    Set to send plot(s) to a gif file, ie. /GIF or GIF=1L. If set a file
    will be produced in the current working directory (see OUTDIR keyword),
    using the following naming conventions: Spacecraft_instrument_pid_# (see
    the PID keyword for customization). If GIF is not set then the plot(s)
    will be put into an x-window.

    PS
      Set to send plot to a ps file. Works just as GIF above.

    PID
    May be used to customize part of the name of a gif file. The value of
    PID may be either a number or a string and will be inserted in the gif
    file name as follows: Spacecraft_instrument_pid_#.gif. If GIF is not
    set then the plot(s) will be put into an x-window and this keyword is
    ignored.

    OUTDIR
    This keyword indiates the output directory where a gif file will be
    placed. If GIF is set but OUTDIR is not, then the gif file will be put
    in the user's current working directory.GIF

    AUTO
    Set this keyword to use autoscaling instead of the variables SCALEMIN
    and SCALEMAX attribute values. The scales will be set to the min and
    max values of the data, after fill values have been filtered from the
    data (see also NONOISE keyword). If the user wishes to modify variable
    scale values for plotting purposes, you may do so by changing the
    appropriate data structure values, ie. struct.variable.scalemin = 0.0.
    Please use great care in modifying the data structures values since
    they will greatly influence what your plots or listings may look like.

    CDAWEB
    Set this keyword to force the margin on the right side of time series
    plots to be 100 pixels. This is the same margin used for spectrograms
    for the color bar. By default, spd_cdawlib_plotmaster will examine the data, and if
    ANY spectrograms will be produced, then it will align the margins
    properly. This keyword is only necessary for use in the CDAWeb system.

    SLOW
    Set this keyword to have spectrogram plotted using the POLYFILL method.
    This method is slower but more accurate than TV (used in the QUICK method).

    SMOOTH
    Set this keyword to have spectrogram data reduced prior to plotting.
    This will increase plotting speed significantly.

    QUICK
    Set this keyword to have spectrograms plotted using the TV method.
    This method is very fast, but will produce inaccurate spectrograms
    if scales are non-linear or if fill data or data gaps are present
    in the data.

    THUMBSIZE
    Set this to change the "thumbnail" size of each image when plotting
    a series of images. The default is 50w x 62h. 12 pixels is added to
    the height to allow for the time stamps under each image. So, if
    you specify a thumsize of 70 pixels, each will actually be 70x82.

    FRAME
    Used to indicate the frame number within a series of images. If you
    specify FRAME = 2, then spd_cdawlib_plotmaster will produce a "full size" version
    of the 3rd image in a sequence of images.

       COMBINE  = if set, all time series and spectrogram plots will be
                  combined into a single window or gif file.
       NONOISE  = if set, filter values outside 3-sigma from the mean
       DEBUG    = if set, turns on additional debug output.
       ELEMENTS = if set, then only these elements of a dimensional variable
                  will be plotted for stack_plot use only (right now).

   LIMIT_MOVIE = if set, then the number of frames in a movie file
   will be limited by the underlying s/w routines (to 200 or so as of
   2/2006)       if not set, no limit on the # of frames (TJK 2/9/2006)

   TOP_TITLE - if set, adjust the top margin a bit to allow a total
               of 3 lines of title.  The value of top_title allows a
               user to pass in an additional line of text, which
               cdaweb is using for the binning labels.

  PLOTMERGE
    Set this keyword to plot multiple time series data on the same panel.
    PLOTMERGE = 'vector' will plot together vector components (i.e. Bx, By, Bz)
    emanating from a single variable.
    PLOTMERGE = 'mission' will plot together identical variables from
    cluster missions (i.e., MMS)


 OUTPUTS:
       out = status flag, 0=0k, -1 = problem occurred.
 AUTHOR:
       Richard Burley, NASA/GSFC/Code 632.0, Feb 22, 1996
       burley@nssdca.gsfc.nasa.gov    (301)286-2864
 MODIFICATION HISTORY:
       8/13/96 : R. Burley    : Add NONOISE keyword
       8/30/96 : R. Baldwin   : Add error handling STATUS,DATASET,IMAGE,GIF
       8/30/96 : R. Baldwin   : Add orbit plotting
	1/7/97  ; T. Kovalick  : Modified many of the code that goes w/ the
				 keywords; GIF, CDAWEB, TSTART,	TSTOP and added
				 the header documentation for them. Still more
				 work to do...
       2/10/97 ; R. Baldwin   : Add SSCWEB keyword and map_keywords.pro
				 function
	6/6/97  ; T. Kovalick  : Added the Stacked time series plot type.

	9/4/97	; T. Kovalick  : Added the ELEMENTS keyword for stack_plot
				 usage, it could also be used in time_series.
        4/98   ; R. Baldwin   : Added virtual variable plot types;
				 plot_map_images.pro
       11/98   ; R. Baldwin   : Added movie_images and movie_map_images


Copyright 1996-2013 United States Government as represented by the
Administrator of the National Aeronautics and Space Administration. All Rights Reserved.

(See external/spdfcdas/spd_cdawlib/spd_cdawlib_plotmaster.pro)


SPD_CDAWLIB_READ_MYCDF[10]

[Previous Routine] [Next Routine] [List of Routines]
 NAME: spd_cdawlib_read_mymetadata
 PURPOSE: 
 To read all of the attribute values for the requested variable, and
       to return this information as an anonymous structure.
 CALLING SEQUENCE:
       metadata = spd_cdawlib_read_mymetadata(vname,CDFid)
 INPUTS:
       vname = string, name of variable whose metadata is being read
       CDFid = integer, id of already opened CDF file
 KEYWORD PARAMETERS:
 OUTPUTS:
       metadata = anonymous structure whose tags are the attribute names
                  and whose fields are the corresponding attribute values.
 AUTHOR:
       Richard Burley, NASA/GSFC/Code 632.0, Feb 13, 1996
       burley@nssdca.gsfc.nasa.gov    (301)286-2864
 MODIFICATION HISTORY:

(See external/spdfcdas/spd_cdawlib/spd_cdawlib_read_mycdf.pro)


SPD_CDAWLIB_READ_MYCDF[11]

[Previous Routine] [Next Routine] [List of Routines]
 NAME: spd_cdawlib_getvar_attribute_names CDFid
 PURPOSE: 
	To return all of the attribute names for the requested variable, as
	an array.
 CALLING SEQUENCE:
       att_array = spd_cdawlib_getvar_attribute_names(vname,CDFid, ALL=ALL)
 INPUTS:
       CDFid = integer, id of already opened CDF file
 KEYWORD PARAMETERS:
	ALL - all attributes are returned
	      default is that just variable scoped attributes are returned
 OUTPUTS:
       att_array = string array of attribute names
 AUTHOR:
       Tami Kovalick
       tami.kovalick@gsfc.nasa.gov    (301)286-9422
 MODIFICATION HISTORY:

(See external/spdfcdas/spd_cdawlib/spd_cdawlib_read_mycdf.pro)


SPD_CDAWLIB_READ_MYCDF[12]

[Previous Routine] [Next Routine] [List of Routines]
 NAME: spd_cdawlib_get_numallvars
 PURPOSE: 
 	To return the total number of variables in the cdf.

 CALLING SEQUENCE:
       num_vars = spd_cdawlib_get_numallvars(CNAME=CNAME)
 INPUTS:
 KEYWORD PARAMETERS:
	CNAME = string, name of a CDF file to be opened and read
	CDFid = integer, id of an already opened CDF file
 OUTPUTS:
       num_vars = number of variables in the CDF
 AUTHOR:
       Tami Kovalick, RITSS, October 27, 2000
 MODIFICATION HISTORY:

(See external/spdfcdas/spd_cdawlib/spd_cdawlib_read_mycdf.pro)


SPD_CDAWLIB_READ_MYCDF[13]

[Previous Routine] [Next Routine] [List of Routines]
 NAME: spd_cdawlib_get_allvarnames
 PURPOSE: 
 	To return a string array containing the names of all of the
	variables in the given CDF file.
 CALLING SEQUENCE:
       vnames = spd_cdawlib_get_allvarnames()
 INPUTS:
 KEYWORD PARAMETERS:
	CNAME = string, name of a CDF file to be opened and read
	CDFid = integer, id of an already opened CDF file
       VAR_TYPE = string, only return the names for variables who have an
                  attribute called 'VAR_TYPE' and whose value matches the
                  value given by this keyword.  (ex. VAR_TYPE='data')
 OUTPUTS:
       vnames = string array of variable names
 AUTHOR:
       Richard Burley, NASA/GSFC/Code 632.0, Feb 13, 1996
       burley@nssdca.gsfc.nasa.gov    (301)286-2864
 MODIFICATION HISTORY:
	4/9/1998 - TJK modified to include all variable when the "var_type"
	keyword isn't used.  The original code only included variables
	that vary by record so some important "support_data" variables
	were being thrown out.

(See external/spdfcdas/spd_cdawlib/spd_cdawlib_read_mycdf.pro)


SPD_CDAWLIB_READ_MYCDF[14]

[Previous Routine] [Next Routine] [List of Routines]

 RCJ 03/30/2012  Commented out this function. It was called once and that
  call is commented out too.
;check the variables_comp array for existence of the variable name, for
;the current cdf.
function check_varcompare, variables_comp, cdf_index, variable_name
;print,'**** ' & help,variables_comp
;print, variable_name, cdf_index, variables_comp
;stop;
x = where(variable_name eq variables_comp(cdf_index,*), xcnt) 
if (xcnt gt 0)then print, variable_name, ' found 1' else print, variable_name, ' not found 0'
if (xcnt gt 0)then return, 1 else return, 0
end

+------------------------------------------------------------------------
 NAME: spd_cdawlib_read_mycdf
 PURPOSE: 
	Read all data and metadata for given variables, from given CDF
       files, and return all information in a single anonymous structure
       of the form: 
          structure_name.variable_name.attribute_name.attribute_value

 CALLING SEQUENCE:
       out = spd_cdawlib_read_mycdf(vnames,cnames)
 INPUTS:
       vnames = string, array of variable names or a single string of
                names separated by a comma.  (ex. 'Epoch,Magfld,Bmax')
       cnames = string, array of CDF filenames or a single string of
                names separated by a comma.
 KEYWORD PARAMETERS:
	ALL = 0: get data and metadata for requested variable(s) only.
             1: get data and metadata for ALL variables in the CDFs.
             2: get data and metadata for all var_type='data' variables.
       NODATASTRUCT = If set, instead of returning the data for each variable
                   in the 'DAT' attribute field, create a 'HANDLE' field
                   and set it to the handle id of a data handle which
                   holds the data for each variable.
       NOQUIET = If set, do NOT set the !QUIET system variable before
                 reading the cdf file(s).
       DEBUG = If set, print out some progress information during reading.
	TSTART = epoch starting value - YYYYMMDD etc. string.
	TSTOP = epoch ending value - YYYYMMDD etc. string.
 OUTPUTS:
       out = anonymous structure holding all data and metadata for the
             requested variables. If an error occurs, that we know how
             to deal w/, an alternate structure is returned, its structure
	      is as follows: ('DATASET',d_set,'ERROR',v_err,'STATUS',v_stat)
	      
 AUTHOR:
       Richard Burley, NASA/GSFC/Code 632.0, Feb 13, 1996
       burley@nssdca.gsfc.nasa.gov    (301)286-2864
 MODIFICATION HISTORY:
	Tami Kovalick, HSTX, 12/16/96 modified to verify whether 
 variables requested in vnames array are actually in the "data" cdfs 
 prior to requesting the data from these variables.  If variables 
 aren't valid then they are removed from the vnames array and the 
 code continues on to create a valid structure.
	Tami Kovalick, HSTX, 12/20/96 modified to allow the use of 
 TSTART and TSTOP keywords (see above).  Use of these keywords will
 force the code to only read the necessary records in the CDF, otherwise
 the code will read the entire CDF.  Could enhance the code to deal
 w/ one or the other keyword - right now they are only used if both
 are set.
	Tami Kovalick, RSTX, 02/13/98, Carrie Gallap started modifications
 to spd_cdawlib_read_mycdf to accommodate "virtual variables" (VV) .  Tami finished 
 up the code and made corrections to several sections.  One new routine was
 written spd_cdawlib_add_mycomponents, this routine is called when a valid virtual
 variable is found in order to add any additional variables needed for
 actually generating the data for the VV.  The routine looks for variable
 attributes w/ the naming convention COMPONENT_n where n is a digit.  The
 basic methodology to the changes is to determine whether any of the
 variables selected are virtual variables, if so then the variable name
 and the source (where the VV was defined - master or data cdfs) are
 stored in a structure called vir_vars, then add the component variables
 to the vnames array.  Do the usual checking to see if the variables requested
 in vnames actually exist. Then continue on w/ getting the metadata for all
 variables (including VV), and continue on w/ the getting the data from
 the CDFs for all variables except the VV.  Population of the VV's data field
 in the "burley" structure are handled at the very end in a case statement 
 which looks for each VV's variable attribute FUNCTION to determine which 
 actual "IDL function" to call, ie. spd_cdawlib_conv_pos.

(See external/spdfcdas/spd_cdawlib/spd_cdawlib_read_mycdf.pro)


SPD_CDAWLIB_READ_MYCDF[1]

[Previous Routine] [Next Routine] [List of Routines]
 This package of IDL functions facilitates reading data and metadata from
 Common Data Format (CDF) files.  While CDF provides all the benefits
 of a portable, self-documenting scientific data format, reading them is
 not always a simple matter.  To make it simple, I have created this IDL
 package so that all of the data and metadata from multiple variables can 
 be read from multiple CDF files ... in one single, simple command.  The 
 function is called 'spd_cdawlib_read_mycdf' and it returns an anonymous structure of
 the form:

       structure_name.variable_name.attribute_name.attribute_value

 From this structure, all data and metadata for the requested variables
 is easily accessed.

 AUTHOR:
       Richard Burley, NASA/GSFC/Code 632.0, Feb 13, 1996
       burley@nssdca.gsfc.nasa.gov    (301)286-2864
 
 NOTES:

 Three additional 'attributes' will be included in the sub-structure for 
 each variable.  The first is the 'VARNAME' field.  Because IDL structure
 tags are always uppercase, and because CDF variable names are case sen-
 sitive, a case sensitive copy of the variable name is created.  The second
 'attribute' to be added is the 'CDFTYPE' field.  This field will hold a
 string value holding the cdf data type.  The last 'attribute' to be
 artificially added will be either the 'DAT' field or, if the keyword
 NODATASTRUCT is set, the 'HANDLE' field.  The 'DAT' field will contain
 the actual data values read from the CDF's for the variable.  The 'HANDLE'
 field will hold a handle_id where the data will reside.

 This package will look for and utilize certain special attributes required
 by the International Solar Terrestrial Physics Key Parameters Generation
 Software Standards and Guidelines.  The existance of these attributes is
 not required for the operation of this software, but will enhance its
 usefullness, primarily by reading variables that will be needed for proper
 utilization of the data, even though you may not have asked for them 
 explicitly.

 This package was tested under IDL version 4.0.1b.  This package was tested
 on CDF's up to version 2.5 and on both r-variables and z-variables.

 CDF variables defined as unsigned integers are, unfortunately, currently
 returned by the IDL CDF_VARGET procedure as signed integers.  This can
 cause sign flips.  This software detects and corrects for this defect for
 data values.  However, it cannot detect and correct for this defect for
 attribute values because the IDL procedure CDF_ATTINQ does not return the
 CDF data type of the attribute.  These problems have been reported to
 RSI.


 Modifications: 
	As of October 2, 2000, this software can run on all of the following
	IDL versions, 5.1, 5.2 and 5.3 (testing for 5.4 will commence soon).
	Some fairly major changes were necessary in order for spd_cdawlib_read_mycdf
	to work under 5.3.  IDL 5.3 enforces the variable naming rules for
	structure tag names.  This change affects this s/w because we basically
	had never checked our tag names, e.g. we used the CDF variable names
	and label attribute values directly.  So in spd_cdawlib_read_mycdf the general
	concept to fixing this problem was to set up a table (which is shared
	in a common block - not my favorite way to go, but definitely the 
	easiest), where there are two tags, equiv and varname.  varname 
	contains the real CDF variable name, equiv contains the "cleaned up,
	IDL acceptable" variable name that can be used as a structure tag
	name... TJK 04/02/2000

 1996, NASA/Goddard Space Flight Center
 This software may be used, copied, or redistributed as long as it is not
 sold and this copyright notice is reproduced on each copy made.  This
 routine is provided as is without any express or implied warranties
 whatsoever.

(See external/spdfcdas/spd_cdawlib/spd_cdawlib_read_mycdf.pro)


SPD_CDAWLIB_READ_MYCDF[2]

[Previous Routine] [Next Routine] [List of Routines]
 NAME: spd_cdawlib_amI_istpptr
 PURPOSE:
       Return true(1) or false(0) depending on whether or not the
       given attribute name qualifies as an ISTP pointer-class attribute.
 CALLING SEQUENCE:
	out = spd_cdawlib_amI_istpptr(attribute_name)
 INPUTS:
	attribute_name = name of a CDF attribute as a string
 KEYWORD PARAMETERS:
 OUTPUTS:
       True(1) or False(0)
 AUTHOR:
       Richard Burley, NASA/GSFC/Code 632.0, Feb 13, 1996
       burley@nssdca.gsfc.nasa.gov    (301)286-2864
 MODIFICATION HISTORY:

(See external/spdfcdas/spd_cdawlib/spd_cdawlib_read_mycdf.pro)


SPD_CDAWLIB_READ_MYCDF[2]

[Previous Routine] [Next Routine] [List of Routines]
 NAME: spd_cdawlib_ami_var
 PURPOSE:
       Return true(1) or false(0) depending on whether or not the
       given attribute name's value is assigned to a real CDF variable name.
 CALLING SEQUENCE:
	out = spd_cdawlib_ami_var(attribute_name)
 INPUTS:
	attribute_name = name of a CDF attribute as a string
 KEYWORD PARAMETERS:
 OUTPUTS:
       True(1) or False(0)
 AUTHOR:
	Tami Kovalick	March 6, 2000

 MODIFICATION HISTORY:

(See external/spdfcdas/spd_cdawlib/spd_cdawlib_read_mycdf.pro)


SPD_CDAWLIB_READ_MYCDF[3]

[Previous Routine] [Next Routine] [List of Routines]
 NAME: spd_cdawlib_parse_display_type
 PURPOSE: 
	Parse and examine the input string.  It should be the value of the
	CDF attribute 'DISPLAY_TYPE'.  Return an array of variable names
       that it 'points' to.
 CALLING SEQUENCE:
	out = spd_cdawlib_parse_display_type(instring)
 INPUTS:
       instring = string, value of a CDF attribute called 'DISPLAY_TYPE'
 KEYWORD PARAMETERS:
 OUTPUTS:
       out = string array, names of other variables required for display
 NOTES: This routine expects to find 'DISPLAY_TYPE' values looking like:
        PLOT_TYPE>x=vname,y=vname ...
        PLOT_TYPE>y=vname,z=vname(*,1),z=vname(*,2) ...
 AUTHOR:
       Richard Burley, NASA/GSFC/Code 632.0, Feb 13, 1996
       burley@nssdca.gsfc.nasa.gov    (301)286-2864
 MODIFICATION HISTORY:
TJK modified 01/27/98 to not parse orbit display type here - the items
specified for the orbit plot type aren't additional variables.
TJK modified 09/25/2001 to not parse the "symsize" keyword because its
value isn't a variable.

(See external/spdfcdas/spd_cdawlib/spd_cdawlib_read_mycdf.pro)


SPD_CDAWLIB_READ_MYCDF[4]

[Previous Routine] [Next Routine] [List of Routines]
 NAME: spd_cdawlib_follow_mydepends
 PURPOSE: 
	Search the metadata anonymous structure for ISTP 'DEPEND' attributes.
       If and when found, add the variable name that it points to to the
       vnames array if it is not already present, and increase the size
       of the dhids and mhids arrays.
 CALLING SEQUENCE:
       spd_cdawlib_follow_mydepends, metadata, vnames, dhids, mhids
 INPUTS:
       metadata = anonymous structure holding attribute values
       vnames   = string array of the names of variables already processed
       vvarys   = string array of the record variance for each variable
       dhids    = array of data handle id's
       mhids    = array of metadata handle id's
 KEYWORD PARAMETERS:
 OUTPUTS:
       dhids    = array of data handle id's
       mhids    = array of metadata handle id's
 AUTHOR:
       Richard Burley, NASA/GSFC/Code 632.0, Feb 13, 1996
       burley@nssdca.gsfc.nasa.gov    (301)286-2864
 MODIFICATION HISTORY:

(See external/spdfcdas/spd_cdawlib/spd_cdawlib_read_mycdf.pro)


SPD_CDAWLIB_READ_MYCDF[5]

[Previous Routine] [Next Routine] [List of Routines]
 NAME: spd_cdawlib_append_mydata
 PURPOSE: 
 	Append the 'new' data to the 'old' data using array concatenation.
 CALLING SEQUENCE:
       out = spd_cdawlib_append_mydata(new,old)
 INPUTS:
       new = data to be appended to the old data
       old = older data that new data is to be appended to
 KEYWORD PARAMETERS:
 OUTPUTS:
       out = product of concatenating the old and new data arrays
 NOTES:
 	Special case check: if old data was from either a skeleton CDF or from
 	a CDF with only a single record, then the last dimension was dropped 
	during the process of saving/retrieving the data from a handle.  
	Must compare the dimensionality of the new and old data to determine 
	if this drop has occured, and if so, reform the old data to include 
       the extra dimension so that the data can be appended.
 AUTHOR:
       Richard Burley, NASA/GSFC/Code 632.0, Feb 13, 1996
       burley@nssdca.gsfc.nasa.gov    (301)286-2864
 MODIFICATION HISTORY:

(See external/spdfcdas/spd_cdawlib/spd_cdawlib_read_mycdf.pro)


SPD_CDAWLIB_READ_MYCDF[6]

[Previous Routine] [Next Routine] [List of Routines]
 NAME: spd_cdawlib_add_mydepends
 PURPOSE: 
	Search the metadata anonymous structure for ISTP 'DEPEND' 
	attributes and add the variable name that it points to to the
       vnames array if it is not already present.  If the DEPEND
	variable is not present in the list, change the data_type so it
	won't be plotted.

 CALLING SEQUENCE:
       spd_cdawlib_add_mydepends, metadata, vnames

 INPUTS:
       metadata = anonymous structure holding attribute values
       vnames   = string array of virtual variables found

 OUTPUTS:
       vnames    = modified variable name that includes component variable
                   names

 NOTES - this is similar to spd_cdawlib_follow_mydepends, except it does less.

 AUTHOR:
 	Tami Kovalick, QSS,   11/29/2006

(See external/spdfcdas/spd_cdawlib/spd_cdawlib_read_mycdf.pro)


SPD_CDAWLIB_READ_MYCDF[7]

[Previous Routine] [Next Routine] [List of Routines]
 NAME: spd_cdawlib_add_mycomponents
 PURPOSE: 
	Search the metadata anonymous structure for ISTP 'COMPONENT' 
	attributes and add the variable name that it points to to the
       vnames array if it is not already present.  If the component
	variable is not present in the list, change the data_type so it
	won't be plotted.

 CALLING SEQUENCE:
       spd_cdawlib_add_mycomponents, metadata, vnames

 INPUTS:
       metadata = anonymous structure holding attribute values
       vnames   = string array of virtual variables found

 OUTPUTS:
       vnames    = modified variable name that includes component variable
                   names

 AUTHOR:
 	Carrie Gallap, Raytheon STX,   1/5/98

(See external/spdfcdas/spd_cdawlib/spd_cdawlib_read_mycdf.pro)


SPD_CDAWLIB_READ_MYCDF[8]

[Previous Routine] [Next Routine] [List of Routines]
 NAME: spd_cdawlib_read_myvariable
 PURPOSE: 
	Return the data for the requested variable.
 CALLING SEQUENCE:
       out = spd_cdawlib_read_myvariable(vname, CDFid, vary, dtype, recs)
 INPUTS:
       vname = string, name of variable to be read from the CDF
       CDFid = integer, id or already opened CDF file.
 KEYWORD PARAMETERS:
	START_REC = first record to read.
	REC_COUNT = number of records to read.
 OUTPUTS:
       out = all data from the CDF for the variable being read
       vary = True(1) or False(0) is variable record-varying
       dtype= string, CDF data type
       recs = integer, number of data records
 AUTHOR:
       Richard Burley, NASA/GSFC/Code 632.0, Feb 13, 1996
       burley@nssdca.gsfc.nasa.gov    (301)286-2864
 MODIFICATION HISTORY:
       96/04/11 : R.Burley :zVar handling when MAXRECS = -1 changed to
                            read REC_COUNT of MAXRECS + 2 & return,DAT
 	96/12/20 ; T. Kovalick modified to take START_REC and REC_COUNT
	keywords (see above).  If they aren't set you will get all of
 	the records in a cdf.

(See external/spdfcdas/spd_cdawlib/spd_cdawlib_read_mycdf.pro)


SPD_CDAWLIB_READ_MYCDF[9]

[Previous Routine] [Next Routine] [List of Routines]
 NAME: spd_cdawlib_read_myattribute
 PURPOSE: 
	Return the value of the requested attribute for the requested variable.
 CALLING SEQUENCE:
       out = spd_cdawlib_read_myattribute(vname,anum,CDFid)
 INPUTS:
       vname = string, name of variable whose attribute is being read
       anum = integer, number of attribute being read
       CDFid = integer, id of already opened CDF file.
 KEYWORD PARAMETERS:
 OUTPUTS:
       out = anonymous structure holding both the name of the attribute
             and the value of the attribute
 AUTHOR:
       Richard Burley, NASA/GSFC/Code 632.0, Feb 13, 1996
       burley@nssdca.gsfc.nasa.gov    (301)286-2864

 MODIFICATION HISTORY:
   	RCJ 11/2003 Added keyword isglobal

(See external/spdfcdas/spd_cdawlib/spd_cdawlib_read_mycdf.pro)


SPD_CDAWLIB_STR_ELEMENT

[Previous Routine] [Next Routine] [List of Routines]
PROCEDURE:  spd_cdawlib_str_element, struct,  tagname, value
PURPOSE:
 Find (or add) an element of a structure.
 
 Input:
   struct,  generic structure
   tagname,    string  (tag name)
 Output:
   value,  Named variable in which value of the structure element is returned.
 Purpose:
   Retrieves the value of a structure element.  This function will not produce
   an error if the tag and/or structure does not exist.
KEYWORDS:
  SUCCESS:  Named variable that will contain a 1 if the element was found
     or a 0 if not found.
  INDEX: a named variable in which the element index is returned.  The index
     will be -2 if struct is not a structure,  -1 if the tag is not found,
     and >= 0 if successful.
  ADD_REPLACE:  Set this keyword to add or replace a structure element.
  DELETE:   Set this keyword to delete the tagname.
  CLOSEST:  Set this keyword to allow near matchs (useful with _extra)
  VALUE: (obsolete) alternate method of returning value. (Will not work with recursion)
Notes:
  1. Value remains unchanged if the structure element does not exist.
  2. If tagname contains a '.' then the structure is recursively searched and
       index will be an array of indices.
  3. If struct is an array then results may be unpredictable.
  4. Elements may be inserted into embedded structures, by including the
       embedded structure name in the tagname string.(example below)

Examples:
    Does an element exist?
    spd_cdawlib_str_element,my_str,'my_tag_name',SUCCESS=s
    What is an element's value?
    spd_cdawlib_str_element,my_str,'my_tag_name',v
    Add an element
    spd_cdawlib_str_element,my_str,'my_tag_name','value',/add
    Add an element to embedded structure:
    spd_cdawlib_str_element,my_str,'my_substr_name.my_tag_name','value',/add

Modifications:
  5/7/97: Added recursive searching of structure hierarchy.  D. Larson
  2014-1-20 : Added mulidimensional elements for arrays of structures

CREATED BY:    Davin Larson
FILE:  spd_cdawlib_str_element.pro
VERSION  1.10
LAST MODIFICATION: 01/10/08
 CREATED BY: Davin Larson
 $LastChangedBy: nikos $
 $LastChangedDate: 2018-02-25 14:58:49 -0800 (Sun, 25 Feb 2018) $
 $LastChangedRevision: 24774 $
 $URL: svn+ssh://thmsvn@ambrosia.ssl.berkeley.edu/repos/spdsoft/tags/spedas_4_0/external/spdfcdas/spd_cdawlib/spd_cdawlib_str_element.pro $

(See external/spdfcdas/spd_cdawlib/spd_cdawlib_str_element.pro)


SPD_CDAWLIB_VIRTUAL_FUNCS[10]

[Previous Routine] [Next Routine] [List of Routines]
 NAME: Function spd_cdawlib_conv_pos_HUNGARIAN 

 PURPOSE: Convert cl_sp_aux positions x,y,z from GSE to GEI (GCI).
          It could be confusing to the user that the GSE positions
          are given in 'reference s/c position' and 'delta s/c positions'
          while all GEI positions will be their real positions, ie, no
          reference s/c and no deltas. 

 INPUT:
    buf           an IDL structure
    org_names     an array of original variables sent to spd_cdawlib_read_mycdf
    index	   variable position in buf

 CALLING SEQUENCE:

         newbuf = spd_cdawlib_conv_pos_hungarian(buf,org_names,index=index)


unction spd_cdawlib_conv_pos_hungarian, buf, org_names,INDEX=INDEX

tatus=0
 Establish error handler
catch, error_status
if(error_status ne 0) then begin
   print, "ERROR= number: ",error_status," in spd_cdawlib_conv_pos_hungarian.pro"
   print, "ERROR= Message: ",!ERR_STRING
   status = -1
   return, status
endif
agnames = tag_names(buf)
agnames1=tag_names(buf.(index))

 look for the COMPONENT_0 attribute tag for this VV.
f(spd_cdawlib_tagindex('COMPONENT_0', tagnames1) ge 0) then begin
  component0=buf.(index).COMPONENT_0
  ; Check if the component0 variable exists 
  component0_index = spd_cdawlib_tagindex(component0,tagnames)
  ; get coordinates
  handle_value,buf.(component0_index).handle,gse_xyz
ndif

 look for the COMPONENT_1 attribute tag for this VV.
f(spd_cdawlib_tagindex('COMPONENT_1', tagnames1) ge 0) then begin
  component1=buf.(index).COMPONENT_1
  component1_index = spd_cdawlib_tagindex(component1,tagnames)
  if (component1_index ne -1) then handle_value,buf.(component1_index).handle,gse_dx_xyz
ndif

 get time values
f(spd_cdawlib_tagindex('DEPEND_0', tagnames1) ge 0) then $
  depend0=buf.(index).DEPEND_0
 Check if the depend0 variable exists 
epend0_index = spd_cdawlib_tagindex(depend0,tagnames)
 get time
andle_value,buf.(depend0_index).handle,depend0

 calculate xyz in gei from gse. Add delta to gse if this is s/c 1,2, or 4
f (component1_index ne -1) then gse_xyz=gse_xyz+gse_dx_xyz
ei_xyz=gse_xyz  ; actual values will be replaced

ear=0 & month=0 & day=0 & hour=0 & minute=0 & sec=0 ; init params for recalc
or i=0L,n_elements(gei_xyz[0,*])-1 do begin
  recalc,year,day,hour,min,sec,epoch=depend0[i] ; setup conversion values
  ; Create scalar variables required when calling geopack routines
  geigse,xgei,ygei,zgei,gse_xyz[0,i],gse_xyz[1,i],gse_xyz[2,i],-1,depend0[i]
  ;
  gei_xyz[0,i]=xgei
  gei_xyz[1,i]=ygei
  gei_xyz[2,i]=zgei
ndfor

uf.(index).handle=handle_create()
andle_value,buf.(index).handle,gei_xyz,/set

 Check that all variables in the original variable list are declared as
 data otherwise set to support_data
 Find variables w/ var_type == data
tatus = spd_cdawlib_check_myvartype(buf, org_names)

eturn, buf


nd


Correct FAST DCF By
UNCTION spd_cdawlib_correct_fast_by, buf, org_names, INDEX=INDEX, DEBUG=DEBUG

;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;

  PURPOSE:

 Sign switch is required because Westward component has incorrect 
 sign for that portion of the FAST orbit where the spacecraft is 
 moving from high to low latitudes.
 For high to low latitude orbits the spin-axis is Westward
 For low to high latitude orbist the spin-axis is Eastward
 Magnetometer data in original key-parameter files appear to be 
 in the minus spin-axis direction.
 Algorithm developed by R. J. Strangeway (UCLA), March 27,2012

 CALLING SEQUENCE:

          new_buf = spd_cdawlib_convert_ni(buf,org_names,index=index)

 VARIABLES:

 Input:

  buf        - an IDL structure built w/in spd_cdawlib_read_mycdf
  org_names  - list of original variables input to spd_cdawlib_read_mycdf. Any
               variables in this list will remain tagged as 
               VAR_TYPE= data otherwise VAR_TYPE = support_data.

 Output:

  new_buf    - an IDL structure containing the populated virtual 
               variable 
 Constants:


 Keyword Parameters: 
 index of variable to populate.

 REQUIRED PROCEDURES:

   none 
 

(See external/spdfcdas/spd_cdawlib/spd_cdawlib_virtual_funcs.pro)


SPD_CDAWLIB_VIRTUAL_FUNCS[11]

[Previous Routine] [Next Routine] [List of Routines]
 NAME: Function spd_cdawlib_compute_cadence

 PURPOSE: Determine the resolution between epoch values so that one
 can easily see where the "burst" data is located.  Originally
 implemented for the messenger_mag_rtn dataset.


 INPUT:
    buf           an IDL structure
    org_names     an array of original variables sent to spd_cdawlib_read_mycdf
    index	   variable position in buf

 CALLING SEQUENCE:

         newbuf = spd_cdawlib_compute_cadence(buf,org_names,index=index)


unction spd_cdawlib_compute_cadence, buf, org_names,INDEX=INDEX

tatus=0
 Establish error handler
atch, error_status
f(error_status ne 0) then begin
  print, "ERROR= number: ",error_status," in spd_cdawlib_compute_cadence"
  print, "ERROR= Message: ",!ERR_STRING
  status = -1
  return, status
ndif
agnames = tag_names(buf)
agnames1=tag_names(buf.(index))

 look for the COMPONENT_0 attribute tag for this VV.
f(spd_cdawlib_tagindex('COMPONENT_0', tagnames1) ge 0) then begin
  component0=buf.(index).COMPONENT_0
  ; Check if the component0 variable exists 
  component0_index = spd_cdawlib_tagindex(component0,tagnames)
  ; get epoch
  handle_value,buf.(component0_index).handle,epoch
ndif

 calculate the cadence from one epoch to the next.
um_epochs = n_elements(epoch)

 Modification made by Ron Yurow (11/13/2014)
 Check to make sure that CDF contains at least three records in order to
 correctly compute a cadence.
 Removed by Ron Yurow (11/14/2014)
 So that an actual cadence will be returned no matter how many records are
 the CDF contains.
if (num_epochs lt 3) then begin 
   print, "ERROR= error detected in spd_cdawlib_compute_cadence"
   print, "ERROR= Message: Not enough epoch values to correctly compute cadence values."
   status = -1
   return, status
endif

adence = make_array(num_epochs, /double)
 Modification made by Ron Yurow (11/14/2014)
 Added special cases to handle when there are only 1 or 2 epochs in the CDF
 A single epoch will result in a cadence of the FILLVAL
 Two epochs will actually result in reasonable values for cadence.
 I think .... 
ase num_epochs of 
:   cadence[0] = buf.(component0_index).fillval
:   begin
      cadence[0] = epoch[1]-epoch[0]
      cadence[1] = epoch[1]-epoch[0]
    end
lse: begin
      cadence[0] = epoch[1]-epoch[0]
      cadence[num_epochs-1] = epoch[num_epochs-1]-epoch[num_epochs-2]

      for i=1L,num_epochs-2 do begin
          if(epoch[i+1]-epoch[i]) < (epoch[i]-epoch[i-1])then $
          cadence[i] = epoch[i+1]-epoch[i] else cadence[i] = epoch[i]-epoch[i-1]
      endfor
    end
ndcase

uf.(index).handle=handle_create()
andle_value,buf.(index).handle,cadence,/set

 Check that all variables in the original variable list are declared as
 data otherwise set to support_data
 Find variables w/ var_type == data
tatus = spd_cdawlib_check_myvartype(buf, org_names)

eturn, buf


nd

Function: spd_cdawlib_apply_rtn_qflag
Purpose: To use the quality variable to "filter out bad messenger 
data points"
Author: Tami Kovalick, Adnet, May, 2012


unction spd_cdawlib_apply_rtn_qflag, astruct, orig_names, index=index

Input: astruct: the structure, created by spd_cdawlib_read_mycdf that should
		 contain at least one Virtual variable.
	orig_names: the list of varibles that exist in the structure.
	index: the virtual variable (index number) for which this function
		is being called to compute.  If this isn't defined, then
		the function will find the 1st virtual variable.

this code assumes that the Component_0 is the "parent" variable, 
Component_1 should be the filter/quality variable.

astruct will contain all of the variables and metadata necessary
to filter out the bad flux values (based on the filter variables values -
a value != 222 or 223. 

tags = tag_names(astruct) ;get the variable names.
v_tagnames=strarr(1)
v_tagindx = spd_cdawlib_vv_names(astruct,names=vv_tagnames) ;find the virtual vars

f keyword_set(index) then begin
 index = index
ndif else begin ;get the 1st vv

 index = vv_tagindx[0]
 if (vv_tagindx[0] lt 0) then return, -1

ndelse

print, 'In spd_cdawlib_apply_rtn_qflag'
print, 'Index = ',index
print, 'Virtual variable ', atags(index)
print, 'original variables ',orig_names
help, /struct, astruct
stop;
_0 = astruct.(index).COMPONENT_0 ;1st component var (real flux var)

f (c_0 ne '') then begin ;this should be the real data
 var_idx = spd_cdawlib_tagindex(c_0, atags)
 itags = tag_names(astruct.(var_idx)) ;tags for the real data.

 d = spd_cdawlib_tagindex('DAT',itags)
   if (d[0] ne -1) then  parent_data = astruct.(var_idx).DAT $
   else begin
     d = spd_cdawlib_tagindex('HANDLE',itags)
     handle_value, astruct.(var_idx).HANDLE, parent_data
   endelse
 fill_val = astruct.(var_idx).fillval

ndif else print, 'spd_cdawlib_apply_rtn_qflag - parent variable not found'

ata_size = size(parent_data)

f (data_size[1] gt 0) then begin 

_0 = astruct.(index).COMPONENT_1 ; should be the quality variable

f (c_0 ne '') then begin ;
 var_idx = spd_cdawlib_tagindex(c_0, atags)
 itags = tag_names(astruct.(var_idx)) ;tags for the real data.

 d = spd_cdawlib_tagindex('DAT',itags)
   if (d[0] ne -1) then  quality_data = astruct.(var_idx).DAT $
   else begin
     d = spd_cdawlib_tagindex('HANDLE',itags)
     handle_value, astruct.(var_idx).HANDLE, quality_data
   endelse
 
ndif else print, 'Quality variable not found'

help, quality_data
stop;

emp = where((quality_data ne 222 and quality_data ne 223), badcnt)
f (badcnt ge 1) then begin
 print, 'found some bad rtn data, replacing ',badcnt, ' out of ', data_size[1],' values with fill.'
 parent_data[temp] = fill_val
ndif else begin
 print, 'All ',astruct.(index).COMPONENT_0,' data good'
ndelse

now, need to fill the virtual variable data structure with this new data array
and "turn off" the original variable.


print, 'badcnt',badcnt
help, parent_data
stop;

emp = handle_create(value=parent_data)

struct.(index).HANDLE = temp

arent_data = 1B
uality_data = 1B

 Check astruct and reset variables not in orignal variable list to metadata,
 so that variables that weren't requested won't be plotted/listed.

  status = spd_cdawlib_check_myvartype(astruct, orig_names)

eturn, astruct

ndif else return, -1 ;if there's no rtn B radial/tangent/normal data return -1

nd

Function: spd_cdawlib_apply_rtn_cadence
Purpose: To use the quality variable to "filter out values
when the time cadence is less than 200.
Author: Tami Kovalick, Adnet, May, 2012


unction spd_cdawlib_apply_rtn_cadence, astruct, orig_names, index=index

Input: astruct: the structure, created by spd_cdawlib_read_mycdf that should
		 contain at least one Virtual variable.
	orig_names: the list of varibles that exist in the structure.
	index: the virtual variable (index number) for which this function
		is being called to compute.  If this isn't defined, then
		the function will find the 1st virtual variable.

this code assumes that the Component_0 is the "parent" variable, 
Component_1 should be the filter/quality variable.

astruct will contain all of the variables and metadata necessary
to filter out the values where the time cadence is less than 200. 

tags = tag_names(astruct) ;get the variable names.
v_tagnames=strarr(1)
v_tagindx = spd_cdawlib_vv_names(astruct,names=vv_tagnames) ;find the virtual vars
f keyword_set(index) then begin
 index = index
ndif else begin ;get the 1st vv

 index = vv_tagindx[0]
 if (vv_tagindx[0] lt 0) then return, -1

ndelse

print, 'In spd_cdawlib_apply_rtn_cadence'
print, 'Index = ',index
print, 'Virtual variable ', atags(index)
print, 'original variables ',orig_names
help, /struct, astruct
stop;
_0 = astruct.(index).COMPONENT_0 ;1st component var (real variable)

f (c_0 ne '') then begin ;this should be the real data
 var_idx = spd_cdawlib_tagindex(c_0, atags)
 itags = tag_names(astruct.(var_idx)) ;tags for the real data.

 d = spd_cdawlib_tagindex('DAT',itags)
   if (d[0] ne -1) then  parent_data = astruct.(var_idx).DAT $
   else begin
     d = spd_cdawlib_tagindex('HANDLE',itags)
     if (astruct.(var_idx).HANDLE ne 0) then begin
       handle_value, astruct.(var_idx).HANDLE, parent_data
     endif else begin ;need to call the virtual function to compute the quality variables when they don't exist
         astruct = spd_cdawlib_apply_rtn_qflag(temporary(astruct),orig_names,index=var_idx)
         handle_value, astruct.(var_idx).HANDLE, parent_data
     endelse

   endelse
 fill_val = astruct.(var_idx).fillval

ndif else print, 'spd_cdawlib_apply_rtn_cadence - parent variable not found'


ata_size = size(parent_data)
ype_code = size(parent_data,/type)

f (data_size[1] gt 0) then begin 

_0 = astruct.(index).COMPONENT_1 ; should be the time cadence variable

f (c_0 ne '') then begin ;
 var_idx = spd_cdawlib_tagindex(c_0, atags)
 itags = tag_names(astruct.(var_idx)) ;tags for the real data.

 d = spd_cdawlib_tagindex('DAT',itags)
   if (d[0] ne -1) then  cadence_data = astruct.(var_idx).DAT $
   else begin
     d = spd_cdawlib_tagindex('HANDLE',itags)
     if (astruct.(var_idx).HANDLE ne 0) then begin
       handle_value, astruct.(var_idx).HANDLE, cadence_data
     endif else begin ;need to call the virtual function to compute the epoch_cadence when it doesn't exist yet.
         astruct = spd_cdawlib_compute_cadence(temporary(astruct),orig_names,index=var_idx)
         handle_value, astruct.(var_idx).HANDLE, cadence_data

     endelse
   endelse
 
ndif else print, 'Cadence variable not defined'
emp = where((cadence_data gt 200), tcnt)
good = data_size[1] - tcnt
if (tcnt ge 1) then begin
f (ngood ge 1) then begin
 print, 'removing rtn data gt 200, making a smaller array, original = ',data_size[1],' new size = ', ngood
 new_data = make_array(ngood, type=type_code)
 new_data = parent_data[temp]
ndif else begin
 new_data = make_array(1, type=type_code)
 new_data[0] = fill_val
 print, 'No cadence <200 data found for ',astruct.(index).COMPONENT_0
ndelse

now, need to fill the virtual variable data structure with this new data array
and "turn off" the original variable.


print, 'tcnt',tcnt
help, new_data
stop;


emp = handle_create(value=new_data)

struct.(index).HANDLE = temp
arent_data = 1B
adence_data = 1B

 Check astruct and reset variables not in orignal variable list to metadata,
 so that variables that weren't requested won't be plotted/listed.

  status = spd_cdawlib_check_myvartype(astruct, orig_names)

eturn, astruct

ndif else return, -1 ;if there's no rtn data return -1

nd

(See external/spdfcdas/spd_cdawlib/spd_cdawlib_virtual_funcs.pro)


SPD_CDAWLIB_VIRTUAL_FUNCS[12]

[Previous Routine] [Next Routine] [List of Routines]
 NAME: Function spd_cdawlib_make_stack_array

 PURPOSE: take the array of data specified by component_0
 and apply the array reduction specified in the display_type
 place the result in the return buffer.

 CALLING SEQUENCE:

          new_buf = spd_cdawlib_make_stack_array(buf,org_names)

 VARIABLES:

 Input:

  astruct    - an IDL structure built w/in spd_cdawlib_read_mycdf
  org_names  - list of original variables input to spd_cdawlib_read_mycdf. Any
               variables in this list will remain tagged as
               VAR_TYPE= data otherwise VAR_TYPE = support_data.
  index - keyword - if set use this index value to find the virtual 
                    variable, otherwise, find the 1st vv in the structure.

 Output:

  new_buf    - an IDL structure containing the populated virtual
               variable

 Keyword Parameters:


 REQUIRED PROCEDURES:

   none

(See external/spdfcdas/spd_cdawlib/spd_cdawlib_virtual_funcs.pro)


SPD_CDAWLIB_VIRTUAL_FUNCS[13]

[Previous Routine] [Next Routine] [List of Routines]
 NAME: Function spd_cdawlib_fix_sparse

 PURPOSE: take the array of data specified by component_0
 and replace all fill values w/ the preceding non-fill value - 
 place the result in the return buffer.

 CALLING SEQUENCE:

          new_buf = spd_cdawlib_fix_sparse(buf,org_names)

 VARIABLES:

 Input:

  astruct    - an IDL structure built w/in read_myCDF
  org_names  - list of original variables input to read_myCDF. Any
               variables in this list will remain tagged as
               VAR_TYPE= data otherwise VAR_TYPE = support_data.
  index - keyword - if set use this index value to find the virtual 
                    variable, otherwise, find the 1st vv in the structure.

 Output:

  new_buf    - an IDL structure containing the populated virtual
               variable

 Keyword Parameters:


 REQUIRED PROCEDURES:

   none

(See external/spdfcdas/spd_cdawlib/spd_cdawlib_virtual_funcs.pro)


SPD_CDAWLIB_VIRTUAL_FUNCS[1]

[Previous Routine] [Next Routine] [List of Routines]

 NAME: Function spd_cdawlib_vtype_names

 PURPOSE: Returns array of names or index numbers where the var_type is
          equal to vtype (eg."data").


unction spd_cdawlib_vtype_names, buf, vtype, NAMES=vNAMES

 tagnames = tag_names(buf)
 tagnums = n_tags(buf)
 vnames=strarr(tagnums)
 vindices=intarr(tagnums)
 Determine names and indices
  ii=0
  for i=0, tagnums-1 do begin
   tagnames1=tag_names(buf.(i))
   if(spd_cdawlib_tagindex('VAR_TYPE', tagnames1) ge 0) then begin
       if(buf.(i).VAR_TYPE eq vtype) then begin
       ;if(buf.(i).VAR_TYPE eq 'data') then begin
          vnames[ii]=tagnames[i]
          vindices(ii)=i
          ii=ii+1
       endif
   endif
  endfor

  wc=where(vnames ne '',wcn)
  if(wc[0] lt 0) then begin
   vnames[0]=wc
   vindices[0]=wc
  endif else begin
   vnames=vnames[wc]
   vindices=vindices[wc]
  endelse

Jan. 6, 2003 - TJK added the "or (n_elements..." below because in IDL 5.6 
if the NAMES keyword is set as "" in the calling routine, IDL doesn't think
the keyword is set (as it does in previous IDL versions).

if(keyword_set(NAMES) or (n_elements(names) gt 0)) then begin
	NAMES=vnames
endif
eturn, vindices
nd

+

 NAME: Function Trap 

 PURPOSE: Trap malformed idl structures or invalid arguments. 

 INPUT;  a   an idl structure

unction spd_cdawlib_buf_trap, a 

 ibad=0
 str_tst=size(a)
 if(str_tst(str_tst[0]+1) ne 8) then begin
   ibad=1
   v_data='DATASET=UNDEFINED'
   v_err='ERROR=a'+strtrim(string(i),2)+' not a structure.'
   v_stat='STATUS=Cannot plot this data'
   a=create_struct('DATASET',v_data,'ERROR',v_err,'STATUS',v_stat)
 endif else begin
 Test for errors trapped in spd_cdawlib_conv_map_image
  atags=tag_names(a)
  rflag=spd_cdawlib_tagindex('DATASET',atags)
  if(rflag[0] ne -1) then ibad=1
 endelse

eturn, ibad
nd

+

 NAME: Function spd_cdawlib_vv_names

 PURPOSE: Returns array of virtual variable names or index numbers.


unction spd_cdawlib_vv_names, buf, NAMES=NAMES

 tagnames = tag_names(buf)
 tagnums = n_tags(buf)
 vnames=strarr(tagnums)
 vindices=intarr(tagnums)
 Determine names and indices
  ii=0
  for i=0, tagnums-1 do begin
   tagnames1=tag_names(buf.(i))
   if(spd_cdawlib_tagindex('VIRTUAL', tagnames1) ge 0) then begin
       if(buf.(i).VIRTUAL) then begin
          vnames[ii]=tagnames[i]
          vindices[ii]=i
          ii=ii+1
       endif
   endif
  endfor
  wc=where(vnames ne '',wcn)
  if(wc[0] lt 0) then begin
   vnames[0]=wc
   vindices[0]=wc
  endif else begin
   vnames=vnames[wc]
   vindices=vindices[wc]
  endelse

TJK IDL6.1 doesn't recognize this keyword as being set since
its defined as a strarr(1)...
if(keyword_set(NAMES)) then NAMES=vnames
f(n_elements(NAMES)) then begin
AMES=vnames
ndif
eturn, vindices 
nd

(See external/spdfcdas/spd_cdawlib/spd_cdawlib_virtual_funcs.pro)


SPD_CDAWLIB_VIRTUAL_FUNCS[2]

[Previous Routine] [Next Routine] [List of Routines]
 NAME: Function spd_cdawlib_check_myvartype

 PURPOSE:
 Check that all variables in the original variable list are declared as
 data otherwise set to ignore_data
 Find variables w/ var_type == data

 CALLING SEQUENCE:

          status = spd_cdawlib_check_myvartype(buf,org_names)

 VARIABLES:

 Input:
  buf        - an IDL structure built w/in spd_cdawlib_read_mycdf
  org_names  - list of original variables input to spd_cdawlib_read_mycdf. Any
               variables in this list will remain tagged as
               VAR_TYPE= data otherwise VAR_TYPE = metadata.

 Output:
  buf    - an IDL structure containing the populated virtual
               variables
  status - 0 ok else failed
 
 Keyword Parameters:


 REQUIRED PROCEDURES:

unction spd_cdawlib_check_myvartype, nbuf, org_names
  status=0
  var_names=strarr(1)
  var_indices = spd_cdawlib_vtype_names(nbuf,'data',NAMES=var_names)
  if(var_indices[0] lt 0) then begin
    print, "STATUS= No variable of type DATA detected."
    print, "ERROR= No var_type=DATA variable found in spd_cdawlib_check_myvartype.pro"
    print, "ERROR= Message: ",var_indices[0]
    status = -1
    return, status
  endif
  org_names=strupcase(org_names)
  
  ; RCJ 08/29/2012   Let's find all 'components'. We'll need this list below.
  compnames=[''] 
  for i=0, n_elements(var_indices)-1 do begin
     tnames=tag_names(nbuf.(i))
     for k=0,n_elements(tnames)-1 do begin
        pos = strpos(tnames[k],'COMPONENT_')
        if (pos eq 0) then compnames=[compnames,nbuf.(var_indices[i]).(k)]
     endfor
  endfor   
    
  for i=0, n_elements(var_indices)-1 do begin
     wc=where(org_names eq var_names[i],wcn)
     if(wc[0] lt 0) then begin  ; this is not the originally requested var.
    ;   print,'***** not requested, make support_data : ',var_names[i]
       nbuf.(var_indices[i]).var_type = 'support_data'
       ;
       wc1=where(strupcase(compnames) eq var_names[i])
       if (wc1[0] ne -1) then nbuf.(var_indices[i]).var_type='additional_data'
   ;    if (wc1[0] ne -1) then print,'********** and a component, make additional_data: ',nbuf.(var_indices[i]).varname
     endif
  endfor   
  ;  Old logic: (RCJ 08/29/2012)
  ;
  ; RCJ 01/23/2007  depend_0s is to be used if one of the vars
  ; becomes additional or ignore_data
   depend_0s=''
   for i=0,n_elements(tag_names(nbuf))-1 do begin
      depend_0s=[depend_0s,nbuf.(i).depend_0]
   endfor
   depend_0s=depend_0s[1:*]
   ; RCJ 11/09/2007  Added same thing for depend_1's
   depend_1s=''
   for i=0,n_elements(tag_names(nbuf))-1 do begin
      if (spd_cdawlib_tagindex('DEPEND_1',tag_names(nbuf.(i))) ge 0) then $
      depend_1s=[depend_1s,nbuf.(i).depend_1]
   endfor
   if n_elements(depend_1s) gt 1 then depend_1s=depend_1s[1:*]
  ;
      ; we don't want the var to be ignored in case we are going to write a cdf,
      ; but we also don't want the var listed/plotted, so turn it into a
      ; 'additional_data'.
     ; if ((nbuf.(var_indices(i)).var_type eq 'data') or $
     ;  (nbuf.(var_indices(i)).var_type eq 'support_data')) then $
     ;   nbuf.(var_indices(i)).var_type = 'additional_data' else $
     ;   nbuf.(var_indices(i)).var_type='ignore_data'
     ; if ((nbuf.(var_indices(i)).var_type eq 'additional_data') or $
     ;  (nbuf.(var_indices(i)).var_type eq 'ignore_data')) then begin
     ;	  if nbuf.(var_indices(i)).depend_0 ne '' then begin
     ;       q=where(depend_0s eq nbuf.(var_indices(i)).depend_0)
     ;       if n_elements(q) eq 1 then $
     ;	        s=execute("nbuf."+nbuf.(var_indices(i)).depend_0+".var_type='additional_data'")
     ;    endif	
     ;       if nbuf.(var_indices(i)).depend_1 ne '' then begin
     ;       q=where(depend_1s eq nbuf.(var_indices(i)).depend_1)
     ;       if n_elements(q) eq 1 then $
     ;	        s=execute("nbuf."+nbuf.(var_indices(i)).depend_1+".var_type='additional_data'")
     ;    endif	
     ; endif	
      ; RCJ 07/14/2008  Now we do want the depends listed.
       print,'*********** not requested: ', nbuf.(var_indices[i]).varname,'  ',nbuf.(var_indices[i]).var_type
       if (nbuf.(var_indices[i]).var_type eq 'data')  then $
         nbuf.(var_indices[i]).var_type='additional_data'
       if (nbuf.(var_indices[i]).var_type eq 'additional_data') then begin
      	  if nbuf.(var_indices[i]).depend_0 ne '' then begin
                   q=where(depend_0s eq nbuf.(var_indices[i]).depend_0)
                   if n_elements(q) eq 1 then $
      	        s=execute("nbuf."+nbuf.(var_indices[i]).depend_0+".var_type='additional_data'")
                endif	
      	  if nbuf.(var_indices[i]).depend_1 ne '' then begin
                   q=where(depend_1s eq nbuf.(var_indices[i]).depend_1)
                   if n_elements(q) eq 1 then $
      	        s=execute("nbuf."+nbuf.(var_indices[i]).depend_1+".var_type='additional_data'")
          endif	
      endif	

    Even older logic:  (RCJ 08/29/2012)

   ;if(wc[0] lt 0) then nbuf.(var_indices[i]).var_type="ignore_data"
   ;if(wc[0] lt 0) then nbuf.(var_indices[i]).var_type="metadata"   

eturn, status
nd

+
 NAME: Function spd_cdawlib_alternate_view

 PURPOSE: Find virtual variables and replace their data w/ the component0
          data 

 CALLING SEQUENCE:

          new_buf = spd_cdawlib_alternate_view(buf,org_names)

 VARIABLES:

 Input:

  buf        - an IDL structure built w/in read_myCDF
  org_names  - list of original variables input to read_myCDF. Any
               variables in this list will remain tagged as 
               VAR_TYPE= data otherwise VAR_TYPE = support_data.

 Output:

  new_buf    - an IDL structure containing the populated virtual 
               variable 
  
 Keyword Parameters: 


 REQUIRED PROCEDURES:

   none

(See external/spdfcdas/spd_cdawlib/spd_cdawlib_virtual_funcs.pro)


SPD_CDAWLIB_VIRTUAL_FUNCS[2]

[Previous Routine] [Next Routine] [List of Routines]
 NAME: Function spd_cdawlib_clamp_to_zero

 PURPOSE: Clamp all values less than or equal to 'clamp_threshold' to zero. 

 CALLING SEQUENCE:

          new_buf = spd_cdawlib_clamp_to_zero(buf,org_names)

 VARIABLES:

 Input:

  buf        - an IDL structure built w/in read_myCDF
  org_names  - list of original variables input to read_myCDF. Any
               variables in this list will remain tagged as 
               VAR_TYPE= data otherwise VAR_TYPE = support_data.

 Output:

  new_buf    - an IDL structure containing the populated virtual 
               variable 
  
 Keyword Parameters: 


 REQUIRED PROCEDURES:

   none

 History: Written by Ron Yurow 08/15, based on spd_cdawlib_alternate_view

(See external/spdfcdas/spd_cdawlib/spd_cdawlib_virtual_funcs.pro)


SPD_CDAWLIB_VIRTUAL_FUNCS[3]

[Previous Routine] [Next Routine] [List of Routines]
 NAME: Function spd_cdawlib_composite_tbl

 PURPOSE: Create a variable that is a composite of of multiple variables. 

 CALLING SEQUENCE:

          new_buf = spd_cdawlib_composite_tbl(buf,org_names)

 VARIABLES:

 Input:

  buf        - an IDL structure built w/in read_myCDF
  org_names  - list of original variables input to read_myCDF. Any
               variables in this list will remain tagged as 
               VAR_TYPE= data otherwise VAR_TYPE = support_data.

 Output:

  new_buf    - an IDL structure containing the populated virtual 
               variable 
  
 Keyword Parameters: 


 REQUIRED PROCEDURES:

   none

 History: Written by Ron Yurow 08/15, based on spd_cdawlib_alternate_view

(See external/spdfcdas/spd_cdawlib/spd_cdawlib_virtual_funcs.pro)


SPD_CDAWLIB_VIRTUAL_FUNCS[4]

[Previous Routine] [Next Routine] [List of Routines]
 NAME: Function spd_cdawlib_arr_slice

 PURPOSE: Create a variable by extracting a subset (slice) of a multidimensional array.  
          Works on variables up to 7 dimensions. 


 CALLING SEQUENCE:

          new_buf = spd_cdawlib_arr_slice (buf,org_names)

 VARIABLES:

 Input:

  buf        - an IDL structure built w/in read_myCDF
  org_names  - list of original variables input to read_myCDF. Any
               variables in this list will remain tagged as 
               VAR_TYPE= data otherwise VAR_TYPE = support_data.

 Output:

  new_buf    - an IDL structure containing the populated virtual 
               variable 
  
 Keyword Parameters: 


 REQUIRED PROCEDURES:

   none

 History: Written by Ron Yurow 05/16, based on spd_cdawlib_alternate_view

(See external/spdfcdas/spd_cdawlib/spd_cdawlib_virtual_funcs.pro)


SPD_CDAWLIB_VIRTUAL_FUNCS[5]

[Previous Routine] [Next Routine] [List of Routines]
 NAME: Function spd_cdawlib_crop_image

 PURPOSE: Crop [60,20,*] images into [20,20,*]

 CALLING SEQUENCE:

          new_buf = spd_cdawlib_crop_image(buf,org_names,index)

 VARIABLES:

 Input:

  buf        - an IDL structure built w/in spd_cdawlib_read_mycdf
  org_names  - list of original variables input to spd_cdawlib_read_mycdf. Any
               variables in this list will remain tagged as 
               VAR_TYPE= data otherwise VAR_TYPE = support_data.
  index      - variable index, so we deal with one variable at a time.

 Output:

  new_buf    - an IDL structure containing the populated virtual 
               variable 

 History: Written by RCJ 12/00, based on spd_cdawlib_alternate_view

(See external/spdfcdas/spd_cdawlib/spd_cdawlib_virtual_funcs.pro)


SPD_CDAWLIB_VIRTUAL_FUNCS[6]

[Previous Routine] [Next Routine] [List of Routines]
 NAME: Function spd_cdawlib_clean_data 

 pURPOSE: Remove data 3*sigma from mean 

 INPUT:

    data          simple data array 

 KEYWORDS:
    FILLVAL       the fill value to be used to replace outlying data.

 CALLING SEQUENCE:

         data = spd_cdawlib_clean_data(data,keywords...)




unction spd_cdawlib_clean_data, data, FILLVAL=FILLVAL

if not keyword_set(FILLVAL) then FILLVAL=1.0+e31;
  
  w=where(data ne FILLVAL,wn)
  if(wn eq 0) then begin
    print, "ERROR = No valid data found in function spd_cdawlib_clean_data";
    print, "STATUS = No valid data found. Re-select time interval.";
  endif
  
   mean= total(data[w[0:(wn-1)]])/fix(wn)
  ; RCJ 10/03/2003 The function moment needs data to have 2 or more elements.
  ; If that's not possible, then the mean will be the only valid element of
  ; data and the sdev will be 0. 



  if n_elements(data[w[0:(wn-1)]]) gt 1 then begin
     result = moment(data[w[0:(wn-1)]],sdev=sig)
     mean=result[0]
  endif else begin
     mean=data[w[0:(wn-1)]]
     sig=0.
  endelse      
  sig3=3.0*sig

  w=where(abs(data-mean) gt sig3, wn);
TJK 4/8/2005 - add the next two lines because we have a case where
 all of the data values are exactly the same, and the "moment" routine
 above returns a sig value greater that the difference between the mean
 and data, so all values are set to fill, which isn't correct at all...
 So to make up for this apparent bug in the moment routine, do the following:

  t = where(data eq data[0], tn)
  if (tn eq n_elements(data)) then begin
wn = 0
print, 'DEBUG spd_cdawlib_clean_data - overriding results from moment func. because '
print, 'all data are the same valid value = ',data[0]
  endif

  if(wn gt 0) then data[w] = FILLVAL

eturn, data
nd

+
 NAME: Function spd_cdawlib_conv_pos 

 PURPOSE: Find virtual variables and compute their data w/ the component0,
          component1,... data.  This function specifically converts position
          information from 1 coordinate system into another. 

 INPUT:

    buf           an IDL structure
    org_names     an array of original variables sent to spd_cdawlib_read_mycdf

 KEYWORDS:
    COORD         string corresponding to coordinate transformation
	           default(SYN-GCI)
	           (ANG-GSE)
    TSTART        start time for synthetic data
    TSTOP         start time for synthetic data

 CALLING SEQUENCE:

         newbuf = spd_cdawlib_conv_pos(buf,org_names,keywords...)


unction spd_cdawlib_conv_pos, buf, org_names, COORD=COORD, TSTART=TSTART, $ 
                  TSTOP=TSTOP, DEBUG=DEBUG, INDEX=INDEX

status=0
 Establish error handler
catch, error_status
if(error_status ne 0) then begin
  print, "ERROR= number: ",error_status," in spd_cdawlib_conv_pos.pro"
  print, "ERROR= Message: ",!ERR_STRING
  status = -1
  return, status
endif

org_names=strupcase(org_names)
if keyword_set(DEBUG) then DEBUG=1L else DEBUG=0L
if not keyword_set(INDEX) then INDEX=0L;
if not keyword_set(COORD) then COORD="SYN-GCI";
if (keyword_set(TSTART) and keyword_set(TSTOP))then begin
       start_time = 0.0D0 ; initialize
       b = size(TSTART) & c = n_elements(b)
       if (b[c-2] eq 5) then start_time = TSTART $ ; double float already
       else if (b[c-2] eq 7) then start_time = encode_cdfepoch(TSTART); string
       stop_time = 0.0D0 ; initialize
       b = size(TSTOP) & c = n_elements(b)
       if (b[c-2] eq 5) then stop_time = TSTOP $ ; double float already
       else if (b[c-2] eq 7) then stop_time = encode_cdfepoch(TSTOP); string
endif

;m3int=fix((stop_time - start_time)/(180.0*1000.0))
; RCJ 07/10/02 Replaced fix w/ round. Fix won't work correctly on long integers
m3int=round((stop_time - start_time)/(180.0*1000.0))
t3min=dblarr(m3int+1)
failed=0 

dep=parse_mydepend0(buf)  
depends=tag_names(dep)
depend0=depends(dep.num)
epoch1='Epoch1'
namest=strupcase(tag_names(buf))

if((COORD eq "SYN-GCI") or (COORD eq "SYN-GEO")) then begin
 Determine time array 
depend0=strupcase(buf.(INDEX).depend_0)
incep=where(namest eq depend0,w)
incep=incep[0]
names=tag_names(buf.(incep))
ntags=n_tags(buf.(incep))
 Check to see if HANDLE a tag name
wh=where(names eq 'HANDLE',whn)
if(whn) then begin
 handle_value, buf.(incep).HANDLE,time 
 datsz=size(time)
endif else begin
 time=buf.(incep).dat
endelse
 Determine position array 
help, buf.sc_pos_syngci, /struct
 vvtag_names=strarr(1)
 vvtag_indices = spd_cdawlib_vv_names(buf,NAMES=vvtag_names)
 vvtag_names = strupcase(vvtag_names)

TJK 12/15/2006, the following doesn't work when reading a 
a1_k0_mpa data file directly (w/o a master) because
the data cdfs have one of the label variables incorrectly
defined as a virtual variable, so you can't just assume
the 1st one in vvtag_indices is the correct one.
 use the index passed in instead of vvtag_indices[0]
  cond0=buf.(vvtag_indices[0]).COMPONENT_0 
 cond0=buf.(index).COMPONENT_0 
 handle_value, buf.(cond0).HANDLE,data
TJK 12/15/2006 these aren't right either - we'll use index
  fillval=buf.(vvtag_indices[0]).fillval 
  rmin=buf.(vvtag_indices[0]).VALIDMIN[0] 
  tmin=buf.(vvtag_indices[0]).VALIDMIN[1] 
  pmin=buf.(vvtag_indices[0]).VALIDMIN[2] 
  rmax=buf.(vvtag_indices[0]).VALIDMAX[0] 
  tmax=buf.(vvtag_indices[0]).VALIDMAX[1] 
  pmax=buf.(vvtag_indices[0]).VALIDMAX[2] 
 fillval=buf.(index).fillval 
 rmin=buf.(index).VALIDMIN[0] 
 tmin=buf.(index).VALIDMIN[1] 
 pmin=buf.(index).VALIDMIN[2] 
 rmax=buf.(index).VALIDMAX[0] 
 tmax=buf.(index).VALIDMAX[1] 
 pmax=buf.(index).VALIDMAX[2] 

  x0=execute('cond0=buf.'+vvtag_indices[0]+'.COMPONENT_0') 
  x0=execute('handle_value, buf.'+org_names[0]+'.HANDLE,data') 
  x0=execute('fillval=buf.'+org_names[0]+'.fillval') 

 if(COORD eq "SYN-GCI") then begin
 r=data[0,*]
 theta=data[1,*]
 phi=data[2,*]
 Check for radius in kilometers; switch to Re
 wrr=where(((r gt 36000.0) and (r lt 48000.0)),wrrn)
 if(wrrn gt 0) then r[wrr] = r[wrr]/6371.2 

 Check validity of data; if outside min and max set to fill
 rhi=where(r gt rmax,rhin)
 if(rhin gt 0) then r[rhi]=fillval
 rlo=where(r lt rmin,rlon)
 if(rlon gt 0) then r[rlo]=fillval
 ;print, rmax, rmin
 ;print, 'DEBUG',min(r, max=maxr) & print, maxr

 thi=where(theta gt tmax,thin)
 if(thin gt 0) then theta[thi]=fillval
 tlo=where(theta lt tmin,tlon)
 if(tlon gt 0) then theta[tlo]=fillval

 phii=where(phi gt pmax,phin)
 if(phin gt 0) then phi[phii]=fillval
 plo=where(phi lt pmin,plon)
 if(plon gt 0) then phi[plo]=fillval

 num=long(n_elements(time))
 stime=time-time[0]
 dtime=(time[num-1] - time[0])/1000.0
 d_m3time=dtime/(60.0*3.0)  ; 3min/interval=(secs/interval) / (secs/3min)
 m3time=fix(d_m3time)

 Compute syn_phi, syn_r, and syn_theta
  syn_phi=dblarr(m3int+1)
  syn_theta=dblarr(m3int+1)
  syn_r=dblarr(m3int+1)
  newtime=dblarr(m3int+1)
  tst_theta=dblarr(num)

 Clean up any bad data; set to fill values outside 3-sigma 
  phi=spd_cdawlib_clean_data(phi,FILLVAL=fillval)
  theta=spd_cdawlib_clean_data(theta,FILLVAL=fillval)
  r=spd_cdawlib_clean_data(r,FILLVAL=fillval)

  wcp=where(phi ne fillval,wcnp)
  wct=where(theta ne fillval,wcnt)
  wcr=where(r ne fillval,wcnr)
  if((wcnp le 0) or (wcnt le 0) or (wcnr le 0)) then begin
    print, 'ERROR= Data all fill'
    print, 'STATUS= No valid data found for this time period'
    return, -1
  endif
  if((wcnp eq 1) or (wcnt eq 1) or (wcnr eq 1)) then begin
    print, 'ERROR= Only one valid point'
    print, 'STATUS= Only one valid point found for this time period'
    return, -1
  endif
 For short intervals < 10 points use wcnp otherwise average the 1st 10 points
 to obtain extrapolation parameters
  ;wcnp=wcnp-1  
  ;if(wcnp gt 10) then wcnp=10 else wcnp=wcnp-1  
 Compute average of all points
  mphi= total(phi[wcp[0:(wcnp-1)]])/fix(wcnp)
  mr= total(r(wcr[0:(wcnr-1)]))/fix(wcnr)
  mtheta= total(theta[wct[0:(wcnt-1)]])/fix(wcnt)
  ampl=double(max(theta[wct]))
print, mphi, mr, mtheta, ampl
  wc=where(theta eq ampl,wcn)

 dphi=phi[wcp[wcnp-1]] - phi[wcp[0]]
 dr=r[wcr[wcnr-1]] - r[wcr[0]]
 dtheta=theta[wct[wcnt-1]] - theta[wct[0]]
 phi_rate=dphi/d_m3time
 r_rate=dr/d_m3time
 theta_rate=dtheta/d_m3time
 nominal_rate=0.75
 new_rate= double(360.0/(nominal_rate + phi_rate))
  print, nominal_rate, phi_rate, new_rate, r_rate

!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
 Skip latitude daily variation approximation
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
  iter=0 
  sign=0
  corr_coef=0.0
  while(corr_coef lt 0.75) do begin 
   T=time(wc[0])/180000.0
;   T1=time(wc[0]-1)/180000.0
;   T2=time(wc[0]-2)/180000.0
;   T3=time(wc[0]+1)/180000.0
;   T4=time(wc[0]+2)/180000.0
   if(iter eq 0) then T=double(T)
;   if(iter eq 1) then T=double((T+T1)/2.0)
;   if(iter eq 2) then T=double((T1+T2)/2.0)
;   if(iter eq 3) then T=double((T+T3)/2.0)
;   if(iter eq 4) then T=double((T4+T3)/2.0)
;print, ampl,  T, mphi, mr, mtheta

; determine array for correlation test
   for i=0L,num-1 do begin
      tm=time[i]/(180.0*1000.0)
;     tst_theta[i] = ampl*sin((2.0*(!pi))*(tm-T)/480.08898)
      if(sign eq 0) then tst_theta[i] = ampl*double(cos((2.0*(!pi))*(tm-T)/new_rate))
      if(sign eq 1) then tst_theta[i] = ampl*double(sin((2.0*(!pi))*(tm-T)/new_rate))
   endfor

   corr_coef=correlate(theta,tst_theta)
   if(DEBUG) then print, iter," CC = ", corr_coef

;   if(iter eq 4) then begin
     if(sign eq 0) then begin
        iter=0 
        sign = 1
     endif
;   endif
   iter=iter+1
;   if(iter gt 5) then goto, break   
   if(iter gt 1) then goto, break   
  endwhile
  break:

   if(corr_coef lt 0.75) then failed=1

 failed=1  ; forces average theta variation to be used approx. 0.0
 Generate 3-min data
  for i=0L,m3int do begin   
   tm = (start_time)/180000.0 + i
   t3min[i]=i*180000.0 + start_time
   half=m3int/2
   it=i-(half+1)
   syn_phi[i] = mphi + phi_rate*it
   ; syn_r[i] = mr + r_rate*i
   syn_r[i] = mr 
  if(failed) then begin
    if(abs(mtheta) > 2.0) then begin
      print, 'WARNING: Check daily latitude variation.' 
      return, -1;
    endif
     syn_theta[i] = 0.0  ; Can't compute daily variation; use this estimate
   ; syn_theta[i] = mtheta ; Can't compute daily variation; use this estimate
   ; syn_theta[i] = mtheta + theta_rate*i 
  endif else begin
     syn_theta[i] = ampl*sin((2.0*(!pi))*(tm-T)/480.08898)
   if(sign eq 0) then syn_theta[i] = ampl*double(cos((2.0*(!pi))*(tm-T)/new_rate))
   if(sign eq 1) then syn_theta[i] = ampl*double(sin((2.0*(!pi))*(tm-T)/new_rate))
  endelse  
 endfor

      print, t3min[0], syn_r[0], syn_theta[0], syn_phi[0]
 Convert spherical to cartesian 
    Determine the offset of the given point from the origin.
 gei=dblarr(3,m3int+1)
 geo=dblarr(3,m3int+1)
 deg2rd=!pi/180.0 
 j=-1
 for i=0L, m3int do begin 
     CT = SIN(syn_theta[i]*deg2rd)
     ST = COS(syn_theta[i]*deg2rd)
     CP = COS(syn_phi[i]*deg2rd)
     SP = SIN(syn_phi[i]*deg2rd)
 Save syn-geo 
      geo(0,i)=syn_r[i]
      geo(1,i)=syn_theta[i]
      geo(2,i)=syn_phi[i]
     Convert GEO spherical coordinates SGEO(1,2,3) [R,LAT,LON]
          to GEO cartesian coordinates in REs GEO(1,2,3) [X,Y,Z].
     RHO =    syn_r[i] * ST
     xgeo = RHO * CP
     ygeo = RHO * SP
     zgeo = syn_r[i] * CT
     xgei=0.0 & ygei=0.0 & zgei=0.0
 Rotate 3-min vectors from geo to gci
     epoch=t3min[i] 
      cdf_epoch, epoch, yr, mo, dy, hr, mn, sc, milli, /break
      if((i mod 100) eq 0) then print, epoch, yr, mo, dy, hr, mn, sc, milli
     geigeo,xgei,ygei,zgei,xgeo,ygeo,zgeo,j,epoch=epoch
       if((i mod 100) eq 0) then print, xgei,ygei,zgei,xgeo,ygeo,zgeo
      gei[0,i]=xgei 
      gei[1,i]=ygei 
      gei[2,i]=zgei 
 endfor

 Modify existing structure 

 nbuf=buf
 Modify depend0 (Epoch1), but don't add it again!!
 dc=where(depends eq 'EPOCH1',dcn)
 if(not dcn) then begin
  nu_ep_handle=handle_create(value=t3min)
  temp_buf=nbuf.(depend0)
  new=create_struct('EPOCH1',temp_buf)
  new.(epoch1).handle=nu_ep_handle
  new.(epoch1).VARNAME=epoch1
  new.(epoch1).LABLAXIS=epoch1
 endif
 Modify position data
 if(COORD eq "SYN-GCI") then begin
   nu_dat_handle=handle_create(value=gei)
   vin=where(vvtag_names eq 'SC_POS_SYNGCI',vinn)
   if(vinn) then begin
     nbuf.(vvtag_indices(vin[0])).handle=nu_dat_handle
     nbuf.(vvtag_indices(vin[0])).depend_0=epoch1
   endif
 endif
 if(COORD eq "SYN-GEO") then begin
   nu_dat_handle=handle_create(value=geo)
   vin=where(vvtag_names eq 'SC_POS_SYNGEO',vinn)
   if(vinn) then begin
     nbuf.(vvtag_indices(vin[0])).handle=nu_dat_handle
     nbuf.(vvtag_indices(vin[0])).depend_0=epoch1
   endif
 endif

 cond0=strupcase(cond0) 
 pc=where(org_names eq cond0,pcn)
 ;blank=' '
 if(pc[0] eq -1) then begin
   ; RCJ 06/16/2004  Only make epoch.var_type = metadata if no other
   ; variable needs epoch as its depend_0. in this case epoch
   ; should still be support_data.
   q=where(strlowcase(depends) eq 'epoch')
   if q[0] eq -1 then nbuf.epoch.var_type='metadata'
   ; RCJ 01/23/2007 The line below does not help listing. Does it do anything useful?
   ;nbuf.sc_pos_geo.depend_0=blank
 endif

 if(not dcn) then nbuf=create_struct(nbuf,new)
endif

if(COORD eq "ANG-GSE") then begin
 nbuf=buf 
 vvtag_names=strarr(1)
 vvtag_indices = spd_cdawlib_vv_names(buf,NAMES=vvtag_names)

 Determine time array 
 depend0=depends(INDEX)
 incep=where(vvtag_names eq namest(INDEX),w)
 incep=incep[0]
;depend0=buf.(vvtag_indices(incep)).DEPEND_0
depend0=buf.(INDEX).DEPEND_0
print, depend0, INDEX
incep=spd_cdawlib_tagindex(depend0, namest)
incep=incep[0]
names=tag_names(buf.(incep))
ntags=n_tags(buf.(incep))
 Check to see if HANDLE a tag name
wh=where(names eq 'HANDLE',whn)
if(whn) then begin
 handle_value, buf.(incep).HANDLE,time 
 datsz=size(time)
endif else begin
 time=buf.(incep).dat
endelse
 Determine position array 
  indat=where(vvtag_names eq namest(INDEX),w)
  indat = indat[0]
 cond0=buf.(INDEX).COMPONENT_0 
 ;cond0=buf.(vvtag_indices(indat)).COMPONENT_0 
print, cond0, INDEX
 handle_value, buf.(cond0).HANDLE,data

 Convert BGSE vector to angular BGSE; 
 data_sz=size(data)
 ang_gse=dblarr(data_sz[1],data_sz[2])
  cart_polar,data[0,*],data[1,*],data[2,*],ang_gse[0,*],ang_gse[1,*],$
             ang_gse[2,*],1,/degrees
 ang_gse[0,*]=sqrt(data[0,*]*data[0,*]+data[1,*]*data[1,*]+data[2,*]*data[2,*])
 ang_gse[0,*]=sqrt(data[0,*]^2+data[1,*]^2+data[2,*]^2)
 ang_gse[1,*]=90.0-(!radeg*acos(data[2,*]/ang_gse[0,*])) 
 ang_gse[2,*]=!radeg*atan(data[1,*],data[0,*]) 
 wc=where(ang_gse[2,*] lt 0.0,wcn)
 if(wcn gt 0) then ang_gse[2,wc] = ang_gse[2,wc]+360.0
 nu_dat_handle=handle_create(value=ang_gse)
 ;nbuf.(vvtag_indices(indat)).handle=nu_dat_handle
 nbuf.(INDEX).handle=nu_dat_handle
endif


 Check that all variables in the original variable list are declared as
 data otherwise set to metadata 
 Find variables w/ var_type == data

  status = spd_cdawlib_check_myvartype(nbuf, org_names)

eturn, nbuf 
nd 


to get help: IDL> spd_cdawlib_ptg,/help
 ancillary routines --------------------------------------------

UNCTION spd_cdawlib_dtand,x
   RETURN,DOUBLE(TAN(x*!DTOR))
ND

UNCTION spd_cdawlib_datand,x
   RETURN,DOUBLE(ATAN(x)/!DTOR)
ND

UNCTION spd_cdawlib_fgeodep,a,b,v1x,v1y,v1z,v2x,v2y,v2z
   RETURN,v1x*v2x + v1y*v2y + v1z*v2z * a*a/(b*b)
ND

(See external/spdfcdas/spd_cdawlib/spd_cdawlib_virtual_funcs.pro)


SPD_CDAWLIB_VIRTUAL_FUNCS[7]

[Previous Routine] [Next Routine] [List of Routines]
 NAME: Function spd_cdawlib_conv_map_image

 PURPOSE: Convert provided idl structure to structure containing neccesary 
          variables for an auroral image map.  Use variables pointed to by
          COMPONENT variable attributes to compute geodetic latitude and
          longitude. Populate GEOD_LAT & GEOD_LONG variables w/ the computed
          values. Return the modifiy idl structure. 

  NEED TO REMOVE UVI DEPENDANCIES.......
 
 CALLING SEQUENCE: 

          new_buf = spd_cdawlib_conv_map_image(buf,org_names)

 VARIABLES:

 Input:

  buf        - an IDL structure built w/in spd_cdawlib_read_mycdf
  org_names  - list of original variables input to spd_cdawlib_read_mycdf. Any
               variables in this list will remain tagged as
               VAR_TYPE= data otherwise VAR_TYPE = support_data.

 Output:

  new_buf    - an IDL structure containing the populated virtual
               variable
 
 Keyword Parameters:


 REQUIRED PROCEDURES:

   none

(See external/spdfcdas/spd_cdawlib/spd_cdawlib_virtual_funcs.pro)


SPD_CDAWLIB_VIRTUAL_FUNCS[8]

[Previous Routine] [Next Routine] [List of Routines]
 NAME: Function spd_cdawlib_height_isis

 PURPOSE: Retrieve only height from vector geo_coord:
 (lat1, lon1, height1, lat2, lon2, height2, lat3, lon3, height3, .....)

 CALLING SEQUENCE:

          new_buf = spd_cdawlib_height_isis(buf,org_names,index)

 VARIABLES:

 Input:

  buf        - an IDL structure built w/in spd_cdawlib_read_mycdf
  org_names  - list of original variables input to spd_cdawlib_read_mycdf. Any
               variables in this list will remain tagged as 
               VAR_TYPE= data otherwise VAR_TYPE = support_data.
  index      - variable index, so we deal with one variable at a time.

 Output:

  new_buf    - an IDL structure containing the populated virtual 
               variable 

 History: Written by RCJ 09/01, based on spd_cdawlib_crop_image

(See external/spdfcdas/spd_cdawlib/spd_cdawlib_virtual_funcs.pro)


SPD_CDAWLIB_VIRTUAL_FUNCS[9]

[Previous Routine] [List of Routines]
 NAME: Function spd_cdawlib_flip_image

 PURPOSE: spd_cdawlib_flip_image [*,*] 

 CALLING SEQUENCE:

          new_buf = spd_cdawlib_flip_image(buf,org_names,index)

 VARIABLES:

 Input:

  buf        - an IDL structure built w/in spd_cdawlib_read_mycdf
  org_names  - list of original variables input to spd_cdawlib_read_mycdf. Any
               variables in this list will remain tagged as 
               VAR_TYPE= data otherwise VAR_TYPE = support_data.
  index      - variable index, so we deal with one variable at a time.

 Output:

  new_buf    - an IDL structure containing the populated virtual 
               variable 

 History: Written by TJK 01/03 for use w/ IDL RPI data

(See external/spdfcdas/spd_cdawlib/spd_cdawlib_virtual_funcs.pro)