New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
Changeset 15540 for NEMO/branches/2021/dev_r14116_HPC-10_mcastril_Mixed_Precision_implementation/src/OCE/DIA/diadct.F90 – NEMO

Ignore:
Timestamp:
2021-11-26T12:27:56+01:00 (3 years ago)
Author:
sparonuz
Message:

Mixed precision version, tested up to 30 years on ORCA2.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2021/dev_r14116_HPC-10_mcastril_Mixed_Precision_implementation/src/OCE/DIA/diadct.F90

    r14219 r15540  
    6161 
    6262   TYPE COORD_SECTION 
    63       REAL(wp) :: lon,lat 
     63      REAL(dp) :: lon,lat 
    6464   END TYPE COORD_SECTION 
    6565 
     
    7373      INTEGER, DIMENSION(nb_point_max)             :: direction         ! vector direction of the point in the section 
    7474      CHARACTER(len=40),DIMENSION(nb_class_max)    :: classname         ! characteristics of the class 
    75       REAL(wp), DIMENSION(nb_class_max)            :: zsigi             ! in-situ   density classes    (99 if you don't want) 
    76       REAL(wp), DIMENSION(nb_class_max)            :: zsigp             ! potential density classes    (99 if you don't want) 
    77       REAL(wp), DIMENSION(nb_class_max)            :: zsal              ! salinity classes   (99 if you don't want) 
    78       REAL(wp), DIMENSION(nb_class_max)            :: ztem              ! temperature classes(99 if you don't want) 
    79       REAL(wp), DIMENSION(nb_class_max)            :: zlay              ! level classes      (99 if you don't want) 
    80       REAL(wp), DIMENSION(nb_type_class,nb_class_max)  :: transport     ! transport output 
    81       REAL(wp)                                         :: slopeSection  ! slope of the section 
     75      REAL(dp), DIMENSION(nb_class_max)            :: zsigi             ! in-situ   density classes    (99 if you don't want) 
     76      REAL(dp), DIMENSION(nb_class_max)            :: zsigp             ! potential density classes    (99 if you don't want) 
     77      REAL(dp), DIMENSION(nb_class_max)            :: zsal              ! salinity classes   (99 if you don't want) 
     78      REAL(dp), DIMENSION(nb_class_max)            :: ztem              ! temperature classes(99 if you don't want) 
     79      REAL(dp), DIMENSION(nb_class_max)            :: zlay              ! level classes      (99 if you don't want) 
     80      REAL(dp), DIMENSION(nb_type_class,nb_class_max)  :: transport     ! transport output 
     81      REAL(dp)                                         :: slopeSection  ! slope of the section 
    8282      INTEGER                                          :: nb_point      ! number of points in the section 
    8383      TYPE(POINT_SECTION),DIMENSION(nb_point_max)      :: listPoint     ! list of points in the sections 
     
    8686   TYPE(SECTION),DIMENSION(nb_sec_max) :: secs ! Array of sections 
    8787  
    88    REAL(wp), ALLOCATABLE, DIMENSION(:,:,:,:) ::  transports_3d  
    89    REAL(wp), ALLOCATABLE, DIMENSION(:,:,:)   ::  transports_2d   
     88   REAL(dp), ALLOCATABLE, DIMENSION(:,:,:,:) ::  transports_3d  
     89   REAL(dp), ALLOCATABLE, DIMENSION(:,:,:)   ::  transports_2d   
    9090 
    9191 
     
    202202     INTEGER              , DIMENSION(1)    ::   ish     ! work array for mpp_sum 
    203203     INTEGER              , DIMENSION(3)    ::   ish2    !   " 
    204      REAL(wp), ALLOCATABLE, DIMENSION(:)    ::   zwork   !   "   
    205      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:)::   zsum    !   " 
     204     REAL(dp), ALLOCATABLE, DIMENSION(:)    ::   zwork   !   "   
     205     REAL(dp), ALLOCATABLE, DIMENSION(:,:,:)::   zsum    !   " 
    206206     !!---------------------------------------------------------------------     
    207207     ! 
     
    587587     ! 
    588588     INTEGER ::   jk, jseg, jclass,jl, isgnu, isgnv    ! loop on level/segment/classes/ice categories 
    589      REAL(wp)::   zumid, zvmid, zumid_ice, zvmid_ice   ! U/V ocean & ice velocity on a cell segment  
    590      REAL(wp)::   zTnorm                               ! transport of velocity through one cell's sides  
    591      REAL(wp)::   ztn, zsn, zrhoi, zrhop, zsshn, zdep  ! temperature/salinity/potential density/ssh/depth at u/v point 
     589     REAL(dp)::   zumid, zvmid, zumid_ice, zvmid_ice   ! U/V ocean & ice velocity on a cell segment  
     590     REAL(dp)::   zTnorm                               ! transport of velocity through one cell's sides  
     591     REAL(dp)::   ztn, zsn, zrhoi, zrhop, zsshn, zdep  ! temperature/salinity/potential density/ssh/depth at u/v point 
    592592     TYPE(POINT_SECTION) ::   k 
    593593      !!-------------------------------------------------------- 
     
    680680                  zsn   = interp(Kmm,k%I,k%J,jk,'V',ts(:,:,:,jp_sal,Kmm) )  
    681681                  zrhop = interp(Kmm,k%I,k%J,jk,'V',rhop)  
    682                   zrhoi = interp(Kmm,k%I,k%J,jk,'V',CASTDP(rhd*rho0+rho0))  
     682                  zrhoi = interp(Kmm,k%I,k%J,jk,'V',rhd*rho0+rho0)  
    683683                  zsshn =  0.5*( ssh(k%I,k%J,Kmm) + ssh(k%I,k%J+1,Kmm)    ) * vmask(k%I,k%J,1)  
    684684               CASE(2,3)  
     
    686686                  zsn   = interp(Kmm,k%I,k%J,jk,'U',ts(:,:,:,jp_sal,Kmm) )  
    687687                  zrhop = interp(Kmm,k%I,k%J,jk,'U',rhop)  
    688                   zrhoi = interp(Kmm,k%I,k%J,jk,'U',CASTDP(rhd*rho0+rho0))  
     688                  zrhoi = interp(Kmm,k%I,k%J,jk,'U',rhd*rho0+rho0)  
    689689                  zsshn =  0.5*( ssh(k%I,k%J,Kmm) + ssh(k%I+1,k%J,Kmm)    ) * umask(k%I,k%J,1)   
    690690               END SELECT  
     
    794794     TYPE(POINT_SECTION) :: k  
    795795     INTEGER  :: jk,jseg,jclass                        ! dummy variables for looping on level/segment/classes   
    796      REAL(wp) :: ztn, zsn, zrhoi, zrhop, zsshn, zdep ! temperature/salinity/ssh/potential density /depth at u/v point  
     796     REAL(dp) :: ztn, zsn, zrhoi, zrhop, zsshn, zdep ! temperature/salinity/ssh/potential density /depth at u/v point  
    797797     !!-------------------------------------------------------------  
    798798  
     
    853853                 zsn   = interp(Kmm,k%I,k%J,jk,'V',ts(:,:,:,jp_sal,Kmm) )  
    854854                 zrhop = interp(Kmm,k%I,k%J,jk,'V',rhop)  
    855                  zrhoi = interp(Kmm,k%I,k%J,jk,'V',CASTDP(rhd*rho0+rho0)) 
     855                 zrhoi = interp(Kmm,k%I,k%J,jk,'V',rhd*rho0+rho0) 
    856856 
    857857              CASE(2,3)  
     
    859859                 zsn   = interp(Kmm,k%I,k%J,jk,'U',ts(:,:,:,jp_sal,Kmm) )  
    860860                 zrhop = interp(Kmm,k%I,k%J,jk,'U',rhop)  
    861                  zrhoi = interp(Kmm,k%I,k%J,jk,'U',CASTDP(rhd*rho0+rho0))  
     861                 zrhoi = interp(Kmm,k%I,k%J,jk,'U',rhd*rho0+rho0)  
    862862                 zsshn =  0.5*( ssh(k%I,k%J,Kmm)    + ssh(k%I+1,k%J,Kmm)    ) * umask(k%I,k%J,1)   
    863863              END SELECT  
     
    987987     INTEGER               :: jclass             ! Dummy loop 
    988988     CHARACTER(len=2)      :: classe             ! Classname  
    989      REAL(wp)              :: zbnd1,zbnd2        ! Class bounds 
    990      REAL(wp)              :: zslope             ! section's slope coeff 
     989     REAL(dp)              :: zbnd1,zbnd2        ! Class bounds 
     990     REAL(dp)              :: zslope             ! section's slope coeff 
    991991     ! 
    992      REAL(wp), DIMENSION(nb_type_class)::   zsumclasses   ! 1D workspace  
     992     REAL(dp), DIMENSION(nb_type_class)::   zsumclasses   ! 1D workspace  
    993993     !!-------------------------------------------------------------  
    994994 
     
    11711171  CHARACTER(len=1), INTENT(IN)                 :: cd_point     ! type of point (U, V) 
    11721172  REAL(dp), DIMENSION(jpi,jpj,jpk), INTENT(IN) :: ptab         ! variable to compute at (ki, kj, kk ) 
    1173   REAL(wp)                                     :: interp       ! interpolated variable  
     1173  REAL(dp)                                     :: interp       ! interpolated variable  
    11741174 
    11751175  !*local declations 
    11761176  INTEGER :: ii1, ij1, ii2, ij2                                ! local integer 
    1177   REAL(wp):: ze3t, ze3, zwgt1, zwgt2, zbis, zdepu            ! local real 
    1178   REAL(wp):: zet1, zet2                                        ! weight for interpolation  
    1179   REAL(wp):: zdep1,zdep2                                       ! differences of depth 
    1180   REAL(wp):: zmsk                                              ! mask value 
     1177  REAL(dp):: ze3t, ze3, zwgt1, zwgt2, zbis, zdepu            ! local real 
     1178  REAL(dp):: zet1, zet2                                        ! weight for interpolation  
     1179  REAL(dp):: zdep1,zdep2                                       ! differences of depth 
     1180  REAL(dp):: zmsk                                              ! mask value 
    11811181  !!---------------------------------------------------------------------- 
    11821182 
Note: See TracChangeset for help on using the changeset viewer.