COSMOS v7.655  COSMOSv7655
(AirShowerMC)
cminTime2WebSec.f
Go to the documentation of this file.
1  subroutine cmintime2websec(obsdetxyz, ldep, depidx, awebmin)
2  implicit none
3 #include "Zglobalc.h"
4 #include "Zmaxdef.h"
5 #include "Zmanagerp.h"
6 #include "Ztrack.h"
7 #include "Ztrackv.h"
8 #include "Zcode.h"
9 #include "Zheavyp.h"
10 #include "Zobs.h"
11 #include "Zobsp.h"
12 #include "Zobsv.h"
13 #include "Zstackv.h"
14 #include "Zprivate.h"
15 ! #include "Zprivate2.h"
16  integer ldep ! layer number of the observation depth
17  integer depidx ! layer index for web array
18  type(coord )::obsdetxyz ! input. observation detector axis in E-xyz
19 ! = ObsSites(loc).pos.xyz where loc is the
20 ! observation layer number.
21 
22  real*8 awebmin(nrbin, nfai, maxnoofsites) ! output. to store min time (ns)
23  ! for each web sector.
24  real*8 r, hdr, Ra, rc
25  type(track):: inci
26  type(coord):: angle
27  integer i, j, ii, jj
28  real*8 faimin, fai, R0, Rbot, rmu, cosz
29  data faimin/-15.0d0/
30  type(coord):: xyz, oxyz, effpos
31  real*8 temp, dtemp, leng
32  integer it
33 
34 
35 
36  call cqincident(inci, angle) ! we may better to use the first
37  ! collision point but not so easy to get it
38  ! since this is called before collision
39 
40  effpos = inci.pos.xyz ! default is 100 km
41 
42 !cc effpos.z = 20.d3 ! so we use 20km instead
43 ! assume web sector is aligned so that incident direcion
44 ! is on fai=0 of the web sector.
45 ! sinz cosf= dirx
46 ! sinz sinf= diry
47 ! cosz = dirz
48 ! tanf = diry/dirx; fai=atan2(diry,dirx)
49 ! L dirx =x L diry =y L dirz = z
50 ! L = z/dirz =
51 ! cosz = inci.vec.coszenith ~ -angle.r(3)
52 
53 ! Top view
54 ! / this is web sector fai=0
55 ! /
56 ! /
57 ! / so fai* = fai-fai0
58 ! / should be used as azimuthal angle of
59 ! / ptcls. Therefore we use
60 ! / fai0 effpos as below
61 ! ------------------------> mag east
62 !
63 ! L cosz = effpos.z
64 ! L sinz = effpos.x
65 ! effpos.y = 0.
66 !
67 
68  leng = effpos.z/(-angle.r(3))
69  effpos.x = sqrt(1.d0-angle.r(3)**2)*leng
70  effpos.y = 0.
71 ! convert it to xyz system
72  call cdet2xyz(obsdetxyz, effpos, effpos)
73 
74  xyz.z = 0.
75  xyz.x = 0.
76  xyz.y = 0.
77  call cdet2xyz(obsdetxyz, xyz, oxyz)
78 !/////////////
79 ! write(0,*) ' layer =', ldep
80 ! write(0,*) ' obsdetxyx=',obsdetxyz.x,
81 ! * obsdetxyz.y, obsdetxyz.z
82 ! write(0,*) ' center =', oxyz.x, oxyz.y, oxyz.z
83 ! write(0,*) ' effposx,y,x=',effpos.x,
84 ! *effpos.y, effpos.z
85 !//////////////
86 
87  r0 = sqrt( (oxyz.x-effpos.x)**2 +
88  * (oxyz.y-effpos.y)**2 +
89  * (oxyz.z-effpos.z)**2 )
90 !////////////
91 ! write(0,*) ' R0=', R0
92 !///////////
93 
94  call cgetmoliereu( obssites(ldep).pos.depth, cosz, rmu)
95 !//////////
96 ! write(0,*) ' mu=', rmu
97 !///////////
98 
99  hdr = 10.**(bin/2.)
100 
101  do i = 1, nrbin
102  rc = rbin(i) * rmu ! in m
103  do j = 1, nfai
104  rbot = 10.d10
105 ! for all web sectors examine 4 corners
106  do ii = 1, 2
107 ! rbin is the center of the web sector in r direction (log10 center).
108  if(ii .eq. 1) then
109  r = rc/hdr
110  else
111  r = rc*hdr
112  endif
113  do jj = j, j+1
114  fai = faimin + (jj-1)*dfai
115  xyz.x = r*cos(fai*torad)
116  xyz.y = r*sin(fai*torad)
117  call cdet2xyz(obsdetxyz, xyz, oxyz)
118 ! *
119 ! * ^
120 ! * ^
121 ! *
122 ! R0 * ^ Ra
123 ! *
124 ! *
125 ! * ^
126  ra = sqrt( (oxyz.x-effpos.x)**2 +
127  * (oxyz.y-effpos.y)**2 +
128  * (oxyz.z-effpos.z)**2 )
129  if( ra-r0 .lt. rbot ) rbot = ra-r0
130  enddo
131  enddo ! for a given fai bi
132 !/////////////
133 ! if(i .gt. 20 .and. j. eq. 1) then
134 ! write(0,*) " ridx=",i, " Rbot=", Rbot
135 ! endif
136 !///////////
137 !/////////////
138 ! Rbot may not be real mininum if incident axis lies
139 ! on the sector. for safety 25 % correction. in n sec
140  dtemp =1.d9* ( rbot - abs(rbot)*0.25 )/c ! ns
141 
142  awebmin(i,j,depidx) = dtemp
143  enddo
144  enddo
145 
146 
147  end
*Zfirst p fm *Zfirst p Zfirst p Zfirst p *Zfirst p *Zfirst pos xyz Zfirst pos xyz *Zfirst pos *Zfirst pos depth
Definition: ZavoidUnionMap.h:1
nodes z
subroutine cqincident(incident, AngleAtObs)
Definition: cmkIncident.f:486
integer nsites ! max real bin
Definition: Zprivate0.h:2
const int maxnoofsites
Definition: Zobs.h:7
! for length to thickness conversion or v v ! integer maxnodes real Hinf ! This is used when making table for dim simulation ! The slant length for vertical height to km is ! divided by LenStep m steps ! It can cover the slant length of about km for cos
Definition: Zatmos.h:8
subroutine cgetmoliereu(dep, cosz, rmu)
Definition: cgetMoliereU.f:11
Definition: Ztrack.h:44
! timing nrbin
Definition: Zprivate2.h:12
block data cblkEvhnp ! currently usable models data RegMdls ad *special data *Cekaon d0
Definition: cblkEvhnp.h:5
latitude latitude this system is used *****************************************************************! type coord sequence union map real y
Definition: Zcoord.h:25
subroutine cdet2xyz(det, a, b)
Definition: cxyz2det.f:48
Definition: Zcoord.h:43
subroutine cmintime2websec(obsdetxyz, ldep, depidx, awebmin)
! timing nfai
Definition: Zprivate2.h:12
! structure defining a particle at production ! Basic idea of what is to be contained in ! the particle structue is that dynamical ones should be included those derivable from the particle code ! is not included ******************************************************type fmom momentum sequence union map real e endmap map real * x
Definition: Zptcl.h:21
dE dx *! Nuc Int sampling table c
Definition: cblkMuInt.h:130