COSMOS v7.655  COSMOSv7655
(AirShowerMC)
cmuNeuDcy.f
Go to the documentation of this file.
1 ! mu---> e + neue + neumu; inclusive treatment
2 ! some kind of Exclusive treatment
3 !
4  subroutine cmuneudcy(pj, polari, inclusive, a, np)
5  implicit none
6 
7 #include "Zptcl.h"
8 #include "Zmass.h"
9 #include "Zcode.h"
10 
11  integer np ! output. no. of produced particles
12  real*8 polari ! input. muon polarization
13  integer inclusive !input. 0--> inclusive treatment
14  ! >0--> Exclusive treatment
15  ! Only Electron is correctly sampled
16  ! 4 momenta of two neutrinos are sampled
17  ! so that the total 4 momentum be conserved.
18  ! Since the formula assumes Me=0, we
19  ! add electron mass to the total energy
20  type(ptcl)::pj ! input. muon
21  type(ptcl):: a(*) ! output. produced ptcls
22 !
23  type(ptcl):: twoNeu
24  real*8 po, f, ecm, cosa, lam
25  integer i, charge, subcode
26  logical try
27 
28  real*8 pab
29 
30  try = .true.
31 ! make 3 ptcls; neu_e, neu_mu, e
32  subcode = -pj%charge
33  call cmkptc(kneue, subcode, 0, a(1))
34  subcode = pj%charge
35  call cmkptc(kneumu, subcode, 0, a(2))
36  charge = pj%charge
37  call cmkptc(kelec, 0, charge, a(3))
38  if(pj%charge .eq. 1) then
39 ! for mu+, polarization should be made to inverse sign
40 ! because e+ goes same as mu+ polarizaion while
41 ! neue trino opposit.
42  po=-polari
43  else
44  po=polari
45  endif
46  do while ( try )
47 ! we fix electron first which is detectabl
48 ! electron ; paralell to neu_mu
49 ! x^2(3-2x + (1-2x)Pcos) dxdcos
50 ! first integrate by cos and get energy distribution
51 ! x^2(3-2x) dx =2x^2(1-x)+x^2: this is the same as neu_mu energy
52 ! (f=x=2E/Mmu)
53 
54  call csneumuemu(f)
55  ecm=f*pj%mass/2
56  if(ecm .le. a(3)%mass) cycle
57 
58 ! angluar distribution is
59 ! ( 1 + lam* cos ) dcos type
60 !
61  lam = (1.-2*f)/(3.-2*f) *po
62 
63  call ksamplin(lam, 1.d0, -1.d0, 1.d0, cosa)
64 ! set px,py,pz
65  pab =sqrt( ecm**2 - a(3)%mass**2 )
66  call cpcos2pxyz(cosa, pab, a(3)%fm)
67  a(3)%fm%p(4) = ecm
68 ! -------------
69  if( inclusive .eq. 0 ) then
70 ! inclusive treatment
71 ! sample energy in f=2e*/mmu: e* is at muon rest sytem
72 ! of neue
73  call csampneueemu(f)
74  ecm=f*pj%mass/2
75 ! sample decay angle of neue at muon rest system
76 ! (1+Pcos)dcos
77  call ksamplin(po, 1.d0, -1.d0, 1.d0, cosa)
78 ! set random momentum about azimuth (px,py,pz)
79  call cpcos2pxyz(cosa, ecm, a(1)%fm)
80  a(1)%fm%p(4) = ecm
81 ! since inclusive, no conservation tried
82 ! neumu; sample energy in f=2e*/mmu: e* is at muon rest sytem
83  call csneumuemu(f)
84  ecm=f*pj%mass/2
85 ! sample decay angle of neumu at muon rest system
86 ! (1+lambda P cos) dcos with
87 ! lambda = (1-2f)/(3-2f)
88  lam=(1.-2*f)/(3.-2*f)
89  call ksamplin(lam*po, 1.d0, -1.d0, 1.d0, cosa)
90 ! set px,py,pz
91  call cpcos2pxyz(cosa, ecm, a(2)%fm)
92  a(2)%fm%p(4) = ecm
93  else
94 ! exclusive; but not possible
95 ! we are interested in only electron energy so that
96 ! other two neus are sampled from remaining 4 momenta
97  twoneu%fm%p(4) = pj%mass - a(3)%fm%p(4)
98  if(twoneu%fm%p(4) .le. 0.) cycle
99  twoneu%fm%p(1) = - a(3)%fm%p(1)
100  twoneu%fm%p(2) = - a(3)%fm%p(2)
101  twoneu%fm%p(3) = - a(3)%fm%p(3)
102  twoneu%mass =
103  * sqrt( pj%mass**2 -2*pj%mass*a(3)%fm%p(4) + a(3)%mass**2)
104 
105  call c2bdcy(twoneu, a(1), a(2))
106 
107 ! another choice may be to sample all 3 by inclusive way
108 ! and forced conservation by next conformal transformation
109 ! call cnbdc2(3, pj.mass, a)
110 ! since we assume massless ; no further transformation
111 ! is needed
112  endif
113 ! **************
114 ! pab =sqrt(a(3).fm.p(1)**2 + a(3).fm.p(2)**2
115 ! * + a(3).fm.p(3)**2 )
116 ! write(*,'("cm ",5G14.5)' )
117 ! * a(1).fm.p(4)+a(2).fm.p(4)+a(3).fm.p(4),
118 ! * 2* a(3).fm.p(4)/pj.mass, a(3).fm.p(3)/pab,
119 ! * po, lam
120 ! * a(1).fm.p(1)+a(2).fm.p(1)+a(3).fm.p(1),
121 ! * a(1).fm.p(2)+a(2).fm.p(2)+a(3).fm.p(2),
122 ! * a(1).fm.p(3)+a(2).fm.p(3)+a(3).fm.p(3)
123 ! *************
124  np = 3
125 ! boost to lab.
126  do i = 1, np
127  call cibstpol(i, pj, a(i), a(i) )
128  enddo
129 ! ***************
130 ! write(*,'("lb ",4G14.5)' )
131 ! * a(1).fm.p(4), a(2).fm.p(4), a(3).fm.p(4),
132 ! * a(1).fm.p(4)+a(2).fm.p(4)+a(3).fm.p(4)
133 ! ***************
134 ! since approximation here is to assume Me=0
135 ! we get Ee < Me sometimes (normally 5/10^5 or less )
136 ! so we reject such an event
137  try = a(3)%fm%p(4) .le. a(3)%mass
138  enddo
139  end
subroutine csneumuemu(f)
Definition: csNeumuEMu.f:16
subroutine cmuneudcy(pj, polari, inclusive, a, np)
Definition: cmuNeuDcy.f:5
max ptcl codes in the kelec
Definition: Zcode.h:2
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
max ptcl codes in the kneue
Definition: Zcode.h:2
subroutine cibstpol(init, p1, p2, po)
Definition: cibst1.f:75
block data cblkEvhnp ! currently usable models data RegMdls ad *special data *Cekaon d0
Definition: cblkEvhnp.h:5
max ptcl codes in the kneumu
Definition: Zcode.h:2
subroutine cpcos2pxyz(cosa, p, pxyz)
Definition: cpCos2pxyz.f:2
subroutine csampneueemu(f)
Definition: csampNeueEMu.f:16
subroutine c2bdcy(p, p1, p2)
Definition: c2bdcy.f:44
subroutine ksamplin(a, b, alpha, beta, x)
Definition: ksampLin.f:15
subroutine cmkptc(code, subcode, charge, p)
Definition: cmkptc.f:15
Definition: Zptcl.h:75