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 14752 – NEMO

Changeset 14752


Ignore:
Timestamp:
2021-04-27T13:31:53+02:00 (3 years ago)
Author:
hadcv
Message:

#2600: QCO-related changes

Location:
NEMO/branches/2021/dev_r14273_HPC-02_Daley_Tiling/src/OCE
Files:
5 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2021/dev_r14273_HPC-02_Daley_Tiling/src/OCE/DOM/domqco.F90

    r14680 r14752  
    123123      CALL dom_qco_r3c( ssh(:,:,Kmm), r3t(:,:,Kmm), r3u(:,:,Kmm), r3v(:,:,Kmm), r3f(:,:) ) 
    124124#endif 
     125      ! dom_qco_r3c defines over [nn_hls, nn_hls-1, nn_hls, nn_hls-1] 
     126      IF( nn_hls == 2 ) CALL lbc_lnk( 'dom_qco_zgr', r3u(:,:,Kbb), 'U', 1._wp, r3v(:,:,Kbb), 'V', 1._wp, & 
     127         &                                           r3u(:,:,Kmm), 'U', 1._wp, r3v(:,:,Kmm), 'V', 1._wp ) 
    125128      ! 
    126129   END SUBROUTINE dom_qco_zgr 
     
    146149      ! 
    147150      ! 
    148       pr3t(:,:) = pssh(:,:) * r1_ht_0(:,:)   !==  ratio at t-point  ==! 
     151      DO_2D_OVR( nn_hls, nn_hls, nn_hls, nn_hls ) 
     152         pr3t(ji,jj) = pssh(ji,jj) * r1_ht_0(ji,jj)   !==  ratio at t-point  ==! 
     153      END_2D 
    149154      ! 
    150155      ! 
     
    154159#if ! defined key_qcoTest_FluxForm 
    155160      !                                ! no 'key_qcoTest_FluxForm' : surface weighted ssh average 
    156          ! [comm_cleanup] ! DO_2D( 0, 0, 0, 0 ) 
    157          DO_2D( nn_hls, nn_hls-1, nn_hls, nn_hls-1 ) 
    158             pr3u(ji,jj) = 0.5_wp * (  e1e2t(ji  ,jj) * pssh(ji  ,jj)  & 
    159                &                    + e1e2t(ji+1,jj) * pssh(ji+1,jj)  ) * r1_hu_0(ji,jj) * r1_e1e2u(ji,jj) 
    160             pr3v(ji,jj) = 0.5_wp * (  e1e2t(ji,jj  ) * pssh(ji,jj  )  & 
    161                &                    + e1e2t(ji,jj+1) * pssh(ji,jj+1)  ) * r1_hv_0(ji,jj) * r1_e1e2v(ji,jj) 
    162          END_2D 
     161      ! [comm_cleanup] ! DO_2D( 0, 0, 0, 0 ) 
     162      DO_2D_OVR( nn_hls, nn_hls-1, nn_hls, nn_hls-1 ) 
     163         pr3u(ji,jj) = 0.5_wp * (  e1e2t(ji  ,jj) * pssh(ji  ,jj)  & 
     164            &                    + e1e2t(ji+1,jj) * pssh(ji+1,jj)  ) * r1_hu_0(ji,jj) * r1_e1e2u(ji,jj) 
     165         pr3v(ji,jj) = 0.5_wp * (  e1e2t(ji,jj  ) * pssh(ji,jj  )  & 
     166            &                    + e1e2t(ji,jj+1) * pssh(ji,jj+1)  ) * r1_hv_0(ji,jj) * r1_e1e2v(ji,jj) 
     167      END_2D 
    163168!!st      ELSE                                         !- Flux Form   (simple averaging) 
    164169#else 
    165          ! [comm_cleanup] ! DO_2D( 0, 0, 0, 0 ) 
    166          DO_2D( nn_hls, nn_hls-1, nn_hls, nn_hls-1 ) 
    167             pr3u(ji,jj) = 0.5_wp * (  pssh(ji,jj) + pssh(ji+1,jj  )  ) * r1_hu_0(ji,jj) 
    168             pr3v(ji,jj) = 0.5_wp * (  pssh(ji,jj) + pssh(ji  ,jj+1)  ) * r1_hv_0(ji,jj) 
    169          END_2D 
     170      ! [comm_cleanup] ! DO_2D( 0, 0, 0, 0 ) 
     171      DO_2D_OVR( nn_hls, nn_hls-1, nn_hls, nn_hls-1 ) 
     172         pr3u(ji,jj) = 0.5_wp * (  pssh(ji,jj) + pssh(ji+1,jj  )  ) * r1_hu_0(ji,jj) 
     173         pr3v(ji,jj) = 0.5_wp * (  pssh(ji,jj) + pssh(ji  ,jj+1)  ) * r1_hv_0(ji,jj) 
     174      END_2D 
    170175!!st      ENDIF 
    171176#endif          
     
    181186         !                                ! no 'key_qcoTest_FluxForm' : surface weighted ssh average 
    182187 
    183             ! [comm_cleanup] ! DO_2D( 0, 0, 0, 0 )                               ! start from 1 since lbc_lnk('F') doesn't update the 1st row/line 
    184             DO_2D( nn_hls, nn_hls-1, nn_hls, nn_hls-1 )                               ! start from 1 since lbc_lnk('F') doesn't update the 1st row/line 
    185                ! round brackets added to fix the order of floating point operations 
    186                ! needed to ensure halo 1 - halo 2 compatibility 
    187                pr3f(ji,jj) = 0.25_wp * ( ( e1e2t(ji  ,jj  ) * pssh(ji  ,jj  )   & 
    188                   &                      + e1e2t(ji+1,jj  ) * pssh(ji+1,jj  )   & 
    189                   &                      )                                      & ! bracket for halo 1 - halo 2 compatibility 
    190                   &                     + ( e1e2t(ji  ,jj+1) * pssh(ji  ,jj+1)  & 
    191                   &                       + e1e2t(ji+1,jj+1) * pssh(ji+1,jj+1)  & 
    192                   &                       )                                     & ! bracket for halo 1 - halo 2 compatibility 
    193                   &                    ) * r1_hf_0(ji,jj) * r1_e1e2f(ji,jj) 
    194             END_2D 
     188      ! [comm_cleanup] ! DO_2D( 0, 0, 0, 0 )                               ! start from 1 since lbc_lnk('F') doesn't update the 1st row/line 
     189      DO_2D_OVR( nn_hls, nn_hls-1, nn_hls, nn_hls-1 )                               ! start from 1 since lbc_lnk('F') doesn't update the 1st row/line 
     190         ! round brackets added to fix the order of floating point operations 
     191         ! needed to ensure halo 1 - halo 2 compatibility 
     192         pr3f(ji,jj) = 0.25_wp * ( ( e1e2t(ji  ,jj  ) * pssh(ji  ,jj  )   & 
     193            &                      + e1e2t(ji+1,jj  ) * pssh(ji+1,jj  )   & 
     194            &                      )                                      & ! bracket for halo 1 - halo 2 compatibility 
     195            &                     + ( e1e2t(ji  ,jj+1) * pssh(ji  ,jj+1)  & 
     196            &                       + e1e2t(ji+1,jj+1) * pssh(ji+1,jj+1)  & 
     197            &                       )                                     & ! bracket for halo 1 - halo 2 compatibility 
     198            &                    ) * r1_hf_0(ji,jj) * r1_e1e2f(ji,jj) 
     199      END_2D 
    195200!!st         ELSE                                      !- Flux Form   (simple averaging) 
    196201#else 
    197             ! [comm_cleanup] ! DO_2D( 0, 0, 0, 0 )                               ! start from 1 since lbc_lnk('F') doesn't update the 1st row/line 
    198             DO_2D( nn_hls, nn_hls-1, nn_hls, nn_hls-1 ) 
    199                ! round brackets added to fix the order of floating point operations 
    200                ! needed to ensure halo 1 - halo 2 compatibility 
    201                pr3f(ji,jj) = 0.25_wp * ( ( pssh(ji,jj  ) + pssh(ji+1,jj  ) ) & 
    202                   &                     + ( pssh(ji,jj+1) + pssh(ji+1,jj+1)  &  
    203                   &                       )                                  & ! bracket for halo 1 - halo 2 compatibility 
    204                   &                    ) * r1_hf_0(ji,jj) 
    205             END_2D 
     202      ! [comm_cleanup] ! DO_2D( 0, 0, 0, 0 )                               ! start from 1 since lbc_lnk('F') doesn't update the 1st row/line 
     203      DO_2D_OVR( nn_hls, nn_hls-1, nn_hls, nn_hls-1 ) 
     204         ! round brackets added to fix the order of floating point operations 
     205         ! needed to ensure halo 1 - halo 2 compatibility 
     206         pr3f(ji,jj) = 0.25_wp * ( ( pssh(ji,jj  ) + pssh(ji+1,jj  ) ) & 
     207            &                     + ( pssh(ji,jj+1) + pssh(ji+1,jj+1)  & 
     208            &                       )                                  & ! bracket for halo 1 - halo 2 compatibility 
     209            &                    ) * r1_hf_0(ji,jj) 
     210      END_2D 
    206211!!st         ENDIF 
    207212#endif 
  • NEMO/branches/2021/dev_r14273_HPC-02_Daley_Tiling/src/OCE/OBS/diaobs.F90

    r14056 r14752  
    9999   CHARACTER(len=8), PUBLIC, DIMENSION(:), ALLOCATABLE ::   cobstypesprof, cobstypessurf   !: Profile & surface obs types 
    100100 
     101#  include "domzgr_substitute.h90" 
    101102   !!---------------------------------------------------------------------- 
    102103   !! NEMO/OCE 4.0 , NEMO Consortium (2018) 
     
    623624      INTEGER :: jtype             ! Data loop variable 
    624625      INTEGER :: jvar              ! Variable number 
    625       INTEGER :: ji, jj            ! Loop counters 
     626      INTEGER :: ji, jj, jk        ! Loop counters 
    626627      REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE :: & 
    627628         & zprofvar                ! Model values for variables in a prof ob 
     
    634635         & zglam,    &             ! Model longitudes for prof variables 
    635636         & zgphi                   ! Model latitudes for prof variables 
     637      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: zdept, zdepw 
    636638 
    637639      !----------------------------------------------------------------------- 
     
    650652 
    651653      IF ( nproftypes > 0 ) THEN 
     654 
     655         ALLOCATE( zdept(jpi,jpj,jpk), zdepw(jpi,jpj,jpk) ) 
     656         DO jk = 1, jpk 
     657            zdept(:,:,jk) = gdept(:,:,jk,Kmm) 
     658            zdepw(:,:,jk) = gdepw(:,:,jk,Kmm) 
     659         END DO 
    652660 
    653661         DO jtype = 1, nproftypes 
     
    687695                  &               nit000, idaystp, jvar,                   & 
    688696                  &               zprofvar(:,:,:,jvar),                    & 
    689                   &               gdept(:,:,:,Kmm), gdepw(:,:,:,Kmm),      &  
     697                  &               zdept(:,:,:), zdepw(:,:,:),      & 
    690698                  &               zprofmask(:,:,:,jvar),                   & 
    691699                  &               zglam(:,:,jvar), zgphi(:,:,jvar),        & 
     
    697705 
    698706         END DO 
     707 
     708         DEALLOCATE( zdept, zdepw ) 
    699709 
    700710      ENDIF 
  • NEMO/branches/2021/dev_r14273_HPC-02_Daley_Tiling/src/OCE/OBS/obs_prep.F90

    r14574 r14752  
    3333   PUBLIC   calc_month_len   ! Calculate the number of days in the months of a year 
    3434 
     35#  include "domzgr_substitute.h90" 
    3536   !!---------------------------------------------------------------------- 
    3637   !! NEMO/OCE 4.0 , NEMO Consortium (2018) 
     
    10741075         & gdepw_1d,      & 
    10751076         & gdepw_0,       &                        
    1076          & gdepw,         & 
     1077         & gdepw, r3t,    & 
    10771078         & gdept,         & 
    10781079         & ln_zco,        & 
     
    11281129         & zglam, &           ! Model longitude at grid points 
    11291130         & zgphi              ! Model latitude at grid points 
     1131      REAL(wp), DIMENSION(jpi,jpj,jpk) :: zdepw 
    11301132      INTEGER, DIMENSION(2,2,kprofno) :: & 
    11311133         & igrdi, &           ! Grid i,j 
     
    11861188      CALL obs_int_comm_2d( 2, 2, kprofno, kpi, kpj, igrdi, igrdj, plam, zglam ) 
    11871189      CALL obs_int_comm_2d( 2, 2, kprofno, kpi, kpj, igrdi, igrdj, pphi, zgphi ) 
    1188       CALL obs_int_comm_3d( 2, 2, kprofno, kpi, kpj, kpk, igrdi, igrdj, gdepw(:,:,:,Kmm), & 
    1189         &                     zgdepw ) 
     1190      DO jk = 1, jpk 
     1191         zdepw(:,:,jk) = gdepw(:,:,jk,Kmm) 
     1192      END DO 
     1193      CALL obs_int_comm_3d( 2, 2, kprofno, kpi, kpj, kpk, igrdi, igrdj, zdepw(:,:,:), zgdepw ) 
    11901194 
    11911195      DO jobs = 1, kprofno 
  • NEMO/branches/2021/dev_r14273_HPC-02_Daley_Tiling/src/OCE/TRA/traatf.F90

    r14712 r14752  
    5353 
    5454   PUBLIC   tra_atf       ! routine called by step.F90 
     55 
     56#if defined key_qco   ||   defined key_linssh 
     57   !!---------------------------------------------------------------------- 
     58   !!   'key_qco'                        Quasi-Eulerian vertical coordinate 
     59   !!       OR         EMPTY MODULE 
     60   !!   'key_linssh'                        Fix in time vertical coordinate 
     61   !!---------------------------------------------------------------------- 
     62CONTAINS 
     63 
     64   SUBROUTINE tra_atf( kt, Kbb, Kmm, Kaa, pts ) 
     65      INTEGER                                  , INTENT(in   ) :: kt             ! ocean time-step index 
     66      INTEGER                                  , INTENT(in   ) :: Kbb, Kmm, Kaa  ! time level indices 
     67      REAL(wp), DIMENSION(jpi,jpj,jpk,jpts,jpt), INTENT(inout) :: pts            ! active tracers 
     68 
     69      WRITE(*,*) 'tra_atf: You should not have seen this print! error?', kt 
     70   END SUBROUTINE tra_atf 
     71 
     72#else 
     73 
    5574   PUBLIC   tra_atf_fix   ! to be used in trcnxt 
    5675   PUBLIC   tra_atf_vvl   ! to be used in trcnxt 
     
    384403   END SUBROUTINE tra_atf_vvl 
    385404 
     405#endif 
     406 
    386407   !!====================================================================== 
    387408END MODULE traatf 
  • NEMO/branches/2021/dev_r14273_HPC-02_Daley_Tiling/src/OCE/TRA/tradmp.F90

    r14072 r14752  
    5353   !! * Substitutions 
    5454#  include "do_loop_substitute.h90" 
     55#  include "domzgr_substitute.h90" 
    5556   !!---------------------------------------------------------------------- 
    5657   !! NEMO/OCE 4.0 , NEMO Consortium (2018) 
Note: See TracChangeset for help on using the changeset viewer.