COSMOS v7.655  COSMOSv7655
(AirShowerMC)
cinitObs.f
Go to the documentation of this file.
1 ! cinitObs: set up observation sites by reference to Zobsp.h
2 ! HeightList is obtained from DepthList.
3 ! However, if DepthList value is negative, HeightList has priority and
4 ! DepthList is obtained from HeightList.
5 ! Variables in Zobsv.h are calculated.
6  subroutine cinitobs
7  implicit none
8 !
9 #include "Zglobalc.h"
10 #include "Ztrackp.h"
11 #include "Zcoord.h"
12 #include "Zpos.h"
13 #include "Zmagfield.h"
14 #include "Zobs.h"
15 #include "Zobsp.h"
16 #include "Zobsv.h"
17 #include "Zearth.h"
18 #include "Zincidentp.h"
19 !
20  integer i, icon
21  logical error
22  character*180 msg
23  type(coord)::south
24  real*8 cvh2thick, cthick2h, mu
25  external cblkobs
26 !
27  noofsites = 0
28  do i = 1, maxnoofsites
29  if( depthlist(i) .eq. 0. ) goto 100 ! exit
30  noofsites = noofsites + 1
31  if( depthlist(i) .lt. 0. ) then
32 ! HeightList has priority
33  depthlist(i) = cvh2thick(heightlist(i))
34  else
35  heightlist(i) = cthick2h(depthlist(i))
36  endif
37  call csetcoord('llh', latitofsite,
38  * longitofsite,
39  * heightlist(i), obssites(i)%pos%xyz )
40  enddo
41  100 continue
42  if(noofsites .eq. 0) then
43  call cerrormsg('No of Observation sites = 0', 0)
44  endif
45 ! set polar angle of the injection pointsite.
46 ! (used when ObsPlane==spherical)
47  call csetcoord('llh', latitofsite, longitofsite,
48  * heightofinj, polarinjpos)
49 ! transform it to polar coord.
50  call ctranscoord2('sph', polarinjpos, polarinjpos)
51 
52  if(endlevel .eq. 0) endlevel = noofsites ! 96.09.18
53  if(endlevel2 .eq. 0) endlevel2 = endlevel
54 ! set magnetic field for the deepest level.
55 ! Magfield is 'ned' here
56  if(howgeomag .gt. 20 .and. howgeomag .le. 30 ) then
57  magfieldned%x = magn
58  magfieldned%y = mage
59  magfieldned%z = magd
60  magfieldned%sys = 'ned'
61  else
62 ! if HowGeomag <=2, this is reset later. don't worry.
63  call cgeomag(yearofgeomag, obssites(noofsites)%pos%xyz,
64  * magfieldned, icon)
65  if(icon .eq. 1) then
66  write(msg, *) ' YearOfGeomag=',yearofgeomag, ' is ok ?'
67  call cerrormsg(msg, 1)
68  endif
69  endif
70 ! to 'hva'
71  call ctransmagto('hva', obssites(noofsites)%pos%xyz,
72  * magfieldned, magfieldhva)
73  call ctransmagto('xyz', obssites(noofsites)%pos%xyz,
74  * magfieldned, magfieldxyz)
75  if(abs(xaxisfromsouth) .gt. 360.d0) then
76 ! if it is > 360, use magnetic east to be the detector x-axis.
77 ! angle form south to x-axis in counter closckwise.
78 ! Note: 'hva' system angle + is clockwise.
79 ! XaxisFromSouth = 90.0 - MagfieldHVA.z
80  xaxisfromsouth = 90.0 - magfieldhva%z
81  endif
82 
83 ! celestial coord. init.
84  call kcelei(latitofsite,
85  * longitofsite, dtgmt,
86  * obssites(noofsites)%pos%height)
87  call kadthi(xaxisfromsouth)
88 
89 
90 ! site coord is made to be in the xyz system.
91  do i = 1, noofsites
92  call ctranscoord2('xyz', obssites(i)%pos%xyz,
93  * obssites(i)%pos%xyz ) ! to xyz
94 ! set ObsSites(i).pos.radiallen, ..depth, height
95  call csetpos2(heightlist(i), depthlist(i), obssites(i)%pos)
96  call cgetmoliereu(obssites(i)%pos%depth, 1.d0, mu)
97  obssites(i)%mu = mu
98  enddo
99 ! detector system coord. x is directed to mag. east.
100 ! z is directed to vertical.
101 ! get their direction cos. in 'xyz' system.
102 !
103  coslatitude = cos(latitofsite*torad)
104  sinlatitude = sin(latitofsite*torad)
105  coslongitude = cos(longitofsite*torad)
106  sinlongitude = sin(longitofsite*torad)
107  detzaxis%r(1) = coslatitude * coslongitude
108  detzaxis%r(2) = coslatitude * sinlongitude
109  detzaxis%r(3) = sinlatitude
110 ! south direction is expressed as
111  south%r(1) = sinlatitude *coslongitude
112  south%r(2) = sinlatitude *sinlongitude
113  south%r(3) = -coslatitude
114 ! in south-vertical system. X-axis is expressed
115  detxaxis%r(1) = cos(xaxisfromsouth * torad)
116  detxaxis%r(2) = sin(xaxisfromsouth * torad)
117  detxaxis%r(3) = 0.
118 ! convert it to 'xyz' system
119  call ctransvectzx(1, detzaxis, south, detxaxis, detxaxis)
120  txyz2det(1,:) = detxaxis%r(:)
121  txyz2det(3,:) = detzaxis%r(:)
122  call cvecprod(detzaxis%r(:), detxaxis%r(:), detyaxis%r(:))
123  txyz2det(2,:) = detyaxis%r(:)
124  tdet2xyz(:,:) = transpose(txyz2det(:,:))
125 ! check if in the ascending order of depth
126  error = .false.
127  do i = 2, noofsites
128  if(depthlist(i-1) .ge. depthlist(i)) then
129  write(msg, *) 'Depth is not in ascending order ',
130  * i, '-th one=',depthlist(i),
131  * ' is < previous one= ', depthlist(i-1)
132  call cerrormsg(msg, 1)
133  error = .true.
134  endif
135  enddo
136  if(error) then
137  call cerrormsg('Obsev. depth/height not in order', 0)
138  endif
139  if(obsplane .eq. spherical .and.
140  * (za1ry .ne. 'is' .and. za1ry .ne. 'cos' ) ) then
141  call cerrormsg(
142  * "ObsPlane==spherical but Za1ry !='is'/'cos'",0)
143  endif
144 ! from v5.66
145  if(borderheightl .eq. 0.) then
146  borderheightl = obssites(noofsites)%pos%height -1.0
147  endif
148  obssites(0)%pos%height = borderheighth
149  obssites(0)%pos%radiallen = borderheighth + eradius
150  obssites(0)%pos%depth = cvh2thick(borderheighth)
151  obssites(noofsites+1)%pos%height = borderheightl
152  obssites(noofsites+1)%pos%radiallen = borderheightl + eradius
153  obssites(noofsites+1)%pos%depth = cvh2thick(borderheightl)
154 
155 ! +++++++++++++++++++++++ for AS ++++++++++++++++
156  noofassites = 0
157  do i = 1, maxnoofassites
158  if( asdepthlist(i) .eq. 0. ) goto 200 ! exit
159  noofassites = noofassites + 1
160  if( asdepthlist(i) .lt. 0. ) then
161 ! HeightList has priority
162  asdepthlist(i) = cvh2thick(asheightlist(i))
163  else
164  asheightlist(i) = cthick2h(asdepthlist(i))
165  endif
166  call csetcoord('llh', latitofsite,
167  * longitofsite,
168  * asheightlist(i), asobssites(i)%pos%xyz )
169  enddo
170  200 continue
171 
172 ! site coord is made to be in the xyz system.
173  do i = 1, noofassites
174  call ctranscoord2('xyz', asobssites(i)%pos%xyz,
175  * asobssites(i)%pos%xyz ) ! to xyz
176 ! set ASObsSites(i).pos.radiallen, ..depth, height
177  call csetpos2(asheightlist(i), asdepthlist(i),
178  * asobssites(i)%pos)
179 ! Moliere Unit should be reset depending on
180 ! the 1ry angle. Here is a tentative one for vertical
181  call cgetmoliereu(asobssites(i)%pos%depth, 1.d0, mu)
182  asobssites(i)%mu = mu
183  enddo
184 
185  end
subroutine cerrormsg(msg, needrtn)
Definition: cerrorMsg.f:4
subroutine kcelei(tlat, tlon, dtgmt, height)
Definition: kceles.f:125
const int maxnoofsites
Definition: Zobs.h:7
subroutine cinitobs
Definition: cinitObs.f: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
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 cgeomag(yearin, llh, h, icon)
Definition: cgeomag.f:25
subroutine cvecprod(a, b, c)
Definition: cvecProd.f:4
const int maxnoofassites
Definition: Zobs.h:12
subroutine ctranscoord2(sys, a, b)
Definition: ctransCoord2.f:2
subroutine kadthi(astox)
Definition: kceles.f:378
block data cblkEvhnp ! currently usable models data RegMdls ad *special data *Cekaon d0
Definition: cblkEvhnp.h:5
subroutine ctransvectzx(init, zax, xax, dir1, dir2)
Definition: ctransVectZx.f:36
subroutine csetcoord(sys, x, y, z, a)
Definition: csetCoord.f:2
subroutine csetpos2(h, d, location)
Definition: csetPos.f:31
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 ctransmagto(sys, pos, a, b)
Definition: ctransMagTo.f:11
Definition: Zcoord.h:43
const int spherical
Definition: Zobs.h:19