Changeset 2228 for LMDZ5/trunk/libf


Ignore:
Timestamp:
Mar 12, 2015, 2:15:18 PM (9 years ago)
Author:
lguez
Message:

Correcting a problem from revision 2218. The type double precision
with option "-fdefault-real-8" of gfortran is promoted to 16-byte
precision and there is no specific procedure in arth with this
precision. Could not add a specific procedure in arth with double
precision because, with ifort, the option "-real-size 64" does not
promote the double precision, so that would make two identical
specific procedures in arth.

In module nrtype, replaced double precision by a parameterized real
kind so that the effective precision does not depend on a compiler
option.

In coefpoly, fxhyp, fyhyp and invert_zoom_x, use the parameterized
real kind defined in nrtype, instead of double precision.

Also, in module nrtype, removed unused derived types sprs2_sp and
sprs2_dp.

Location:
LMDZ5/trunk/libf
Files:
6 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/bibio/arth.F90

    r1907 r2228  
    77  INTERFACE arth
    88     ! Returns an arithmetic progression, given a first term "first", an
    9      ! increment and a number of terms "n".
     9     ! increment and a number of terms "n" (including "first").
    1010
    1111     MODULE PROCEDURE arth_r, arth_i
    12      ! The difference between the procedures is the type of
    13      ! arguments "first" and "increment" and of function result.
     12     ! The difference between the procedures is the kind and type of
     13     ! arguments first and increment and of function result.
    1414  END INTERFACE
    1515
     
    2222    REAL, INTENT(IN) :: first,increment
    2323    INTEGER, INTENT(IN) :: n
    24     REAL, DIMENSION(n) :: arth_r
     24    REAL arth_r(n)
    2525
    26     ! Variables local to the procedure:
    27 
     26    ! Local:
    2827    INTEGER :: k,k2
    2928    REAL :: temp
     
    5049       end do
    5150    end if
     51
    5252  END FUNCTION arth_r
    5353
     
    5757
    5858    INTEGER, INTENT(IN) :: first,increment,n
    59     INTEGER, DIMENSION(n) :: arth_i
     59    INTEGER arth_i(n)
     60
     61    ! Local:
    6062    INTEGER :: k,k2,temp
     63
     64    !---------------------------------------
     65
    6166    if (n > 0) arth_i(1)=first
    6267    if (n <= NPAR_ARTH) then
     
    7883       end do
    7984    end if
     85
    8086  END FUNCTION arth_i
    8187
  • LMDZ5/trunk/libf/bibio/nrtype.F90

    r2218 r2228  
    33  implicit none
    44
    5   integer, parameter:: wp = kind(0.) ! working precision for real type
     5  integer, parameter:: k8 = selected_real_kind(13)
    66
    77  ! Frequently used mathematical constants (with precision to spare):
     
    1313  REAL, PARAMETER :: EULER=0.5772156649015328606065120900824024310422
    1414
    15   DOUBLE PRECISION, PARAMETER:: &
    16        PI_D = 3.141592653589793238462643383279502884197d0
    17   DOUBLE PRECISION, PARAMETER:: &
    18        PIO2_D=1.57079632679489661923132169163975144209858d0
    19   DOUBLE PRECISION, PARAMETER:: &
    20        TWOPI_D=6.283185307179586476925286766559005768394d0
    21 
    22   ! Derived data types for sparse matrices, single and double
    23   ! precision (see use in Chapter B2):
    24 
    25   TYPE sprs2_sp
    26      INTEGER :: n,len
    27      REAL, DIMENSION(:), POINTER :: val
    28      INTEGER, DIMENSION(:), POINTER :: irow
    29      INTEGER, DIMENSION(:), POINTER :: jcol
    30   END TYPE sprs2_sp
    31 
    32   TYPE sprs2_dp
    33      INTEGER :: n,len
    34      DOUBLE PRECISION, DIMENSION(:), POINTER :: val
    35      INTEGER, DIMENSION(:), POINTER :: irow
    36      INTEGER, DIMENSION(:), POINTER :: jcol
    37   END TYPE sprs2_dp
     15  REAL(K8), PARAMETER:: &
     16       PI_D = 3.141592653589793238462643383279502884197_k8
     17  REAL(K8), PARAMETER:: &
     18       PIO2_D=1.57079632679489661923132169163975144209858_k8
     19  REAL(K8), PARAMETER:: &
     20       TWOPI_D=6.283185307179586476925286766559005768394_k8
    3821
    3922END MODULE nrtype
  • LMDZ5/trunk/libf/dyn3d_common/coefpoly_m.F90

    r2218 r2228  
    2525    ! a0, a1, a2, a3.
    2626
    27     DOUBLE PRECISION, intent(in):: xf1, xf2, xprim1, xprim2, xtild1, xtild2
    28     DOUBLE PRECISION, intent(out):: a0, a1, a2, a3
     27    use nrtype, only: k8
     28
     29    REAL(K8), intent(in):: xf1, xf2, xprim1, xprim2, xtild1, xtild2
     30    REAL(K8), intent(out):: a0, a1, a2, a3
    2931
    3032    ! Local:
    31     DOUBLE PRECISION xtil1car, xtil2car, derr, x1x2car
     33    REAL(K8) xtil1car, xtil2car, derr, x1x2car
    3234
    3335    !------------------------------------------------------------
  • LMDZ5/trunk/libf/dyn3d_common/fxhyp_m.F90

    r2218 r2228  
    2020    use arth_m, only: arth
    2121    use invert_zoom_x_m, only: invert_zoom_x, nmax
    22     use nrtype, only: pi, pi_d, twopi, twopi_d
     22    use nrtype, only: pi, pi_d, twopi, twopi_d, k8
    2323    use principal_cshift_m, only: principal_cshift
    2424
     
    3636    REAL dzoom, step
    3737    real d_rlonv(iim)
    38     DOUBLE PRECISION xtild(0:2 * nmax)
    39     DOUBLE PRECISION fhyp(nmax:2 * nmax), ffdx, beta, Xprimt(0:2 * nmax)
    40     DOUBLE PRECISION Xf(0:2 * nmax), xxpr(2 * nmax)
    41     DOUBLE PRECISION fa, fb
     38    REAL(K8) xtild(0:2 * nmax)
     39    REAL(K8) fhyp(nmax:2 * nmax), ffdx, beta, Xprimt(0:2 * nmax)
     40    REAL(K8) Xf(0:2 * nmax), xxpr(2 * nmax)
     41    REAL(K8) fa, fb
    4242    INTEGER i, is2
    43     DOUBLE PRECISION xmoy, fxm
     43    REAL(K8) xmoy, fxm
    4444
    4545    !----------------------------------------------------------------------
     
    175175
    176176          call invert_zoom_x(xf, xtild, Xprimt, rlonm025(:iim), &
    177                xprimm025(:iim), xuv = - 0.25d0)
     177               xprimm025(:iim), xuv = - 0.25_k8)
    178178          call invert_zoom_x(xf, xtild, Xprimt, rlonv(:iim), xprimv(:iim), &
    179                xuv = 0d0)
     179               xuv = 0._k8)
    180180          call invert_zoom_x(xf, xtild, Xprimt, rlonu(:iim), xprimu(:iim), &
    181                xuv = 0.5d0)
     181               xuv = 0.5_k8)
    182182          call invert_zoom_x(xf, xtild, Xprimt, rlonp025(:iim), &
    183                xprimp025(:iim), xuv = 0.25d0)
     183               xprimp025(:iim), xuv = 0.25_k8)
    184184       end if test_grossismx
    185185
  • LMDZ5/trunk/libf/dyn3d_common/fyhyp_m.F90

    r2218 r2228  
    1717
    1818    use coefpoly_m, only: coefpoly
     19    use nrtype, only: k8
    1920
    2021    include "dimensions.h"
     
    3031    ! Local:
    3132
    32     DOUBLE PRECISION champmin, champmax
     33    REAL(K8) champmin, champmax
    3334    INTEGER, PARAMETER:: nmax=30000, nmax2=2*nmax
    3435    REAL dzoom ! distance totale de la zone du zoom (en radians)
    35     DOUBLE PRECISION ylat(jjm + 1), yprim(jjm + 1)
    36     DOUBLE PRECISION yuv
    37     DOUBLE PRECISION, save:: yt(0:nmax2)
    38     DOUBLE PRECISION fhyp(0:nmax2), beta
    39     DOUBLE PRECISION, save:: ytprim(0:nmax2)
    40     DOUBLE PRECISION fxm(0:nmax2)
    41     DOUBLE PRECISION, save:: yf(0:nmax2)
    42     DOUBLE PRECISION yypr(0:nmax2)
    43     DOUBLE PRECISION yvrai(jjm + 1), yprimm(jjm + 1), ylatt(jjm + 1)
    44     DOUBLE PRECISION pi, pis2, epsilon, y0, pisjm
    45     DOUBLE PRECISION yo1, yi, ylon2, ymoy, yprimin
    46     DOUBLE PRECISION yfi, yf1, ffdy
    47     DOUBLE PRECISION ypn, deply, y00
     36    REAL(K8) ylat(jjm + 1), yprim(jjm + 1)
     37    REAL(K8) yuv
     38    REAL(K8), save:: yt(0:nmax2)
     39    REAL(K8) fhyp(0:nmax2), beta
     40    REAL(K8), save:: ytprim(0:nmax2)
     41    REAL(K8) fxm(0:nmax2)
     42    REAL(K8), save:: yf(0:nmax2)
     43    REAL(K8) yypr(0:nmax2)
     44    REAL(K8) yvrai(jjm + 1), yprimm(jjm + 1), ylatt(jjm + 1)
     45    REAL(K8) pi, pis2, epsilon, y0, pisjm
     46    REAL(K8) yo1, yi, ylon2, ymoy, yprimin
     47    REAL(K8) yfi, yf1, ffdy
     48    REAL(K8) ypn, deply, y00
    4849    SAVE y00, deply
    4950
     
    5152    INTEGER jpn, jjpn
    5253    SAVE jpn
    53     DOUBLE PRECISION a0, a1, a2, a3, yi2, heavyy0, heavyy0m
    54     DOUBLE PRECISION fa(0:nmax2), fb(0:nmax2)
     54    REAL(K8) a0, a1, a2, a3, yi2, heavyy0, heavyy0m
     55    REAL(K8) fa(0:nmax2), fb(0:nmax2)
    5556    REAL y0min, y0max
    5657
    57     DOUBLE PRECISION heavyside
     58    REAL(K8) heavyside
    5859
    5960    !-------------------------------------------------------------------
  • LMDZ5/trunk/libf/dyn3d_common/invert_zoom_x_m.F90

    r2218 r2228  
    1010
    1111    use coefpoly_m, only: coefpoly
    12     use nrtype, only: pi, pi_d, twopi_d
     12    use nrtype, only: pi, pi_d, twopi_d, k8
    1313
    1414    include "dimensions.h"
     
    1818    ! for clon
    1919
    20     DOUBLE PRECISION, intent(in):: Xf(0:), xtild(0:), Xprimt(0:) ! (0:2 * nmax)
     20    REAL(K8), intent(in):: Xf(0:), xtild(0:), Xprimt(0:) ! (0:2 * nmax)
    2121    real, intent(out):: xlon(:), xprimm(:) ! (iim)
    2222
    23     DOUBLE PRECISION, intent(in):: xuv
     23    REAL(K8), intent(in):: xuv
    2424    ! 0. si calcul aux points scalaires
    2525    ! 0.5 si calcul aux points U
    2626
    2727    ! Local:
    28     DOUBLE PRECISION xo1, Xfi, a0, a1, a2, a3, Xf1, Xprimin
     28    REAL(K8) xo1, Xfi, a0, a1, a2, a3, Xf1, Xprimin
    2929    integer i, it, iter
    30     DOUBLE PRECISION, parameter:: my_eps = 1d-6
     30    REAL(K8), parameter:: my_eps = 1e-6_k8
    3131
    32     DOUBLE PRECISION xxprim(iim), xvrai(iim)
     32    REAL(K8) xxprim(iim), xvrai(iim)
    3333    ! intermediary variables because xlon and xprimm are simple precision
    3434
     
    3636
    3737    DO i = 1, iim
    38        Xfi = - pi_d + (i + xuv - 0.75d0) * twopi_d / iim
     38       Xfi = - pi_d + (i + xuv - 0.75_k8) * twopi_d / iim
    3939
    4040       it = 2 * nmax
     
    5454            xtild(it), xtild(it + 1), a0, a1, a2, a3)
    5555       Xf1 = Xf(it)
    56        Xprimin = a1 + xvrai(i) * (2d0 * a2 + xvrai(i) * 3d0 * a3)
     56       Xprimin = a1 + xvrai(i) * (2._k8 * a2 + xvrai(i) * 3._k8 * a3)
    5757       xo1 = xvrai(i)
    5858       iter = 1
     
    6363          xo1 = xvrai(i)
    6464          Xf1 = a0 + xvrai(i) * (a1 + xvrai(i) * (a2 + xvrai(i) * a3))
    65           Xprimin = a1 + xvrai(i) * (2d0 * a2 + xvrai(i) * 3d0 * a3)
     65          Xprimin = a1 + xvrai(i) * (2._k8 * a2 + xvrai(i) * 3._k8 * a3)
    6666       end DO
    6767
Note: See TracChangeset for help on using the changeset viewer.