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/TOP_SRC/TRP/trcnxt.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/TOP_SRC/TRP/trcnxt.F90

    r5656 r6140  
    3333   USE trdtra 
    3434   USE tranxt 
     35   USE trcbdy          ! BDY open boundaries 
     36   USE bdy_par, only: lk_bdy 
    3537# if defined key_agrif 
    3638   USE agrif_top_interp 
     
    4143 
    4244   PUBLIC   trc_nxt          ! routine called by step.F90 
    43    PUBLIC   trc_nxt_alloc    ! routine called by nemogcm.F90 
    4445 
    45    REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:) ::   r2dt 
     46   REAL(wp) ::   r2dttrc 
    4647 
    4748   !!---------------------------------------------------------------------- 
     
    5152   !!---------------------------------------------------------------------- 
    5253CONTAINS 
    53  
    54    INTEGER FUNCTION trc_nxt_alloc() 
    55       !!---------------------------------------------------------------------- 
    56       !!                   ***  ROUTINE trc_nxt_alloc  *** 
    57       !!---------------------------------------------------------------------- 
    58       ALLOCATE( r2dt(jpk), STAT=trc_nxt_alloc ) 
    59       ! 
    60       IF( trc_nxt_alloc /= 0 )   CALL ctl_warn('trc_nxt_alloc : failed to allocate array') 
    61       ! 
    62    END FUNCTION trc_nxt_alloc 
    63  
    6454 
    6555   SUBROUTINE trc_nxt( kt ) 
     
    10191         WRITE(numout,*) 'trc_nxt : time stepping on passive tracers' 
    10292      ENDIF 
    103  
     93      ! 
    10494#if defined key_agrif 
    10595      CALL Agrif_trc                   ! AGRIF zoom boundaries 
    10696#endif 
    107       ! Update after tracer on domain lateral boundaries 
    108       DO jn = 1, jptra 
     97      DO jn = 1, jptra                 ! Update after tracer on domain lateral boundaries 
    10998         CALL lbc_lnk( tra(:,:,:,jn), 'T', 1. )    
    11099      END DO 
    111100 
     101      IF( lk_bdy )  CALL trc_bdy( kt ) 
    112102 
    113 #if defined key_bdy 
    114 !!      CALL bdy_trc( kt )               ! BDY open boundaries 
    115 #endif 
    116  
    117  
    118       ! set time step size (Euler/Leapfrog) 
    119       IF( neuler == 0 .AND. kt ==  nittrc000 ) THEN  ;  r2dt(:) =     rdttrc(:)   ! at nittrc000             (Euler) 
    120       ELSEIF( kt <= nittrc000 + nn_dttrc )     THEN  ;  r2dt(:) = 2.* rdttrc(:)   ! at nit000 or nit000+1 (Leapfrog) 
     103      !                                ! set time step size (Euler/Leapfrog) 
     104      IF( neuler == 0 .AND. kt ==  nittrc000 ) THEN  ;  r2dttrc =     rdttrc   ! at nittrc000             (Euler) 
     105      ELSEIF( kt <= nittrc000 + nn_dttrc )     THEN  ;  r2dttrc = 2.* rdttrc   ! at nit000 or nit000+1 (Leapfrog) 
    121106      ENDIF 
    122107 
    123       ! trends computation initialisation 
    124       IF( l_trdtrc )  THEN 
    125          CALL wrk_alloc( jpi, jpj, jpk, jptra, ztrdt )  !* store now fields before applying the Asselin filter 
     108      IF( l_trdtrc )  THEN             ! trends: store now fields before the Asselin filter application 
     109         CALL wrk_alloc( jpi, jpj, jpk, jptra, ztrdt ) 
    126110         ztrdt(:,:,:,:)  = trn(:,:,:,:) 
    127111      ENDIF 
    128       ! Leap-Frog + Asselin filter time stepping 
    129       IF( neuler == 0 .AND. kt == nittrc000 ) THEN        ! Euler time-stepping at first time-step 
    130          !                                                ! (only swap) 
     112      !                                ! Leap-Frog + Asselin filter time stepping 
     113      IF( neuler == 0 .AND. kt == nittrc000 ) THEN    ! Euler time-stepping at first time-step (only swap) 
    131114         DO jn = 1, jptra 
    132115            DO jk = 1, jpkm1 
     
    134117            END DO 
    135118         END DO 
    136          !                                               
    137       ELSE 
    138          ! Leap-Frog + Asselin filter time stepping 
    139          IF( lk_vvl ) THEN   ;   CALL tra_nxt_vvl( kt, nittrc000, rdttrc, 'TRC', trb, trn, tra,      & 
    140            &                                                                sbc_trc, sbc_trc_b, jptra )      ! variable volume level (vvl)  
    141          ELSE                ;   CALL tra_nxt_fix( kt, nittrc000,         'TRC', trb, trn, tra, jptra )      ! fixed    volume level  
     119      ELSE                                            ! Asselin filter + swap 
     120         IF( ln_linssh ) THEN   ;   CALL tra_nxt_fix( kt, nittrc000,         'TRC', trb, trn, tra, jptra )  !     linear ssh 
     121         ELSE                   ;   CALL tra_nxt_vvl( kt, nittrc000, rdttrc, 'TRC', trb, trn, tra,      & 
     122           &                                                                   sbc_trc, sbc_trc_b, jptra )  ! non-linear ssh 
    142123         ENDIF 
     124         ! 
     125         DO jn = 1, jptra 
     126            CALL lbc_lnk( trb(:,:,:,jn), 'T', 1._wp )  
     127            CALL lbc_lnk( trn(:,:,:,jn), 'T', 1._wp ) 
     128            CALL lbc_lnk( tra(:,:,:,jn), 'T', 1._wp ) 
     129         END DO 
    143130      ENDIF 
    144  
    145       ! trends computation 
    146       IF( l_trdtrc ) THEN                                      ! trends 
     131      ! 
     132      IF( l_trdtrc ) THEN              ! trends: send Asselin filter trends to trdtra manager for further diagnostics 
    147133         DO jn = 1, jptra 
    148134            DO jk = 1, jpkm1 
    149                zfact = 1.e0 / r2dt(jk)   
     135               zfact = 1._wp / r2dttrc   
    150136               ztrdt(:,:,jk,jn) = ( trb(:,:,jk,jn) - ztrdt(:,:,jk,jn) ) * zfact  
    151137               CALL trd_tra( kt, 'TRC', jn, jptra_atf, ztrdt ) 
Note: See TracChangeset for help on using the changeset viewer.