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/traatf.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/traatf.F90

    r14644 r15540  
    9393      !! 
    9494      INTEGER  ::   ji, jj, jk, jn   ! dummy loop indices 
    95       REAL(wp) ::   zfact            ! local scalars 
    96       REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) ::   ztrdt, ztrds 
     95      REAL(dp) ::   zfact            ! local scalars 
     96      REAL(dp), ALLOCATABLE, DIMENSION(:,:,:) ::   ztrdt, ztrds 
    9797      !!---------------------------------------------------------------------- 
    9898      ! 
     
    154154         ! 
    155155         IF( ln_linssh ) THEN   ;   CALL tra_atf_fix( kt, Kbb, Kmm, Kaa, nit000,        'TRA', pts, jpts )  ! linear free surface  
    156          ELSE                   ;   CALL tra_atf_vvl( kt, Kbb, Kmm, Kaa, nit000, CASTWP(rn_Dt), 'TRA', pts, sbc_tsc, sbc_tsc_b, jpts )  ! non-linear free surface 
     156         ELSE                   ;   CALL tra_atf_vvl( kt, Kbb, Kmm, Kaa, nit000, rn_Dt, 'TRA', pts, sbc_tsc, sbc_tsc_b, jpts )  ! non-linear free surface 
    157157         ENDIF 
    158158         ! 
     
    172172      ! 
    173173      !                        ! control print 
    174       IF(sn_cfctl%l_prtctl)   CALL prt_ctl( tab3d_1=CASTWP(pts(:,:,:,jp_tem,Kmm)), clinfo1=' nxt  - Tn: ', mask1=tmask,   & 
    175          &                                  tab3d_2=CASTWP(pts(:,:,:,jp_sal,Kmm)), clinfo2=       ' Sn: ', mask2=tmask ) 
     174      IF(sn_cfctl%l_prtctl)   CALL prt_ctl( tab3d_1=pts(:,:,:,jp_tem,Kmm), clinfo1=' nxt  - Tn: ', mask1=tmask,   & 
     175         &                                  tab3d_2=pts(:,:,:,jp_sal,Kmm), clinfo2=       ' Sn: ', mask2=tmask ) 
    176176      ! 
    177177      IF( ln_timing )   CALL timing_stop('tra_atf') 
     
    198198      ! 
    199199      INTEGER  ::   ji, jj, jk, jn   ! dummy loop indices 
    200       REAL(wp) ::   ztn, ztd         ! local scalars 
     200      REAL(dp) ::   ztn, ztd         ! local scalars 
    201201      !!---------------------------------------------------------------------- 
    202202      ! 
     
    236236      INTEGER                                  , INTENT(in   ) ::  Kbb, Kmm, Kaa ! time level indices 
    237237      INTEGER                                  , INTENT(in   ) ::  kit000    ! first time step index 
    238       REAL(wp)                                 , INTENT(in   ) ::  p2dt      ! time-step 
     238      REAL(dp)                                 , INTENT(in   ) ::  p2dt      ! time-step 
    239239      CHARACTER(len=3)                         , INTENT(in   ) ::  cdtype    ! =TRA or TRC (tracer indicator) 
    240240      INTEGER                                  , INTENT(in   ) ::  kjpt      ! number of tracers 
    241241      REAL(dp), DIMENSION(jpi,jpj,jpk,kjpt,jpt), INTENT(inout) ::  pt        ! tracer fields 
    242242      REAL(wp), DIMENSION(jpi,jpj    ,kjpt)    , INTENT(in   ) ::  psbc_tc   ! surface tracer content 
    243       REAL(wp), DIMENSION(jpi,jpj    ,kjpt)    , INTENT(in   ) ::  psbc_tc_b ! before surface tracer content 
     243      REAL(dp), DIMENSION(jpi,jpj    ,kjpt)    , INTENT(in   ) ::  psbc_tc_b ! before surface tracer content 
    244244      ! 
    245245      LOGICAL  ::   ll_traqsr, ll_rnf, ll_isf   ! local logical 
     
    247247      REAL(dp) ::   zfact, zfact1, ztc_a , ztc_n , ztc_b , ztc_f , ztc_d    ! local scalar 
    248248      REAL(dp) ::   zfact2, ze3t_b, ze3t_n, ze3t_a, ze3t_f, ze3t_d, zscale  !   -      - 
    249       REAL(wp), ALLOCATABLE, DIMENSION(:,:,:,:) ::   ztrd_atf 
     249      REAL(dp), ALLOCATABLE, DIMENSION(:,:,:,:) ::   ztrd_atf 
    250250      !!---------------------------------------------------------------------- 
    251251      ! 
Note: See TracChangeset for help on using the changeset viewer.