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 3294 for trunk/NEMOGCM/NEMO/OPA_SRC/TRA/tranxt.F90 – NEMO

Ignore:
Timestamp:
2012-01-28T17:44:18+01:00 (12 years ago)
Author:
rblod
Message:

Merge of 3.4beta into the trunk

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMOGCM/NEMO/OPA_SRC/TRA/tranxt.F90

    r2715 r3294  
    3636   USE obc_oce 
    3737   USE obctra          ! open boundary condition (obc_tra routine) 
    38    USE bdy_par         ! Unstructured open boundary condition (bdy_tra_frs routine) 
    39    USE bdytra          ! Unstructured open boundary condition (bdy_tra_frs routine) 
     38   USE bdy_oce 
     39   USE bdytra          ! open boundary condition (bdy_tra routine) 
    4040   USE in_out_manager  ! I/O manager 
    4141   USE lbclnk          ! ocean lateral boundary conditions (or mpp link) 
    4242   USE prtctl          ! Print control 
    4343   USE traqsr          ! penetrative solar radiation (needed for nksr) 
    44    USE traswp          ! swap array 
    45    USE obc_oce  
    4644#if defined key_agrif 
    4745   USE agrif_opa_update 
    4846   USE agrif_opa_interp 
    4947#endif 
     48   USE wrk_nemo        ! Memory allocation 
     49   USE timing          ! Timing 
    5050 
    5151   IMPLICIT NONE 
     
    8181      !!              - Apply lateral boundary conditions on (ta,sa)  
    8282      !!             at the local domain   boundaries through lbc_lnk call,  
    83       !!             at the radiative open boundaries (lk_obc=T),  
    84       !!             at the relaxed   open boundaries (lk_bdy=T), and 
     83      !!             at the one-way open boundaries (lk_obc=T),  
    8584      !!             at the AGRIF zoom     boundaries (lk_agrif=T) 
    8685      !! 
     
    9594      INTEGER  ::   jk, jn    ! dummy loop indices 
    9695      REAL(wp) ::   zfact     ! local scalars 
    97       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  ztrdt, ztrds 
    98       !!---------------------------------------------------------------------- 
    99  
     96      REAL(wp), POINTER, DIMENSION(:,:,:) ::  ztrdt, ztrds 
     97      !!---------------------------------------------------------------------- 
     98      ! 
     99      IF( nn_timing == 1 )  CALL timing_start( 'tra_nxt') 
     100      ! 
    100101      IF( kt == nit000 ) THEN 
    101102         IF(lwp) WRITE(numout,*) 
     
    111112      CALL lbc_lnk( tsa(:,:,:,jp_sal), 'T', 1. ) 
    112113      ! 
    113 #if defined key_obc || defined key_bdy || defined key_agrif 
    114       CALL tra_unswap 
    115 #endif 
    116  
    117114#if defined key_obc  
    118115      IF( lk_obc )   CALL obc_tra( kt )  ! OBC open boundaries 
    119116#endif 
    120117#if defined key_bdy  
    121       IF( lk_bdy )   CALL bdy_tra_frs( kt )  ! BDY open boundaries 
     118      IF( lk_bdy )   CALL bdy_tra( kt )  ! BDY open boundaries 
    122119#endif 
    123120#if defined key_agrif 
    124121      CALL Agrif_tra                     ! AGRIF zoom boundaries 
    125 #endif 
    126  
    127 #if defined key_obc || defined key_bdy || defined key_agrif 
    128       CALL tra_swap 
    129122#endif 
    130123  
     
    136129      ! trends computation initialisation 
    137130      IF( l_trdtra )   THEN                    ! store now fields before applying the Asselin filter 
    138          ALLOCATE( ztrdt(jpi,jpj,jpk) )   ;    ztrdt(:,:,:) = tsn(:,:,:,jp_tem)  
    139          ALLOCATE( ztrds(jpi,jpj,jpk) )   ;    ztrds(:,:,:) = tsn(:,:,:,jp_sal) 
     131         CALL wrk_alloc( jpi, jpj, jpk, ztrdt, ztrds ) 
     132         ztrdt(:,:,:) = tsn(:,:,:,jp_tem)  
     133         ztrds(:,:,:) = tsn(:,:,:,jp_sal) 
    140134      ENDIF 
    141135 
     
    148142      ELSE                                            ! Leap-Frog + Asselin filter time stepping 
    149143         ! 
    150          IF( lk_vvl )  THEN   ;   CALL tra_nxt_vvl( kt, 'TRA', tsb, tsn, tsa, jpts )  ! variable volume level (vvl)      
    151          ELSE                 ;   CALL tra_nxt_fix( kt, 'TRA', tsb, tsn, tsa, jpts )  ! fixed    volume level  
     144         IF( lk_vvl )  THEN   ;   CALL tra_nxt_vvl( kt, nit000, 'TRA', tsb, tsn, tsa, jpts )  ! variable volume level (vvl)      
     145         ELSE                 ;   CALL tra_nxt_fix( kt, nit000, 'TRA', tsb, tsn, tsa, jpts )  ! fixed    volume level  
    152146         ENDIF 
    153147      ENDIF  
     
    155149#if defined key_agrif 
    156150      ! Update tracer at AGRIF zoom boundaries 
    157       CALL tra_unswap 
    158151      IF( .NOT.Agrif_Root() )    CALL Agrif_Update_Tra( kt )      ! children only 
    159       CALL tra_swap 
    160152#endif       
    161153      ! 
     
    169161         CALL trd_tra( kt, 'TRA', jp_tem, jptra_trd_atf, ztrdt ) 
    170162         CALL trd_tra( kt, 'TRA', jp_sal, jptra_trd_atf, ztrds ) 
    171          DEALLOCATE( ztrdt )      ;     DEALLOCATE( ztrds )  
     163         CALL wrk_dealloc( jpi, jpj, jpk, ztrdt, ztrds ) 
    172164      END IF 
    173165      ! 
     
    176168         &                       tab3d_2=tsn(:,:,:,jp_sal), clinfo2=       ' Sn: ', mask2=tmask ) 
    177169      ! 
     170      ! 
     171      IF( nn_timing == 1 )  CALL timing_stop('tra_nxt') 
     172      ! 
    178173   END SUBROUTINE tra_nxt 
    179174 
    180175 
    181    SUBROUTINE tra_nxt_fix( kt, cdtype, ptb, ptn, pta, kjpt ) 
     176   SUBROUTINE tra_nxt_fix( kt, kit000, cdtype, ptb, ptn, pta, kjpt ) 
    182177      !!---------------------------------------------------------------------- 
    183178      !!                   ***  ROUTINE tra_nxt_fix  *** 
     
    203198      !!---------------------------------------------------------------------- 
    204199      INTEGER         , INTENT(in   )                               ::   kt       ! ocean time-step index 
     200      INTEGER         , INTENT(in   )                               ::   kit000   ! first time step index 
    205201      CHARACTER(len=3), INTENT(in   )                               ::   cdtype   ! =TRA or TRC (tracer indicator) 
    206202      INTEGER         , INTENT(in   )                               ::   kjpt     ! number of tracers 
     
    214210      !!---------------------------------------------------------------------- 
    215211 
    216       IF( kt == nit000 )  THEN 
     212      IF( kt == kit000 )  THEN 
    217213         IF(lwp) WRITE(numout,*) 
    218          IF(lwp) WRITE(numout,*) 'tra_nxt_fix : time stepping' 
     214         IF(lwp) WRITE(numout,*) 'tra_nxt_fix : time stepping', cdtype 
    219215         IF(lwp) WRITE(numout,*) '~~~~~~~~~~~' 
    220216      ENDIF 
     
    245241 
    246242 
    247    SUBROUTINE tra_nxt_vvl( kt, cdtype, ptb, ptn, pta, kjpt ) 
     243   SUBROUTINE tra_nxt_vvl( kt, kit000, cdtype, ptb, ptn, pta, kjpt ) 
    248244      !!---------------------------------------------------------------------- 
    249245      !!                   ***  ROUTINE tra_nxt_vvl  *** 
     
    270266      !!---------------------------------------------------------------------- 
    271267      INTEGER         , INTENT(in   )                               ::   kt       ! ocean time-step index 
     268      INTEGER         , INTENT(in   )                               ::   kit000   ! first time step index 
    272269      CHARACTER(len=3), INTENT(in   )                               ::   cdtype   ! =TRA or TRC (tracer indicator) 
    273270      INTEGER         , INTENT(in   )                               ::   kjpt     ! number of tracers 
     
    281278      REAL(wp) ::   zfact2, ze3t_b, ze3t_n, ze3t_a, ze3t_f, ze3t_d   !   -      - 
    282279      !!---------------------------------------------------------------------- 
    283  
    284       IF( kt == nit000 ) THEN 
     280      ! 
     281      IF( kt == kit000 ) THEN 
    285282         IF(lwp) WRITE(numout,*) 
    286          IF(lwp) WRITE(numout,*) 'tra_nxt_vvl : time stepping' 
     283         IF(lwp) WRITE(numout,*) 'tra_nxt_vvl : time stepping', cdtype 
    287284         IF(lwp) WRITE(numout,*) '~~~~~~~~~~~' 
    288285      ENDIF 
Note: See TracChangeset for help on using the changeset viewer.