*------------------------------------------------------------------------ * VIEW visualizes a reconstruction matrix * -====- * * visualizes a reconstruction matrix * - reads reconstruction matrix and * - writtes it as 2-dim histograms to a PAW/hbook ntuple file * * written by Markus Muehlbauer *------------------------------------------------------------------------ IMPLICIT NONE INTEGER nwpawc,icycle,istat PARAMETER (nwpawc = 1000000) REAL paw(nwpawc) COMMON /pawc/paw CHARACTER name*80,filename*80 ! commonblocks holding the reconstruction matrices INTEGER NTERMS PARAMETER (NTERMS = 300) INTEGER e(NTERMS,4), num REAL C(NTERMS,4) COMMON /matrix/ C,e,num ! other variables CHARACTER*8 col(NTERMS),xcol(NTERMS) CHARACTER*8 row(NTERMS),xrow(NTERMS) INTEGER icol(NTERMS),irow(NTERMS),nrow,ncol REAL wcol(NTERMS),wrow(NTERMS) INTEGER i,j,m REAL x,y 10 FORMAT (X,A,$) 20 FORMAT (A) PRINT *,'VIEW - a reconstruction matrix' PRINT *,'==== (standard matrix layout)' PRINT * PRINT * PRINT 10,'Enter the name of the matrix to view: ' READ (5,20) filename ! read the matrices name = filename(:INDEX(filename,' ')-1)//'.map' print *, 'Reading the matrix '// > name(:index(name,' ')) CALL viewInit (name) ! init HBOOK CALL hlimit(nwpawc) ! open the result hbook file name = 'view_'//filename(:INDEX(filename,' ')-1)//'.hbook' print *, 'Writing the matrix view ' > //name(:index(name,' ')) CALL hropen(21,'Output',name,'NX',4096,istat) ! find the row/column labels nrow = 0 ncol = 0 DO i=1,num WRITE (col(i),'(2I1,''yy'')') e(i,1),e(i,2) WRITE (row(i),'(''xx'',2I1)') e(i,3),e(i,4) m = 0 DO j= 1,ncol IF (col(i) .EQ. xcol(j)) m = j ENDDO IF (m .EQ. 0) THEN ncol = ncol+1 xcol(ncol) = col(i) m = ncol ENDIF icol(i) = m wcol(i) = 0.5**e(i,1) * 0.06**e(i,2) m = 0 DO j= 1,nrow IF (row(i) .EQ. xrow(j)) m = j ENDDO IF (m .EQ. 0) THEN nrow = nrow+1 xrow(nrow) = row(i) m = nrow ENDIF irow(i) = m wrow(i) = 0.25**e(i,3) * 0.03**e(i,4) ENDDO CALL hbook2(1, 'weigth',ncol,0.5,0.5+ncol,nrow,0.5,0.5+nrow,0) CALL hbook2(10,'Adelta',ncol,0.5,0.5+ncol,nrow,0.5,0.5+nrow,0) CALL hbook2(20,'Adxdz' ,ncol,0.5,0.5+ncol,nrow,0.5,0.5+nrow,0) CALL hbook2(30,'Ay' ,ncol,0.5,0.5+ncol,nrow,0.5,0.5+nrow,0) CALL hbook2(40,'Adydz' ,ncol,0.5,0.5+ncol,nrow,0.5,0.5+nrow,0) CALL hlabel(1, ncol,xcol,'NX') CALL hlabel(1, nrow,xrow,'NY') CALL hlabel(10,ncol,xcol,'NX') CALL hlabel(10,nrow,xrow,'NY') CALL hlabel(20,ncol,xcol,'NX') CALL hlabel(20,nrow,xrow,'NY') CALL hlabel(30,ncol,xcol,'NX') CALL hlabel(30,nrow,xrow,'NY') CALL hlabel(40,ncol,xcol,'NX') CALL hlabel(40,nrow,xrow,'NY') DO i=1,num x = icol(i) y = irow(i) CALL HFILL(1, x,y,wcol(i)*wrow(i)) CALL HFILL(10,x,y,C(i,1)) CALL HFILL(20,x,y,C(i,2)) CALL HFILL(30,x,y,C(i,3)) CALL HFILL(40,x,y,C(i,4)) ENDDO CALL hrout(0,icycle,' ') CALL hrend('Output') STOP END SUBROUTINE viewInit (filename) IMPLICIT NONE CHARACTER filename*(*) * -- load the Gen reconstruction map * ! transport map common block INTEGER NTERMS PARAMETER (NTERMS = 300) INTEGER e(NTERMS,4), edum(4), num REAL C(NTERMS,4), cdum(4) COMMON /matrix/ C,e,num ! other variables INTEGER eof,ii,jj ! clear all the map arrays num = 0 DO ii=1,NTERMS DO jj=1,4 C(ii,jj)=0. ENDDO DO jj=1,4 e(ii,jj)=0 ENDDO ENDDO ! read the map data from the file OPEN (UNIT=97,FILE=filename,STATUS='OLD') READ (97,'(4(E14.7E2,X),4I1)',IOSTAT=eof) > cdum(2),cdum(3),cdum(4),cdum(1),(edum(jj),jj=1,4) DO WHILE (eof .GE. 0) num=num+1 DO ii=1,4 C(num,ii)=cdum(ii) ENDDO DO ii=1,4 e(num,ii)=edum(ii) ENDDO READ (97,'(4(E14.7E2,X),4I1)',IOSTAT=eof) > cdum(2),cdum(3),cdum(4),cdum(1),(edum(jj),jj=1,4) ENDDO CLOSE (97) RETURN END