/[PAMELA software]/PamVMC/trk/src/f77/gpucollection.F
ViewVC logotype

Contents of /PamVMC/trk/src/f77/gpucollection.F

Parent Directory Parent Directory | Revision Log Revision Log


Revision 1.5 - (show annotations) (download)
Fri Jun 12 18:39:59 2009 UTC (15 years, 7 months ago) by pam-rm2
Branch: MAIN
CVS Tags: v1r0, HEAD
Changes since 1.1: +88 -45 lines
Error occurred while calculating annotation data.
- Introduced user-defined names of output files and random seeds number.
Users can do it use options of PamVMCApplication constructor:
PamVMCApplication(const char* name,  const char *title, const char*
filename="pamtest", Int_t seed=0).
The Random object that I use is TRandom3 object which has astronomical
large period (in case of default initialization 0). All random generators
in the code use this object by calling of gRandom singleton which keeps
it.

- Corrected TOF digitization routine. No problems with TDC hits due to
hadronic interactions anymore.

- Some small changes was done to compile code under Root 5.23. +
geant4_vmc v. 2.6 without any warnings

- Some classes of PamG4RunConfiguartion was changed for geant4_vmc v.
2.6.Some obsolete classes was deleted as soon as developers implemented
regions.

- Navigation was changed from "geomRootToGeant4" to "geomRoot", because on
VMC web page written that as soon as Geant4 has no option ONLY/MANY
translation of overlapped geometry to Geant4 through VGM could be wrong.
I'd like to stay with Root navigation:
http://root.cern.ch/root/vmc/Geant4VMC.html. This should be default
option.

- New Tracker digitization routine written by Sergio was implemented

- PamVMC again became compatible with geant4_vmc v.2.5 and ROOT 5.20.
 The problem was that ROOT developers introduced in TVirtualMC class a new
method SetMagField and new base class:TVirtualMagField from which
user-defined classes shoukd be derived

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 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 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 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
124 if(stripqxtanti(j).gt.1.e-8) then
125
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 c PRINT*,'1NPSTRIPX ',NP, ' NTSTRX ', NT,' ISTRIPX ', ISTRIPX(NSTRPX)
140 c PRINT*,'2Q ',QSTRIPX(NSTRPX),' XS ', XSTRIPX(NSTRPX)
141 c PRINT*,' '
142
143 ENDIF
144
145 endif
146 enddo
147
148 c PRINT*, 'NSTRPX', NSTRPX
149
150 ******************** Y side *************************
151
152 c=cistry/cdec
153
154
155 do j=1,nstripy
156
157 jmen1=j-1
158 jm1=1
159 if(jmen1.lt.1) then
160 jm1=0
161 jmen1=1
162 endif
163
164 jmen2=j-2
165 jm2=1
166 if(jmen2.lt.1) then
167 jm2=0
168 jmen2=1
169 endif
170
171 jpiu1=j+1
172 jp1=1
173 if(jpiu1.gt.nstripy) then
174 jp1=0
175 jpiu1=nstripy
176 endif
177
178 jpiu2=j+2
179 jp2=1
180 if(jpiu2.gt.nstripy) then
181 jp2=0
182 jpiu2=nstripy
183 endif
184
185 stripqytanti(j)=proytanti(np,nt,j)*(1.-2.*c)+
186 + c*(1.-2.*c)*(jm1*proytanti(np,nt,jmen1)+jp1*
187 + proytanti(np,nt,jpiu1))+
188 + (c**2)*(jm2*proytanti(np,nt,jmen2)+2.*proytanti(np,nt,j)+
189 + jp2*proytanti(np,nt,jpiu2))
190
191 if(stripqytanti(j).gt.1.e-8) then
192
193
194 IVA1=INT((J-1)/128)+1
195 IF(badva1(NP*2-1,LADD,IVA1).EQ.1) THEN
196
197 NSTRPY=NSTRPY+1
198 IF(NSTRPY.GT.MAXSTR) THEN
199 WRITE(6,*) 'ERROR - NSTRPY > MAXSTR'
200 NSTRPY=MAXSTR
201 ENDIF
202 floatadcy=stripqytanti(j)*ycalib
203 NPSTRIPY(NSTRPY)=NP
204 NTSTRIPY(NSTRPY)=NT
205 ISTRIPY(NSTRPY)=J+(LADD-1)*1024
206 QSTRIPY(NSTRPY)=FLOATADCY
207 YSTRIPY(NSTRPY)=GLOBSTRIPY(NP,NT,J)
208 c PRINT*,'1NPSTRIPY ',NP, ' NTSTRY ', NT,' ISTRIPY ', ISTRIPY(NSTRPY)
209 c PRINT*,'2Q ',QSTRIPY(NSTRPY),' YS ', YSTRIPY(NSTRPY)
210
211 ENDIF
212
213 endif
214
215 enddo
216
217 c PRINT*, 'NSTRPY', NSTRPY
218 END
219

  ViewVC Help
Powered by ViewVC 1.1.23