COSMOS v7.655  COSMOSv7655
(AirShowerMC)
cEfield0.f
Go to the documentation of this file.
1  module modefield
2  implicit none
3 ! next one is only for printing
4  namelist /efparam/ howefield, defofr, myef
5 
6  type efield
7  sequence
8  real(8)::ef(3)=0.
9  real(8)::h1=0., h2=0.
10  real(8)::r1=0., r2=0.
11  real(8)::t1=0., t2=0.
12  end type efield
13 
14  integer,parameter:: nmaxefield=5
15 ! HowEfield and myEf are namelist inputable
16 ! parameters
17  integer,save:: howefield=0
18  ! 0-->no Efield assumed
19  ! 1-->simple Efield defined by myEf
20  ! 2-->User supplies Efield subroutine cmyEfield.f
21 
22  character(len=1),save:: defofr ='h' ! define distance to the shower axis
23  ! h--> horizontal distance
24  ! p--> perpendicular to the shower axis.
25  type(efield),save:: myef(nmaxefield)
26  integer,save:: nefield = 0 ! acutal # of E flied
27 
28  logical,save:: checkh(nmaxefield) = .false.
29  logical,save:: checkr(nmaxefield) = .false.
30  logical,save:: checkt(nmaxefield) = .false.
31  logical,save:: useh=.false.
32  logical,save:: user=.false.
33  logical,save:: uset=.false.
34 
35 
36 
37  real(8),save::efxyz(3,nmaxefield) !copy of
38  ! myEf(:)%Ef(3) but in E-xyz coordinate
39 
40  contains
41 ! Nest two sub are used only at test time
42  subroutine cefieldread
43  implicit none
44  read(*, efparam)
45  end subroutine cefieldread
46 
47  subroutine cefieldwrite
48  implicit none
49  write(0, efparam)
50  end subroutine cefieldwrite
51 
52  subroutine cefieldcheck
53  implicit none
54  integer:: i
55 
56  if(howefield /= 1 ) return !!!!!
57  do i = nmaxefield, 1, -1 ! last non zero Ef
58  if(dot_product(myef(i)%Ef(:),myef(i)%Ef(:)) > 0 ) then
59  nefield = i
60  exit
61  endif
62  enddo
63  checkh(1:nefield) =
64  * myef(1:nefield)%H1**2+myef(1:nefield)%H2**2 > 0.
65  checkr(1:nefield) =
66  * myef(1:nefield)%R1**2+myef(1:nefield)%R2**2 > 0.
67  checkt(1:nefield) =
68  * myef(1:nefield)%T1**2+myef(1:nefield)%T2**2 > 0.
69  do i = 1, nefield
70  useh = useh .or. checkh(i)
71  user = user .or. checkr(i)
72  uset = uset .or. checkt(i)
73  enddo
74  useh = useh .and. .not. uset ! useT has priority
75 
76  if( nefield >= 1 ) then
77  ! check if height is from low to heigh
78  do i = 1, nefield
79  if( myef(i)%H1 > myef(i)%H2) then
80  write(0,*) i,'-th Efiled height error'
81  write(0,*)
82  * 'H1=', myef(i)%H1,' >', myef(i)%H2,'=H2'
83  stop
84  endif
85  if( myef(i)%R1 > myef(i)%R2) then
86  write(0,*) i,'-th Efiled Radius error'
87  write(0,*)
88  * 'R1=', myef(i)%R1, ' >', myef(i)%R2,'=R2'
89  stop
90  endif
91  if( myef(i)%T1 > myef(i)%T2) then
92  write(0,*) i,'-th Efiled Time error'
93  write(0,*)
94  * 'T1=', myef(i)%T1, ' >', myef(i)%T2,'=T2'
95  stop
96  endif
97  if( nefield > i ) then
98  if( myef(i+1)%H1 < myef(i)%H2 ) then
99  write(0,*)
100  * i,'-th Ef height region<=',myef(i)%H2
101  write(0,*)
102  * ' but is not < next region=',myef(i+1)%H1
103  stop
104  endif
105  endif
106  enddo
107  endif
108  write(0,*) ' # of Efield(s)=',nefield
109  end subroutine cefieldcheck
110 
111 
112  subroutine cefielddet2xyz
113  ! convert Ef in det system into E-xyz system
114  ! should be called once before starting tracking
115  implicit none
116  integer::i
117  do i = 1, nefield
118  call cdet2xyzd(myef(i)%Ef(:), efxyz(:,i))
119  enddo
120  end subroutine cefielddet2xyz
121 
122  subroutine cefield0(aTrack, Efout)
123 ! Electric field is given depending on particle position
124 ! and/or time.
125 ! H T R
126 ! given not given --> H is used R at that H is used. if R is out
127 ! of range, E=0. else E at H
128 ! if R is not given E at H
129 ! not given given --> T is used same as above, use T instead of H.
130 ! given given --> T is used //
131 ! not gvien not given use first R,.if it exists
132 ! if in range, use E(1) else E=0
133 ! if R absent, use E(1)
134  implicit none
135 #include "Zglobalc.h"
136 #include "Ztrack.h"
137 #include "Zincidentv.h"
138  type(track):: atrack ! input. Track info in E-xyz.
139  ! position and "where" info are used.
140  real(8),intent(out):: Efout(3) ! Elecric field
141  ! in E-xyz system. V/m.
142  integer:: i, hindex, tindex, out
143  logical,save:: first=.true.
144  real(8)::time
145 
146  real(8)::r
147  real(8)::Zero(3)=(/0.,0.,0./)
148 
149  if( first ) then ! convert Ef in det into E-xyz
150  call cefieldcheck
151  call cefielddet2xyz
152  first = .false.
153 !!!!!!!
154 ! call cEfieldWrite
155 !!!!!!!!!
156  endif
157 
158  hindex = 0
159  if(useh) then
160  do i = 1, nefield
161  if(checkh(i)) then
162  if( atrack%pos%height >= myef(i)%H1 .and.
163  * atrack%pos%height <= myef(i)%H2 ) then
164  hindex = i
165  exit
166  endif
167  endif
168  enddo
169  if( hindex == 0) then ! H is out of range
170  efout(:) = zero(:)
171  else
172  ! see if R is in the range
173  call cefieldcheckr(atrack, hindex, out)
174  if(out == 0 ) then
175  ! Efout(:) = myEf(hindex)%Ef(:) ! bug
176  efout(:) = efxyz(:,hindex)
177  else
178  efout(:) = zero(:)
179  endif
180  endif
181  elseif(uset) then
182  tindex = 0
183  do i = 1, nefield
184  if(checkt(i)) then
185  time = atrack%t/c*tonsec
186  if( time >= myef(i)%T1 .and.
187  * time <= myef(i)%T2 ) then
188  tindex = i
189  exit
190  endif
191  endif
192  enddo
193  if( tindex == 0 ) then ! T is out of range
194  efout(:) = zero(:)
195  else
196  ! see if R is in the range
197  call cefieldcheckr(atrack, tindex, out)
198  if(out == 0 ) then
199 ! Efout(:) = myEf(tindex)%Ef(:) bug
200  efout(:) = efxyz(:,tindex)
201  else
202  efout(:) = zero(:)
203  endif
204  endif
205  else ! H,T is not used.
206  i = 1 ! use first data if possible
207  if( checkr(i) ) then ! check first R if any
208  call cefieldcheckr(atrack, i, out)
209  if(out == 0 ) then
210 ! Efout(:) = myEf(i)%Ef(:)
211  efout(:) = efxyz(:,i)
212  else
213  efout(:) = zero(:)
214  endif
215  else ! no check of R. assume first Ef is applied
216 ! Efout(:) = myEf(i)%Ef(:)
217  efout(:) = efxyz(:,i)
218  endif
219  endif
220  end subroutine cefield0
221 
222  subroutine cefieldcheckr(aTrack, i, out)
223  implicit none
224 #include "Ztrack.h"
225  type(track):: atrack ! input
226  integer,intent(in):: i ! R or H index
227  integer,intent(out)::out ! 0 aTrack is in the range or no check is needed
228  ! else out of range
229  real(8):: r
230 
231  if( checkr(i) ) then
232  ! core distance
233  if(defofr == 'p' ) then ! perpedicular distance
234  call cgetpcoredist(atrack, r)
235  elseif(defofr == 'h') then ! horizontal distance
236  call cgethcoredist(atrack, r)
237  else
238  write(0,*) ' DefofR =',defofr, ' invalid'
239  stop
240  endif
241  if( r >= myef(i)%R1 .and.
242  * r <= myef(i)%R2 ) then
243  out = 0
244  else ! R is out of range
245  out = 1
246  endif
247  else
248  out = 0
249  endif
250  end subroutine cefieldcheckr
251 
252 
253  end module modefield
254 
255  subroutine cgetpcoredist(aTrack, r)
256  implicit none
257 #include "Ztrack.h"
258 #include "Zincidentv.h"
259 #include "Zobs.h"
260 #include "Zobsv.h"
261  type(track):: atrack ! input. in E-xyz system
262  real(8),intent(out):: r ! Perpendicular core distance
263 
264  real(8):: rdet(3) ! ptcl pos in det-sys
265 
266  call cxyz2det(obssites(atrack%where)%pos%xyz,
267  * atrack%pos%xyz%r(:), rdet(:))
268  r = abs(dot_product(rdet(:), angleatobscopy%r(:))) ! Angle.. is dwn.g
269  end subroutine cgetpcoredist
270 
271  subroutine cgethcoredist(aTrack, r)
272  implicit none
273 #include "Ztrack.h"
274 #include "Zincidentv.h"
275 #include "Zobs.h"
276 #include "Zobsv.h"
277  type(track):: atrack ! input. in E-xyz system
278  real(8),intent(out):: r ! Perpendicular core distance
279 
280  real(8):: rdet(3) ! ptcl pos in det-sys
281  real(8):: Raxis(3) ! shower core at the same height
282  ! as the ptcl
283 
284 
285  call cxyz2det(obssites(atrack%where)%pos%xyz,
286  * atrack%pos%xyz%r(:), rdet(:))
287  raxis(:) =
288  * (atrack%pos%height - obssites(atrack%where)%pos%height) /
289  * angleatobscopy%r(3) ! length from origin( <0 )
290  * * angleatobscopy%r(:) ! vector (now upgoing) since
291  ! AngleAtObsCopy is downogin.
292  r = sqrt(sum( ( rdet(:)-raxis(:))**2 ))
293  end subroutine cgethcoredist
294 
real(8), dimension(3, nmaxefield), save efxyz
Definition: cEfield0.f:37
subroutine cefieldread
Definition: cEfield0.f:43
integer, save howefield
Definition: cEfield0.f:17
logical, save useh
Definition: cEfield0.f:31
Definition: Ztrack.h:44
type(efield), dimension(nmaxefield), save myef
Definition: cEfield0.f:25
integer, parameter nmaxefield
Definition: cEfield0.f:14
logical, dimension(nmaxefield), save checkt
Definition: cEfield0.f:30
block data cblkElemag data *AnihiE ! Eposi< 1 TeV, anihilation considered *X0/365.667/, ! radiation length of air in kg/m2 *Ecrit/81.e-3/, ! critical energy of air in GeV *MaxComptonE/1./, ! compton is considered below 1 GeV *MaxPhotoE/1.e-3/, ! above this, PhotoElectric effect neg. *MinPhotoProdE/153.e-3/, ! below 153 MeV, no gp --> hadrons ! scattering const not MeV *Knockon true
Definition: cblkElemag.h:7
subroutine cefielddet2xyz
Definition: cEfield0.f:113
logical, dimension(nmaxefield), save checkr
Definition: cEfield0.f:29
logical, save user
Definition: cEfield0.f:32
subroutine cefieldcheck
Definition: cEfield0.f:53
integer, save nefield
Definition: cEfield0.f:26
subroutine cdet2xyzd(a, b)
Definition: cxyz2det.f:101
subroutine cefieldcheckr(aTrack, i, out)
Definition: cEfield0.f:223
subroutine cgethcoredist(aTrack, r)
Definition: cEfield0.f:272
character(len=1), save defofr
Definition: cEfield0.f:22
logical, dimension(nmaxefield), save checkh
Definition: cEfield0.f:28
subroutine cefieldwrite
Definition: cEfield0.f:48
block data cblkElemag data *AnihiE ! Eposi< 1 TeV, anihilation considered *X0/365.667/, ! radiation length of air in kg/m2 *Ecrit/81.e-3/, ! critical energy of air in GeV *MaxComptonE/1./, ! compton is considered below 1 GeV *MaxPhotoE/1.e-3/, ! above this, PhotoElectric effect neg. *MinPhotoProdE/153.e-3/, ! below 153 MeV, no gp --> hadrons ! scattering const not MeV *Knockon ! knockon is considered Obsolete *PhotoProd false
Definition: cblkElemag.h:7
subroutine cgetpcoredist(aTrack, r)
Definition: cEfield0.f:256
subroutine cefield0(aTrack, Efout)
Definition: cEfield0.f:123
logical, save uset
Definition: cEfield0.f:33
subroutine cxyz2det(det, a, b)
Definition: cxyz2det.f:7
dE dx *! Nuc Int sampling table c
Definition: cblkMuInt.h:130