Standard Broadband Format Manual


Table of Contents

Chapter 5: Element Field and Element Code Descriptions


Appendix D

Sample Programs


The following two programs are examples of retrieving and storing data in the SERI Standard Broadband Format (SBF). The first example is a program fragment used to read data stored in SBF. The second example, Program GeoTec, converts an existing Research Cooperator Format file of Georgia Institute of Technology data to SBF. Both programs were written in FORTRAN-77 on a VAX 1173 with a VMS operating system. System assumptions include opening the input file with unit number 11, the output file with 41, and the data file with 42.


Sample Data Retrieval Program

 ! Program excerpt reading one block of one-minute data stored in SBF.
 ! Variables for Header Lines 1 and 2 correspond to the fields listed in
 ! Chapter 4, "Header Field Descriptions." The arrays, Dat and Iflag, hold
 ! an entire block of data/null elements and flags respectively. The control
 ! variables are:

 !     Jfirst - beginning of data line.
 !     Jlast - end of data line.
 !     LinDat - total number of data lines (eliminates the two header lines).

            CHARACTER*2 Orient, Elemnt, BlkInt
			CHARACTER*10, Units
            CHARACTER*20, Sitnam
            CHARACTER*49 Instnm
			DIMENSION	Dat(512), Iflag(512)

 !     Header line 1:


   100 FORMAT (A20, I49, A10, I1)

 !     Header line 2:

   200 FORMAT (I2, I5, I6, I5, I4, I5, I3, A2, I3, 2(I3.2, 5I2.2),
      2 I2, I3, A2, I2, A2, I3, I2, I3)
      
 !     Data element lines:

   300 FORMAT (8 (F8.3, I2))

 !     Note: "In.m" means field-width "n" with a minimum of "m" places
 !           filled. Leading zeroes will be used to fill if the number
 !           comprises less than "m" places. Used for the Start Time,
 !           End Time, and element fields.

             READ (11, 100) Sitnam, Instnm, Units, Ifoot
             READ (11, 200) Irank, Ilat, Ilong, Ielev, Izone, Ielem, Izen,
    2                 Orient, Iazim, Iyr, Imo, Idy, Ihr, Imi, Isc, Jyr,
    3                 Jmo, Jdy, Jhr, Jmi, Jsc, Mode, IntElm, ElmInt,
    4                 Intblk, BlkInt, NumElm, NumNul, IBlkFc
 
             Jfirst = 1
             Jlast = 8
             LinDat = IBlkFc - 2 
 ! The following loops through a block, reading the eight element fields in 
 ! each line. 
 
      DO 2000 I = 1 LinDat
            READ (li, 300) ( Dat(J), Iflag(J), J = Jfirst, Jlast)
            Jfirst = Jfirst + 8
            Jlast = Jlast + 8 
 2000 CONTINUE

Sample Data Conversion Program


    Program Geotec
