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

Go to the source code of this file.

Modules

module  modbefield
 

Functions/Subroutines

subroutine cgetefield (aTrack)
 
subroutine cdefbymagande (aTrack, leng, dispmr, dispmd, newmom)
 
real(8) function, dimension(nv) fbedeflection (t, u, nv)
 

Variables

real(8), dimension(3), save bfld
 
real(8), dimension(3), save efld
 
real(8), save eval =0.29979
 
real(8), save ptclmass
 
real(8), save ptclz
 

Function/Subroutine Documentation

◆ 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().

40  use modbefield
41  use modefield
42  implicit none
43 #include "Zglobalc.h"
44 #include "Ztrack.h"
45 #include "Ztrackv.h"
46 #include "Zmass.h"
47 
48  type(track)::atrack ! input. current track
49  real(8),intent(in):: leng ! moved length in m
50  type(coord)::dispmr ! output displacement
51  type(coord)::dispmd ! output new direction cos
52  real(8),intent(out):: newmom(3) ! chnaged momentum
53 
54  integer,parameter:: nsim=6
55  integer,parameter::nstep=1 ! if 2, accuracy may increse
56  real(8):: t(0:nstep), u(6,0:nstep)
57 !xxxxxxxxxx next equivalence does not work (ifort)
58 ! real(8):: r(3,0:nstep), p(3,0:nstep)
59 ! equivalence( r(1,0), u(1,0) )
60 ! equivalence( p(1,0), u(4,0) )
61  real(8):: dt ! time step in s.
62  real(8),external:: fbedeflection ! function to give f of u'=f
63  ! where u=(r,p), u'=(v, Ze(E+VxB)
64  real(8):: p2, e, gamma, bt
65  integer::n
66 !!!!!!!!!!
67  real(8),save:: pos(3)=(/0.,0.,0./)
68 !!!!!!!!!!!!!!!
69 
70 ! here we assume B is given by Mag (const).
71  bfld(:) =(/mag%x, mag%y, mag%z/)
72 ! Bfld(:) =(/0.3d-4, 0.d0, 0.d0/) ! test
73 
74  call cgetefield(atrack) ! ans is in Efld
75 
76  u(1:3, 0) = 0. ! r=0 we need only dr
77 ! u(1:3, 0) = aTrack.pos.xyz.r(1:3)
78 
79  u(4:6, 0) = atrack%p%fm%p(1:3) ! px,py,pz in GeV/c
80  ptclz = atrack%p%charge
81  ptclmass =atrack%p%mass
82  e = atrack%p%fm%p(4)
83  gamma = e/ptclmass
84  bt = sqrt( (gamma-1)*(gamma+1))/gamma
85  dt = leng/c/bt
86  forall(n=0:nstep) t(n) = n*dt
87  call ksrunge_kutta4(t, u, nstep, nsim, dt,
88  * fbedeflection)
89  dispmr%r(:) = u(1:3,nstep) - u(1:3,0)
90 !!!!!!!!!!
91 ! pos(:) = pos(:) + dispmr.r(:)
92 ! write(*,'(a,1p, 3g14.4)') 'pos ', pos(:)
93 ! write(*,'(a,1p, 3g14.4)') 'pos2 ',u(1:3,nstep)
94 !!!!!!!!!!!!!!!
95  p2 =dot_product( u(4:6,nstep), u(4:6,nstep) )
96  if( p2 > 0.) then
97  dispmd%r(:) = u(4:6,nstep)/ sqrt( p2)
98  else
99  dispmd%r(:) = (/0.,0.,1./)
100  endif
101  newmom(:) = u(4:6,nstep)
subroutine cgetefield(aTrack)
Definition: cdefByMagAndE.f:11
dE dx *! Nuc Int sampling table e
Definition: cblkMuInt.h:130
Definition: Ztrack.h:44
real(8) function, dimension(nv) fbedeflection(t, u, nv)
integer leng
Definition: interface2.h:1
real(8), dimension(3), save bfld
Definition: cdefByMagAndE.f:2
nodes t
Definition: Zcoord.h:43
real(8), save ptclmass
Definition: cdefByMagAndE.f:6
real(8), save ptclz
Definition: cdefByMagAndE.f:7
integer n
Definition: Zcinippxc.h:1
dE dx *! Nuc Int sampling table c
Definition: cblkMuInt.h:130
Here is the call graph for this function:
Here is the caller graph for this function:

◆ 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().

11  use modbefield
12  use modefield
13  implicit none
14 #include "Zglobalc.h"
15 #include "Ztrack.h"
16 #include "Ztrackv.h"
17 #include "Zmass.h"
18 
19  type(track)::atrack ! input. current track
20  if(howefield == 1 ) then
21  call cefield0(atrack, efld)
22  else
23 #if defined (MYEFIELD)
24 ! not simple Efield; user must define next
25  call cmyefield(atrack, efld)
26 #else
27  write(0,*) "HowEfield=",howefield," invalid"
28  write(0,*) "You must define MYEFIELD in Zcondc%h"
29  write(0,*)
30  * "and prepare cmyEfield subroutine in your apps.",
31  * "Interface is cmyEfield(aTrack,Efout); see",
32  * "manual or cEfield0 in Cosmos/Module"
33  stop
34 #endif
35  endif
subroutine cmyefield(aTrack, Efout)
Definition: cmyEfield.f:2
integer, save howefield
Definition: cEfield0.f:17
Definition: Ztrack.h:44
real(8), dimension(3), save efld
Definition: cdefByMagAndE.f:3
subroutine cefield0(aTrack, Efout)
Definition: cEfield0.f:123
Here is the call graph for this function:
Here is the caller graph for this function:

◆ 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.

105 ! charged ptcl motion in E and B
106 ! dp/dt =Ze(E+ VxB)=ZeE+Ze(VyBz-VzBy, VzBx-BxBz, VxBy-VyBx)
107 ! u=(x,y,z, px,py,pz) u'=(v, force)
108 ! v = pc/E
109  use modbefield
110  implicit none
111 #include "Zglobalc.h"
112  integer,intent(in):: nv ! # of variable; simultaneous eq
113  real(8),intent(in):: t ! given time
114  real(8),intent(in):: u(nv) ! value of u for du/dt=f
115  real(8)::ans(nv) ! f
116 ! f(1:3) = dr/dt = beta c = pc/E
117 ! f(4;6) = dp/dt = Ze(E+vxB)
118  real(8)::p2, e
119  real(8)::vp(3), temp(3)
120  vp(:) = u(4:6) ! p
121  p2= dot_product( vp, vp)
122  e = sqrt(ptclmass**2 + p2)
123 ! gamma = E/m
124 ! beta = sqrt( (gamma-1)*(gamma+1))/gamma
125  ans(1:3) = vp(:)*c/e ! pc/E = c*beta => v
126  call kvec_prod3(ans(1:3), bfld, temp(1:3)) ! vxB
127  ans(4:6) = ptclz*eval*(temp(1:3) + efld(1:3))
128 
dE dx *! Nuc Int sampling table e
Definition: cblkMuInt.h:130
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
Definition: cNRLAtmos.f:29
real(8), dimension(3), save bfld
Definition: cdefByMagAndE.f:2
real(8), save eval
Definition: cdefByMagAndE.f:4
nodes t
real(8), dimension(3), save efld
Definition: cdefByMagAndE.f:3
real(8), save ptclmass
Definition: cdefByMagAndE.f:6
real(8), save ptclz
Definition: cdefByMagAndE.f:7
dE dx *! Nuc Int sampling table c
Definition: cblkMuInt.h:130