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 6140 for trunk/NEMOGCM/NEMO/OPA_SRC/DOM/domain.F90 – NEMO

Ignore:
Timestamp:
2015-12-21T12:35:23+01:00 (8 years ago)
Author:
timgraham
Message:

Merge of branches/2015/dev_merge_2015 back into trunk. Merge excludes NEMOGCM/TOOLS/OBSTOOLS/ for now due to issues with the change of file type. Will sort these manually with further commits.

Branch merged as follows:
In the working copy of branch ran:
svn merge svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/trunk@HEAD
Small conflicts due to bug fixes applied to trunk since the dev_merge_2015 was copied. Bug fixes were applied to the branch as well so these were easy to resolve.
Branch committed at this stage

In working copy run:
svn switch svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/trunk
to switch working copy

Run:
svn merge --reintegrate svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/branches/2015/dev_merge_2015
to merge the branch into the trunk and then commit - no conflicts at this stage.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMOGCM/NEMO/OPA_SRC/DOM/domain.F90

    r5836 r6140  
    1313   !!            3.3  !  2010-11  (G. Madec)  initialisation in C1D configuration 
    1414   !!            3.6  !  2013     ( J. Simeon, C. Calone, G. Madec, C. Ethe ) Online coarsening of outputs 
     15   !!            3.7  !  2015-11  (G. Madec, A. Coward)  time varying zgr by default 
    1516   !!---------------------------------------------------------------------- 
    1617    
     
    3637   ! 
    3738   USE in_out_manager  ! I/O manager 
     39   USE wrk_nemo        ! Memory Allocation 
    3840   USE lib_mpp         ! distributed memory computing library 
    3941   USE lbclnk          ! ocean lateral boundary condition (or mpp link) 
     
    4547   PUBLIC   dom_init   ! called by opa.F90 
    4648 
    47    !! * Substitutions 
    48 #  include "domzgr_substitute.h90" 
    4949   !!------------------------------------------------------------------------- 
    5050   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     
    7070      !!              - 1D configuration, move Coriolis, u and v at T-point 
    7171      !!---------------------------------------------------------------------- 
    72       INTEGER ::   jk          ! dummy loop argument 
     72      INTEGER ::   jk          ! dummy loop indices 
    7373      INTEGER ::   iconf = 0   ! local integers 
     74      REAL(wp), POINTER, DIMENSION(:,:) ::   z1_hu_0, z1_hv_0 
    7475      !!---------------------------------------------------------------------- 
    7576      ! 
     
    8283      ENDIF 
    8384      ! 
    84                              CALL dom_nam      ! read namelist ( namrun, namdom ) 
    85                              CALL dom_clo      ! Closed seas and lake 
    86                              CALL dom_hgr      ! Horizontal mesh 
    87                              CALL dom_zgr      ! Vertical mesh and bathymetry 
    88                              CALL dom_msk      ! Masks 
    89       IF( ln_sco )           CALL dom_stiff    ! Maximum stiffness ratio/hydrostatic consistency 
    90       ! 
    91       ht_0(:,:) = 0._wp                        ! Reference ocean depth at T-points 
    92       hu_0(:,:) = 0._wp                        ! Reference ocean depth at U-points 
    93       hv_0(:,:) = 0._wp                        ! Reference ocean depth at V-points 
    94       DO jk = 1, jpk 
     85      !                       !==  Reference coordinate system  ==! 
     86      ! 
     87                     CALL dom_nam               ! read namelist ( namrun, namdom ) 
     88                     CALL dom_clo               ! Closed seas and lake 
     89                     CALL dom_hgr               ! Horizontal mesh 
     90                     CALL dom_zgr               ! Vertical mesh and bathymetry 
     91                     CALL dom_msk               ! Masks 
     92      IF( ln_sco )   CALL dom_stiff             ! Maximum stiffness ratio/hydrostatic consistency 
     93      ! 
     94      ht_0(:,:) = e3t_0(:,:,1) * tmask(:,:,1)   ! Reference ocean thickness 
     95      hu_0(:,:) = e3u_0(:,:,1) * umask(:,:,1) 
     96      hv_0(:,:) = e3v_0(:,:,1) * vmask(:,:,1) 
     97      DO jk = 2, jpk 
    9598         ht_0(:,:) = ht_0(:,:) + e3t_0(:,:,jk) * tmask(:,:,jk) 
    9699         hu_0(:,:) = hu_0(:,:) + e3u_0(:,:,jk) * umask(:,:,jk) 
     
    98101      END DO 
    99102      ! 
    100       IF( lk_vvl         )   CALL dom_vvl_init ! Vertical variable mesh 
    101       ! 
    102       IF( lk_c1d         )   CALL cor_c1d      ! 1D configuration: Coriolis set at T-point 
    103       ! 
    104       ! 
    105       hu(:,:) = 0._wp                          ! Ocean depth at U-points 
    106       hv(:,:) = 0._wp                          ! Ocean depth at V-points 
    107       ht(:,:) = 0._wp                          ! Ocean depth at T-points 
    108       DO jk = 1, jpkm1 
    109          hu(:,:) = hu(:,:) + fse3u_n(:,:,jk) * umask(:,:,jk) 
    110          hv(:,:) = hv(:,:) + fse3v_n(:,:,jk) * vmask(:,:,jk) 
    111          ht(:,:) = ht(:,:) + fse3t_n(:,:,jk) * tmask(:,:,jk) 
    112       END DO 
    113       !                                        ! Inverse of the local depth 
    114       hur(:,:) = 1._wp / ( hu(:,:) + 1._wp - umask_i(:,:) ) * umask_i(:,:) 
    115       hvr(:,:) = 1._wp / ( hv(:,:) + 1._wp - vmask_i(:,:) ) * vmask_i(:,:) 
    116  
    117                              CALL dom_stp      ! time step 
    118       IF( nmsh /= 0      )   CALL dom_wri      ! Create a domain file 
    119       IF( .NOT.ln_rstart )   CALL dom_ctl      ! Domain control 
     103      !              !==  time varying part of coordinate system  ==! 
     104      ! 
     105      IF( ln_linssh ) THEN          ! Fix in time : set to the reference one for all 
     106         !       before        !          now          !       after         ! 
     107         ;  gdept_b = gdept_0  ;   gdept_n = gdept_0   !        ---          ! depth of grid-points 
     108         ;  gdepw_b = gdepw_0  ;   gdepw_n = gdepw_0   !        ---          ! 
     109         ;                     ;   gde3w_n = gde3w_0   !        ---          ! 
     110         !                                                                   
     111         ;    e3t_b =   e3t_0  ;     e3t_n =   e3t_0   ;   e3t_a =  e3t_0    ! scale factors 
     112         ;    e3u_b =   e3u_0  ;     e3u_n =   e3u_0   ;   e3u_a =  e3u_0    ! 
     113         ;    e3v_b =   e3v_0  ;     e3v_n =   e3v_0   ;   e3v_a =  e3v_0    ! 
     114         ;                     ;     e3f_n =   e3f_0   !        ---          ! 
     115         ;    e3w_b =   e3w_0  ;     e3w_n =   e3w_0   !        ---          ! 
     116         ;   e3uw_b =  e3uw_0  ;    e3uw_n =  e3uw_0   !        ---          ! 
     117         ;   e3vw_b =  e3vw_0  ;    e3vw_n =  e3vw_0   !        ---          ! 
     118         ! 
     119         CALL wrk_alloc( jpi,jpj,   z1_hu_0, z1_hv_0 ) 
     120         ! 
     121         z1_hu_0(:,:) = ssumask(:,:) / ( hu_0(:,:) + 1._wp - ssumask(:,:) )     ! _i mask due to ISF 
     122         z1_hv_0(:,:) = ssvmask(:,:) / ( hv_0(:,:) + 1._wp - ssvmask(:,:) ) 
     123         ! 
     124         !        before       !          now          !       after         ! 
     125         ;                     ;      ht_n =    ht_0   !                     ! water column thickness 
     126         ;     hu_b =    hu_0  ;      hu_n =    hu_0   ;    hu_a =    hu_0   !  
     127         ;     hv_b =    hv_0  ;      hv_n =    hv_0   ;    hv_a =    hv_0   ! 
     128         ;  r1_hu_b = z1_hu_0  ;   r1_hu_n = z1_hu_0   ; r1_hu_a = z1_hu_0   ! inverse of water column thickness 
     129         ;  r1_hv_b = z1_hv_0  ;   r1_hv_n = z1_hv_0   ; r1_hv_a = z1_hv_0   ! 
     130         ! 
     131         CALL wrk_dealloc( jpi,jpj,   z1_hu_0, z1_hv_0 ) 
     132         ! 
     133      ELSE                         ! time varying : initialize before/now/after variables 
     134         ! 
     135         CALL dom_vvl_init  
     136         ! 
     137      ENDIF 
     138      ! 
     139      IF( lk_c1d         )   CALL cor_c1d       ! 1D configuration: Coriolis set at T-point 
     140      ! 
     141                             CALL dom_stp       ! time step 
     142      IF( nmsh /= 0 .AND. .NOT. ln_iscpl )                         CALL dom_wri      ! Create a domain file 
     143      IF( nmsh /= 0 .AND.       ln_iscpl .AND. .NOT. ln_rstart )   CALL dom_wri      ! Create a domain file 
     144      IF( .NOT.ln_rstart )   CALL dom_ctl       ! Domain control 
    120145      ! 
    121146      IF( nn_timing == 1 )   CALL timing_stop('dom_init') 
     
    135160      !!---------------------------------------------------------------------- 
    136161      USE ioipsl 
    137       NAMELIST/namrun/ cn_ocerst_indir, cn_ocerst_outdir, nn_stocklist, ln_rst_list,               & 
    138          &             nn_no   , cn_exp    , cn_ocerst_in, cn_ocerst_out, ln_rstart , nn_rstctl,   & 
    139          &             nn_it000, nn_itend  , nn_date0    , nn_leapy     , nn_istate , nn_stock ,   & 
    140          &             nn_write, ln_dimgnnn, ln_mskland  , ln_cfmeta    , ln_clobber, nn_chunksz, nn_euler 
    141       NAMELIST/namdom/ nn_bathy, rn_bathy , rn_e3zps_min, rn_e3zps_rat, nn_msh, rn_hmin,   & 
    142          &             nn_acc   , rn_atfp     , rn_rdt      , rn_rdtmin ,                  & 
    143          &             rn_rdtmax, rn_rdth     , nn_closea , ln_crs,    & 
    144          &             jphgr_msh, & 
    145          &             ppglam0, ppgphi0, ppe1_deg, ppe2_deg, ppe1_m, ppe2_m, & 
    146          &             ppsur, ppa0, ppa1, ppkth, ppacr, ppdzmin, pphmax, ldbletanh, & 
     162      NAMELIST/namrun/ cn_ocerst_indir, cn_ocerst_outdir, nn_stocklist, ln_rst_list,                 & 
     163                       nn_no   , cn_exp   , cn_ocerst_in, cn_ocerst_out, ln_rstart , nn_rstctl ,     & 
     164         &             nn_it000, nn_itend , nn_date0    , nn_time0     , nn_leapy  , nn_istate ,     & 
     165         &             nn_stock, nn_write , ln_mskland  , ln_clobber   , nn_chunksz, nn_euler  ,     & 
     166         &             ln_cfmeta, ln_iscpl 
     167      NAMELIST/namdom/ nn_bathy, rn_bathy , rn_e3zps_min, rn_e3zps_rat, nn_msh, rn_hmin, rn_isfhmin, & 
     168         &             rn_atfp , rn_rdt   , nn_closea   , ln_crs      , jphgr_msh ,                  & 
     169         &             ppglam0, ppgphi0, ppe1_deg, ppe2_deg, ppe1_m, ppe2_m,                         & 
     170         &             ppsur, ppa0, ppa1, ppkth, ppacr, ppdzmin, pphmax, ldbletanh,                  & 
    147171         &             ppa2, ppkth2, ppacr2 
    148172#if defined key_netcdf4 
     
    178202         WRITE(numout,*) '      number of the last time step    nn_itend   = ', nn_itend 
    179203         WRITE(numout,*) '      initial calendar date aammjj    nn_date0   = ', nn_date0 
     204         WRITE(numout,*) '      initial time of day in hhmm     nn_time0   = ', nn_time0 
    180205         WRITE(numout,*) '      leap year calendar (0/1)        nn_leapy   = ', nn_leapy 
    181206         WRITE(numout,*) '      initial state output            nn_istate  = ', nn_istate 
     
    186211         ENDIF 
    187212         WRITE(numout,*) '      frequency of output file        nn_write   = ', nn_write 
    188          WRITE(numout,*) '      multi file dimgout              ln_dimgnnn = ', ln_dimgnnn 
    189213         WRITE(numout,*) '      mask land points                ln_mskland = ', ln_mskland 
    190214         WRITE(numout,*) '      additional CF standard metadata ln_cfmeta  = ', ln_cfmeta 
    191215         WRITE(numout,*) '      overwrite an existing file      ln_clobber = ', ln_clobber 
    192216         WRITE(numout,*) '      NetCDF chunksize (bytes)        nn_chunksz = ', nn_chunksz 
     217         WRITE(numout,*) '      IS coupling at the restart step ln_iscpl   = ', ln_iscpl 
    193218      ENDIF 
    194219 
     
    258283         WRITE(numout,*) '      min depth of the ocean    (>0) or    rn_hmin   = ', rn_hmin 
    259284         WRITE(numout,*) '      min number of ocean level (<0)       ' 
     285         WRITE(numout,*) '      treshold to open the isf cavity   rn_isfhmin   = ', rn_isfhmin, ' (m)' 
    260286         WRITE(numout,*) '      minimum thickness of partial      rn_e3zps_min = ', rn_e3zps_min, ' (m)' 
    261287         WRITE(numout,*) '         step level                     rn_e3zps_rat = ', rn_e3zps_rat 
     
    267293         WRITE(numout,*) '      ocean time step                       rn_rdt    = ', rn_rdt 
    268294         WRITE(numout,*) '      asselin time filter parameter         rn_atfp   = ', rn_atfp 
    269          WRITE(numout,*) '      acceleration of converge              nn_acc    = ', nn_acc 
    270          WRITE(numout,*) '        nn_acc=1: surface tracer rdt        rn_rdtmin = ', rn_rdtmin 
    271          WRITE(numout,*) '                  bottom  tracer rdt        rdtmax    = ', rn_rdtmax 
    272          WRITE(numout,*) '                  depth of transition       rn_rdth   = ', rn_rdth 
    273295         WRITE(numout,*) '      suppression of closed seas (=0)       nn_closea = ', nn_closea 
    274296         WRITE(numout,*) '      online coarsening of dynamical fields ln_crs    = ', ln_crs 
     
    297319      e3zps_rat = rn_e3zps_rat 
    298320      nmsh      = nn_msh 
    299       nacc      = nn_acc 
    300321      atfp      = rn_atfp 
    301322      rdt       = rn_rdt 
    302       rdtmin    = rn_rdtmin 
    303       rdtmax    = rn_rdtmin 
    304       rdth      = rn_rdth 
    305323 
    306324#if defined key_netcdf4 
     
    403421      INTEGER  ::   ji, jj, jk  
    404422      REAL(wp) ::   zrxmax 
    405       REAL(wp), DIMENSION(4) :: zr1 
     423      REAL(wp), DIMENSION(4) ::   zr1 
    406424      !!---------------------------------------------------------------------- 
    407425      rx1(:,:) = 0._wp 
     
    412430         DO jj = 2, jpjm1 
    413431            DO jk = 1, jpkm1 
    414                zr1(1) = umask(ji-1,jj  ,jk) *abs( (gdepw_0(ji  ,jj  ,jk  )-gdepw_0(ji-1,jj  ,jk  )  &  
    415                     &                         +gdepw_0(ji  ,jj  ,jk+1)-gdepw_0(ji-1,jj  ,jk+1)) & 
    416                     &                        /(gdepw_0(ji  ,jj  ,jk  )+gdepw_0(ji-1,jj  ,jk  )  & 
    417                     &                         -gdepw_0(ji  ,jj  ,jk+1)-gdepw_0(ji-1,jj  ,jk+1) + rsmall) ) 
    418                zr1(2) = umask(ji  ,jj  ,jk) *abs( (gdepw_0(ji+1,jj  ,jk  )-gdepw_0(ji  ,jj  ,jk  )  & 
    419                     &                         +gdepw_0(ji+1,jj  ,jk+1)-gdepw_0(ji  ,jj  ,jk+1)) & 
    420                     &                        /(gdepw_0(ji+1,jj  ,jk  )+gdepw_0(ji  ,jj  ,jk  )  & 
    421                     &                         -gdepw_0(ji+1,jj  ,jk+1)-gdepw_0(ji  ,jj  ,jk+1) + rsmall) ) 
    422                zr1(3) = vmask(ji  ,jj  ,jk) *abs( (gdepw_0(ji  ,jj+1,jk  )-gdepw_0(ji  ,jj  ,jk  )  & 
    423                     &                         +gdepw_0(ji  ,jj+1,jk+1)-gdepw_0(ji  ,jj  ,jk+1)) & 
    424                     &                        /(gdepw_0(ji  ,jj+1,jk  )+gdepw_0(ji  ,jj  ,jk  )  & 
    425                     &                         -gdepw_0(ji  ,jj+1,jk+1)-gdepw_0(ji  ,jj  ,jk+1) + rsmall) ) 
    426                zr1(4) = vmask(ji  ,jj-1,jk) *abs( (gdepw_0(ji  ,jj  ,jk  )-gdepw_0(ji  ,jj-1,jk  )  & 
    427                     &                         +gdepw_0(ji  ,jj  ,jk+1)-gdepw_0(ji  ,jj-1,jk+1)) & 
    428                     &                        /(gdepw_0(ji  ,jj  ,jk  )+gdepw_0(ji  ,jj-1,jk  )  & 
    429                     &                         -gdepw_0(ji,  jj  ,jk+1)-gdepw_0(ji  ,jj-1,jk+1) + rsmall) ) 
    430                zrxmax = MAXVAL(zr1(1:4)) 
    431                rx1(ji,jj) = MAX(rx1(ji,jj), zrxmax) 
     432               zr1(1) = ABS(  ( gdepw_0(ji  ,jj,jk  )-gdepw_0(ji-1,jj,jk  )               &  
     433                    &          +gdepw_0(ji  ,jj,jk+1)-gdepw_0(ji-1,jj,jk+1) )            & 
     434                    &       / ( gdepw_0(ji  ,jj,jk  )+gdepw_0(ji-1,jj,jk  )               & 
     435                    &          -gdepw_0(ji  ,jj,jk+1)-gdepw_0(ji-1,jj,jk+1) + rsmall )  ) * umask(ji-1,jj,jk) 
     436               zr1(2) = ABS(  ( gdepw_0(ji+1,jj,jk  )-gdepw_0(ji  ,jj,jk  )               & 
     437                    &          +gdepw_0(ji+1,jj,jk+1)-gdepw_0(ji  ,jj,jk+1) )            & 
     438                    &       / ( gdepw_0(ji+1,jj,jk  )+gdepw_0(ji  ,jj,jk  )               & 
     439                    &          -gdepw_0(ji+1,jj,jk+1)-gdepw_0(ji  ,jj,jk+1) + rsmall )  ) * umask(ji  ,jj,jk) 
     440               zr1(3) = ABS(  ( gdepw_0(ji,jj+1,jk  )-gdepw_0(ji,jj  ,jk  )               & 
     441                    &          +gdepw_0(ji,jj+1,jk+1)-gdepw_0(ji,jj  ,jk+1) )            & 
     442                    &       / ( gdepw_0(ji,jj+1,jk  )+gdepw_0(ji,jj  ,jk  )               & 
     443                    &          -gdepw_0(ji,jj+1,jk+1)-gdepw_0(ji,jj  ,jk+1) + rsmall )  ) * vmask(ji,jj  ,jk) 
     444               zr1(4) = ABS(  ( gdepw_0(ji,jj  ,jk  )-gdepw_0(ji,jj-1,jk  )               & 
     445                    &          +gdepw_0(ji,jj  ,jk+1)-gdepw_0(ji,jj-1,jk+1) )            & 
     446                    &       / ( gdepw_0(ji,jj  ,jk  )+gdepw_0(ji,jj-1,jk  )               & 
     447                    &          -gdepw_0(ji,jj  ,jk+1)-gdepw_0(ji,jj-1,jk+1) + rsmall )  ) * vmask(ji,jj-1,jk) 
     448               zrxmax = MAXVAL( zr1(1:4) ) 
     449               rx1(ji,jj) = MAX( rx1(ji,jj) , zrxmax ) 
    432450            END DO 
    433451         END DO 
Note: See TracChangeset for help on using the changeset viewer.