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

Annotation of /gpamela/gpspe/gpucollection.F

Parent Directory Parent Directory | Revision Log Revision Log


Revision 3.2 - (hide annotations) (download)
Wed May 20 09:17:59 2009 UTC (15 years, 9 months ago) by bottai
Branch: MAIN
Changes since 3.1: +80 -39 lines
 new xstrips simulation

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

  ViewVC Help
Powered by ViewVC 1.1.23