~frederix/+junk/matrix

« back to all changes in this revision

Viewing changes to sum/matrix_com.f95

  • Committer: Rikkert Frederix
  • Date: 2019-04-16 06:39:16 UTC
  • Revision ID: frederix@physik.uzh.ch-20190416063916-cypd32mxh3d9jqv2
added a counter to count the number of times the gluon3 subroutine is
called. Foudnt hat matrix_com2.f95 is highly inefficient in recycling computed
wavefunctions. 

Show diffs side-by-side

added added

removed removed

Lines of Context:
7
7
  !            maximal, (next-1)!)
8
8
  ! alphas   = the value of the strong coupling
9
9
  ! sqrtshat = collision energy
10
 
  integer, parameter   :: next=5
11
 
  integer, parameter   :: npermtry=24
12
 
  integer*8, parameter :: npoints=10000
 
10
  integer, parameter   :: next=4
 
11
  integer, parameter   :: npermtry=6
 
12
  integer*8, parameter :: npoints=1
13
13
  real*8, parameter    :: alphas=0.12d0
14
14
  real*8, parameter    :: sqrtshat=1000d0
15
15
! constants:  
24
24
  integer, dimension(next) :: ifinal
25
25
  data ifinal(1:next) / -1,-1,nfin*1 /
26
26
  complex*16, dimension(npermtry,0:maskr(next)) :: amp
 
27
  integer*8 :: icounter=0
27
28
end module parameters
28
29
 
29
30
program matrix
157
158
  uncertainty=sqrt(abs(uncertainty-integral**2)/dble(npoints))
158
159
  if (npoints.gt.10) write (*,*) 'sigma:',integral,'+/-',uncertainty,'(',100d0*uncertainty/integral,'%)'
159
160
 
 
161
  write (*,*) 'icounter:',icounter
 
162
 
160
163
contains
161
164
  logical function fail_cuts()
162
165
    ! Cuts on the phase-space point.
412
415
           b3=merge_bits(zero,ext,maskr(isplit))
413
416
           do ib=1,nwf(b3)
414
417
              do ia=1,nwf(a3)
 
418
                 icounter=icounter+1
415
419
                 call gluon3(wf(1,ia,a3),pp(0,a3), &
416
420
                             wf(1,ib,b3),pp(0,b3), &
417
421
                             wfout)