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

Contents of /gpamela/gpspe/gpucollection.F

Parent Directory Parent Directory | Revision Log Revision Log


Revision 3.1 - (show annotations) (download)
Tue May 2 11:55:31 2006 UTC (18 years, 7 months ago) by bottai
Branch: MAIN
CVS Tags: v4r6, v4r7, v4r8, v4r9, v4r14, v4r12, v4r13, v4r10, v4r11
subroutine for the simulation of strip signasubroutine for the simulation of strip signal

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

  ViewVC Help
Powered by ViewVC 1.1.23