/[PAMELA software]/DarthVader/CalorimeterLevel2/src/selftrig.for
ViewVC logotype

Diff of /DarthVader/CalorimeterLevel2/src/selftrig.for

Parent Directory Parent Directory | Revision Log Revision Log | View Patch Patch

revision 1.1 by mocchiut, Fri May 19 13:15:51 2006 UTC revision 1.3 by mocchiut, Fri Mar 30 11:17:17 2007 UTC
# Line 1  Line 1 
1  C  C
2    C
3    C NOTE: THIS ROUTINE DOES NOT SEEMS TO WORK CORRECTLY, HAS TO BE CHECKED CAREFULLY
4    C
5    C
6  C---------------------------------------------------------------------  C---------------------------------------------------------------------
7        SUBROUTINE SELFTRIG        SUBROUTINE SELFTRIG
8  C---------------------------------------------------------------------  C---------------------------------------------------------------------
# Line 12  C Line 16  C
16        parameter (wcorr=1.0)        parameter (wcorr=1.0)
17        PARAMETER (MIP2GEV=0.0001059994)        PARAMETER (MIP2GEV=0.0001059994)
18        PARAMETER (PI=3.14159265358979324)        PARAMETER (PI=3.14159265358979324)
19        PARAMETER (calwidth=24.2)  CC      PARAMETER (calwidth=24.2)
20          PARAMETER (calwidth=24.1)
21        PARAMETER (ztopx=-26.18)        PARAMETER (ztopx=-26.18)
22        PARAMETER (ztopy=-26.76)        PARAMETER (ztopy=-26.76)
23        PARAMETER (zbotx=-45.17)        PARAMETER (zbotx=-45.17)
# Line 54  C Line 59  C
59        CALL VZERO(parz,2*22)        CALL VZERO(parz,2*22)
60        DO i = 1,22        DO i = 1,22
61           DO j = 1,96           DO j = 1,96
62              parz(1,i) = parz(1,i) + ESTRIP(1,i,j) ! sum up the energy in each x-plane              parz(1,i) = parz(1,i) + DEXY(1,i,j) ! sum up the energy in each x-plane
63              parz(2,i) = parz(2,i) + ESTRIP(2,i,j) ! sum up the energy in each y-plane              parz(2,i) = parz(2,i) + DEXY(2,i,j) ! sum up the energy in each y-plane
64              enet = enet + ESTRIP(1,i,j) + ESTRIP(2,i,j) ! sum up the total energy              enet = enet + DEXY(1,i,j) + DEXY(2,i,j) ! sum up the total energy
65           ENDDO           ENDDO
66           IF (parz(1,i).GE.parze) THEN ! find plane with max energy           IF (parz(1,i).GE.parze) THEN ! find plane with max energy
67              parze = parz(1,i)   ! the energy              parze = parz(1,i)   ! the energy
# Line 83  C Line 88  C
88        DO i = 1,22        DO i = 1,22
89           DO j = 1,94           DO j = 1,94
90    
91              IF ((ESTRIP(1,i,j)+              IF ((DEXY(1,i,j)+
92       &           ESTRIP(1,i,j+1)+       &           DEXY(1,i,j+1)+
93       &           ESTRIP(1,i,j+2)).GT.xemax3(i)) THEN       &           DEXY(1,i,j+2)).GT.xemax3(i)) THEN
94                 xemax3(i)=ESTRIP(1,i,j)+                 xemax3(i)=DEXY(1,i,j)+
95       &                   ESTRIP(1,i,j+1)+       &                   DEXY(1,i,j+1)+
96       &                   ESTRIP(1,i,j+2)       &                   DEXY(1,i,j+2)
97                 xncnt(i)=j+1                 xncnt(i)=j+1
98              ENDIF              ENDIF
99              IF ((ESTRIP(2,i,j)+              IF ((DEXY(2,i,j)+
100       &           ESTRIP(2,i,j+1)+       &           DEXY(2,i,j+1)+
101       &           ESTRIP(2,i,j+2)).GT.yemax3(i)) THEN       &           DEXY(2,i,j+2)).GT.yemax3(i)) THEN
102                 yemax3(i)=ESTRIP(2,i,j)+                 yemax3(i)=DEXY(2,i,j)+
103       &                   ESTRIP(2,i,j+1)+       &                   DEXY(2,i,j+1)+
104       &                   ESTRIP(2,i,j+2)       &                   DEXY(2,i,j+2)
105                 yncnt(i)=j+1                 yncnt(i)=j+1
106              ENDIF              ENDIF
107    
# Line 345  C Line 350  C
350  C  C
351  c     Sum up energies  c     Sum up energies
352  C  C
353              esumw = esumw + xypos*ESTRIP(view,nplane,npos)              esumw = esumw + xypos*DEXY(view,nplane,npos)
354              esum = esum + ESTRIP(view,nplane,npos)              esum = esum + DEXY(view,nplane,npos)
355           ENDDO           ENDDO
356  C  C
357   7100    CONTINUE   7100    CONTINUE
# Line 386  C       Line 391  C      
391        nrec=0        nrec=0
392        DO i=nsmax-width,nsmax+width        DO i=nsmax-width,nsmax+width
393  C  C
394           IF(i.GT.0.AND.i.LT.97.AND.ESTRIP(view,nplane,i).GT.0.0) THEN           IF(i.GT.0.AND.i.LT.97.AND.DEXY(view,nplane,i).GT.0.0) THEN
395  C              C            
396              nrec=nrec+1              nrec=nrec+1
397  C  C
398              CALL STRIP2POS(view,nplane,i,xypos,zpos)              CALL STRIP2POS(view,nplane,i,xypos,zpos)
399  C              C            
400              s1=s2              s1=s2
401              s2=s2+ESTRIP(view,nplane,i)              s2=s2+DEXY(view,nplane,i)
402              mx=(mx*s1+xypos*ESTRIP(view,nplane,i))/s2              mx=(mx*s1+xypos*DEXY(view,nplane,i))/s2
403              mx2=(mx2*s1+(xypos**2)*ESTRIP(view,nplane,i))/s2              mx2=(mx2*s1+(xypos**2)*DEXY(view,nplane,i))/s2
404  C  C
405           ENDIF           ENDIF
406  C          C        
# Line 501  c     Calculate the x- or y-position in Line 506  c     Calculate the x- or y-position in
506        nwaf=int((nstrip-1)/32) !what wafer (0-2)        nwaf=int((nstrip-1)/32) !what wafer (0-2)
507        wstr=mod(nstrip-1,32) !what strip in the wafer (0-31)        wstr=mod(nstrip-1,32) !what strip in the wafer (0-31)
508        wpos=0.096+0.122+wstr*0.244 !the position of the strip center in the wafer        wpos=0.096+0.122+wstr*0.244 !the position of the strip center in the wafer
509        pos=wpos+nwaf*8.0005-12.0005 !the position in the plane (oigo shifted to center of plane)  c      pos=wpos+nwaf*8.0005-12.0005 !the position in the plane (oigo shifted to center of plane)
510          pos=wpos+nwaf*8.0505-12.0005 !the position in the plane (oigo shifted to center of plane)
511            
512  c     Calculate z position and add x-y-offset depending on the plane number  c     Calculate z position and add x-y-offset depending on the plane number
513    

Legend:
Removed from v.1.1  
changed lines
  Added in v.1.3

  ViewVC Help
Powered by ViewVC 1.1.23