subroutine radmon(rmnem,ir,cunitsi,mv,mrem,ierr) ! RADMON SUBROUTINE PLOT C.RAD MG 95.01.11 !tpl call radmon(mnem,ele,cunits,mv,mrem,ierr) !convert cu to mrem ! ierr =-1 if bad mnem, -10 if below .01 mrem, -100 if above 10000. ! implicit none ! integer*4 maxtot,nmn parameter (maxtot=100) parameter (nmn=10) ! real mv,mrem,mrmin,mrmax real c(4,nmn) ! 4 coeffs,10 radiation monitor types ! character*12 rmnem,radmnems(6),rname(maxtot) ! integer*2 cunitsi integer*4 cunits ! integer*4 vnumbr integer*4 nele(0:6) integer*4 radtype(maxtot,6),length(maxtot) data radtype /maxtot*0,maxtot*0,maxtot*0,maxtot*nmn, & maxtot*0,maxtot*0/ !init intd typ integer*4 npt,ipn,u,il,i,j,imn,ierr integer*4 irt,ir ! logical,save:: first(6)=.true. logical,save:: init=.false. ! real expo data mrmin/0.00101/ data mrmax/10000.0/ data first/3*.true.,.FALSE.,2*.true./ !NO NEED FOR INTD COEFF data radmnems/'RAD GAMM MON','RAD NEUT MON','RAD LGAM MON', & 'RADNEUT INTD', 'RAD TEST MON','RAD MONITORS'/ data nele(0)/0/ ! do i=1,6 if (rmnem == radmnems(i)) imn=i if(.not.init) nele(i)=vnumbr(radmnems(i)) if(nele(i) > maxtot) then nele(i)=maxtot call csr_bell call strout(' radmon !! need to enlarge type array ') endif enddo init=.true. cunits=cunitsi !to allow clip cunits=max(-10000,min(10000,cunits)) mv=0.0 mrem=0.0 ierr=0 ! ---------------------------------------------------------------------- ! ----do the following only if it's the first time for this mnemonic---- if (first(imn)) then first(imn)=.false. call vmgtyp(rmnem,1,nele(imn), radtype(1,imn)) call vmgprpn(rmnem,1,nele(imn),42, radtype(1,imn)) !till vmgtyp fixed call vmgetf('RAD COEFFNUM',1,40,c) endif ! ---------------------------------------------------------------------- irt=radtype(ir,imn) !get back if (irt > 0) then if (irt > nmn) then ierr=-1 print *,' WARNING: WRONG RADIATION MONITOR TYPE' go to 100 endif ! mv=(5.*float(cunits))/2. !2000 computer units=5000 mV ! NO! mv to cunits depends on type of monitor...see info in database ! for mutiplicative factor and offset. ! print *,' ir irt c(1) c(2) c(3) c(4) cunits' ! print *,ir,irt,(c(il,irt),il=1,4),cunits if(irt == nmn) then !last is always intd type mrem=float(cunits)/8000.*60. !8000 counts per mrem, 1 min elseif (c(4,irt) /= 0.) then expo=((c(2,irt)*(cunits+c(3,irt)))/c(4,irt)) expo=max(-10.0,min(10.0,expo)) !limit range ! TYPE 9090, expo,c(1,irt),c(2,irt),c(3,irt),c(4,irt) 9090 format(' expo, c ',5e12.4) mrem=c(1,irt)*10**expo if (c(2,irt) == 0.) then mrem=c(1,irt)*(cunits+c(3,irt))/c(4,irt) endif if (mrem < mrmin) then !dont lowlim dig system mrem=mrmin ierr=ierr-10 endif endif if (mrem > mrmax) then mrem=mrmax ierr=ierr-100 endif endif 100 continue return end