(file) Return to gukine.f CVS log (file) (dir) Up to [HallC] / geant_gep / src

  1 jones 1.1       subroutine gukine
  2           c
  3 brash 1.2 c
  4           c This is a subroutine to generate (x,y,theta,phi,delta-p) at
  5           c the focal plane for proton from the H(e,e'p) reaction. 
  6           c It makes use of a simple kinematics routine, some knowledge
  7           c of the extended target acceptances, and polynomials for the
  8           c transport through the spectrometer from John Lerose.
  9 jones 1.1 c
 10                 implicit none
 11                 integer       ikine,itra,istak,ivert,ipart,itrtyp,napart,ipaold
 12                 real          pkine,amass,charge,tlife,vert,pvert
 13                 common/gckine/ikine,pkine(10),itra,istak,ivert,ipart,itrtyp
 14                +      ,napart(5),amass,charge,tlife,vert(3),pvert(4),ipaold
 15                 integer nubuf
 16                 parameter (nubuf=10)
 17                 real ubuf(nubuf),rndm(3)
 18                 integer ntbeam,nttarg,nvtx
 19                 save nvtx
 20                 real plab(3),ptot,etot
 21                 real*8 ang,angr,phi,phir,psir
 22 brash 1.2       real mp,ea,pa,remain
 23 brash 1.4       real r2,r3
 24 jones 1.1       integer nt,ierri,i0,i1,i2,i3
 25 brash 1.2       integer i,j,k,ichoice,ichoice2,iremain
 26 jones 1.1       real*8 rotmat,xyz(3),xyznew(3),termang
 27                 integer ic,ii,jj
 28 brash 1.2       integer*4 junk1,ikinsetting
 29 jones 1.1       real*8 xfp,yfp,tthfp,tphfp,pfp,junk2,junk3,thfp,phfp
 30                 real*8 e0(10),eang(10),hang(10),targ_thick(10)
 31 brash 1.2       real*8 xtgt,ytgt,thtgt,phtgt,ptgt,dptgt
 32 brash 1.4       real yf,ff,thetaf
 33 jones 1.1       character*80 junkline
 34           c
 35 brash 1.4 c The following variables are the SIMC variables
 36           c
 37                 real*8 x,y,z                            !(cm)
 38                 real*8 dpp                              !delta p/p (%)
 39                 real*8 dxdz,dydz                        !X,Y slope in spectrometer
 40                 real*8 x_fp,y_fp,dx_fp,dy_fp            !Focal plane values to return
 41                 real*8 p_spec,th_spec                   !spectrometer setting
 42                 real*8 fry                              !vertical position@tgt (+y=down)  
 43                 real*8 pathlen
 44                 logical ms_flag                         !mult. scattering flag
 45                 logical wcs_flag                        !wire chamber smearing flag
 46                 logical decay_flag                      !check for particle decay
 47                 logical ok_spec                         !true if particle makes it
 48                 real*8 resmult,m2
 49           c
 50 jones 1.1       include 'fpp_local.h'
 51                 include 'geant_local.h'
 52           c
 53           c      include 'parameter.h'
 54           c      include 'espace_type.h'
 55           c      include 'detector.h'
 56           c      include 'transport.h'
 57           c      include 'option.h'
 58           c
 59 brash 1.2       common/kincom/rotmat(3,3)
 60                 call grndm ( rndm , 3 )
 61 jones 1.1 c
 62 brash 1.2  111  format(a80)
 63                 iremain=nevent/1000
 64                 remain=nevent/1000.0
 65           c      if(iremain.eq.remain) write(*,*)'nevent =',nevent
 66 jones 1.1       write(*,*)'nevent =',nevent
 67           
 68                 if(nevent.eq.0) then
 69 brash 1.2 c         write(*,*)'Getting kinematics setting ...'
 70 jones 1.1 	 open(unit=1,file='geant_kinematics.dat',type='UNKNOWN')
 71                    read(1,*)ikinsetting
 72           	 close(unit=1)
 73                    open(unit=1,file='hdr_gep.dat',status='old')
 74                    do i=1,10
 75                       read(1,*)e0(i),eang(i),hang(i),targ_thick(i)
 76                    enddo
 77                    einc=e0(ikinsetting)
 78                    hrse_ang=eang(ikinsetting)
 79                    hrsh_ang=-1.0*hang(ikinsetting)
 80 brash 1.2          trg_thk=targ_thick(ikinsetting)
 81 jones 1.1          close(unit=1)
 82                 endif
 83           
 84 brash 1.2 c
 85           c Now we have the incident electron energy and the angles of 
 86           c the two spectrometers, as well as the target thickness.
 87           c We need to use a) kinematics routines and b) some knowledge
 88           c of the extended target acceptances to choose the x,y,theta,phi,
 89           c and dpmom at the target.
 90           c
 91                 call kincalc(einc,hrse_ang,hrsh_ang,trg_thk,xtgt,ytgt,
 92                $        thtgt,phtgt,ptgt,dptgt)
 93           
 94           c
 95           c At this point, after using polynomials from Lerose, we should
 96           c have x,y,theta,phi, and dpmom at the focal plane.
 97           c
 98           c      write(*,*)'Back from kincalc ...'
 99           c      write(*,*)xtgt,ytgt,thtgt,phtgt,dptgt