!	Converts one Georgia Tech archival tape file from
!   NCDC's Research Cooperator Format (RCF) to SERI's
!   Standard Broadband Format. The program assumes the
!   incoming RCF file is sorted (collated) by date and
!   then element code. Another common RCF collation 
!   sequence organizes the file by element code first and
!   date second. The VAX Sort/Merge utility was used to 
!   reorganize files with the latter collation.
!
!             Variable Descriptions
!
!   Input variables to read RCF values: 
!     Iarcd - First part of RCF's R&T code indicating
!               averaged, integrated, or instantaneous data. 
!     Iartm - Second part of R&T code indicating measurement 
!               time period (one-minute in this case).
!     Inelm - Element code indicating the measurement type.
!     Newhr - Hour during which measurement was taken.
!     Newdy - Day during which measurement was taken.
!     Newso - Month during which measurement was taken.
!     Newyr - Year during which measurement was taken. 
!     Nexp - Exponent for converting the RCF data fields.
!     Idata(60) - Array storing one hour (one RCF record)
!                 of one-minute data. 
!     Iflag(60) - Array storing the data's accompanying flags. 
!
!   Output variables to write SBF values:
!     Headl(25) - Array containing the First Header line for each 
!                 of Georgia Tech's 25 elements or measurements. 
!                 The data are taken from a text file ('Geo.fil'). 
!     Head2(25) - Array containing the Second Header line, also
!                 taken from a file except for time information.
!     Istart - Start Time hour; controls hour loop in blocking.
!     Olddy - Start Time day. 
!     Oldmo - Start Time month; index in Monend array.
!     Oldyr - Start Time year.
!     Khr - End Time hour.
!     Kdy - End Time day.
!     Kmo - End Time month.
!     Kyr - End Time year. 
!     Datnew(25,0:23,60) - Array storing one day's worth of minute
!                          data for each of the element types.
!     Newflg(25,0:23,60) - Array storing the data flags. 
! 
!   Control variables:
!    Monend(12) - Array containing the last day of each month.
!    Ndays - Last day of Oldmo. 
!    Istart - First hour of the current 8-hour block. 
!    Iend - Last hour of the current 8-hour block. 
!    Master - Loop control to create three blocks per day.
!    Kntdat(25,3) - Flag indicating if data are present in the
!                   element's current block; if data missing 
!                   the block is not written (thus saving space).
!    Nelm, Nmin, Nhr, Nblk - Counters for loops and array indexes; 
!                            values are 25, 60, 8, and 3 respectively.
!
!    Conversion variables:
!      Oldelm(25) - Array of RCF element codes used to check
!                     for valid element codes and to reorder the
!                     records into SBF element code order.
!      Factor(25) - Converts element from RCF units to SBF
!                     preferred units. The solar parameters
!                     are converted from kilojoules to Watts per
!                     square meter. Station pressure is converted
!                     from millibars to kiloPascals.
!      Myflag(0:99) - Converts RCF flags to equivalent SBF flags.
!

          INTEGER*2    Oldelm(25), Myflag(0:99),
      2                Newflg(25,0:23,60), Iflag(60), Oldhr,
      3                Olddy, Oldmo, Oldyr, Monend(12)
          INTEGER*4    Idata(60), Kntdat(25,3) / 75*0 /
          REAL*8       Datnew(25,0:23,60), Factor(25)
          CHARACTER*80 Headl(25), Head2(25)
          
          DATA Oldelm /2010, 2011, 2012, 1000, 1001, 1002,
      2                 1003, 1460, 1461, 3000, 5000, 6000,
      3                 6001, 7010, 7000, 9300, 9301, 9320,
      4                 9321, 9200, 9201, 9210, 9211, 9400,
      5                 9150 / 

          DATA Factor /15*16.6,i667, 8*1., }*10.,,^1*1. /
          DATA Myflag /11*99, 0, 2, 3, 2, 3, 2, 3, 3*99, 0, 2, 3, 2,
      2                    3, 2, 3, 2*99, 30*5, 10*4, 20*6, 10*99/
          DATA Monend /31, 28, 31, 30, 31, 30, 31, 31, 30, 31, 30, 31/ 

 300 FORMAT ( a80 )
! 400 FORMAT reads the RCF format.
  400 FORMAT ( 7x, il. i2, i4, 4i2, 2x, i3, 60(i7, i2) )
! 500 FORMAT writes starting and ending times for Header Line 2.
  500 FORMAT ( 4i2.2, '0100 ', 4i2.2 )
! 600 FORMAT writes one hour of data and flags plus four nulls.
 
  600 FORMAT ( 7( 8( f8.3, i2.2 ),/ ), 4( f8.3, i2.2 ),
     +         4( '-999.99999'))
! Initialize files. (Brief examples of each type of file follow the program.)
   	   
   	   OPEN ( 11, File = 'RCFGeo', Status = 'Old', Recordsize = 567 )
       OPEN ( 41, File = 'SBFGeo', Status = 'New' )
       OPEN ( 42, File = 'Geo.fil', Status = 'Old' )
 
       Olddy = 1

! Get Header Line text descriptions for each of the elements or parameters.
 
      DO Nelm = 1, 25
        READ ( 42, 300 ) Head1(Nelm)
        READ ( 42, 300 ) Head2(Nelm)
      END DO! (I)

! 1000: Read 1 logical record from RCF.

 1000 CONTINUE

        READ ( 11, 400, ERR=1000, END=2000 ) Iarcd, Iartm,
     2 Inelm, Newyr, Newmo, Newdy, Newhr, Nexp,
     3 ( Idata(J), Iflag(J), J=1,60 )
        IF ( Newmo .lt. 1 .or. Newmo .gt. 12 )           GO TO 1000
        GO TO 3000

! 2000: End of file. Set Newdy as end-of-file flag and 
!         Ndays to last day of the month.

2000 CONTINUE

       Newdy = -1

