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/TRA/traqsr.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/TRA/traqsr.F90

    r14986 r15540  
    6161   ! 
    6262   INTEGER  ::   nqsr    ! user choice of the type of light penetration 
    63    REAL(wp) ::   xsi0r   ! inverse of rn_si0 
    64    REAL(wp) ::   xsi1r   ! inverse of rn_si1 
     63   REAL(dp) ::   xsi0r   ! inverse of rn_si0 
     64   REAL(dp) ::   xsi1r   ! inverse of rn_si1 
    6565   ! 
    66    REAL(wp) , PUBLIC, DIMENSION(3,61)   ::   rkrgb    ! tabulated attenuation coefficients for RGB absorption 
     66   REAL(dp) , PUBLIC, DIMENSION(3,61)   ::   rkrgb    ! tabulated attenuation coefficients for RGB absorption 
    6767   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_chl   ! structure of input Chl (file informations, fields read) 
    6868 
     
    112112      REAL(wp) ::   zchl, zcoef, z1_2        ! local scalars 
    113113      REAL(wp) ::   zc0 , zc1 , zc2 , zc3    !    -         - 
    114       REAL(wp) ::   zzc0, zzc1, zzc2, zzc3   !    -         - 
     114      REAL(dp) ::   zzc0, zzc1, zzc2, zzc3   !    -         - 
    115115      REAL(wp) ::   zz0 , zz1 , ze3t, zlui   !    -         - 
    116116      REAL(wp) ::   zCb, zCmax, zpsi, zpsimax, zrdpsi, zCze 
    117       REAL(wp) ::   zlogc, zlogze, zlogCtot, zlogCze 
     117      REAL(wp)  :: zlogc 
     118      REAL(dp)  :: zlogze, zlogCtot, zlogCze 
    118119      REAL(wp), ALLOCATABLE, DIMENSION(:,:)   :: ze0, ze1, ze2, ze3 
    119       REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) :: ztrdt, zetot, ztmp3d 
     120      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:)  :: ztmp3d 
     121      REAL(dp), ALLOCATABLE, DIMENSION(:,:,:)  :: ztrdt, zetot 
    120122      !!---------------------------------------------------------------------- 
    121123      ! 
     
    317319      ENDIF 
    318320      !                       ! print mean trends (used for debugging) 
    319       IF(sn_cfctl%l_prtctl)   CALL prt_ctl( tab3d_1=CASTWP(pts(:,:,:,jp_tem,Krhs)), clinfo1=' qsr  - Ta: ', mask1=tmask, clinfo3='tra-ta' ) 
     321      IF(sn_cfctl%l_prtctl)   CALL prt_ctl( tab3d_1=pts(:,:,:,jp_tem,Krhs), clinfo1=' qsr  - Ta: ', mask1=tmask, clinfo3='tra-ta' ) 
    320322      ! 
    321323      IF( ln_timing )   CALL timing_stop('tra_qsr') 
     
    343345      INTEGER  ::   ji, jj, jk                  ! dummy loop indices 
    344346      INTEGER  ::   ios, irgb, ierror, ioptio   ! local integer 
    345       REAL(wp) ::   zz0, zc0 , zc1, zcoef      ! local scalars 
    346       REAL(wp) ::   zz1, zc2 , zc3, zchl       !   -      - 
     347      REAL(dp) ::   zz0, zc0 , zc1, zcoef      ! local scalars 
     348      REAL(dp) ::   zz1, zc2 , zc3, zchl       !   -      - 
    347349      ! 
    348350      CHARACTER(len=100) ::   cn_dir   ! Root directory for location of ssr files 
     
    424426         IF(lwp)  WRITE(numout,*) '   ==>>>   2 bands light penetration' 
    425427         ! 
    426          nksr = trc_oce_ext_lev( rn_si1, 100._wp )    ! level of light extinction 
     428         nksr =trc_oce_ext_lev( CASTDP(rn_si1), 100._wp )    ! level of light extinction 
    427429         IF(lwp) WRITE(numout,*) '        level of light extinction = ', nksr, ' ref depth = ', gdepw_1d(nksr+1), ' m' 
    428430         ! 
Note: See TracChangeset for help on using the changeset viewer.