/[PAMELA software]/gpamela/gpspe/gpucollection.F
ViewVC logotype

Annotation of /gpamela/gpspe/gpucollection.F

Parent Directory Parent Directory | Revision Log Revision Log


Revision 3.4 - (hide annotations) (download)
Fri Apr 23 10:05:53 2010 UTC (14 years, 7 months ago) by pam-fi
Branch: MAIN
CVS Tags: HEAD
Changes since 3.3: +2 -5 lines
 version compatible with kinematics and badva1 read from files

1 bottai 3.1 *-- Author : Elena Taddei-Sergio Bottai 09/08/2005
2    
3     SUBROUTINE GPUCOLLECTION(np,nt)
4    
5     ***************************************************************************
6     * *
7     * *
8     * *
9     * Here we calculate the signal appearing on each ADC channel *
10     * starting from the charge collected on every strip of the silicon *
11     * sensor. Noise is kept from data of beam test. Capacitive coupling *
12     * between strips and energy to ADC calibration are introduced too. *
13     * *
14     * *
15     * Called by: GPDSPE *
16     * *
17     ***************************************************************************
18    
19     #include "gpstripspe.inc"
20 pam-fi 3.4
21 bottai 3.2 c
22     c new strip capacitance simulation 19/02/09 S. Bottai
23     c
24     c
25 bottai 3.1 dimension stripqxtanti(nstripx)
26     dimension stripqytanti(nstripy)
27    
28    
29    
30    
31    
32     ********zeroing**************
33    
34     do i=1,nstripx
35     stripqxtanti(i)=0.
36     enddo
37     do i=1,nstripy
38     stripqytanti(i)=0.
39     enddo
40    
41     ***************************
42     if(NT.eq.1.or.NT.eq.4) LADD=1
43     if(NT.eq.2.or.NT.eq.5) LADD=2
44     if(NT.eq.3.or.NT.eq.6) LADD=3
45    
46     *
47     * Odd strip, X side --> charge shared between adjacent strips
48     * EFFCOUPL --> coupling efficiency (capacitance to backplane =0?)
49     * SHIFTMASK --> asymmetry in charge division on X view
50     * different in each sensor (mask)
51    
52    
53     do j=(1+8),(nstripx-7),2
54     proxtanti(np,nt,j-1)=
55     + proxtanti(np,nt,j-1)+
56     + 0.5*effcoupl*proxtanti(np,nt,j)*(1.-shiftmask)
57    
58     proxtanti(np,nt,j+1)=
59     + proxtanti(np,nt,j+1)+
60     + 0.5*effcoupl*proxtanti(np,nt,j)*(1.+shiftmask)
61     proxtanti(np,nt,j)=0.
62     enddo
63    
64    
65     *
66     * Capacitive coupling: a fraction of the charge arriving at one strip
67     * appears at the output of the neighbouring amplifiers
68     * This fraction is about Cis/Cdec, where Cis is the interstrip
69     * capacitance and Cdec is the decoupling capacitance (see Turchetta)
70     * An algorithm has been chosen that is precise for low values of the
71     * capacitive coupling, i.e. if the INDUCED charge on a given strip
72     * is little compared with the COLLECTED one.
73     *
74    
75    
76     ******************** X side *************************
77    
78     c=cistrx/cdec
79     c2=cistrx2/cdec
80    
81    
82 bottai 3.2 do j=8,nstripx-6,2 ! only even strips on X side
83     CV jm2=1
84     CV IF(j-2.lt.8) jm2=0
85     CV jp2=1
86     CV IF(j+2.gt.(nstripx-6)) jp2=0
87     CV jm4=1
88     CV IF(j-4.lt.8) jm4=0
89     CV jp4=1
90     CV IF(j+4.gt.(nstripx-6)) jp4=0
91    
92    
93     stripqxtanti(j)=proxtanti(np,nt,j)
94     SUMF=0.
95 pam-fi 3.4 ccc DO KK=1,15
96 bottai 3.3 DO KK=1,4
97 bottai 3.2 KF=KK*2
98     IF(KK.EQ.1) FN=F1
99     IF(KK.EQ.2) FN=F2
100     IF(KK.EQ.3) FN=F3
101     IF(KK.EQ.4) FN=F4
102     IF(KK.GE.5) FN=F1/KK
103     IF((J-KF).GE.8) THEN
104     stripqxtanti(j)=stripqxtanti(j)+FN*proxtanti(np,nt,j-KF)
105     SUMF=SUMF+FN
106     ENDIF
107     IF((J+KF).LE.(nstripx-6)) THEN
108     stripqxtanti(j)=stripqxtanti(j)+FN*proxtanti(np,nt,j+KF)
109     SUMF=SUMF+FN
110     ENDIF
111     ENDDO
112    
113     stripqxtanti(j)=stripqxtanti(j)-SUMF*proxtanti(np,nt,j)
114    
115     cv stripqxtanti(j)=proxtanti(np,nt,j)*(1.-2.*(c+c2))+
116     cv + c*(1.-2.*c)*(jm2*proxtanti(np,nt,j-2)
117     cv + +jp2*proxtanti(np,nt,j+2))+
118     cv + (c**2)*(jm4*proxtanti(np,nt,j-4)*(1.+c2/(c**2))+
119     cv + 2.*proxtanti(np,nt,j)+jp4*proxtanti(np,nt,j+4)*(1.+c2/(c**2)))
120    
121 bottai 3.1
122     if(stripqxtanti(j).gt.1.e-8) then
123 bottai 3.2
124     IVA1=INT((J/2-1)/128)+1
125     IF(badva1(NP*2,LADD,IVA1).EQ.1) THEN
126     NSTRPX=NSTRPX+1
127     floatadcx=stripqxtanti(j)*xcalib
128     IF(NSTRPX.GT.MAXSTR) THEN
129     WRITE(6,*) 'ERROR - NSTRPX > MAXSTR'
130     NSTRPX=MAXSTR
131     ENDIF
132     NPSTRIPX(NSTRPX)=NP
133     NTSTRIPX(NSTRPX)=NT
134     ISTRIPX(NSTRPX)=(J/2)+(LADD-1)*1024
135     QSTRIPX(NSTRPX)=floatadcx
136     XSTRIPX(NSTRPX)=GLOBSTRIPX(NP,NT,J)
137     ENDIF
138    
139 bottai 3.1 endif
140     enddo
141    
142    
143     ******************** Y side *************************
144    
145     c=cistry/cdec
146    
147    
148     do j=1,nstripy
149    
150     jmen1=j-1
151     jm1=1
152     if(jmen1.lt.1) then
153     jm1=0
154     jmen1=1
155     endif
156    
157     jmen2=j-2
158     jm2=1
159     if(jmen2.lt.1) then
160     jm2=0
161     jmen2=1
162     endif
163    
164     jpiu1=j+1
165     jp1=1
166     if(jpiu1.gt.nstripy) then
167     jp1=0
168     jpiu1=nstripy
169     endif
170    
171     jpiu2=j+2
172     jp2=1
173     if(jpiu2.gt.nstripy) then
174     jp2=0
175     jpiu2=nstripy
176     endif
177    
178     stripqytanti(j)=proytanti(np,nt,j)*(1.-2.*c)+
179     + c*(1.-2.*c)*(jm1*proytanti(np,nt,jmen1)+jp1*
180     + proytanti(np,nt,jpiu1))+
181     + (c**2)*(jm2*proytanti(np,nt,jmen2)+2.*proytanti(np,nt,j)+
182     + jp2*proytanti(np,nt,jpiu2))
183    
184     if(stripqytanti(j).gt.1.e-8) then
185 bottai 3.2
186    
187     IVA1=INT((J-1)/128)+1
188     IF(badva1(NP*2-1,LADD,IVA1).EQ.1) THEN
189    
190     NSTRPY=NSTRPY+1
191     IF(NSTRPY.GT.MAXSTR) THEN
192     WRITE(6,*) 'ERROR - NSTRPY > MAXSTR'
193     NSTRPY=MAXSTR
194     ENDIF
195     floatadcy=stripqytanti(j)*ycalib
196     NPSTRIPY(NSTRPY)=NP
197     NTSTRIPY(NSTRPY)=NT
198     ISTRIPY(NSTRPY)=J+(LADD-1)*1024
199     QSTRIPY(NSTRPY)=FLOATADCY
200     YSTRIPY(NSTRPY)=GLOBSTRIPY(NP,NT,J)
201    
202 bottai 3.1 ENDIF
203 bottai 3.2
204 bottai 3.1 endif
205    
206     enddo
207    
208    
209     END
210    

  ViewVC Help
Powered by ViewVC 1.1.23