Skip to content

Commit

Permalink
Fixes needed for compilation with gfortran8
Browse files Browse the repository at this point in the history
Compilation with gfortran8 failing due to
mismatch in array dimension when calling
subroutines. Array dimensions were adapted
where needed.
  • Loading branch information
mfasDa committed May 24, 2018
1 parent 678a3fd commit bb7fb55
Show file tree
Hide file tree
Showing 7 changed files with 29 additions and 20 deletions.
8 changes: 4 additions & 4 deletions LHAPDF/lhapdf-5.9.1/src/wrapacfgpg.f
Expand Up @@ -542,7 +542,7 @@ SUBROUTINE WATE32
!ccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
SUBROUTINE AURGAM(I,NDRV,X,S,ANS)
DIMENSION F1(32),F2(32),F3(32)
DIMENSION AF(3),AS(3)
DIMENSION AF(10),AS(10)
DIMENSION CALCO(8,20,32)
COMMON/W5051I7/CALCO
DATA DELTA/0.8000E-01/
Expand Down Expand Up @@ -572,7 +572,7 @@ SUBROUTINE AURGAM(I,NDRV,X,S,ANS)
!ccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
SUBROUTINE AFGINT(I,NDRV,X,S,ANS)
DIMENSION F1(32),F2(32),F3(32)
DIMENSION AF(3),AS(3)
DIMENSION AF(10),AS(10)
DIMENSION CALCO(8,20,32)
COMMON/W5051IA/CALCO
DATA DELTA/0.8000E-01/
Expand Down Expand Up @@ -602,7 +602,7 @@ SUBROUTINE AFGINT(I,NDRV,X,S,ANS)
!ccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
SUBROUTINE AFGIN2(I,NDRV,X,S,ANS)
DIMENSION F1(32),F2(32),F3(32)
DIMENSION AF(3),AS(3)
DIMENSION AF(10),AS(10)
DIMENSION CELCO(8,20,32)
COMMON/W5051IB/CELCO
DATA DELTA/0.8000E-01/
Expand Down Expand Up @@ -651,7 +651,7 @@ FUNCTION AFGETFV(X,FVL)
double precision &
& XI(32),WI(32),XX(33)
COMMON/W5051I9/XI,WI,XX,NTERMS
DIMENSION A(4),B(4)
DIMENSION A(10),B(10)
N=4
EPS=1.E-7
XAM=XX(1)-EPS
Expand Down
14 changes: 7 additions & 7 deletions LHAPDF/lhapdf-5.9.1/src/wrapgjr.f
Expand Up @@ -8,15 +8,15 @@ subroutine GJRevolve(xin,qin,pdf)
integer ngridx,ngridq,jx,jq
CHARACTER*80 LINE
dimension pdf(-6:6)
integer ng(2),init,set,i,j,k,l,nset,iset
integer ng(9),init,set,i,j,k,l,nset,iset
double precision fgrid(118,99,-5:3,0:26),grid(217)
!double precision fgrid(118,99,-5:3,0:0),grid(217)
! common/fgridc/fgrid
double precision upv,dnv,usea,dsea,str,chm,bot,glu
double precision arg(2)
double precision arg(9)
double precision lha_dfint
double precision lha_gjr08
data ng /118,99/
data ng /118,99,0,0,0,0,0,0,0/

data grid &
& /1d-9,1.25d-9,1.6d-9,2d-9,2.5d-9,3.16d-9,4d-9,5d-9,6.3d-9,8d-9, &
Expand Down Expand Up @@ -138,7 +138,7 @@ subroutine GJRevolve(xin,qin,pdf)
arg(1) = 1d-9
arg(2) = qalfa*qalfa
! imem = 0
alfas = lha_dfint(2,arg,ng,grid,fgrid(1,1,3,imem))
alfas = lha_dfint(9,arg,ng,grid,fgrid(1,1,3,imem))
return
!
!cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
Expand All @@ -159,14 +159,14 @@ subroutine GJRevolve(xin,qin,pdf)

double precision function LHA_GJR08(x,Q2,grid,fgrid,ng,n,set)
implicit none
integer ng(2),n,set
double precision grid(217),arg(2),x,Q2
integer ng(9),n,set
double precision grid(217),arg(9),x,Q2
double precision lha_dfint
double precision fgrid(118,99,-5:3,0:26)
! common/fgridc/fgrid
arg(1) = x
arg(2) = Q2
LHA_GJR08 = lha_dfint(2,arg,ng,grid,fgrid(1,1,n,set))
LHA_GJR08 = lha_dfint(9,arg,ng,grid,fgrid(1,1,n,set))
end

!cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
Expand Down
2 changes: 1 addition & 1 deletion LHAPDF/lhapdf-5.9.1/src/wrapgrv.f
Expand Up @@ -5,7 +5,7 @@ subroutine GRVevolve(xin,qin,pdf)
implicit real*8 (a-h,o-z)
include 'parmsetup.inc'
PARAMETER(ngrid=2)
PARAMETER (NPART=6, NX=68, NQ=27, NARG=2)
PARAMETER (NPART=6, NX=68, NQ=27, NARG=5)
character*16 name(nmxset)
integer nmem(nmxset),ndef(nmxset),mmem
common/NAME/name,nmem,ndef,mmem
Expand Down
13 changes: 11 additions & 2 deletions LHAPDF/lhapdf-5.9.1/src/wraphkn.f
Expand Up @@ -3,7 +3,7 @@ subroutine hknevolve(x,Q,f)
implicit none
integer nq,nx,nd,nff,nset,nhess
! PARAMETER (NQ=33, NX=117, ND=94, NFF=7,sets=19)
PARAMETER (NQ=33, NX=117, ND=7, NFF=7, nhess=19)
PARAMETER (NQ=117, NX=117, ND=7, NFF=7, nhess=19)
include 'parmsetup.inc'
character*16 name(nmxset)
integer nmem(nmxset),ndef(nmxset),mmem
Expand Down Expand Up @@ -33,7 +33,16 @@ subroutine hknevolve(x,Q,f)
& 1.000000D+05, 1.778279D+05, 3.162278D+05, 5.623413D+05, &
& 1.000000D+06, 4.641589D+06, &
& 1.000000D+07, 4.641589D+07, &
& 1.000000D+08 /
& 1.000000D+08, &
& 0,0,0,0,0,0,0, &
& 0,0,0,0,0,0,0,0,0,0, &
& 0,0,0,0,0,0,0,0,0,0, &
& 0,0,0,0,0,0,0,0,0,0, &
& 0,0,0,0,0,0,0,0,0,0, &
& 0,0,0,0,0,0,0,0,0,0, &
& 0,0,0,0,0,0,0,0,0,0, &
& 0,0,0,0,0,0,0,0,0,0, &
& 0,0,0,0,0,0,0 /

DATA XG / &
& 1.000000D-09, 1.333521D-09, 1.778279D-09, 2.371374D-09, &
Expand Down
8 changes: 4 additions & 4 deletions LHAPDF/lhapdf5.5.1/src/wrapacfgpg.f
Expand Up @@ -538,7 +538,7 @@ SUBROUTINE WATE32
!ccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
SUBROUTINE AURGAM(I,NDRV,X,S,ANS)
DIMENSION F1(32),F2(32),F3(32)
DIMENSION AF(3),AS(3)
DIMENSION AF(10),AS(10)
DIMENSION CALCO(8,20,32)
COMMON/W5051I7/CALCO
DATA DELTA/0.8000E-01/
Expand Down Expand Up @@ -568,7 +568,7 @@ SUBROUTINE AURGAM(I,NDRV,X,S,ANS)
!ccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
SUBROUTINE AFGINT(I,NDRV,X,S,ANS)
DIMENSION F1(32),F2(32),F3(32)
DIMENSION AF(3),AS(3)
DIMENSION AF(10),AS(10)
DIMENSION CALCO(8,20,32)
COMMON/W5051IA/CALCO
DATA DELTA/0.8000E-01/
Expand Down Expand Up @@ -598,7 +598,7 @@ SUBROUTINE AFGINT(I,NDRV,X,S,ANS)
!ccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
SUBROUTINE AFGIN2(I,NDRV,X,S,ANS)
DIMENSION F1(32),F2(32),F3(32)
DIMENSION AF(3),AS(3)
DIMENSION AF(10),AS(10)
DIMENSION CELCO(8,20,32)
COMMON/W5051IB/CELCO
DATA DELTA/0.8000E-01/
Expand Down Expand Up @@ -647,7 +647,7 @@ FUNCTION AFGETFV(X,FVL)
double precision &
& XI(32),WI(32),XX(33)
COMMON/W5051I9/XI,WI,XX,NTERMS
DIMENSION A(4),B(4)
DIMENSION A(10),B(10)
N=4
EPS=1.E-7
XAM=XX(1)-EPS
Expand Down
2 changes: 1 addition & 1 deletion LHAPDF/lhapdf5.5.1/src/wrapgrv.f
Expand Up @@ -5,7 +5,7 @@ subroutine GRVevolve(xin,qin,pdf)
implicit real*8 (a-h,o-z)
include 'parmsetup.inc'
PARAMETER(ngrid=2)
PARAMETER (NPART=6, NX=68, NQ=27, NARG=2)
PARAMETER (NPART=6, NX=68, NQ=27, NARG=5)
character*16 name(nmxset)
integer nmem(nmxset),ndef(nmxset),mmem
common/NAME/name,nmem,ndef,mmem
Expand Down
2 changes: 1 addition & 1 deletion LHAPDF/lhapdf5.5.1/src/wrapmrst.f
Expand Up @@ -20,7 +20,7 @@ subroutine MRSTevolve(x,Q,pdf)
&,f6(nx,nq) &
&,f7(nx,nq) &
&,f8(nx,nq) &
&,fc(nx,nqc),fb(nx,nqb)
&,fc(nx,37),fb(nx,37)
real*8 qq(nq),xx(nx), &
&cc1(0:nhess,nx,nq,4,4,nmxset),cc2(0:nhess,nx,nq,4,4,nmxset), &
&cc3(0:nhess,nx,nq,4,4,nmxset),cc4(0:nhess,nx,nq,4,4,nmxset), &
Expand Down

0 comments on commit bb7fb55

Please sign in to comment.