Go to the source code of this file.
◆ cdefbymagande()
subroutine cdefbymagande |
( |
type(track) |
aTrack, |
|
|
real(8), intent(in) |
leng, |
|
|
type(coord) |
dispmr, |
|
|
type(coord) |
dispmd, |
|
|
real(8), dimension(3), intent(out) |
newmom |
|
) |
| |
Definition at line 40 of file cdefByMagAndE.f.
References modbefield::bfld, c, cgetefield(), modbefield::ptclmass, and modbefield::ptclz.
Referenced by cmagdef().
49 real(8),
intent(in)::
leng 52 real(8),
intent(out):: newmom(3)
54 integer,
parameter:: nsim=6
55 integer,
parameter::nstep=1
56 real(8)::
t(0:nstep), u(6,0:nstep)
64 real(8):: p2,
e, gamma, bt
67 real(8),
save:: pos(3)=(/0.,0.,0./)
71 bfld(:) =(/mag%x, mag%y, mag%z/)
79 u(4:6, 0) = atrack%p%fm%p(1:3)
80 ptclz = atrack%p%charge
84 bt = sqrt( (gamma-1)*(gamma+1))/gamma
86 forall(
n=0:nstep)
t(
n) =
n*dt
87 call ksrunge_kutta4(
t, u, nstep, nsim, dt,
89 dispmr%r(:) = u(1:3,nstep) - u(1:3,0)
95 p2 =dot_product( u(4:6,nstep), u(4:6,nstep) )
97 dispmd%r(:) = u(4:6,nstep)/ sqrt( p2)
99 dispmd%r(:) = (/0.,0.,1./)
101 newmom(:) = u(4:6,nstep)
subroutine cgetefield(aTrack)
dE dx *! Nuc Int sampling table e
real(8) function, dimension(nv) fbedeflection(t, u, nv)
real(8), dimension(3), save bfld
dE dx *! Nuc Int sampling table c
◆ cgetefield()
subroutine cgetefield |
( |
type(track) |
aTrack | ) |
|
Definition at line 11 of file cdefByMagAndE.f.
References modefield::cefield0(), cmyefield(), modbefield::efld, and modefield::howefield.
Referenced by cdefbymagande(), and cmaxefefflen().
23 #if defined (MYEFIELD) 27 write(0,*)
"HowEfield=",
howefield,
" invalid" 28 write(0,*)
"You must define MYEFIELD in Zcondc%h" 30 *
"and prepare cmyEfield subroutine in your apps.",
31 *
"Interface is cmyEfield(aTrack,Efout); see",
32 *
"manual or cEfield0 in Cosmos/Module" subroutine cmyefield(aTrack, Efout)
real(8), dimension(3), save efld
subroutine cefield0(aTrack, Efout)
◆ fbedeflection()
real(8) function, dimension(nv) fbedeflection |
( |
real(8), intent(in) |
t, |
|
|
real(8), dimension(nv), intent(in) |
u, |
|
|
integer, intent(in) |
nv |
|
) |
| |
Definition at line 105 of file cdefByMagAndE.f.
References modbefield::bfld, c, modbefield::efld, modbefield::eval, modbefield::ptclmass, and modbefield::ptclz.
111 #include "Zglobalc.h" 112 integer,
intent(in):: nv
113 real(8),
intent(in)::
t 114 real(8),
intent(in):: u(nv)
119 real(8)::vp(3),
temp(3)
121 p2= dot_product( vp, vp)
dE dx *! Nuc Int sampling table e
atmos%rho(atmos%nodes) **exp(-(z-atmos%z(atmos%nodes))/Hinf) elseif(z .lt. atmos%z(1)) then ans=atmos%rho(1) **exp((atmos%z(1) -z)/atmos%H(1)) else call kdwhereis(z, atmos%nodes, atmos%z, 1, i) a=atmos%a(i) if(a .ne. 0.d0) then ans=atmos%rho(i) **(1+a *(z-atmos%z(i))/atmos%H(i)) **(-1.0d0-1.d0/a) else ans=*atmos%rho(i) *exp(-(z-atmos%z(i))/atmos%H(i)) endif endif ! zsave=z ! endif cvh2den=ans end ! ---------------------------------- real *8 function cvh2temp(z) implicit none ! vettical height to temperatur(Kelvin) real *8 z ! input. vertical height in m ! output is temperature of the atmospher in Kelvin real *8 ans integer i if(z .gt. atmos%z(atmos%nodes)) then ans=atmos%T(atmos%nodes) elseif(z .lt. atmos%z(1)) then ans=atmos%T(1)+atmos%b(1) *(z - atmos%z(1)) else call kdwhereis(z, atmos%nodes, atmos%z, 1, i) ans=atmos%T(i)+atmos%b(i) *(z-atmos%z(i)) endif cvh2temp=ans end !--------------------------------------------- real *8 function cthick2h(t) implicit none real *8 t ! input. air thickness in kg/m^2 real *8 logt, ans integer i real *8 dod0, fd, a logt=log(t) if(t .ge. atmos%cumd(1)) then ans=atmos%z(1) - *(logt - atmos%logcumd(1)) *atmos%H(1) elseif(t .le. atmos%cumd(atmos%nodes)) then ans=atmos%z(atmos%nodes) - *Hinf *log(t/atmos%cumd(atmos%nodes)) else call kdwhereis(t, atmos%nodes, atmos%cumd, 1, i) ! i is such that X(i) > x >=x(i+1) ans
real(4), dimension(:), allocatable, save temp
real(8), dimension(3), save bfld
real(8), dimension(3), save efld
dE dx *! Nuc Int sampling table c