13 #include "Zmagfield.h" 18 #include "Zincidentp.h" 24 real*8 cvh2thick, cthick2h, mu
29 if( depthlist(i) .eq. 0. )
goto 100
30 noofsites = noofsites + 1
31 if( depthlist(i) .lt. 0. )
then 33 depthlist(i) = cvh2thick(heightlist(i))
35 heightlist(i) = cthick2h(depthlist(i))
39 * heightlist(i), obssites(i)%pos%xyz )
42 if(noofsites .eq. 0)
then 43 call cerrormsg(
'No of Observation sites = 0', 0)
47 call csetcoord(
'llh', latitofsite, longitofsite,
48 * heightofinj, polarinjpos)
52 if(endlevel .eq. 0) endlevel = noofsites
53 if(endlevel2 .eq. 0) endlevel2 = endlevel
56 if(howgeomag .gt. 20 .and. howgeomag .le. 30 )
then 60 magfieldned%sys =
'ned' 63 call cgeomag(yearofgeomag, obssites(noofsites)%pos%xyz,
66 write(msg, *)
' YearOfGeomag=',yearofgeomag,
' is ok ?' 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 80 xaxisfromsouth = 90.0 - magfieldhva%z
85 * longitofsite, dtgmt,
86 * obssites(noofsites)%pos%height)
87 call kadthi(xaxisfromsouth)
93 * obssites(i)%pos%xyz )
95 call csetpos2(heightlist(i), depthlist(i), obssites(i)%pos)
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
111 south%r(1) = sinlatitude *coslongitude
112 south%r(2) = sinlatitude *sinlongitude
113 south%r(3) = -coslatitude
115 detxaxis%r(1) =
cos(xaxisfromsouth * torad)
116 detxaxis%r(2) = sin(xaxisfromsouth * torad)
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(:,:))
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)
137 call cerrormsg(
'Obsev. depth/height not in order', 0)
140 * (za1ry .ne.
'is' .and. za1ry .ne.
'cos' ) )
then 142 *
"ObsPlane==spherical but Za1ry !='is'/'cos'",0)
145 if(borderheightl .eq. 0.)
then 146 borderheightl = obssites(noofsites)%pos%height -1.0
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)
158 if( asdepthlist(i) .eq. 0. )
goto 200
159 noofassites = noofassites + 1
160 if( asdepthlist(i) .lt. 0. )
then 162 asdepthlist(i) = cvh2thick(asheightlist(i))
164 asheightlist(i) = cthick2h(asdepthlist(i))
168 * asheightlist(i), asobssites(i)%pos%xyz )
173 do i = 1, noofassites
175 * asobssites(i)%pos%xyz )
177 call csetpos2(asheightlist(i), asdepthlist(i),
182 asobssites(i)%mu = mu
subroutine cerrormsg(msg, needrtn)
subroutine kcelei(tlat, tlon, dtgmt, height)
! 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
subroutine cgetmoliereu(dep, cosz, rmu)
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
subroutine cgeomag(yearin, llh, h, icon)
subroutine cvecprod(a, b, c)
subroutine ctranscoord2(sys, a, b)
block data cblkEvhnp ! currently usable models data RegMdls ad *special data *Cekaon d0
subroutine ctransvectzx(init, zax, xax, dir1, dir2)
subroutine csetcoord(sys, x, y, z, a)
subroutine csetpos2(h, d, location)
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
subroutine ctransmagto(sys, pos, a, b)