~frederix/+junk/matrix

« back to all changes in this revision

Viewing changes to sum/matrix_com.f95

  • Committer: Rikkert Frederix
  • Date: 2019-04-15 13:25:50 UTC
  • Revision ID: frederix@physik.uzh.ch-20190415132550-yqx10nynqxuhbwu9
matrix_com2.f95 now working. 

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=4
11
 
  integer, parameter   :: npermtry=6
12
 
  integer*8, parameter :: npoints=1
 
10
  integer, parameter   :: next=5
 
11
  integer, parameter   :: npermtry=24
 
12
  integer*8, parameter :: npoints=10000
13
13
  real*8, parameter    :: alphas=0.12d0
14
14
  real*8, parameter    :: sqrtshat=1000d0
15
15
! constants:  
89
89
        ! next-1 particles, dotting that into the gluon polarisation
90
90
        ! for the next particle.
91
91
        call compute_amplitude(iperm)
92
 
!!$        write (*,*) ip(1:next) ,'=>',iperm
 
92
     enddo
 
93
 
 
94
!!$     do iperm=1,1
 
95
!!$        write (*,*) ips(1:next,iperm) ,'=>',iperm
93
96
!!$        do i=0,maskr(next)
94
97
!!$           write (*,*) i,amp(iperm,i)
95
98
!!$        enddo
96
 
     enddo
 
99
!!$     enddo
 
100
 
97
101
     ! Loop over all colour ordered amplitudes computed, and multiply
98
102
     ! by the colour factor to get the matrix element squared. If
99
103
     ! npermtry<nperm, also include the weight from the MC-ing over
321
325
  integer, dimension(next) :: ipss
322
326
  integer :: iflag
323
327
  do i=1,next-1
324
 
     ips(i)=i+1
 
328
     ips(i)=i
325
329
  enddo
326
330
  do i=1,iperm-1
327
331
     call ipnext(ips,next-1,iflag)
328
332
  enddo
329
 
  ipss(1)=1
330
 
  ipss(2:next)=ips(:)
 
333
  ipss(1:next-1)=ips(:)
 
334
  ipss(next)=next
331
335
end subroutine set_iperm
332
336
 
333
337
subroutine get_iperm_rn(ips)
339
343
  integer,dimension(next) :: ips
340
344
  real*8, external :: rn
341
345
  ! Create a pool of numbers to pick from
342
 
  do i=1,next-1
343
 
     ileft(i)=i+1
 
346
  do i=1,next
 
347
     ileft(i)=i
344
348
  enddo
345
 
  ! First number in permutation is always 1: this removes all cyclic
346
 
  ! permutations.
347
 
  ips(1)=1
348
349
  ! Randomly remove a number from the pool 'ileft' and add it to the
349
350
  ! 'ips' permutation list.
350
 
  do i=2,next
 
351
  do i=1,next-1
351
352
     k=0
352
 
     itemp=int(rn(1)*(next-i+1))+1
 
353
     itemp=int(rn(1)*(next-i))+1
353
354
     do j=1,itemp
354
355
        k=k+1
355
356
        do while (ileft(k).eq.0)
359
360
     ips(i)=ileft(k)
360
361
     ileft(k)=0
361
362
  enddo
 
363
  ! Last number in permutation is always 'next': this removes all cyclic
 
364
  ! permutations.
 
365
  ips(next)=next
362
366
end subroutine get_iperm_rn
363
367
 
364
368
subroutine compute_amplitude(iperm)