! NMRGET SUBROUTINE MAGNET C.HARD SBP 91.04.16 ! call nmrget(sen1,sen2) ! Normal dipole and hardbend field in real*4 gauss. ! Warning, accesses control system. subroutine nmrget(sen1,sen2) implicit none ! integer(4) i,nmrind integer(4) nmrread(4) integer(4) high,low integer(4) ish(7) ! real sens(2),weight(7),gauss,sen1,sen2,unix_flt_tovms ! data ish /-8,-4,0,-12,-8,-4,0/ data weight /10000.,1000.,100.,10.,1.,.1,.01/ ! call vxgetn( 'CSR NMR READ' ,1,4,nmrread) do nmrind=1,2 low=nmrread(nmrind*2) high=nmrread(-1+nmrind*2) gauss=0. do i=1,7 if(i > 3) then gauss=gauss+weight(i)*float(and(15, ishft(low,ish(i)))) else gauss=gauss+weight(i)*float(and(15, ishft(high,ish(i)))) endif enddo if(nmrind == 1) then sen1=gauss else sen2=gauss endif sens(nmrind)=unix_flt_tovms(gauss) !to put in db enddo call vmputn('CSR STATBLOK',23,24,sens) end subroutine