Document title: Fortran program OAWATSREAD used in generating the NDADS DE datatype WATS_2S_ASCII. Project: DE NDADS Datatype: WATS_2S_ASCII EID: SOFTWARE Super-EID: SOFTWARE There may be other documents also identified by this super-EID. NDADS filename: wats_oawatsread_de.for TRF entry: b47610.for in NSSDC's controlled digital document library, Dec. 1998. Document text follows: ---------------------- PROGRAM OAWATSREAD DIMENSION BUFF(13), IBUFF(13), ARY(9000) CHARACTER IN_FILE*10, OUT_FILE*50, IN_DIR*50, OUT_DIR*50, INF*60, $ INFOUT*60, FIRST_FILE*60, ARY*60 INTEGER*4 MAP(10), CONTEXT, N REAL*4 DATA(9) DATA BUFF(11)/99999./ DATA MAP/9, 13, 32, 33, 34, 37, 38, 39, 40, 76/ EQUIVALENCE (BUFF,IBUFF) PRINT*,'Enter input directory' READ(5, '(A50)')IN_DIR PRINT*,'Enter output directory' READ(5, '(A50)')OUT_DIR PRINT*,'Enter filr name (with *, example d*.dat)' READ(5, '(A10)')IN_FILE INF = IN_DIR//IN_FILE CALL LIB$FIND_FILE(INF, INFOUT, CONTEXT) I=1 ARY(I) = INFOUT FIRST_FILE = INFOUT 11 CALL LIB$FIND_FILE(INF, INFOUT, CONTEXT) IF(INFOUT.NE.FIRST_FILE)THEN I=I+1 ARY(I) = INFOUT GOTO 11 ENDIF IF(I.NE.1) I=I-1 jjj=0 DO K = 1, I c N = INDEX(ARY(K), ']') c OUT_FILE = OUT_DIR//ARY(K)(N+1:N+7)//'ASC' OPEN (UNIT=20,FILE=ARY(K),STATUS='OLD',FORM='UNFORMATTED') 30 READ (20,END=99) (BUFF(J),J=1,13) jjj=jjj+1 c open first daily file if(k.eq.1.and.jjj.eq.1) then write(out_file,1234) ibuff(1) OPEN (UNIT=21,FILE=OUT_FILE,STATUS='NEW') iold_date=ibuff(1) goto 4321 endif i_date=ibuff(1) if(i_date.lt.81200.or.i_date.gt.83050) then write(11,*) i_date,iold_date goto 30 endif if(i_date.ne.iold_date) then c close previous daily file and start new one close(21) write(out_file,1234) ibuff(1) 1234 format(I5,'_WATS_DE_2S_V01.ASC') OPEN (UNIT=21,FILE=OUT_FILE,STATUS='NEW') iold_date=i_date jjj=1 endif c find orbit parameters 4321 CALL OAREAD(IBUFF(1), IBUFF(2), IERR, MAP, DATA) c variables MODE, TIME1 and TIME2 are no longer needed c mode=ibits(idata(10,ii),0,8) is same as word 3 c time2=ibits(idata(10,ii),16,8) c time1=ibits(idata(10,ii),24,8) c c word 3: mode iw3=ibuff(3) if(iw3.lt.1.or.iw3.gt.9) ibuff(3)=9 c adding the slot position to word 4: iw4=ibuff(4) if(iw4.ne.1.and.iw4.ne.0) iw4=9 islot=IBITS(IBUFF(10),8,8) if(islot.lt.1.or.islot.gt.4) islot=9 ibuff(4)=islot*10+iw4 c word 5: mass iw5=ibuff(5) if(iw5.lt.1.or.iw5.gt.99) ibuff(5)=-9 c o/a parameter L xl=data(7) if(xl.lt.0.or.xl.gt.99.) data(7)=-9.0 c temperature te=buff(7) if(te.lt.200.or.te.gt.4000.0) buff(7)=-9.0 te=buff(12) if(te.lt.200.or.te.gt.4000.0) buff(12)=-9.0 c velocity ve=buff(8) if(abs(ve).gt.4000.0) buff(8)=9999.0 ve=buff(11) if(abs(ve).gt.4000.0) buff(11)=9999.0 ve=buff(13) if(abs(ve).gt.4000.0) buff(13)=9999.0 c decoding the instrument counting levels (word 9; not 10 as wrongly C indicated in the format.sfdu file) and the baffle times (word 10) ic1=IBITS(IBUFF(9),0,16) if(ic1.lt.0.or.ic1.gt.99999) ic1=-9 ic2=IBITS(IBUFF(9),16,16) if(ic2.lt.0.or.ic2.gt.99999) ic2=-9 it1=IBITS(IBUFF(10),24,8) if(it1.lt.0.or.it1.gt.999) it1=-9 it2=IBITS(IBUFF(10),16,8) if(it2.lt.0.or.it2.gt.999) it2=-9 c store in daily file in ASCII format WRITE (21,31) (IBUFF(J),J=1,5),BUFF(6),buff(12),buff(7), & buff(8),ic1,ic2,it1,it2,BUFF(13),buff(11),IFIX(DATA(1)), & (DATA(I), I=2,9) 31 FORMAT (1X,I5,I9,2I2,I3,E12.5,2F7.1,F8.1,1X,2I5,1X,2I3/1X, $ 2F8.1,I6,F7.1,F6.1,F7.1,2F6.2,F5.2,F6.1,F7.1) GOTO 30 99 CONTINUE CLOSE(20) ENDDO CLOSE(21) c write(7,*) ary(k),out_file,jjj END