zyl 发表于 2017-10-17 20:55:35

如何提高精度?

程序定义的变量是单精度,但是想提高计算精度。我把变量都定义成为REAL(KIND=8)之后,程序报实参与虚参不匹配,所以困惑了。给位大大,帮帮忙改下呗,谢谢谢谢!
PROGRAM MAIN
   
IMPLICIT NONE
INTEGER I
REAL T
REALCCU,CNBSN
REAL RES      
REAL*8 ACU,ASC
REAL B,RRR
REAL CAV
REALt1,t2
REAL*16Q,F
REAL y   
REAL Iop
F=0.000

t1=0.0
Iop=8930.0
B=12.84
RRR=150
ACU=3.80233E-5
ASC=3.80233E-5
t2=2.0
y=5.0
Q=Iop**2*y*(EXP(-2.0*y*t1/2.0)-EXP(-2.0*y*t2/2.0)) &
            /(2.0*Acu**2.0)
WRITE(*,*) "Q=",Q
DO I=1,11
   T=89.0+(i-1)*0.1
   CALL CNB3SN(T,B,CNBSN)
   CALL CCCU(T,CCU)
   CALL DIANZULV(T,B,RRR,RES)
   CAV=(CCU*ACU+CNBSN*ASC)/(ACU+ASC)
      F=CAV*0.001/RES+F
END DO
STOP
END
   

SUBROUTINE CNB3SN(T,B,CNBSN)
IMPLICIT NONE
REAL   b4,b3,b2,b1,b0
REALT,B
REALCNBSN
   IF(T>0.0.AND.T<10.4 ) THEN
         b4=0.0
         b3=38.8-1.8*B+0.0634*B**2
         b2=-110*exp(-0.434*B)
         b1=207.0-3.83*B+2.86*B**2
         b0=0
         
   ELSEIF(T>10.4.AND.T<26.113 ) THEN   
         b4=0.0
         b3=7.42
         b2=0.0
         b1=1522.0
         b0=0.0
ELSEIF(T>=26.113 .AND. T<169.416) THEN
         b4=0.0
         b3=0.0
         b2=-61.635
         b1=19902.0
         b0=-305807.0
ELSEIF(T>=169.416 .AND. T<300.0) THEN
         b4=0.0
         b3=0.0
         b2=-7.4636
         b1=4411.0
         b0=763801.0
ELSE
             b4=0.0
             b3=0.0
             b2=0.0
             b1=0.0
             b0=1415377.0
ENDIF
         CNBSN=b4*(T**4)+b3*(T**3)+b2*(T**2)+b1*T+b0
RETURN
END   
SUBROUTINE CCCU(T,CCU)
IMPLICIT NONE
REAL a0,a1,a2,a3,a4,a5,a6,a7
REAL dens,aa1,aa2,aa3,aa4,aa
REAL T
REAL CCU
a0=-1.91844
a1=-0.15973
a2=8.61013
a3=-18.996
a4=21.9661
a5=-12.7328
a6=3.54322
a7=-0.3797
aa1=a0*((log10(T))**0.0)+a1*((log10(T))**1.0)
aa2=a2*((log10(T))**2.0)+a3*((log10(T))**3.0)
aa3=a4*((log10(T))**4.0)+a5*((log10(T))**5.0)   
aa4=a6*((log10(T))**6.0)+a7*((log10(T))**7.0)
aa=aa1+aa2+aa3+aa4
dens=8960.0
CCU=dens*(10.0**aa)*1.0
WRITE(*,*) "CCU=",CCU
RETURN
END
   
   
SUBROUTINE DIANZULV(T,B,RRR,RES)   
REAL RES1,RES2,RES3,RES
    RES1=1.7E-8/RRR
    RES2=1.0E-8/(2.33*10**9/T**5+9.57*10**5/T**3+163.0/T)
    RES3=(0.37E-10+0.0005E-10*RRR)*B
    RES=RES1+RES2+RES3
    RETURN
    END

pasuka 发表于 2017-10-17 21:35:18

不想修改程序的话,可以通过添加编译器的编译指令实现
譬如gfortran可以参考 https://gcc.gnu.org/onlinedocs/gcc-7.2.0/gfortran/Fortran-Dialect-Options.html#Fortran-Dialect-Options
-fdefault-real-8
Set the default real type to an 8 byte wide type. This option also affects the kind of non-double real constants like 1.0, and does promote the default width of DOUBLE PRECISION to 16 bytes if possible, unless -fdefault-double-8 is given, too. Unlike -freal-4-real-8, it does not promote variables with explicit kind declaration.
或者
-freal-4-real-8
-freal-4-real-10
-freal-4-real-16
-freal-8-real-4
-freal-8-real-10
-freal-8-real-16
Promote all REAL(KIND=M) entities to REAL(KIND=N) entities. If REAL(KIND=N) is unavailable, then an error will be issued. All other real kind types are unaffected by this option. These options should be used with care and may not be suitable for your codes. Areas of possible concern include calls to external procedures, alignment in EQUIVALENCE and/or COMMON, generic interfaces, BOZ literal constant conversion, and I/O. Inspection of the intermediate representation of the translated Fortran code, produced by -fdump-tree-original, is suggested.

zyl 发表于 2017-10-18 10:56:06

已解决,谢谢!
页: [1]
查看完整版本: 如何提高精度?