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

Contents of /gpamela/gpspe/gpudiffusion.F

Parent Directory Parent Directory | Revision Log Revision Log


Revision 3.2 - (show annotations) (download)
Tue May 8 15:02:39 2007 UTC (17 years, 6 months ago) by bottai
Branch: MAIN
CVS Tags: v4r14, v4r12, v4r13
Changes since 3.1: +8 -4 lines
 correction of a bug concerning Lorentz anglangle drift

1 SUBROUTINE GPUDIFFUSION(IACT,TRAPAR,NUMVOL,DELOSS,STEP,ITYPAR)
2 ********************************************************************************
3 *
4 * To perform diffusion of electron and holes bunch inside the silicon
5 * detectors of the spectrometer
6 *
7 * Variables definition:
8 * IN:
9 * IACT, integer specifing the action to be taken. It is the INWVOL
10 * variable in GCTRAK common
11 * 0: Track is inside a volume
12 * 1: Entering a new volume or is a new track
13 * 2: Track is exiting current volume
14 * TRAPAR, track parameter, is the VECT vector in GCTRAK common (x,y,z..)
15 * NUMVOL, integr array of numbers identifying the DETECTOR (NUMBV di gustep)
16 *
17 * DELOSS, energy loss in the step (GeV)
18 * ITYPAR, id particella della traccia(vhit(9) che sarà iparspe nell'entupla finale)
19 * OUT:
20 *
21 *
22 * Called by: GPUSPE
23 * Author: Elena Taddei, 04/08/2005 , S. Bottai 30/01/06
24 *
25 *************************************************************************************
26 #include "gpstripspe.inc"
27 #include "gpgeo.inc"
28 #include "gpgene.inc"
29 #include "gpkey.inc"
30
31 INTEGER IACT,NUMVOL(20)
32 REAL DELOSS, TRAPAR(7),xyzspa(3),VPOS(3),xyzspac(3)
33 REAL BMAGNET(3),STRPOSL(3),STRPOSG(3)
34 INTEGER ONCE
35 DATA ONCE /0/
36 SAVE ONCE
37
38 IF(NUMVOL(1).NE.0) THEN
39 NSPEPLANE=NUMVOL(1)
40 ELSE IF(NUMVOL(1).EQ.0) THEN
41 NSPEPLANE=6
42 ENDIF
43
44
45 VPOS(1)=TRAPAR(1)-STEP/2.*TRAPAR(4)
46 VPOS(2)=TRAPAR(2)-STEP/2.*TRAPAR(5)
47 VPOS(3)=TRAPAR(3)-STEP/2.*TRAPAR(6)
48
49
50 delossmev=deloss*1000.
51
52
53 call gmtod(VPOS,xyzspa,1)
54 zup=TSPA(3)-xyzspa(3)
55 zdown=TSPA(3)+xyzspa(3)
56
57
58 nearstripx=nearstx(xyzspa(1),xyzspa(2))
59 if(nearstripx.ne.0) then
60
61
62 dx=xyzspa(1)-xstrip(nearstripx)
63
64 ****************************************************************************
65 *
66 * X-view strips collect holes, Y-view strips collect electrons.
67 * Both charge carriers are shifted due to the magnetic field.
68 * The shift for holes is significant, because it is
69 * orthogonal to read-out strips.
70 * A correction for this effect is introduced.
71 * v is along -Z; B is along -Y --> shift is along -X
72 *
73 *****************************************************************************
74 IF(FFIELD.NE.0) THEN
75 CALL GUFLD(VPOS,BMAGNET)
76
77 c
78 c to be checked
79 c
80 xshift=xyzspa(1)+zdown*hallmob*1.e-4*BMAGNET(2)/10.
81 IF(NSPEPLANE.EQ.6) xshift=xyzspa(1)-
82 + zdown*hallmob*1.e-4*BMAGNET(2)/10.
83
84 else
85 xshift=xyzspa(1)
86 endif
87
88 *
89 * Now widths of Gaussian functions can be calculated by means of
90 * the routine sigmadiffus, that gives sigma in m --> *100 --> cm
91 *
92 sigxi=amax1(0.00014,100.*sigmadiffus(zdown)) !perchè min=1.4 um?
93
94 *
95 * Sharing of the charge on strips.
96 * erf(x) from cernlib computes the (signed) integral of the gaussian
97 * function from -x to x (sigma=sqrt(1./2.), x0=0). If you have gaussian
98 * function with x0=a, sigma=b, area between -x and x is obtainable by the
99 * following formula:
100 *
101 * A = erf((x-a)/(sqrt(2.)*b)) A>0 if x-a>0; A<0 if x-a<0
102 *
103 * erfc(x) (ALWAYS > 0) computes the complementary function, i.e.
104 * 2*integral between x and +infinity
105 * --> 0.5*erfc(x)=area of the gaussian between x to +inf.
106 *
107
108
109 NSTRIPLOW=MIN(23,NEARSTRIPX)
110 NSTRIPHIGH=MIN(15,NSTRIPX-NEARSTRIPX)
111
112 DO J=(NEARSTRIPX-NSTRIPLOW+8),(NEARSTRIPX+NSTRIPHIGH-6)
113 xqdivjm1=xstrip(j)-pitchx/2.
114 xqdivj=xstrip(j)+pitchx/2.
115 qfract=0.5*erfc((xqdivjm1-xshift)/(sqrt(2.)*sigxi))
116 + -0.5*erfc((xqdivj-xshift)/(sqrt(2.)*sigxi))
117
118 proxtanti(NSPEPLANE,numvol(2),j)=
119 + proxtanti(NSPEPLANE,numvol(2),j)+delossmev*qfract
120 IF(GLOBSTRIPX(NSPEPLANE,NUMVOL(2),J).EQ.0.) THEN
121 STRPOSL(1)=XSTRIP(J)
122 STRPOSL(2)=0.
123 STRPOSL(3)=0.
124 CALL GDTOM(STRPOSL,STRPOSG,1)
125 GLOBSTRIPX(NSPEPLANE,NUMVOL(2),J)=STRPOSG(1)
126 ENDIF
127
128 enddo
129 endif
130
131
132
133
134
135 nearstripy=nearsty(xyzspa(1),xyzspa(2))
136 if(nearstripy.ne.0) then
137
138 dy=xyzspa(2)-ystrip(nearstripy)
139
140
141 sigyi=amax1(0.00023,100.*sigmadiffus(zup ) ) !perchè min=2.3 um?
142
143 *
144 * The standard deviation on the Y side is increased
145 * according to a parabolic behaviour + a constant term near p-stop
146 *
147 py=pitchy
148 if (abs(dy).lt.abs((py-psy2)/2.)) then
149 sigyi=sigyi-psy1*(dy**2)+(py-psy2)*psy1*abs(dy)
150 else
151 sigyi=sigyi-psy1*(((py-psy2)/2.)**2)
152 + +(py-psy2)*psy1*abs((py-psy2)/2.)
153 endif
154
155
156 NSTRIPLOW=MIN(7,NEARSTRIPY)
157 NSTRIPHIGH=MIN(7,NSTRIPY-NEARSTRIPY)
158 do j=(NEARSTRIPY-NSTRIPLOW+1),(NEARSTRIPY+NSTRIPHIGH)
159 yqdivjm1=ystrip(j)-py/2.
160 yqdivj=ystrip(j)+py/2.
161 qfract=0.5*erfc((yqdivjm1-xyzspa(2))/(sqrt(2.)*sigyi))
162 + -0.5*erfc((yqdivj-xyzspa(2))/(sqrt(2.)*sigyi))
163
164 proytanti(NSPEPLANE,numvol(2),j)=
165 + proytanti(NSPEPLANE,numvol(2),j)+delossmev*qfract
166
167 IF(GLOBSTRIPY(NSPEPLANE,NUMVOL(2),J).EQ.0.) THEN
168 STRPOSL(1)=0.
169 STRPOSL(2)=YSTRIP(J)
170 STRPOSL(3)=0.
171 CALL GDTOM(STRPOSL,STRPOSG,1)
172 GLOBSTRIPY(NSPEPLANE,NUMVOL(2),J)=STRPOSG(2)
173 ENDIF
174
175 enddo
176
177 endif
178
179
180
181
182
183 END
184
185 *
186 * ////////////////////////////////////////////////////////////////////////////////////////
187 *
188 real function sigmadiffus(zp)
189 *********************************************************************
190 * Width of the Gaussian function due to diffusion spread is found.
191 * x,y,z : where charge is generated (position in given in cm)
192 * As output standard deviation (m) due to diffusion in silicon
193 * Diffusion coefficients are proportional to mobility: D=kTm/q,
194 * where m is mobility: this is true in the Internatinal System
195 * of units, not in GCS. We compute this quantity in the
196 * I.S. (renormalitation for m --> cm has been taken into account:
197 * zpsi=zp/100. ! cm --> m
198 * Efield=Efield*100. ! V/cm --> V/m --> 10^-4 )
199 * WARNING!! Sigma is independent on the carrier mobility m,
200 * because hdiff = c*m but time = c/m. As a consequence,
201 * sigma is independent on the dopant concentration.
202 * E-h pairs created are mostly confined in a tube of about 1 um diameter.
203 **********************************************************************
204 #include "gpstripspe.inc"
205
206 zm=zp/100. ! cm --> m
207 Evm=ebias*100. ! V/cm --> V/m
208
209 vdepl=55.
210 vappl=70.
211 thick=3.e-4
212 *
213 * timemu = collection time * mobility
214 *
215 timemu=abs(-(thick**2/(2.*vdepl))*log(1-(2*vdepl*zm)/
216 + ((vdepl+vappl)*thick)))
217
218 sigmadiffus=sqrt((2.*boltis*temperature*timemu)/eis)+dsigma
219
220 return
221 end
222
223 * ////////////////////////////////////////////////////////////
224
225
226
227 real function xstrip(j)
228 cv parameter.........
229 #include "gpstripspe.inc"
230 parameter (jlastx=2042)
231 parameter (xlast=5.333/2.-0.07315)
232 parameter (jfirstx=8)
233 parameter (xfirst=0.07315-5.333/2.)
234
235 px=pitchx
236 py=pitchy
237 if(j.lt.jfirstx.or.j.gt.jlastx) then
238 write(6,*) 'error , stripx=',j,'not existing'
239 xstrip=-1.e10
240 endif
241 xstrip=(j-jfirstx)*px+xfirst
242
243 end
244
245
246 real function ystrip(j)
247 cv parameter.........
248 #include "gpstripspe.inc"
249 parameter (jlasty=1024)
250 parameter (ylast=7./2.-0.09855)
251 parameter (jfirsty=1)
252 parameter (yfirst=0.0985-7./2.)
253
254 px=pitchx
255 py=pitchy
256 if(j.lt.jfirsty.or.j.gt.jlasty) then
257 write(6,*) 'error , stripy=',j,'not existing'
258 ystrip=-1.e10
259 endif
260 ystrip=(j-jfirsty)*py+yfirst
261
262 end
263
264
265
266 function nearstx(x,y)
267 cv parameter.........
268 #include "gpstripspe.inc"
269 parameter (jlastx=2042)
270 parameter (xlast=5.333/2.-0.07315)
271 parameter (jfirstx=8)
272 parameter (xfirst=0.07315-5.333/2.)
273 parameter (y1xstrip=0.1117-7./2.)
274 parameter (y2xstrip=7./2.-0.09)
275
276 px=pitchx
277 py=pitchy
278 if(x.lt.(xfirst-px/2.).or.x.gt.(xlast+px/2.)) then
279 nearstx=0
280 return
281 endif
282 if(y.lt.y1xstrip.or.y.gt.y2xstrip) then
283 nearstx=0
284 return
285 endif
286
287 nearstx=int((x-xfirst)/px)+jfirstx
288 if( (x-xstrip(nearstx)).gt.(px/2.) ) nearstx=nearstx+1
289
290
291 end
292
293 function nearsty(x,y)
294 cv parameter.........
295 #include "gpstripspe.inc"
296 parameter (jlasty=1024)
297 parameter (ylast=7./2.-0.09855)
298 parameter (jfirsty=1)
299 parameter (yfirst=0.0985-7./2.)
300
301 parameter (x1ystrip=0.0894-5.333/2.)
302 parameter (x2ystrip=5.333/2.-0.1221)
303
304 px=pitchx
305 py=pitchy
306 if(y.lt.(yfirst-py/2.).or.y.gt.(ylast+py/2.)) then
307 nearsty=0
308 return
309 endif
310 if(x.lt.x1ystrip.or.x.gt.x2ystrip) then
311 nearsty=0
312 return
313 endif
314
315 nearsty=int((y-yfirst)/py)+jfirsty
316 if( (y-ystrip(nearsty)).gt.(py/2.) ) nearsty=nearsty+1
317
318
319
320 end

  ViewVC Help
Powered by ViewVC 1.1.23