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 13942 for NEMO/branches/2020/dev_r13312_AGRIF-03-04_jchanut_vinterp_tstep/tests/CANAL/MY_SRC – NEMO

Ignore:
Timestamp:
2020-12-01T17:14:18+01:00 (4 years ago)
Author:
jchanut
Message:

Merged with trunk @13787

Location:
NEMO/branches/2020/dev_r13312_AGRIF-03-04_jchanut_vinterp_tstep
Files:
1 deleted
7 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2020/dev_r13312_AGRIF-03-04_jchanut_vinterp_tstep

    • Property svn:externals
      •  

        old new  
        88 
        99# SETTE 
        10 ^/utils/CI/sette@13292        sette 
         10^/utils/CI/sette@13559        sette 
  • NEMO/branches/2020/dev_r13312_AGRIF-03-04_jchanut_vinterp_tstep/tests/CANAL/MY_SRC/domvvl.F90

    r13295 r13942  
    99   !!            3.6  !  2014-11  (P. Mathiot) add ice shelf capability 
    1010   !!            4.1  !  2019-08  (A. Coward, D. Storkey) rename dom_vvl_sf_swp -> dom_vvl_sf_update for new timestepping 
     11   !!            4.x  ! 2020-02  (G. Madec, S. Techene) introduce ssh to h0 ratio 
    1112   !!---------------------------------------------------------------------- 
    1213 
    13    !!---------------------------------------------------------------------- 
    14    !!   dom_vvl_init     : define initial vertical scale factors, depths and column thickness 
    15    !!   dom_vvl_sf_nxt   : Compute next vertical scale factors 
    16    !!   dom_vvl_sf_update   : Swap vertical scale factors and update the vertical grid 
    17    !!   dom_vvl_interpol : Interpolate vertical scale factors from one grid point to another 
    18    !!   dom_vvl_rst      : read/write restart file 
    19    !!   dom_vvl_ctl      : Check the vvl options 
    20    !!---------------------------------------------------------------------- 
    2114   USE oce             ! ocean dynamics and tracers 
    2215   USE phycst          ! physical constant 
     
    3629   PRIVATE 
    3730 
    38    PUBLIC  dom_vvl_init       ! called by domain.F90 
    39    PUBLIC  dom_vvl_zgr        ! called by isfcpl.F90 
    40    PUBLIC  dom_vvl_sf_nxt     ! called by step.F90 
    41    PUBLIC  dom_vvl_sf_update  ! called by step.F90 
    42    PUBLIC  dom_vvl_interpol   ! called by dynnxt.F90 
    43  
    4431   !                                                      !!* Namelist nam_vvl 
    4532   LOGICAL , PUBLIC :: ln_vvl_zstar           = .FALSE.    ! zstar  vertical coordinate 
     
    6350   REAL(wp)        , ALLOCATABLE, SAVE, DIMENSION(:,:)   :: frq_rst_hdv                 ! retoring period for low freq. divergence 
    6451 
     52#if defined key_qco 
     53   !!---------------------------------------------------------------------- 
     54   !!   'key_qco'      EMPTY MODULE      Quasi-Eulerian vertical coordonate 
     55   !!---------------------------------------------------------------------- 
     56#else 
     57   !!---------------------------------------------------------------------- 
     58   !!   Default key      Old management of time varying vertical coordinate 
     59   !!---------------------------------------------------------------------- 
     60    
     61   !!---------------------------------------------------------------------- 
     62   !!   dom_vvl_init     : define initial vertical scale factors, depths and column thickness 
     63   !!   dom_vvl_sf_nxt   : Compute next vertical scale factors 
     64   !!   dom_vvl_sf_update   : Swap vertical scale factors and update the vertical grid 
     65   !!   dom_vvl_interpol : Interpolate vertical scale factors from one grid point to another 
     66   !!   dom_vvl_rst      : read/write restart file 
     67   !!   dom_vvl_ctl      : Check the vvl options 
     68   !!---------------------------------------------------------------------- 
     69 
     70   PUBLIC  dom_vvl_init       ! called by domain.F90 
     71   PUBLIC  dom_vvl_zgr        ! called by isfcpl.F90 
     72   PUBLIC  dom_vvl_sf_nxt     ! called by step.F90 
     73   PUBLIC  dom_vvl_sf_update  ! called by step.F90 
     74   PUBLIC  dom_vvl_interpol   ! called by dynnxt.F90 
     75    
    6576   !! * Substitutions 
    6677#  include "do_loop_substitute.h90" 
     
    135146      ! 
    136147   END SUBROUTINE dom_vvl_init 
    137    ! 
     148 
     149 
    138150   SUBROUTINE dom_vvl_zgr(Kbb, Kmm, Kaa) 
    139151      !!---------------------------------------------------------------------- 
     
    261273            IF( cn_cfg == "orca" .OR. cn_cfg == "ORCA" ) THEN 
    262274               IF( nn_cfg == 3 ) THEN   ! ORCA2: Suppress ztilde in the Foxe Basin for ORCA2 
    263                   ii0 = 103   ;   ii1 = 111        
    264                   ij0 = 128   ;   ij1 = 135   ;    
     275                  ii0 = 103 + nn_hls - 1   ;   ii1 = 111 + nn_hls - 1       
     276                  ij0 = 128 + nn_hls       ;   ij1 = 135 + nn_hls 
    265277                  frq_rst_e3t( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) =  0.0_wp 
    266278                  frq_rst_hdv( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) =  1.e0_wp / rn_Dt 
     
    322334      LOGICAL                ::   ll_do_bclinic         ! local logical 
    323335      REAL(wp), DIMENSION(jpi,jpj)     ::   zht, z_scale, zwu, zwv, zhdiv 
    324       REAL(wp), DIMENSION(jpi,jpj,jpk) ::   ze3t 
     336      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::   ze3t 
     337      LOGICAL , DIMENSION(:,:,:), ALLOCATABLE ::   llmsk 
    325338      !!---------------------------------------------------------------------- 
    326339      ! 
     
    435448         ! Maximum deformation control 
    436449         ! ~~~~~~~~~~~~~~~~~~~~~~~~~~~ 
    437          ze3t(:,:,jpk) = 0._wp 
    438          DO jk = 1, jpkm1 
    439             ze3t(:,:,jk) = tilde_e3t_a(:,:,jk) / e3t_0(:,:,jk) * tmask(:,:,jk) * tmask_i(:,:) 
    440          END DO 
    441          z_tmax = MAXVAL( ze3t(:,:,:) ) 
    442          CALL mpp_max( 'domvvl', z_tmax )                 ! max over the global domain 
    443          z_tmin = MINVAL( ze3t(:,:,:) ) 
    444          CALL mpp_min( 'domvvl', z_tmin )                 ! min over the global domain 
     450         ALLOCATE( ze3t(jpi,jpj,jpk), llmsk(jpi,jpj,jpk) ) 
     451         DO_3D( 0, 0, 0, 0, 1, jpkm1 ) 
     452            ze3t(ji,jj,jk) = tilde_e3t_a(ji,jj,jk) / e3t_0(ji,jj,jk) * tmask(ji,jj,jk) * tmask_i(ji,jj) 
     453         END_3D 
     454         ! 
     455         llmsk(   1:Nis1,:,:) = .FALSE.   ! exclude halos from the checked region 
     456         llmsk(Nie1: jpi,:,:) = .FALSE. 
     457         llmsk(:,   1:Njs1,:) = .FALSE. 
     458         llmsk(:,Nje1: jpj,:) = .FALSE. 
     459         ! 
     460         llmsk(Nis0:Nie0,Njs0:Nje0,:) = tmask(Nis0:Nie0,Njs0:Nje0,:) == 1._wp                  ! define only the inner domain 
     461         z_tmax = MAXVAL( ze3t(:,:,:), mask = llmsk )   ;   CALL mpp_max( 'domvvl', z_tmax )   ! max over the global domain 
     462         z_tmin = MINVAL( ze3t(:,:,:), mask = llmsk )   ;   CALL mpp_min( 'domvvl', z_tmin )   ! min over the global domain 
    445463         ! - ML - test: for the moment, stop simulation for too large e3_t variations 
    446464         IF( ( z_tmax >  rn_zdef_max ) .OR. ( z_tmin < - rn_zdef_max ) ) THEN 
    447             IF( lk_mpp ) THEN 
    448                CALL mpp_maxloc( 'domvvl', ze3t, tmask, z_tmax, ijk_max ) 
    449                CALL mpp_minloc( 'domvvl', ze3t, tmask, z_tmin, ijk_min ) 
    450             ELSE 
    451                ijk_max = MAXLOC( ze3t(:,:,:) ) 
    452                ijk_max(1) = mig0_oldcmp(ijk_max(1)) 
    453                ijk_max(2) = mjg0_oldcmp(ijk_max(2)) 
    454                ijk_min = MINLOC( ze3t(:,:,:) ) 
    455                ijk_min(1) = mig0_oldcmp(ijk_min(1)) 
    456                ijk_min(2) = mjg0_oldcmp(ijk_min(2)) 
    457             ENDIF 
     465            CALL mpp_maxloc( 'domvvl', ze3t, llmsk, z_tmax, ijk_max ) 
     466            CALL mpp_minloc( 'domvvl', ze3t, llmsk, z_tmin, ijk_min ) 
    458467            IF (lwp) THEN 
    459468               WRITE(numout, *) 'MAX( tilde_e3t_a(:,:,:) / e3t_0(:,:,:) ) =', z_tmax 
     
    464473            ENDIF 
    465474         ENDIF 
     475         DEALLOCATE( ze3t, llmsk ) 
    466476         ! - ML - end test 
    467477         ! - ML - Imposing these limits will cause a baroclinicity error which is corrected for below 
     
    10301040   END SUBROUTINE dom_vvl_ctl 
    10311041 
     1042#endif 
     1043 
    10321044   !!====================================================================== 
    10331045END MODULE domvvl 
  • NEMO/branches/2020/dev_r13312_AGRIF-03-04_jchanut_vinterp_tstep/tests/CANAL/MY_SRC/stpctl.F90

    r13216 r13942  
    4949      !! 
    5050      !! ** Method  : - Save the time step in numstp 
    51       !!              - Print it each 50 time steps 
    5251      !!              - Stop the run IF problem encountered by setting nstop > 0 
    5352      !!                Problems checked: |ssh| maximum larger than 10 m 
     
    6867      REAL(wp)                        ::   zzz                                   ! local real  
    6968      REAL(wp), DIMENSION(9)          ::   zmax, zmaxlocal 
    70       LOGICAL                         ::   ll_wrtstp, ll_colruns, ll_wrtruns 
     69      LOGICAL                         ::   ll_wrtstp, ll_colruns, ll_wrtruns, ll_0oce 
    7170      LOGICAL, DIMENSION(jpi,jpj,jpk) ::   llmsk 
    7271      CHARACTER(len=20)               ::   clname 
     
    119118      !                                   !==            test of local extrema           ==! 
    120119      !                                   !==  done by all processes at every time step  ==! 
    121       llmsk(:,:,1) = ssmask(:,:) == 1._wp 
     120      ! 
     121      llmsk(   1:Nis1,:,:) = .FALSE.                                              ! exclude halos from the checked region 
     122      llmsk(Nie1: jpi,:,:) = .FALSE. 
     123      llmsk(:,   1:Njs1,:) = .FALSE. 
     124      llmsk(:,Nje1: jpj,:) = .FALSE. 
     125      ! 
     126      llmsk(Nis0:Nie0,Njs0:Nje0,1) = ssmask(Nis0:Nie0,Njs0:Nje0) == 1._wp         ! define only the inner domain 
     127      ! 
     128      ll_0oce = .NOT. ANY( llmsk(:,:,1) )                                         ! no ocean point in the inner domain? 
     129      ! 
    122130      IF( ll_wd ) THEN 
    123131         zmax(1) = MAXVAL( ABS( ssh(:,:,Kmm) + ssh_ref ), mask = llmsk(:,:,1) )   ! ssh max 
     
    125133         zmax(1) = MAXVAL( ABS( ssh(:,:,Kmm)           ), mask = llmsk(:,:,1) )   ! ssh max 
    126134      ENDIF 
    127       llmsk(:,:,:) = umask(:,:,:) == 1._wp 
     135      llmsk(Nis0:Nie0,Njs0:Nje0,:) = umask(Nis0:Nie0,Njs0:Nje0,:) == 1._wp        ! define only the inner domain 
    128136      zmax(2) = MAXVAL(  ABS( uu(:,:,:,Kmm) ), mask = llmsk )                     ! velocity max (zonal only) 
    129       llmsk(:,:,:) = tmask(:,:,:) == 1._wp 
     137      llmsk(Nis0:Nie0,Njs0:Nje0,:) = tmask(Nis0:Nie0,Njs0:Nje0,:) == 1._wp        ! define only the inner domain 
    130138      zmax(3) = MAXVAL( -ts(:,:,:,jp_sal,Kmm), mask = llmsk )                     ! minus salinity max 
    131139      zmax(4) = MAXVAL(  ts(:,:,:,jp_sal,Kmm), mask = llmsk )                     !       salinity max 
     
    143151         zmax(5:8) = 0._wp 
    144152      ENDIF 
    145       zmax(9) = REAL( nstop, wp )                                              ! stop indicator 
     153      zmax(9) = REAL( nstop, wp )                                                 ! stop indicator 
     154      ! 
    146155      !                                   !==               get global extrema             ==! 
    147156      !                                   !==  done by all processes if writting run.stat  ==! 
    148157      IF( ll_colruns ) THEN 
    149158         zmaxlocal(:) = zmax(:) 
    150          CALL mpp_max( "stpctl", zmax )          ! max over the global domain 
     159         CALL mpp_max( "stpctl", zmax )          ! max over the global domain: ok even of ll_0oce = .true.  
    151160         nstop = NINT( zmax(9) )                 ! update nstop indicator (now sheared among all local domains) 
    152       ENDIF 
     161      ELSE 
     162         ! if no ocean point: MAXVAL returns -HUGE => we must overwrite this value to avoid error handling bellow. 
     163         IF( ll_0oce )   zmax(1:4) = (/ 0._wp, 0._wp, -1._wp, 1._wp /)   ! default "valid" values... 
     164      ENDIF 
     165      ! 
     166      zmax(3) = -zmax(3)                         ! move back from max(-zz) to min(zz) : easier to manage!  
     167      zmax(5) = -zmax(5)                         ! move back from max(-zz) to min(zz) : easier to manage! 
     168      IF( ll_colruns ) THEN 
     169         zmaxlocal(3) = -zmaxlocal(3)            ! move back from max(-zz) to min(zz) : easier to manage!  
     170         zmaxlocal(5) = -zmaxlocal(5)            ! move back from max(-zz) to min(zz) : easier to manage! 
     171      ENDIF 
     172      ! 
    153173      !                                   !==              write "run.stat" files              ==! 
    154174      !                                   !==  done only by 1st subdomain at writting timestep  ==! 
    155175      IF( ll_wrtruns ) THEN 
    156          WRITE(numrun,9500) kt, zmax(1), zmax(2), -zmax(3), zmax(4) 
    157          istatus = NF90_PUT_VAR( nrunid, nvarid(1), (/ zmax(1)/), (/kt/), (/1/) ) 
    158          istatus = NF90_PUT_VAR( nrunid, nvarid(2), (/ zmax(2)/), (/kt/), (/1/) ) 
    159          istatus = NF90_PUT_VAR( nrunid, nvarid(3), (/-zmax(3)/), (/kt/), (/1/) ) 
    160          istatus = NF90_PUT_VAR( nrunid, nvarid(4), (/ zmax(4)/), (/kt/), (/1/) ) 
    161          istatus = NF90_PUT_VAR( nrunid, nvarid(5), (/-zmax(5)/), (/kt/), (/1/) ) 
    162          istatus = NF90_PUT_VAR( nrunid, nvarid(6), (/ zmax(6)/), (/kt/), (/1/) ) 
    163          IF( ln_zad_Aimp ) THEN 
    164             istatus = NF90_PUT_VAR( nrunid, nvarid(7), (/ zmax(7)/), (/kt/), (/1/) ) 
    165             istatus = NF90_PUT_VAR( nrunid, nvarid(8), (/ zmax(8)/), (/kt/), (/1/) ) 
    166          ENDIF 
     176         WRITE(numrun,9500) kt, zmax(1), zmax(2), zmax(3), zmax(4) 
     177         DO ji = 1, 6 + 2 * COUNT( (/ln_zad_Aimp/) ) 
     178            istatus = NF90_PUT_VAR( nrunid, nvarid(ji), (/zmax(ji)/), (/kt/), (/1/) ) 
     179         END DO 
    167180         IF( kt == nitend )   istatus = NF90_CLOSE(nrunid) 
    168181      END IF 
     
    170183      !                                   !==  done by all processes at every time step  ==! 
    171184      ! 
    172       IF(   zmax(1) >   20._wp .OR.   &                   ! too large sea surface height ( > 20 m ) 
    173          &  zmax(2) >   10._wp .OR.   &                   ! too large velocity ( > 10 m/s) 
    174 !!$         &  zmax(3) >=   0._wp .OR.   &                   ! negative or zero sea surface salinity 
    175 !!$         &  zmax(4) >= 100._wp .OR.   &                   ! too large sea surface salinity ( > 100 ) 
    176 !!$         &  zmax(4) <    0._wp .OR.   &                   ! too large sea surface salinity (keep this line for sea-ice) 
    177          &  ISNAN( zmax(1) + zmax(2) + zmax(3) ) .OR.   &               ! NaN encounter in the tests 
    178          &  ABS(   zmax(1) + zmax(2) + zmax(3) ) > HUGE(1._wp) ) THEN   ! Infinity encounter in the tests 
     185      IF(  zmax(1) >   20._wp .OR.   &                   ! too large sea surface height ( > 20 m ) 
     186         & zmax(2) >   10._wp .OR.   &                   ! too large velocity ( > 10 m/s) 
     187!!$         & zmax(3) <=   0._wp .OR.   &                   ! negative or zero sea surface salinity 
     188!!$         & zmax(4) >= 100._wp .OR.   &                   ! too large sea surface salinity ( > 100 ) 
     189!!$         & zmax(4) <    0._wp .OR.   &                   ! too large sea surface salinity (keep this line for sea-ice) 
     190         & ISNAN( zmax(1) + zmax(2) + zmax(3) ) .OR.   &               ! NaN encounter in the tests 
     191         & ABS(   zmax(1) + zmax(2) + zmax(3) ) > HUGE(1._wp) ) THEN   ! Infinity encounter in the tests 
    179192         ! 
    180193         iloc(:,:) = 0 
     
    183196            IF( lwm .AND. kt /= nitend )   istatus = NF90_CLOSE(nrunid) 
    184197            ! get global loc on the min/max 
    185             CALL mpp_maxloc( 'stpctl', ABS(ssh(:,:,         Kmm)), ssmask(:,:  ), zzz, iloc(1:2,1) )   ! mpp_maxloc ok if mask = F  
    186             CALL mpp_maxloc( 'stpctl', ABS( uu(:,:,:,       Kmm)),  umask(:,:,:), zzz, iloc(1:3,2) ) 
    187             CALL mpp_minloc( 'stpctl',      ts(:,:,:,jp_sal,Kmm) ,  tmask(:,:,:), zzz, iloc(1:3,3) ) 
    188             CALL mpp_maxloc( 'stpctl',      ts(:,:,:,jp_sal,Kmm) ,  tmask(:,:,:), zzz, iloc(1:3,4) ) 
     198            llmsk(Nis0:Nie0,Njs0:Nje0,1) = ssmask(Nis0:Nie0,Njs0:Nje0 ) == 1._wp         ! define only the inner domain 
     199            CALL mpp_maxloc( 'stpctl', ABS(ssh(:,:,         Kmm)), llmsk(:,:,1), zzz, iloc(1:2,1) )   ! mpp_maxloc ok if mask = F  
     200            llmsk(Nis0:Nie0,Njs0:Nje0,:) = umask(Nis0:Nie0,Njs0:Nje0,:) == 1._wp        ! define only the inner domain 
     201            CALL mpp_maxloc( 'stpctl', ABS( uu(:,:,:,       Kmm)), llmsk(:,:,:), zzz, iloc(1:3,2) ) 
     202            llmsk(Nis0:Nie0,Njs0:Nje0,:) = tmask(Nis0:Nie0,Njs0:Nje0,:) == 1._wp        ! define only the inner domain 
     203            CALL mpp_minloc( 'stpctl',      ts(:,:,:,jp_sal,Kmm) , llmsk(:,:,:), zzz, iloc(1:3,3) ) 
     204            CALL mpp_maxloc( 'stpctl',      ts(:,:,:,jp_sal,Kmm) , llmsk(:,:,:), zzz, iloc(1:3,4) ) 
    189205            ! find which subdomain has the max. 
    190206            iareamin(:) = jpnij+1   ;   iareamax(:) = 0   ;   iareasum(:) = 0 
     
    199215         ELSE                    ! find local min and max locations: 
    200216            ! if we are here, this means that the subdomain contains some oce points -> no need to test the mask used in maxloc 
    201             iloc(1:2,1) = MAXLOC( ABS( ssh(:,:,         Kmm)), mask = ssmask(:,:  ) == 1._wp ) + (/ nimpp - 1, njmpp - 1    /) 
    202             iloc(1:3,2) = MAXLOC( ABS(  uu(:,:,:,       Kmm)), mask =  umask(:,:,:) == 1._wp ) + (/ nimpp - 1, njmpp - 1, 0 /) 
    203             iloc(1:3,3) = MINLOC(       ts(:,:,:,jp_sal,Kmm) , mask =  tmask(:,:,:) == 1._wp ) + (/ nimpp - 1, njmpp - 1, 0 /) 
    204             iloc(1:3,4) = MAXLOC(       ts(:,:,:,jp_sal,Kmm) , mask =  tmask(:,:,:) == 1._wp ) + (/ nimpp - 1, njmpp - 1, 0 /) 
     217            llmsk(Nis0:Nie0,Njs0:Nje0,1) = ssmask(Nis0:Nie0,Njs0:Nje0 ) == 1._wp        ! define only the inner domain 
     218            iloc(1:2,1) = MAXLOC( ABS( ssh(:,:,         Kmm)), mask = llmsk(:,:,1) ) 
     219            llmsk(Nis0:Nie0,Njs0:Nje0,:) = umask(Nis0:Nie0,Njs0:Nje0,:) == 1._wp        ! define only the inner domain 
     220            iloc(1:3,2) = MAXLOC( ABS(  uu(:,:,:,       Kmm)), mask = llmsk(:,:,:) ) 
     221            llmsk(Nis0:Nie0,Njs0:Nje0,:) = tmask(Nis0:Nie0,Njs0:Nje0,:) == 1._wp        ! define only the inner domain 
     222            iloc(1:3,3) = MINLOC(       ts(:,:,:,jp_sal,Kmm) , mask = llmsk(:,:,:) ) 
     223            iloc(1:3,4) = MAXLOC(       ts(:,:,:,jp_sal,Kmm) , mask = llmsk(:,:,:) ) 
     224            DO ji = 1, 4   ! local domain indices ==> global domain indices, excluding halos 
     225               iloc(1:2,ji) = (/ mig0(iloc(1,ji)), mjg0(iloc(2,ji)) /) 
     226            END DO 
    205227            iareamin(:) = narea   ;   iareamax(:) = narea   ;   iareasum(:) = 1         ! this is local information 
    206228         ENDIF 
    207229         ! 
    208230         WRITE(ctmp1,*) ' stp_ctl: |ssh| > 20 m  or  |U| > 10 m/s  or  S <= 0  or  S >= 100  or  NaN encounter in the tests' 
    209          CALL wrt_line( ctmp2, kt, '|ssh| max',  zmax(1), iloc(:,1), iareasum(1), iareamin(1), iareamax(1) ) 
    210          CALL wrt_line( ctmp3, kt, '|U|   max',  zmax(2), iloc(:,2), iareasum(2), iareamin(2), iareamax(2) ) 
    211          CALL wrt_line( ctmp4, kt, 'Sal   min', -zmax(3), iloc(:,3), iareasum(3), iareamin(3), iareamax(3) ) 
    212          CALL wrt_line( ctmp5, kt, 'Sal   max',  zmax(4), iloc(:,4), iareasum(4), iareamin(4), iareamax(4) ) 
     231         CALL wrt_line( ctmp2, kt, '|ssh| max', zmax(1), iloc(:,1), iareasum(1), iareamin(1), iareamax(1) ) 
     232         CALL wrt_line( ctmp3, kt, '|U|   max', zmax(2), iloc(:,2), iareasum(2), iareamin(2), iareamax(2) ) 
     233         CALL wrt_line( ctmp4, kt, 'Sal   min', zmax(3), iloc(:,3), iareasum(3), iareamin(3), iareamax(3) ) 
     234         CALL wrt_line( ctmp5, kt, 'Sal   max', zmax(4), iloc(:,4), iareasum(4), iareamin(4), iareamax(4) ) 
    213235         IF( Agrif_Root() ) THEN 
    214236            WRITE(ctmp6,*) '      ===> output of last computed fields in output.abort* files' 
  • NEMO/branches/2020/dev_r13312_AGRIF-03-04_jchanut_vinterp_tstep/tests/CANAL/MY_SRC/usrdef_istate.F90

    r13295 r13942  
    6666      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~~~   ' 
    6767      ! 
    68       IF (ln_sshnoise) CALL RANDOM_NUMBER(zrandom) 
    6968      zjetx = ABS(rn_ujetszx)/2. 
    7069      zjety = ABS(rn_ujetszy)/2. 
    7170      ! 
     71      zf0   = 2._wp * omega * SIN( rad * rn_ppgphi0 ) 
     72      ! 
    7273      SELECT CASE(nn_initcase) 
     74 
     75      CASE(-1)    ! stratif at rest 
     76 
     77         ! sea level: 
     78         pssh(:,:) = 0. 
     79         ! temperature: 
     80         pts(:,:,1,jp_tem) = 25. !!30._wp 
     81         pts(:,:,2:jpk,jp_tem) = 22. !!24._wp 
     82         ! salinity:   
     83         pts(:,:,:,jp_sal) = 35._wp 
     84         ! velocities: 
     85         pu(:,:,:) = 0. 
     86         pv(:,:,:) = 0. 
     87 
    7388      CASE(0)    ! rest 
    7489          
     
    98113            zbeta = 2._wp * omega * COS( rad * rn_ppgphi0 ) / ra 
    99114            WHERE( ABS(gphit) <= zjety ) 
    100                pssh(:,:) = - rn_uzonal / grav * ( ff_t(:,:) * gphit(:,:) * 1.e3 + 0.5 * zbeta * gphit(:,:) * gphit(:,:) * 1.e6 ) 
    101             ELSEWHERE 
    102                pssh(:,:) = - rn_uzonal / grav * ( ff_t(:,:) * SIGN(zjety, gphit(:,:)) * 1.e3   & 
     115               pssh(:,:) = - rn_uzonal / grav * ( zf0 * gphit(:,:) * 1.e3 + 0.5 * zbeta * gphit(:,:) * gphit(:,:) * 1.e6 ) 
     116            ELSEWHERE 
     117               pssh(:,:) = - rn_uzonal / grav * ( zf0 * SIGN(zjety, gphit(:,:)) * 1.e3   & 
    103118                  &                             + 0.5 * zbeta * zjety * zjety * 1.e6 ) 
    104119            END WHERE 
     
    109124         pts(:,:,jpk,jp_sal) = 0. 
    110125         DO jk=1, jpkm1 
    111             pts(:,:,jk,jp_sal) = gphit(:,:) 
     126            WHERE( ABS(gphit) <= zjety ) 
     127!!$            WHERE( ABS(gphit) <= zjety*0.5 .AND. ABS(glamt) <= zjety*0.5 ) ! for a square of salt 
     128               pts(:,:,jk,jp_sal) = 35. 
     129            ELSEWHERE 
     130               pts(:,:,jk,jp_sal) = 30. 
     131            END WHERE                     
    112132         END DO 
    113133         ! velocities: 
     
    134154            WHERE( ABS(gphit) <= zjety ) 
    135155               pssh(:,:) = - SIGN(rn_uzonal, gphit(:,:)) / grav   & 
    136                   &        * ( ff_t(:,:) * gphit(:,:) * 1.e3 + 0.5 * zbeta * gphit(:,:) * gphit(:,:) * 1.e6 ) 
     156                  &        * ( zf0 * gphit(:,:) * 1.e3 + 0.5 * zbeta * gphit(:,:) * gphit(:,:) * 1.e6 ) 
    137157            ELSEWHERE 
    138158               pssh(:,:) = - SIGN(rn_uzonal, gphit(:,:)) / grav   & 
    139                   &        * ( ff_t(:,:) * SIGN(zjety, gphit(:,:)) * 1.e3 + 0.5 * zbeta * zjety * zjety * 1.e6 ) 
     159                  &        * ( zf0 * SIGN(zjety, gphit(:,:)) * 1.e3 + 0.5 * zbeta * zjety * zjety * 1.e6 ) 
    140160            END WHERE 
    141161         END SELECT 
     
    143163         pts(:,:,:,jp_tem) = 10._wp 
    144164         ! salinity:   
    145          pts(:,:,:,jp_sal) = 2. 
    146          DO jk=1, jpkm1 
    147             WHERE( ABS(gphiv) <= zjety ) pts(:,:,jk,jp_sal) = 2. + SIGN(1.,gphiv(:,:)) 
     165         pts(:,:,:,jp_sal) = 30. 
     166         DO jk=1, jpkm1 
     167            WHERE( ABS(gphiv) <= zjety ) pts(:,:,jk,jp_sal) = 30. + SIGN(1.,gphiv(:,:)) 
    148168         END DO 
    149169         ! velocities: 
     
    176196         ! salinity:   
    177197         DO jk=1, jpkm1 
    178             pts(:,:,jk,jp_sal) = gphit(:,:) 
     198            pts(:,:,jk,jp_sal) = pssh(:,:) 
    179199         END DO 
    180200         ! velocities: 
     
    210230         zf0   = 2._wp * omega * SIN( rad * rn_ppgphi0 ) 
    211231         zumax = rn_vtxmax * SIGN(1._wp, zf0) ! Here Anticyclonic: set zumax=-1 for cyclonic 
    212          zlambda = SQRT(2._wp)*rn_lambda       ! Horizontal scale in meters  
     232         zlambda = SQRT(2._wp)*rn_lambda*1.e3       ! Horizontal scale in meters  
    213233         zn2 = 3.e-3**2 
    214234         zH = 0.5_wp * 5000._wp 
     
    281301       
    282302      IF (ln_sshnoise) THEN 
     303         CALL RANDOM_SEED() 
    283304         CALL RANDOM_NUMBER(zrandom) 
    284305         pssh(:,:) = pssh(:,:) + ( 0.1  * zrandom(:,:) - 0.05 ) 
  • NEMO/branches/2020/dev_r13312_AGRIF-03-04_jchanut_vinterp_tstep/tests/CANAL/MY_SRC/usrdef_nam.F90

    r13286 r13942  
    5050   LOGICAL , PUBLIC ::   ln_sshnoise=.false. ! add random noise on initial ssh 
    5151   REAL(wp), PUBLIC ::   rn_lambda  = 50.    ! gaussian lambda 
     52   INTEGER , PUBLIC ::   nn_perio   =    0   ! periodicity of the channel (0=closed, 1=E-W) 
    5253 
    5354   !!---------------------------------------------------------------------- 
     
    7980      !! 
    8081      NAMELIST/namusr_def/  rn_domszx, rn_domszy, rn_domszz, rn_dx, rn_dy, rn_dz, rn_0xratio, rn_0yratio   & 
    81          &                 , nn_fcase, rn_ppgphi0, rn_vtxmax, rn_uzonal, rn_ujetszx, rn_ujetszy   & 
    82          &                 , rn_u10, rn_windszx, rn_windszy, rn_uofac   & 
    83          &                 , nn_botcase, nn_initcase, ln_sshnoise, rn_lambda 
     82         &                 , nn_fcase, rn_ppgphi0, rn_u10, rn_windszx, rn_windszy & !!, rn_uofac   & 
     83         &                 , rn_vtxmax, rn_uzonal, rn_ujetszx, rn_ujetszy  & 
     84         &                 , nn_botcase, nn_initcase, ln_sshnoise, rn_lambda, nn_perio 
    8485      !!---------------------------------------------------------------------- 
    8586      ! 
     
    148149         WRITE(numout,*) '      add random noise on initial ssh   ln_sshnoise= ', ln_sshnoise 
    149150         WRITE(numout,*) '      Gaussian lambda parameter          rn_lambda = ', rn_lambda 
    150          WRITE(numout,*) '   ' 
    151          WRITE(numout,*) '   Lateral boundary condition of the global domain' 
    152          WRITE(numout,*) '      EW_CANAL : closed basin               jperio = ', kperio 
     151         WRITE(numout,*) '      Periodicity of the basin            nn_perio = ', nn_perio 
    153152      ENDIF 
     153      !                             ! Set the lateral boundary condition of the global domain 
     154      kperio = nn_perio                    ! EW_CANAL configuration : closed basin 
    154155      ! 
    155156   END SUBROUTINE usr_def_nam 
  • NEMO/branches/2020/dev_r13312_AGRIF-03-04_jchanut_vinterp_tstep/tests/CANAL/MY_SRC/usrdef_sbc.F90

    r12740 r13942  
    1717   USE sbc_oce         ! Surface boundary condition: ocean fields 
    1818   USE phycst          ! physical constants 
    19    USE usrdef_nam, ONLY : rn_u10, rn_uofac, rn_windszy  
     19   USE usrdef_nam, ONLY : rn_u10, rn_uofac, rn_windszy, rn_windszx  
    2020   ! 
    2121   USE in_out_manager  ! I/O manager 
     
    6969         ! 
    7070         utau(:,:) = 0._wp 
    71          IF( rn_u10 /= 0. .AND. rn_windszy > 0. ) THEN 
    72             WHERE( ABS(gphit) <= rn_windszy/2. ) utau(:,:) = zrhocd * rn_u10 * rn_u10 
    73          ENDIF 
    7471         vtau(:,:) = 0._wp 
    7572         taum(:,:) = 0._wp 
     
    8178         qsr (:,:) = 0._wp 
    8279         !          
     80      ENDIF 
     81 
     82      IF( rn_u10 /= 0. .AND. rn_windszy > 0. ) THEN 
     83         IF( nyear == 1 .AND. nmonth == 1 .AND. nday <= 10 ) THEN 
     84            WHERE( ABS(gphit) <= rn_windszy/2. .AND. ABS(glamt) <= rn_windszx/2. ) utau(:,:) = zrhocd * rn_u10 * rn_u10 
     85         ELSE 
     86            utau(:,:) = 0. 
     87         ENDIF 
    8388      ENDIF 
    8489 
  • NEMO/branches/2020/dev_r13312_AGRIF-03-04_jchanut_vinterp_tstep/tests/CANAL/MY_SRC/usrdef_zgr.F90

    r12740 r13942  
    197197         zmaxlam = MAXVAL(glamt) 
    198198         CALL mpp_max( 'usrdef_zgr', zmaxlam )                 ! max over the global domain 
    199          zscl = rpi / zmaxlam 
    200          z2d(:,:) = 0.5 * ( 1. - COS( glamt(:,:) * zscl ) ) 
    201          z2d(:,:) = REAL(jpkm1 - NINT( 0.75 * REAL(jpkm1,wp) * z2d(:,:) ), wp) 
     199         zscl = 0.5 * rpi / zmaxlam 
     200         z2d(:,:) = COS( glamt(:,:) * zscl ) 
     201         z2d(:,:) = REAL(jpkm1 - NINT( 0.5 * REAL(jpkm1,wp) * z2d(:,:) ), wp) 
    202202      END SELECT 
    203203      ! 
Note: See TracChangeset for help on using the changeset viewer.