Code indexing in gitaly is broken and leads to code not being visible to the user. We work on the issue with highest priority.

Skip to content
Snippets Groups Projects
user.f95 3.68 KiB
Newer Older
ulrich_y's avatar
ulrich_y committed



                 !!!!!!!!!!!!!!!!!!!!!
                     MODULE  USER
                 !!!!!!!!!!!!!!!!!!!!!

  use functions

  implicit none

!==!==!==!==!==!==!==!==!==!==!==!==!==!==!==!==!==!==!==!==!==!==!==!==!

  integer, parameter :: nr_q = 10
  integer, parameter :: nr_bins =200
  real, parameter :: &
     min_val(nr_q) = (/ 25., 115., 0.6, 0.6, 25., 25.,25.,25., 4000., 4000. /)
  real, parameter :: &
     max_val(nr_q) = (/ 45., 155., 1., 1., 45., 45.,45., 45., 14000., 14000. /)

!==!==!==!==!==!==!==!==!==!==!==!==!==!==!==!==!==!==!==!==!==!==!==!==!

!==!==!==!==!==!==!==!==!==!==!==!==!==!==!==!==!==!==!==!==!==!==!==!==!

    !! ============================================== !!
    !! DO NOT EVEN THINK ABOUT CHANGING ANYTHING HERE !!
    !! ============================================== !!

  logical ::  pass_cut(nr_q)
  character (len = 10), dimension(nr_q) :: names
  character(len=10) :: filenamesuffix


!==!==!==!==!==!==!==!==!==!==!==!==!==!==!==!==!==!==!==!==!==!==!==!==!

            !! ----------------------------------------- !!
            !!     There are two versions of binning     !!
            !!     One for computing   d \sigma/ d Q     !!
            !!     One for computing  Q d \sigma/ d Q    !!
            !!  choose by setting the variable bin_kind  !!
            !! ----------------------------------------- !!
  integer :: bin_kind = 0       !!  0 for d \sig/dQ; +1 for Q d \sig/dQ;


  contains




  SUBROUTINE FIX_MU

  !! ==== Specify the scale mu AND musq==mu**2 ==== !!

  mu = Me

  musq = mu**2

  END SUBROUTINE FIX_MU



  SUBROUTINE INITUSER
  print*, "This is a MESA legacy run with the cuts:"
  print*," 25 pi/180._prec< thetae < 45 pi/180._prec "
  print*, " Ee(out) > 45 MeV "
  END SUBROUTINE




  FUNCTION QUANT(q1,q2,q3,q4,q5,q6,q7)

  real (kind=prec), intent(in) :: q1(4),q2(4),q3(4),q4(4), q5(4),q6(4),q7(4)
  real (kind=prec) :: q1lab(4),q2lab(4),q3lab(4),q4lab(4),q5lab(4),q6lab(4)
  real (kind=prec) :: quant(nr_q)
  real (kind=prec) :: thetae, cthetae, qsqE, qsqP, epsE, epsP

  pol1 = (/ 0._prec, 0._prec, 0._prec, 0._prec /)

  pass_cut = .true.
  call fix_mu

  q1lab = boost_rf(q2,q1) ! incoming electron
  q2lab = boost_rf(q2,q2) ! proton at rest
  q3lab = boost_rf(q2,q3) ! outgoing electron
  q4lab = boost_rf(q2,q4) ! outgoing proton
  q5lab = boost_rf(q2,q5) ! outgoing photon (if present)
  q6lab = boost_rf(q2,q6) ! outgoing photon (if present)

  cthetae = cos_th(q1lab,q3lab)
  thetae = acos(cos_th(q1lab,q3lab))
  qsqE = -sq(q1-q3)
  qsqP = -sq(q2-q4)

  epsE = 1./(1. + 2*(1 + qsqe/(4.*Mproton**2))*(tan(0.5*thetae))**2)
  epsP = 1./(1. + 2*(1 + qsqp/(4.*Mproton**2))*(tan(0.5*thetae))**2)

  if(thetae < 25*pi/180._prec) pass_cut=.false.
  if(thetae > 45*pi/180._prec) pass_cut=.false.
  if(q3lab(4) < 45.) pass_cut=.false.
  if(abs(qsqE-8000) > 1000) pass_cut(5)=.false. 
  if(abs(qsqP-8000) > 1000) pass_cut(6)=.false. 
  
  if(abs(qsqE-8000) > 2000) pass_cut(7)=.false. 
  if(abs(qsqP-8000) > 2000) pass_cut(8)=.false. 

  names(1) = "thetae"
  quant(1) = 180*thetae/pi
  names(2) = "Ee"
  quant(2) = q3lab(4) 
  names(3) = "epsE"
  quant(3) = epse
  names(4) = "epsP"
  quant(4) = epsp
  names(5) = "thetaeE1"
  quant(5) = 180*thetae/pi
  names(6) = "thetaeP1"
  quant(6) = 180*thetae/pi
  names(7) = "thetaeE2"
  quant(7) = 180*thetae/pi
  names(8) = "thetaeP2"
  quant(8) = 180*thetae/pi
  names(9) = "qsqE"
  quant(9) = qsqe
  names(10) = "qsqP"
  quant(10) = qsqp

  END FUNCTION QUANT






                 !!!!!!!!!!!!!!!!!!!!!!!
                     END MODULE  USER
                 !!!!!!!!!!!!!!!!!!!!!!!