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 6051 for branches/2015/dev_CMCC_merge_2015/NEMOGCM/NEMO/OPA_SRC/DOM – NEMO

Ignore:
Timestamp:
2015-12-15T10:46:14+01:00 (8 years ago)
Author:
lovato
Message:

Merge branches/2015/dev_r5056_CMCC4_simplification (see ticket #1456)

Location:
branches/2015/dev_CMCC_merge_2015/NEMOGCM/NEMO/OPA_SRC/DOM
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • branches/2015/dev_CMCC_merge_2015/NEMOGCM/NEMO/OPA_SRC/DOM/daymod.F90

    r5563 r6051  
    2020   !! 
    2121   !!   we suppose that the time step is deviding the number of second of in a day 
    22    !!             ---> MOD( rday, rdttra(1) ) == 0 
     22   !!             ---> MOD( rday, rdt ) == 0 
    2323   !! 
    2424   !!           ----------- WARNING ----------- 
     
    7878            &           'You must do a restart at higher frequency (or remove this stop and recompile the code in I8)' ) 
    7979      ENDIF 
    80       ! all calendar staff is based on the fact that MOD( rday, rdttra(1) ) == 0 
    81       IF( MOD( rday     , rdttra(1) ) /= 0. )   CALL ctl_stop( 'the time step must devide the number of second of in a day' ) 
     80      ! all calendar staff is based on the fact that MOD( rday, rdt ) == 0 
     81      IF( MOD( rday     , rdt ) /= 0. )   CALL ctl_stop( 'the time step must devide the number of second of in a day' ) 
    8282      IF( MOD( rday     , 2.        ) /= 0. )   CALL ctl_stop( 'the number of second of in a day must be an even number'    ) 
    83       IF( MOD( rdttra(1), 2.        ) /= 0. )   CALL ctl_stop( 'the time step (in second) must be an even number'           ) 
     83      IF( MOD( rdt, 2.        ) /= 0. )   CALL ctl_stop( 'the time step (in second) must be an even number'           ) 
    8484      nsecd   = NINT(rday           ) 
    8585      nsecd05 = NINT(0.5 * rday     ) 
    86       ndt     = NINT(      rdttra(1)) 
    87       ndt05   = NINT(0.5 * rdttra(1)) 
     86      ndt     = NINT(      rdt) 
     87      ndt05   = NINT(0.5 * rdt) 
    8888 
    8989      IF( .NOT. lk_offline ) CALL day_rst( nit000, 'READ' ) 
     
    223223      nsec_week  = nsec_week  + ndt 
    224224      nsec_day   = nsec_day   + ndt 
    225       adatrj  = adatrj  + rdttra(1) / rday 
    226       fjulday = fjulday + rdttra(1) / rday 
     225      adatrj  = adatrj  + rdt / rday 
     226      fjulday = fjulday + rdt / rday 
    227227      IF( ABS(fjulday - REAL(NINT(fjulday),wp)) < zprec )   fjulday = REAL(NINT(fjulday),wp)   ! avoid truncation error 
    228228      IF( ABS(adatrj  - REAL(NINT(adatrj ),wp)) < zprec )   adatrj  = REAL(NINT(adatrj ),wp)   ! avoid truncation error 
     
    334334               ! parameters correspondting to nit000 - 1 (as we start the step loop with a call to day) 
    335335               ndastp = ndate0 - 1     ! ndate0 read in the namelist in dom_nam, we assume that we start run at 00:00 
    336                adatrj = ( REAL( nit000-1, wp ) * rdttra(1) ) / rday 
     336               adatrj = ( REAL( nit000-1, wp ) * rdt ) / rday 
    337337               ! note this is wrong if time step has changed during run 
    338338            ENDIF 
     
    340340            ! parameters correspondting to nit000 - 1 (as we start the step loop with a call to day) 
    341341            ndastp = ndate0 - 1        ! ndate0 read in the namelist in dom_nam, we assume that we start run at 00:00 
    342             adatrj = ( REAL( nit000-1, wp ) * rdttra(1) ) / rday 
     342            adatrj = ( REAL( nit000-1, wp ) * rdt ) / rday 
    343343         ENDIF 
    344344         IF( ABS(adatrj  - REAL(NINT(adatrj),wp)) < 0.1 / rday )   adatrj = REAL(NINT(adatrj),wp)   ! avoid truncation error 
  • branches/2015/dev_CMCC_merge_2015/NEMOGCM/NEMO/OPA_SRC/DOM/dom_oce.F90

    r5930 r6051  
    3535   REAL(wp), PUBLIC ::   rn_e3zps_rat    !: minimum thickness ration for partial steps 
    3636   INTEGER , PUBLIC ::   nn_msh          !: = 1 create a mesh-mask file 
    37    INTEGER , PUBLIC ::   nn_acc          !: = 0/1 use of the acceleration of convergence technique 
    3837   REAL(wp), PUBLIC ::   rn_atfp         !: asselin time filter parameter 
    39    REAL(wp), PUBLIC ::   rn_rdt          !: time step for the dynamics (and tracer if nacc=0) 
    40    REAL(wp), PUBLIC ::   rn_rdtmin       !: minimum time step on tracers 
    41    REAL(wp), PUBLIC ::   rn_rdtmax       !: maximum time step on tracers 
    42    REAL(wp), PUBLIC ::   rn_rdth         !: depth variation of tracer step 
     38   REAL(wp), PUBLIC ::   rn_rdt          !: time step for the dynamics and tracer 
    4339   INTEGER , PUBLIC ::   nn_closea       !: =0 suppress closed sea/lake from the ORCA domain or not (=1) 
    4440   INTEGER , PUBLIC ::   nn_euler        !: =0 start with forward time step or not (=1) 
     
    9995   REAL(wp), PUBLIC ::   e3zps_rat       !: minimum thickness ration for partial steps 
    10096   INTEGER , PUBLIC ::   nmsh            !: = 1 create a mesh-mask file 
    101    INTEGER , PUBLIC ::   nacc            !: = 0/1 use of the acceleration of convergence technique 
    10297   REAL(wp), PUBLIC ::   atfp            !: asselin time filter parameter 
    103    REAL(wp), PUBLIC ::   rdt             !: time step for the dynamics (and tracer if nacc=0) 
    104    REAL(wp), PUBLIC ::   rdtmin          !: minimum time step on tracers 
    105    REAL(wp), PUBLIC ::   rdtmax          !: maximum time step on tracers 
    106    REAL(wp), PUBLIC ::   rdth            !: depth variation of tracer step 
     98   REAL(wp), PUBLIC ::   rdt             !: time step for the dynamics and tracer 
    10799 
    108100   !                                                  !!! associated variables 
    109101   INTEGER , PUBLIC                 ::   neuler        !: restart euler forward option (0=Euler) 
    110102   REAL(wp), PUBLIC                 ::   atfp1         !: asselin time filter coeff. (atfp1= 1-2*atfp) 
    111    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   rdttra  !: vertical profile of tracer time step 
    112    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   r2dtra  !: = 2*rdttra except at nit000 (=rdttra) if neuler=0 
     103   REAL(wp), PUBLIC                 ::   r2dt          !: = 2*rdt except at nit000 (=rdt) if neuler=0 
    113104 
    114105   !!---------------------------------------------------------------------- 
     
    331322      ierr(:) = 0 
    332323      ! 
    333       ALLOCATE( rdttra(jpk), r2dtra(jpk), mig(jpi), mjg(jpj), nfiimpp(jpni,jpnj),  & 
     324      ALLOCATE( mig(jpi), mjg(jpj), nfiimpp(jpni,jpnj),  & 
    334325         &      nfipproc(jpni,jpnj), nfilcit(jpni,jpnj), STAT=ierr(1) ) 
    335326         ! 
  • branches/2015/dev_CMCC_merge_2015/NEMOGCM/NEMO/OPA_SRC/DOM/domain.F90

    r5836 r6051  
    138138         &             nn_no   , cn_exp    , cn_ocerst_in, cn_ocerst_out, ln_rstart , nn_rstctl,   & 
    139139         &             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 
     140         &             nn_write, ln_mskland  , ln_cfmeta , ln_clobber   , nn_chunksz, nn_euler 
    141141      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, & 
     142         &             rn_atfp , rn_rdt   , nn_closea   , ln_crs , jphgr_msh, & 
    145143         &             ppglam0, ppgphi0, ppe1_deg, ppe2_deg, ppe1_m, ppe2_m, & 
    146144         &             ppsur, ppa0, ppa1, ppkth, ppacr, ppdzmin, pphmax, ldbletanh, & 
     
    186184         ENDIF 
    187185         WRITE(numout,*) '      frequency of output file        nn_write   = ', nn_write 
    188          WRITE(numout,*) '      multi file dimgout              ln_dimgnnn = ', ln_dimgnnn 
    189186         WRITE(numout,*) '      mask land points                ln_mskland = ', ln_mskland 
    190187         WRITE(numout,*) '      additional CF standard metadata ln_cfmeta  = ', ln_cfmeta 
     
    267264         WRITE(numout,*) '      ocean time step                       rn_rdt    = ', rn_rdt 
    268265         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 
    273266         WRITE(numout,*) '      suppression of closed seas (=0)       nn_closea = ', nn_closea 
    274267         WRITE(numout,*) '      online coarsening of dynamical fields ln_crs    = ', ln_crs 
     
    297290      e3zps_rat = rn_e3zps_rat 
    298291      nmsh      = nn_msh 
    299       nacc      = nn_acc 
    300292      atfp      = rn_atfp 
    301293      rdt       = rn_rdt 
    302       rdtmin    = rn_rdtmin 
    303       rdtmax    = rn_rdtmin 
    304       rdth      = rn_rdth 
    305294 
    306295#if defined key_netcdf4 
  • branches/2015/dev_CMCC_merge_2015/NEMOGCM/NEMO/OPA_SRC/DOM/domstp.F90

    r4292 r6051  
    4141      !!      filter parameter read in namelist 
    4242      !!              - Model time step: 
    43       !!      nacc = 0 : synchronous time intergration.  
    44       !!      There is one time step only, defined by: rdt, rdttra(k)=rdt 
    45       !!      nacc = 1 : accelerating the convergence. There is 2 different 
    46       !!      time steps for dynamics and tracers: 
    47       !!        rdt      : dynamical part 
    48       !!        rdttra(k): temperature and salinity 
    49       !!      The tracer time step is a function of vertical level. the model 
    50       !!      reference time step ( i.e. for wind stress, surface heat and 
    51       !!      salt fluxes) is the surface tracer time step is rdttra(1). 
    52       !!         N.B. depth dependent acceleration of convergence is not im- 
    53       !!      plemented for s-coordinate. 
     43      !!                synchronous time intergration. 
     44      !!      There is one time step only, defined by: rdt for dynamics and 
     45      !!      tracer,wind stress, surface heat and salt fluxes 
    5446      !! 
    55       !! ** Action  : - rdttra   : vertical profile of tracer time step 
     47      !! ** Action  : [REMOVED - rdttra: vertical profile of tracer time step] 
    5648      !!              - atfp1    : = 1 - 2*atfp 
    5749      !! 
     
    7264      atfp1 = 1. - 2. * atfp 
    7365 
    74       SELECT CASE ( nacc ) 
     66      IF(lwp) WRITE(numout,*)'               synchronous time stepping' 
     67      IF(lwp) WRITE(numout,*)'               dynamics and tracer time step = ', rdt/3600., ' hours' 
    7568 
    76          CASE ( 0 )                ! Synchronous time stepping 
    77             IF(lwp) WRITE(numout,*)'               synchronous time stepping' 
    78             IF(lwp) WRITE(numout,*)'               dynamics and tracer time step = ', rdt/3600., ' hours' 
    79  
    80             rdttra(:) = rdt 
    81  
    82          CASE ( 1 )                ! Accelerating the convergence 
    83             IF(lwp) WRITE(numout,*) '              no tracer damping in the turbocline' 
    84             IF(lwp) WRITE(numout,*)'               accelerating the convergence' 
    85             IF(lwp) WRITE(numout,*)'               dynamics time step = ', rdt/3600., ' hours' 
    86             IF( ln_sco .AND. rdtmin /= rdtmax .AND. lk_vvl )   & 
    87                  & CALL ctl_stop ( ' depth dependent acceleration of convergence not implemented in s-coordinates & 
    88                  &                   nor in variable volume' ) 
    89             IF(lwp) WRITE(numout,*)'         tracers   time step :  dt (hours)  level' 
    90  
    91             DO jk = 1, jpk 
    92                IF( gdept_1d(jk) <= rdth ) rdttra(jk) = rdtmin 
    93                IF( gdept_1d(jk) >  rdth ) THEN 
    94                   rdttra(jk) = rdtmin + ( rdtmax - rdtmin )   & 
    95                                       * ( EXP( ( gdept_1d(jk ) - rdth ) / rdth ) - 1. )   & 
    96                                       / ( EXP( ( gdept_1d(jpk) - rdth ) / rdth ) - 1. ) 
    97                ENDIF 
    98                IF(lwp) WRITE(numout,"(36x,f5.2,5x,i3)") rdttra(jk)/3600., jk 
    99             END DO   
    100  
    101          CASE DEFAULT              ! E R R O R  
    102  
    103             WRITE(ctmp1,*) ' nacc value e r r o r, nacc= ',nacc 
    104             CALL ctl_stop( ctmp1 ) 
    105  
    106       END SELECT 
    10769 
    10870   END SUBROUTINE dom_stp 
Note: See TracChangeset for help on using the changeset viewer.