100 brash 1.4 c      x(1)=tan(phtgt)
101           c      x(2)=ytgt
102           c      x(3)=tan(thtgt)
103           c      x(4)=dptgt
104 brash 1.2       y_target=ytgt*100.0
105 brash 1.4 c
106           c Here is where we call the SIMC routines to calculate the focal plane 
107           c quantities from the target quantities.
108           c
109           c      xfp=xfinal(x,4)*100.0
110           c      phfp=atan(thetaf(x,4))/3.14159265*180.0
111           c      yfp=yf(x,4)*100.0
112           c      thfp=atan(ff(x,4))/3.14159265*180.0
113                 p_spec=ptgt
114                 th_spec=hrsh_ang
115                 dpp=dptgt*100.00
116                 x=xtgt
117                 y=ytgt
118                 z=0.0
119                 dxdz=tan(phtgt*3.14159265/180.0)
120                 dydz=tan(thtgt*3.14159265/180.0)
121           c      write(*,*)p_spec,th_spec,dpp
122           c      write(*,*)x,y,z
123           c      write(*,*)dxdz,dydz
124           c
125           c Call to SIMC routine
126 brash 1.4 c
127                 decay_flag=.false.
128                 wcs_flag=.false.
129                 ms_flag=.false.
130                 m2=(938.2796**2)
131                 call mc_hms (p_spec, th_spec, dpp, x, y, z, dxdz, dydz,
132                >          x_fp, dx_fp, y_fp, dy_fp, m2,
133                >          ms_flag, wcs_flag, decay_flag, resmult, fry, 
134                > ok_spec, pathlen)
135           c      write(*,*)p_spec,th_spec,dpp
136           c      write(*,*)x,y,z
137           c      write(*,*)dxdz,dydz
138                 write(6,*)x_fp,dx_fp,y_fp,dy_fp,ok_spec
139           c      write(*,*)m2,ms_flag,wcs_flag,decay_flag
140           c      write(*,*)resmult,fry,ok_spec,pathlen
141           
142                 xfp=x_fp
143                 phfp=atan(dx_fp)/3.14159265*180.0
144                 yfp=y_fp
145                 thfp=atan(dy_fp)/3.14159265*180.0
146           c
147 brash 1.4       do ii=1,20
148           	ntuple_array(ii)=0.0
149                 enddo
150                 ntuple_array(11)=real(xfp)
151                 ntuple_array(12)=real(yfp)
152                 ntuple_array(13)=real(thfp)
153                 ntuple_array(14)=real(phfp)
154           c
155 brash 1.3       pcentral=ptgt
156 brash 1.4       pfp=dptgt 
157           c    
158           c
159 brash 1.2 c	write(*,*)'Focal plane quantities ...'
160           c	write(*,*)xfp,yfp,thfp,phfp,pcentral,pfp
161           
162           c      xfp=xtgt      ! in cm
163           c      yfp=ytgt      ! in cm
164           c      thfp=thtgt/3.14159265*180.0   ! in degrees
165           c      phfp=phtgt/3.14159265*180.0   ! in degrees
166           c      pcentral=ptgt ! in MeV/c
167           c      pfp=dptgt     ! fraction of central momentum
168           c
169           c Finally, we convert this information over to a format that GEANT likes.
170           c
171 jones 1.1 
172 brash 1.2  1135 dpmom=pfp
173                 pfp=pcentral*(1.0+pfp)
174                 pmom=pfp
175                 ea=sqrt(pfp**2+938.2796**2)
176                 tinit=ea-938.2796
177                 vert(1)=xfp
178                 vert(2)=yfp
179                 vert(3)=0.0
180                 ntbeam  = 0.0
181                 nttarg  = 0.0
182                 ubuf(1) = 0.0
183                 
184            1000 continue
185           c     
186                 ipart      = 14           ! geant pid  (8=pi+,9,pi-, 14 =p)
187                 ptot=pfp/1000.
188 jones 1.1       call grndm ( rndm , 3 )
189 brash 1.2       angr=thfp*3.14159265/180.0
190                 phir=phfp*3.14159265/180.0
191                 psir=datan(dtan(phir)*dcos(angr))
192           
193                 ang=thfp
194                 phi=phfp
195 jones 1.1 c
196 brash 1.2 c these are the actual parameters for the track.  
197 jones 1.1 c
198 brash 1.2       xinit=vert(1)
199                 yinit=vert(2)
200                 thinit=angr
201                 phiinit=phir
202                 
203           c      sptransport.l.particle.fp_h.ph=dtan(angr)
204           c      sptransport.l.particle.fp_h.th=dtan(phir)
205           c      
206           c      sptransport.l.particle.fp_h.x=vert(1)/100.0
207           c      
208           c      sptransport.l.particle.fp_h.y=vert(2)/100.0
209 jones 1.1 c
210           c
211 brash 1.2 c next we misalign the track to simulate misalignment of the
212           c entire space frame with respect to the vdc's
213 jones 1.1 c
214 brash 1.2 c just include the translational offsets to start
215 jones 1.1 c
216 brash 1.2 c	write(*,*)vert(1),vert(2),angr,phir,psir
217           
218           	xofff=0.0
219           	yofff=0.0
220           	thofff=0.0
221           	phofff=0.0
222           	psofff=0.0
223           c
224           c Define the inverse Euler rotation for (thofff,phiofff,psiofff)
225           c
226           c
227                 rotmat(1,1)=dcos(psofff)*dcos(thofff)+dsin(psofff)*dsin(thofff)
228                $     *dsin(phofff)
229                 rotmat(1,2)=-dcos(phofff)*dsin(thofff)
230                 rotmat(1,3)=-dsin(psofff)*dcos(thofff)+dcos(psofff)*dsin(thofff)
231                $     *dcos(phofff)
232                 rotmat(2,1)=dcos(psofff)*dsin(thofff)-dsin(psofff)*dcos(thofff)
233                $     *dsin(phofff)
234                 rotmat(2,2)=dcos(phofff)*dcos(thofff)
235                 rotmat(2,3)=-dsin(psofff)*dsin(thofff)-dcos(psofff)*dcos(thofff)
236                $     *dsin(phofff)
237 brash 1.2       rotmat(3,1)=dsin(psofff)*dcos(phofff)
238                 rotmat(3,2)=dsin(phofff)
239                 rotmat(3,3)=dcos(psofff)*dcos(phofff)
240           c
241           c
242                 vert(1)=vert(1)-xofff
243                 vert(2)=vert(2)-yofff
244           c     
245                 xyz(1)=dsin(psir)
246                 xyz(2)=dcos(psir)*dsin(angr)
247                 xyz(3)=dcos(psir)*dcos(angr)
248           c
249                 do ic=1,3
250                    xyznew(ic)=xyz(1)*rotmat(ic,1)+
251                &        xyz(2)*rotmat(ic,2)+xyz(3)*rotmat(ic,3)
252                 enddo
253           
254                 angr=datan(xyznew(2)/xyznew(3))
255                 termang=xyznew(3)/dcos(angr)
256                 if(termang.gt.1.0) termang=1.0
257                 if(termang.lt.-1.0) termang=-1.0
258 brash 1.2       psir=dacos(termang)*abs(xyznew(1))/xyznew(1)
259                 phir=datan(dtan(psir)/dcos(angr))
260           	
261           c	write(*,*)vert(1),vert(2),angr,phir,psir
262 jones 1.1 
263                 call gsvert ( vert,ntbeam,nttarg,ubuf,0,nvtx )
264 brash 1.2       etot       = ea - 938.2796
265 jones 1.1       plab(1)    = ptot*dsin(psir)
266                 plab(2)    = ptot*dsin(angr)*dcos(psir)
267                 plab(3)    = ptot*dcos(angr)*dcos(psir)
268 brash 1.2 
269 jones 1.1       call hfill ( 100, etot, 0., 1. )
270 brash 1.2 
271 jones 1.1       call gskine ( plab,ipart,nvtx,ubuf,0,nt )
272 brash 1.2 
273 jones 1.1       if ( nt.le.0 ) then
274                     write ( 6,* ) ' gukine: error defining track'
275                     write ( 6,* ) '         i=',i,' nt=',nt
276                     stop
277                 end if
278 brash 1.2 
279                 nevent=nevent+1
280           
281 jones 1.1       return
282 brash 1.2 
283                 end
284           
285                 subroutine kincalc(e0,eang,hang,trg,xtgt,ytgt,
286                $        thtgt,phtgt,ptgt,dptgt)
287           
288                 implicit none
289           
290                 real*8 e0,eang,hang,trg,xtgt,ytgt,thtgt,phtgt,ptgt,dptgt
291                 real*8 fg,gf
292                 integer i,j,k
293                 real*8 mt,mtg,mr,mpi,mn,mp,me,pi,mhe,alpha
294                 real*8 escat,pscat,pcentral,thetae,phie,thetap,phip
295                 real rndm(3)
296           
297                 fg=3.14159265/180.0
298                 gf=1.0/fg
299           
300                 me  = 0.511
301                 mpi = 139.57
302                 mp  = 938.2796
303 brash 1.2       mn  = 939.5731
304                 mhe = 2808.41
305                 mt  = mp
306                 mtg = mt/1.e3
307                 
308                 alpha=1./137.
309           
310           
311            1432 call grndm ( rndm , 3 )
312                 escat=mp/(1.0+mp/e0-cos(fg*eang))
313                 pscat=sqrt(e0**2+escat**2-
314                $     2.0*e0*escat*cos(fg*eang))
315                 pcentral=pscat
316           
317           c     First, we assume that whichever are is the more backward will
318           c     determine the acceptance.  We then randomly choose the theta
319           c     and phi for the arm that determines the acceptance within the
320           c     usual full HRS acceptance and then determine from kinematics 
321           c     what the corresponding theta and phi are for the other arm.
322           
323                 if (abs(eang).gt.abs(hang)) then
324 brash 1.2          phie=-.065+rndm(1)*.130
325                    thetae=-.030+rndm(2)*.060
326                    escat=mp/(1.0+mp/e0-cos(fg*eang+thetae)*cos(phie))
327                    pscat=sqrt(e0**2+escat**2-
328                $        2.0*e0*escat*cos(fg*eang+thetae)*cos(phie))
329                    phip=dasin(escat*dsin(phie)/pscat)
330                    thetap=dasin((escat*sin(fg*eang+thetae)*cos(phie))/
331                $        (pscat*cos(phip)))-fg*hang
332                 else
333           c Hadron arm defining acceptance
334            1221    call grndm ( rndm, 3)
335                    phie=-.065+rndm(1)*.130
336                    thetae=-.030+rndm(2)*.060
337                    escat=mp/(1.0+mp/e0-cos(fg*eang+thetae)*cos(phie))
338                    pscat=sqrt(e0**2+escat**2-
339                $        2.0*e0*escat*cos(fg*eang+thetae)*cos(phie))
340                    phip=-1.0*dasin(escat*sin(phie)/pscat)
341                    thetap=dasin((escat*sin(fg*eang+thetae)*cos(phie))/
342                $        (pscat*cos(phip)))-fg*hang
343                    if(abs(thetap).gt.0.030.or.abs(phip).gt.0.065) goto 1221
344                 endif
345 brash 1.2 
346                 ptgt=pscat
347                 dptgt=(pcentral-pscat)/pcentral
348 jones 1.1 c
349 brash 1.2 c Following statement to fill just the high and low dp bins
350           c which have very low statistics.  This is normally commented
351           c out.
352           c
353           c      if(abs(dptgt).le.0.030) goto 1432
354           c
355                 thtgt=thetap
356                 phtgt=phip
357                 xtgt=0.0
358                 ytgt=0.0
359           
360                 return 
361 jones 1.1       end

Analyzer/Replay: Mark Jones, Documents: Stephen Wood
Powered by
ViewCVS 0.9.2-cvsgraph-1.4.0