! How many days in a month?

       IF ( Oldmo.EQ.2 .AND. MOD(Oldyr,4).EQ.0 ) THEN
            Ndays = 29
       ELSE
            Ndays = Monend(Oldmo)
       END IF!
       
 ! 3000: If it is a new day, write the preceding records
 !         in three 8-hour blocks of data for each of the
 !         25 parameters. Otherwise, convert the record 7
 !         to the SBF format.
 
  3000 CONTINUE
         IF ( Newdy .NE. Olddy ) THEN 
                Iend = -l 
           DO Master = l, 3
               Iend = Iend + 8
               Istart = Iend - 7
 ! If last block of day; establish ending date.
 
         IF ( Iend .EQ. 23 ) THEN
             Khr = 0
             Kyr = Oldyr 

! If last day of file; what is tomorrow?

         IF ( Newdy .EQ. -l ) TEEN
          
! Just another day. 

         IF ( Olddy .NE. Ndays ) THEN
             Kmo = Oldmo
             Kdy = Olddy + l

! Tomorrow is a new month.
 
         ELSE
             Kdy = 1 
             Kmo = Oldmo + 1

! Tomorrow is a new year.
         
         IF ( Kmo .EQ. 13 ) THEN 
             Kmo = 1
             Kyr = Oldyr + 1
         END IF! 
         
       END IF!

! Else, if NOT last day of file.

     ELSE 
       Kmo = Newmo
       Kdy = Newdy
     END IF!

! Else, if NOT the last block of the day. 

    ELSE
      Kyr = Oldyr
      Kmo = Oldmo
      Kdy = Olddy 
      Khr = Iend + 1
    END IF!

! Write the Header Lines (if Kntdat indicates data are present):

   DO Nelm = 1, 25
     IF ( Kntdat (Nelm,Master) .GT. 0 ) THEN
       WRITE ( 41, 300 ) Headl(Nelm)
       WRITE ( Head2 (Nelm) (37:57), 500 ) Oldyr, Oldmo, Olddy,
 +             Istart, Kyr, Kmo, Kdy, Khr
       WRITE ( 41, 300 ) Head2 (Nelm)

