COSMOS v7.655  COSMOSv7655
(AirShowerMC)
ctransMagTo.f File Reference

Go to the source code of this file.

Functions/Subroutines

subroutine ctransmagto (sys, pos, a, b)
 
subroutine cmag2ecent (pos, a, b)
 
subroutine cned2ecent (pos, a, b)
 
subroutine cxyz2ned (pos, a, b)
 
subroutine cxyz2hva (pos, a, b)
 
subroutine cned2hva (a, b)
 
subroutine chva2ned (a, b)
 

Function/Subroutine Documentation

◆ chva2ned()

subroutine chva2ned ( type(magfield a,
type(magfield b 
)

Definition at line 248 of file ctransMagTo.f.

References cos, and csetmagfield().

Referenced by cmag2ecent(), and ctransmagto().

248 ! inverse of the above
249  implicit none
250 #include "Zglobalc.h"
251 #include "Zcoord.h"
252 #include "Zmagfield.h"
253  type(magfield)::a
254  type(magfield)::b
255  real*8 n, e, d
256 !
257 #ifdef UNIONMAP
258  n = a%h *cos(a%a*torad)
259  e = a%h *sin(a%a*torad)
260  d = a%v
261 #else
262  n = a%x *cos(a%z*torad)
263  e = a%x *sin(a%z*torad)
264  d = a%y
265 #endif
266  call csetmagfield('ned', n, e, d, b)
dE dx *! Nuc Int sampling table e
Definition: cblkMuInt.h:130
! 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
dE dx *! Nuc Int sampling table d
Definition: cblkMuInt.h:130
real(4), save a
Definition: cNRLAtmos.f:20
subroutine csetmagfield(sys, b1, b2, b3, b)
brief set Calculated magnetic field to /magfield/ b
Definition: csetMagField.f:6
real(4), save b
Definition: cNRLAtmos.f:21
integer n
Definition: Zcinippxc.h:1
Here is the call graph for this function:
Here is the caller graph for this function:

◆ cmag2ecent()

subroutine cmag2ecent ( type(coord pos,
type(magfield a,
type(magfield b 
)

Definition at line 64 of file ctransMagTo.f.

References cerrormsg(), chva2ned(), cned2ecent(), and ctranscoord2().

Referenced by ctransmagto().

64 ! to earth_center system (xyz system)
65  implicit none
66 #include "Zcoord.h"
67 #include "Zmagfield.h"
68  type(magfield)::a
69  type(magfield)::b
70  type(coord)::pos
71 !
72  type(coord)::postemp
73  character*70 msg
74 !
75  call ctranscoord2('llh', pos, postemp)
76  if(a%sys .eq. 'ned') then
77  call cned2ecent(postemp, a, b)
78  elseif(a%sys .eq. 'hva') then
79  call chva2ned(a, b)
80  call cned2ecent(postemp, b, b)
81  else
82  write(msg, *) 'cMag2eCent: mag system=',
83  * a%sys,
84  * ' not yet supported'
85  call cerrormsg(msg, 0)
86  endif
subroutine cerrormsg(msg, needrtn)
Definition: cerrorMsg.f:4
subroutine chva2ned(a, b)
Definition: ctransMagTo.f:248
subroutine cned2ecent(pos, a, b)
Definition: ctransMagTo.f:90
subroutine ctranscoord2(sys, a, b)
Definition: ctransCoord2.f:2
real(4), save a
Definition: cNRLAtmos.f:20
real(4), save b
Definition: cNRLAtmos.f:21
Definition: Zcoord.h:43
Here is the call graph for this function:
Here is the caller graph for this function:

◆ cned2ecent()

subroutine cned2ecent ( type(coord pos,
type(magfield a,
type(magfield b 
)

Definition at line 90 of file ctransMagTo.f.

References cerrormsg(), cos, and csetmagfield().

Referenced by cmag2ecent().

90 ! pos: /coord/ input. pos.sys should be 'llh'
91 ! a: /magfield/ input. in 'ned' system
92 ! b: /magfield/ output. in 'xyz' system
93 ! b can be the same one as a.
94  implicit none
95 #include "Zglobalc.h"
96 #include "Zcoord.h"
97 #include "Zmagfield.h"
98 !
99  type(coord)::pos
100  type(magfield)::a
101  type(magfield)::b
102  character*70 msg
103 !
104  real*8 cosphi, sinphi, coslam, sinlam, x, y, z
105 !
106  if(pos%sys .ne. 'llh') then
107  write(msg, *)'cned2eCent: input pos%sys=',pos%sys,
108  * ' invalid. should be llh'
109  call cerrormsg(msg, 0)
110  endif
111 #ifdef UNIONMAP
112  cosphi = cos(pos%lat*torad)
113  sinphi = sin(pos%lat*torad)
114  coslam = cos(pos%long*torad)
115  sinlam = sin(pos%long*torad)
116  x = - (a%d *cosphi + a%n*sinphi) *
117  * coslam
118  * - a%e *sinlam
119  y = - (a%d *cosphi + a%n*sinphi)* sinlam
120  * + a%e*coslam
121  z = - a%d *sinphi + a%n* cosphi
122 #else
123  cosphi = cos(pos%r(1)*torad)
124  sinphi = sin(pos%r(1)*torad)
125  coslam = cos(pos%r(2)*torad)
126  sinlam = sin(pos%r(2)*torad)
127  x = - (a%z *cosphi + a%x*sinphi) *
128  * coslam
129  * - a%y *sinlam
130  y = - (a%z *cosphi + a%x*sinphi)* sinlam
131  * + a%y*coslam
132  z = - a%z *sinphi + a%x* cosphi
133 #endif
134  call csetmagfield('xyz', x, y, z, b)
subroutine cerrormsg(msg, needrtn)
Definition: cerrorMsg.f:4
nodes z
! 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
latitude latitude this system is used *****************************************************************! type coord sequence union map real y
Definition: Zcoord.h:25
real(4), save a
Definition: cNRLAtmos.f:20
subroutine csetmagfield(sys, b1, b2, b3, b)
brief set Calculated magnetic field to /magfield/ b
Definition: csetMagField.f:6
real(4), save b
Definition: cNRLAtmos.f:21
Definition: Zcoord.h:43
! 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
Here is the call graph for this function:
Here is the caller graph for this function:

◆ cned2hva()

subroutine cned2hva ( type(magfield a,
type(magfield b 
)

Definition at line 210 of file ctransMagTo.f.

References csetmagfield().

Referenced by ctransmagto(), cxyz2hva(), drawgeomag(), and geomag().

210 ! transform magnetic components from norht-east-down system
211 ! to horizontal-vertical-deflection_angle system.
212 ! a: /magfield/ input.
213 ! b: /magfield/ output. b can be the same entity as a.
214 ! b.h: horizontal component
215 ! b.v: vertical component
216 ! b.a: deflection angle (deg). + is from the north to
217 ! the clockwise direction.
218  implicit none
219 #include "Zglobalc.h"
220 #include "Zmagfield.h"
221 !
222  type(magfield)::a
223  type(magfield)::b
224  real*8 h, v, ang
225 !
226 #ifdef UNIONMAP
227  h = sqrt(a%n**2+a%e**2)
228  if(a%e .eq. 0. .and. a%n .eq. 0.) then
229  ang = 0.
230  else
231  ang = atan2(a%e, a%n)*todeg
232  endif
233  v = a%d
234 #else
235  h = sqrt(a%x**2+a%y**2)
236  if(a%y .eq. 0. .and. a%x .eq. 0.) then
237  ang = 0.
238  else
239  ang = atan2(a%y, a%x)*todeg
240  endif
241  v = a%z
242 #endif
243 !
244  call csetmagfield('hva', h, v, ang, b)
real(4), dimension(:), allocatable, save h
Definition: cNRLAtmos.f:28
real(4), save a
Definition: cNRLAtmos.f:20
subroutine csetmagfield(sys, b1, b2, b3, b)
brief set Calculated magnetic field to /magfield/ b
Definition: csetMagField.f:6
real(4), save b
Definition: cNRLAtmos.f:21
Here is the call graph for this function:
Here is the caller graph for this function:

◆ ctransmagto()

subroutine ctransmagto ( character*(*)  sys,
type(coord pos,
type(magfield a,
type(magfield b 
)

Definition at line 11 of file ctransMagTo.f.

References cerrormsg(), chva2ned(), cmag2ecent(), cned2hva(), cxyz2hva(), and cxyz2ned().

Referenced by cfixmag(), cgeomfunc(), cinitobs(), cinitracking(), cmagdef(), and geomag().

11 !
12 ! sys: character*(*). input. 'xyz', 'hva', 'ned'
13 ! the target coordinate system where
14 ! magnetic filed is represented.
15 ! pos: /coord/. input. position where mag is given
16 ! a: /magfield/ input.
17 ! b: /magfield/ output. transformed component, b.sys=sys
18 !
19  implicit none
20 
21 #include "Zcoord.h"
22 #include "Zmagfield.h"
23  character*(*) sys
24  type(magfield)::a
25  type(magfield)::b
26  type(coord)::pos
27 !
28  character*70 msg
29 !
30  if( a%sys .eq. sys) then
31  b = a
32  elseif(sys .eq. 'xyz') then
33  call cmag2ecent(pos, a, b)
34  elseif(a%sys .eq. 'xyz') then ! current system
35  if(sys .eq. 'hva') then
36  call cxyz2hva(pos, a, b)
37  elseif(sys .eq. 'ned') then
38  call cxyz2ned(pos, a, b)
39  else
40  write(msg, *) ' ctransMagTo: sys=', sys, ' invalid'
41  call cerrormsg(msg, 0)
42  endif
43  elseif(a%sys .eq. 'hva') then
44  if( sys .eq. 'ned') then
45  call chva2ned(a, b)
46  else
47  write(msg, *) ' ctransMagTo: sys=', sys, ' invalid'
48  call cerrormsg(msg, 0)
49  endif
50  elseif(a%sys .eq. 'ned') then
51  if(sys .eq. 'hva') then
52  call cned2hva(a, b)
53  else
54  write(msg, *) ' ctransMagTo: sys=', sys, ' invalid'
55  call cerrormsg(msg, 0)
56  endif
57  else
58  write(msg, *) ' ctransMagTo: a%sys=', a%sys, ' invalid'
59  call cerrormsg(msg, 0)
60  endif
subroutine cerrormsg(msg, needrtn)
Definition: cerrorMsg.f:4
subroutine chva2ned(a, b)
Definition: ctransMagTo.f:248
*Zfirst p fm *Zfirst p Zfirst p Zfirst p *Zfirst p *Zfirst pos xyz Zfirst pos xyz sys
Definition: ZavoidUnionMap.h:1
subroutine cned2hva(a, b)
Definition: ctransMagTo.f:210
subroutine cmag2ecent(pos, a, b)
Definition: ctransMagTo.f:64
real(4), save a
Definition: cNRLAtmos.f:20
real(4), save b
Definition: cNRLAtmos.f:21
subroutine cxyz2ned(pos, a, b)
Definition: ctransMagTo.f:138
Definition: Zcoord.h:43
subroutine cxyz2hva(pos, a, b)
Definition: ctransMagTo.f:197
Here is the call graph for this function:
Here is the caller graph for this function:

◆ cxyz2hva()

subroutine cxyz2hva ( type(coord pos,
type(magfield a,
type(magfield b 
)

Definition at line 197 of file ctransMagTo.f.

References cned2hva(), and cxyz2ned().

Referenced by ctransmagto().

197  implicit none
198 #include "Zglobalc.h"
199 #include "Zcoord.h"
200 #include "Zmagfield.h"
201 !
202  type(coord)::pos
203  type(magfield)::a
204  type(magfield)::b
205 !
206  call cxyz2ned(pos, a, b)
207  call cned2hva(a, b)
subroutine cned2hva(a, b)
Definition: ctransMagTo.f:210
real(4), save a
Definition: cNRLAtmos.f:20
real(4), save b
Definition: cNRLAtmos.f:21
subroutine cxyz2ned(pos, a, b)
Definition: ctransMagTo.f:138
Definition: Zcoord.h:43
Here is the call graph for this function:
Here is the caller graph for this function:

◆ cxyz2ned()

subroutine cxyz2ned ( type(coord pos,
type(magfield a,
type(magfield b 
)

Definition at line 138 of file ctransMagTo.f.

References cerrormsg(), cos, and csetmagfield().

Referenced by ctransmagto(), and cxyz2hva().

138  implicit none
139 #include "Zglobalc.h"
140 #include "Zcoord.h"
141 #include "Zmagfield.h"
142 !
143  type(coord)::pos
144  type(magfield)::a
145  type(magfield)::b
146  real*8 cosphi, sinphi, coslam, sinlam, x, y, z
147  real*8 adcans, n, e, d
148  character*70 msg
149 !
150  if(pos%sys .ne. 'llh') then
151  write(msg, *)'cxyz2ned: input pos%sys=',pos%sys,
152  * ' invalid. should be llh'
153  call cerrormsg(msg, 0)
154  endif
155  if(a%sys .ne. 'xyz') then
156  write(msg, *) 'cxyz2ned: a%sys=', a%sys, ' invalid'
157  call cerrormsg(msg, 0)
158  endif
159 #ifdef UNIONMAP
160 !
161  cosphi = cos(pos%lat*torad)
162  sinphi = sin(pos%lat*torad)
163  coslam = cos(pos%long*torad)
164  sinlam = sin(pos%long*torad)
165  x = a%x
166  y = a%y
167  z = a%z
168 ! -(a.d*cosphi + a.n*sinphi)
169  adcans = x * coslam + y *sinlam
170  d =- ( adcans*cosphi + z * sinphi )
171 ! n = -x*sinphi*coslam - y*sinphi*sinlam + z*cosphi
172  n = - adcans*sinphi + z * cosphi
173 ! e = (y + (d*cosphi + n*sinphi)*sinlam) * coslam -
174 ! * (x + (d*cosphi + n*sinphi)* coslam) * sinlam
175  e = -x*sinlam + y*coslam
176 #else
177 !
178  cosphi = cos(pos%r(1)*torad)
179  sinphi = sin(pos%r(1)*torad)
180  coslam = cos(pos%r(2)*torad)
181  sinlam = sin(pos%r(2)*torad)
182  x = a%x
183  y = a%y
184  z = a%z
185 ! -(a.z*cosphi + a.x*sinphi)
186  adcans = x * coslam + y *sinlam
187  d =- ( adcans*cosphi + z * sinphi )
188  n = - adcans*sinphi + z * cosphi
189 ! e = (y + (d*cosphi + n*sinphi)*sinlam) * coslam -
190 ! * (x + (d*cosphi + n*sinphi)* coslam) * sinlam
191  e = -x*sinlam + y*coslam
192 #endif
193  call csetmagfield('ned', n, e, d, b)
subroutine cerrormsg(msg, needrtn)
Definition: cerrorMsg.f:4
nodes z
dE dx *! Nuc Int sampling table e
Definition: cblkMuInt.h:130
! 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
latitude latitude this system is used *****************************************************************! type coord sequence union map real y
Definition: Zcoord.h:25
dE dx *! Nuc Int sampling table d
Definition: cblkMuInt.h:130
real(4), save a
Definition: cNRLAtmos.f:20
subroutine csetmagfield(sys, b1, b2, b3, b)
brief set Calculated magnetic field to /magfield/ b
Definition: csetMagField.f:6
real(4), save b
Definition: cNRLAtmos.f:21
Definition: Zcoord.h:43
integer n
Definition: Zcinippxc.h:1
! 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
Here is the call graph for this function:
Here is the caller graph for this function: