subroutine butfilget(raw,infil,ave,BPM_TYP) ! BUTFILGET SUBROUTINE ORBIT C.ORBIT SBP 2002.06.18 !tpl call butfilget(raw,filnm,ave,but_typ) !int*4 raw(4,120), real*4 ave ! integer but_typ(120) !use 1-100: 0 if old proc, 1 if DSP ! note above is state when data TAKEN, not necessarily present state ! ------------------------------------------------------ ! integer *4 raw(4,120) !destination for raw readings ! real ave !floating button average ! character*(*) filename !name (with or without a directory) ! !of the orbit or buttons file. ! ----------------------------------------------------------- ! Jan 2008 sbp remove mpm dependencies (vnumbr, vmgprop) implicit none integer(4) jj(4),maxsat,minped,null,ier,raw(4,120),j,ntry integer loc,props(3),i,il,str_set,nda, ios,bpm_typ(120) integer dat_typ,mel,vnumbr, iloc real ave data maxsat,minped/19500,3400/ character(120) dummy,fulfil,orbfil,buth_line(10) character(12) mnem,butsavmnem(20) integer(4) nel,nbutsavdat,butsavdat(1000),butsavptr(20),sptr integer lun,lunget common /buth_save/ buth_line,str_set common /buth_save/ nbutsavdat,butsavmnem,butsavptr,butsavdat character(*) infil logical butdone ! orbfil=infil nbutsavdat=0 !# of save set mnem at end sptr=1 !ptr for 1st save set val if any ave=0 butdone=.false. lun=lunget() open(unit=lun,file=orbfil,action='read', status='old',iostat=ios) if (ios /= 0) then print *,' ',orbfil(1:50),' missing' print *,' returning with no change to data ' return endif il=0 !line # nda=0 do while(.true.) 111 read(lun,70,end=999)dummy if(butdone) goto 222 !save time reading as buts if already through do i=7,40,6 !clear overflow in old format if(dummy(i:i+5).eq.'******') dummy(i:i+5)=' 0' enddo 70 format(a80) il=il+1 !lines read so far if(il.lt.10) then buth_line(il)=dummy !save header in common if(il.eq.1) then !get save set str_set=0 iloc=index(dummy, ';') if(iloc.gt.1) then read(dummy(iloc+1:iloc+5),*,err=1133) str_set endif endif 1133 continue endif read(dummy,*,err=222,end=6677) loc, & raw(1,loc),raw(2,loc),raw(3,loc),raw(4,loc),bpm_typ(loc) goto 6678 !got flag wd ok, else set to 0 6677 read(dummy,*,err=222,end=222) loc, & raw(1,loc),raw(2,loc),raw(3,loc),raw(4,loc) !old files lack flag bpm_typ(loc)=0 6678 continue if(raw(1,loc).ne.0) then if(loc.le.100) then ave=ave+raw(1,loc)+raw(2,loc)+raw(3,loc)+raw(4,loc) nda=nda+1 endif endif ! if error, assume that it is a comment goto 333 !skip steering test if data ok 222 if(il.gt.30) butdone=.true. !30 lines, then hit comment if(butdone) then !check for steering data after orbit if(dummy(1:1).eq.' ') then mnem = dummy(2:13) if (mnem == '') cycle ! Ignore blank lines at end-of-file. if (dummy(14:) == '') cycle read(dummy(14:),*,err=333) nel, dat_typ if(dat_typ.eq.0) then !integer nbutsavdat=nbutsavdat+1 butsavptr(nbutsavdat)=sptr butsavmnem(nbutsavdat)=mnem read(LUN,205,err=333,end=999) (butsavdat(j),j=sptr,sptr+nel-1) sptr=sptr+nel else !skip if not integer do i=1,nel read(LUN,70,end=999,err=333)dummy enddo endif 205 format(12x,10i6) endif endif 333 continue enddo ! while(.true.) 999 continue if(nda.gt.0) ave=ave/(4.*float(nda)) ! print *,nda,' butns read ', ' ave=',ave close(unit=lun) return end subroutine butfilget