! Write the Data Sets for one 8-hour block:

               DO Nhr = Istart, Iend
                 WRITE ( 41, 600 > ( Datnew(Nelm, Nhr, Nmin),
 +                       Newflg(Nelm, Nhr, Nmin), Nmin = 1,60 )
               END DO! (Nhr)
               Kntdat(Nelm,Master) = 0
             END IF!
           END DO! (Nelm) 
           END DO! (Master)

             IF ( Newdy .EQ. -1 )                         GO TO 9000
         END IF!

! Not a new day, so process the new record just read.

         IF ( Newdy .EQ. 0 ) GO TO 9000
           Oldyr = Newyr
           Oldmo = Newso
           Olddy = Newdy
           Oldhr = Newhr
           
! Check if RCF R&T code and element number legitimate:
! On error - skip the record, go back to beginning, and
! read a new record.

        IF ( Iarcd .LT. 1 .OR. Iarcd .GT. 3 )              GO TO 1000
 
      DO Nelm = l, 25
        IF ( Inelm .EQ. Oldelm(Nelm) )                     GO TO 7000
      END DO! (Nelm)
        GO TO 1000

! Convert data and flags to new format.

 7000 CONTINUE
        Nblk = 1 + Newhr / 8
      DO Nmin = 1, 60
        IF ( Iflag(Nmin) .EQ. 99 ) THEN
             Datnew (Nelm, Newhr, Nmin) = 9900.
             Newflg (Nelm, Newhr, Nmin) = 99
        ELSE
            Kntdat (Nelm, Nblk) = 1
            Datnew (Nelm, Newhr, Nmin) = Float ( Idata(Nmin) ) *
   +                             ( 10. ** Nexp ) * Factor (Nelm)
            IF ( Abs (Datnew(Nelm, Newhr, Nmin)) .GT. 5000 ) THEN
                 Datnew (Nelm, Newhr, Nmin) = 9900.
                 Newflg (Nelm, Newhr, Nmin) = 99
        ELSE
                 Newflg (Nelm, Newhr, Nmin) = Myflag ( Iflag(Nmin) ) 
        END IF
    END IF
  END DO! (Nmin)

! Read the next record.

   GO TO 1000
   
! Finished, so close files.
 9000 CONTINUE
      END

Example RCF Input File

File excerpt showing collation sequence:

000388410110008007010801-0100002421200002441200002451200002481200002491200002521... 000386410110018007010801-0100002431200002451200002471200002491200002521200002551... 000388410110028007010801-0100002561300002571300002591300002621300002641300002651... 000388410110038007010801-0109999999909999999909999999909999999909999999909999999... 000388410114608007010801-0100001611200001631200001661200001681200001701200001721... 000388410114618007010801-0100001851300001871300001901300001921300001951300001961... 000388410120108007010801-0100004371200004371200004391200004401200004421200004411... 000388410120118007010801-0100000019900000019900000019900000029900000029900000019... 000388410120128007010801-0100000019900000019900000019900000019900000019900000019... 000388410130008007010801-0100000411200000411200000421200000421200000421200000431... 000388410150008007010801-0100000111200000111200000111200000111200000111200000111... 000388410160008007010801-0100002412200002412200002422200002432200002402200002382... 000388410170008007010801-0100001491200001511200001521200001541200001541200001551... 000388410170108007010801-0100002981200002991200003001200003001200003011200003011... 000388410191508007010801-0100000001200000011200000001200000001200000011200000001... 00038843019200800701080100000000561200000551200000181200000401200000391200000481... 00038843019201800701080100000000631200000721200000551200000501200000611200000301... 000388420192108007010801-0100000141200000131200000161200000151200000321200000251... 000388420192118007010801-0100000151200000171200000191200000181200000341200000341... 000388420193008007010801-0100002211200002221200002231200002231200002231200002221... 000388420193018007010801-0100002211200002221200002241200002241200002241200002221... 000388420193208007010801-0100001451200001521300001551200001551200001521200001491...

Complete record (one hour) of direct normal data:

000388410120108007010801-0100004371200004371200004391200004401200004421200004411 20000440120000441120000441120000442120000443120000444120000443120000444120000445 12000044612000044912000045212000045312000045412000045812000045712000045812000045 71200004591200004591200004581200004601200004611200004611200004641200004651200004 66120000467120000424120999999990000471120000470120000470120000470120000470120000 47112000047312000047512000047612000047912000047912000047812000047912000048012000 04821200004831200004801200004811200004801200004821200004831200004841200004841200
0048412

Example SBF Output File 1

Block header plus one set (one hour) of direct normal data:

GEORGIA TECH SEMRTS:Direct Normal, Eppley NIP                Watts/m*m 0

1 3377 -8438 327 -50 1000 992X999 800701080100 800701160000 0 1MI 8HR 60 4 66
728.33302 728.33302 731.66702 733.33302 736.66702 735.00002 733.33302 735.00002
735.00002 736.66702 738.33302 740.00002 738.33302 740.00002 741.66702 743.33402
748.33402 753.33302 755.00002 756.66702 763.33302 761.66702 763.33302 761.66702
765.00002 765.00002 763.33302 766.66702 768.33402 768.33402 773.33402 775.00002
776.66702 778.33402 706.667029900.00099 785.00002 783.33302 783.33302 783.33302
783.33302 785.00002 788.33302 791.66702 793.33402 798.33402 798.33402 796.66702
798.33402 800.00002 803.33402 805.00002 800.00002 801.66702 800.00002 803.33402
805.00002 806.66702 806.66702 806.66702-999.99999-999.99999-999.99999-999.99999

Example Header Line Text File

GEORGIA TECH SEMRTS:Direct Normal, Eppley NIP                        Watts/m*m 0
 1 3377 -8438 292 -50 1000 992X999 ????????0100 ????????0000 0  1MI 8HR 60 4 66 
GEORGIA TECH SEMRTS:Direct Normal, Eppley NIP                        Watts/m*m 0
 1 3377 -8438 292 -50 1001 992X999 ????????0100 ????????0000 0  1MI 8HR 60 4 66
GEORGIA TECH SEMRTS:Direct Normal, Lambda LI-200S                    Watts/m*m 0
 1 3377 -8438 292 -50 1002 992X999 ????????0100 ????????0000 0  1MI 8HR 60 4 66
GEORGIA TECH SEMRTS:Global Horizontal, Eppley PSP                    Watts/m*m 0 
 1 3377 -8438 292 -50 1100 0UP 0 ????????0100 ????????0000 0 1MI 8HR 60 4 66
GEORGIA TECH SEMRTS:Global Horizontal, Spectrolab SR75               Watts/m*m 0 
 1 3377 -8438 292 -50 1101 0UP 0 ????????0100 ????????0000 0 1MI 8HR 60 4 66 
GEORGIA TECH SEMRTS:Global Horizontal, Lambda LI-200S                Watts/m*m 0
 1 3377 -8438 292 -50 1101 0UP 0 ????????0100 ????????0000 0 1MI 8HR 60 4 66
GEORGIA TECH SEMRTS:Global Horizontal, Dodge SS-100                  Watts/m*m 0
 1 3377 -8438 292 -50 1101 OUP O ????????0100 ????????0000 0 1MI 8HR 60 4 66
GEORGIA TECH SEMRTS:Global Latitude Tilt, Eppley PSP                 Watts/m*m 0
 1 3377 -8438 292 -50 1200 34UPl80 ????????0100 ????????0000 0 1MI 8HR 60 4 66
GEORGIA TECH SEMRTS:Global Latitude Tilt, Lambda LI-200S             Watts/m*m 0
 1 3377 -8438 292 -50 1201 34UP180 ????????0100 ????????0000 0 1MI 8HR 60 4 66
GEORGIA TECH SEMRTS:Diffuse, Eppley PSP with shading disk            Watts/m*m 0
 1 3377 -8438 292 -50 1400 0UP 0 ????????0100 ????????0000 0 1MI 8HR 60 4 66
GEORGIA TECH SEMRTS:Ultraviolet, Eppley TUVR                        Watts/m*m 0
 1 3377 -8438 292 -50 3100 0UP 0 ????????0100 ????????0000 0 1MI 8HR 60 4 66
GEORGIA TECH SEMRTS:Infrared (Total Global), Swissteco FUNK         Watts/m*m 0
 1 3377 -8438 292 -50 4100 0UP 0 ????????0100 ????????0000 0 1MI 8HR 60 4 66
GEORGIA TECH SEMRTS:Infrared, Eppley PIR                            Watts/m*m 0
 1 3377 -8438 292 -50 4101 0UP 0 ????????0100 ????????0000 0 1MI 8HR 60 4 66
GEORGIA TECH SEMRTS:Direct Normal Spectral, Eppley NIP with RG630   Watts/m*m 0
 1 3377 -8438 292 -50 6000 992X999 ????????0100 ????????0000 0 1MI 8HR 60 4 66
GEORGIA TECH SEMRTS:Global Spectral, Eppley PSP with RG630          Watts/m*m 0
 1 3377 -8438 292 -50 6100 0UP 0 ????????0100 ????????0000 0 1MI 8HR 60 4 66
GEORGIA TECH SEMRTS:Dry Bulb Temp. - lower level, R.M. Young 43406B Degrees C O
 1 3377 -8438 292 -50 8100 99NA999 ????????0100 ????????0000 0 1MI 8HR 60 4 66
GEORGIA TECH SEMRTS:Dry Bulb Temp. - upper level, R.M. Young 43406B Degrees C O
l 3377 -8438 292 -50 8101 99NA999 ????????0100 ????????0000 0 1MI 8HR 60 4 66
GEORGIA TECH SEMRTS:Dewpoint Temp. - lower level, R.M. Young 43406B Degrees C O
1 3377 -8438 292 -50 8120 99NA999 ????????0100 ????????0000 0 1MI 8HR 60 4 66
GEORGIA TECH SEMRTS:Dewpoint Temp. - upper level, R.M. Young 43406B Degrees C 0
1 3377 -8438 292 -50 8121 99NA999 ????????0100 ????????0000 0 lM1 8HR 60 4 66
GEORGIA TECH SEMRTS:Wind Direction - lower level, R.M. Young 8002 Degrees N 0
 l 3377 -8438 292 -50 8200 99NA999 ????????0100 ????????0000 0 1MI 8HR 60 4 66
GEORGIA TECH SEMRTS:Wind Direction - upper level, R.M. Young 8002 Degrees @ 0
 1 3377 -8438 292 -50 8201 99NA999 ????????0100 ????????0000 0 lM1 8HR 60 4 66
GEORGIA TECH SEMRTS:Wind Speed - lower level, R.M. Young 8002 m/s 0
 1 3377 -8438 292 -50 8210 99NA999 ????????0100 ????????0000 0 1MI 8HR 60 4 66
GEORGIA TECH SEMRTS:Wind Speed - upper level, R.M. Young 8002 m/s 0
 1 3377 -8438 292 -50 8211 99NA999 ????????0100 ????????0000 0 lMl 8HR 60 4 66
GEORGIA TECH SEMRTS:Station Pressure, YSI 14446 kiloPascalO
 1 3377 -8438 292 -50 8300 99NA999 ????????0100 ????????0000 0 1MI 8HR 60 4 66
GEORGIA TECH SEMRTS:Hour Cum. Rain, Belfor 5915RXE12 Weighing Gage mm 0
 1 3377 -8438 292 -50 8400 99NA999 ????????0100 ????????0000 0 1MI 8HR 60 4 66

Table of Contents
Return to RReDC Homepage ( http://www.nrel.gov/rredc )