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

Ignore:
Timestamp:
2011-03-30T17:58:35+02:00 (13 years ago)
Author:
rblod
Message:

First attempt to put dynamic allocation on the trunk

File:
1 edited

Legend:

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

    r2528 r2715  
    5656   PUBLIC   tra_nxt_vvl   ! to be used in trcnxt 
    5757 
    58    REAL(wp)                 ::   rbcp            ! Brown & Campana parameters for semi-implicit hpg 
    59    REAL(wp), DIMENSION(jpk) ::   r2dt   ! vertical profile time step, =2*rdttra (leapfrog) or =rdttra (Euler) 
     58   REAL(wp) ::   rbcp   ! Brown & Campana parameters for semi-implicit hpg 
    6059 
    6160   !! * Substitutions 
     
    6362   !!---------------------------------------------------------------------- 
    6463   !! NEMO/OPA 3.3 , NEMO-Consortium (2010)  
    65    !! $Id $ 
    66    !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     64   !! $Id$ 
     65   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
    6766   !!---------------------------------------------------------------------- 
    6867CONTAINS 
     
    104103         IF(lwp) WRITE(numout,*) '~~~~~~~' 
    105104         ! 
    106          rbcp    = 0.25 * (1. + atfp) * (1. + atfp) * ( 1. - atfp)       ! Brown & Campana parameter for semi-implicit hpg 
     105         rbcp = 0.25 * (1. + atfp) * (1. + atfp) * ( 1. - atfp)      ! Brown & Campana parameter for semi-implicit hpg 
    107106      ENDIF 
    108107 
     
    131130  
    132131      ! set time step size (Euler/Leapfrog) 
    133       IF( neuler == 0 .AND. kt == nit000 ) THEN   ;   r2dt(:) =     rdttra(:)      ! at nit000             (Euler) 
    134       ELSEIF( kt <= nit000 + 1 )           THEN   ;   r2dt(:) = 2.* rdttra(:)      ! at nit000 or nit000+1 (Leapfrog) 
     132      IF( neuler == 0 .AND. kt == nit000 ) THEN   ;   r2dtra(:) =     rdttra(:)      ! at nit000             (Euler) 
     133      ELSEIF( kt <= nit000 + 1 )           THEN   ;   r2dtra(:) = 2.* rdttra(:)      ! at nit000 or nit000+1 (Leapfrog) 
    135134      ENDIF 
    136135 
     
    153152         ENDIF 
    154153      ENDIF  
    155  
     154      ! 
    156155#if defined key_agrif 
    157156      ! Update tracer at AGRIF zoom boundaries 
     
    160159      CALL tra_swap 
    161160#endif       
    162  
     161      ! 
    163162      ! trends computation 
    164163      IF( l_trdtra ) THEN      ! trend of the Asselin filter (tb filtered - tb)/dt      
    165164         DO jk = 1, jpkm1 
    166             zfact = 1.e0 / r2dt(jk)              
     165            zfact = 1.e0 / r2dtra(jk)              
    167166            ztrdt(:,:,jk) = ( tsb(:,:,jk,jp_tem) - ztrdt(:,:,jk) ) * zfact 
    168167            ztrds(:,:,jk) = ( tsb(:,:,jk,jp_sal) - ztrds(:,:,jk) ) * zfact 
     
    172171         DEALLOCATE( ztrdt )      ;     DEALLOCATE( ztrds )  
    173172      END IF 
    174  
     173      ! 
    175174      !                        ! control print 
    176175      IF(ln_ctl)   CALL prt_ctl( tab3d_1=tsn(:,:,:,jp_tem), clinfo1=' nxt  - Tn: ', mask1=tmask,   & 
     
    203202      !!              - (ta,sa) time averaged (t,s)   (ln_dynhpg_imp = T) 
    204203      !!---------------------------------------------------------------------- 
    205       INTEGER         , INTENT(in   )                               ::  kt       ! ocean time-step index 
    206       CHARACTER(len=3), INTENT(in   )                               ::  cdtype   ! =TRA or TRC (tracer indicator) 
    207       INTEGER         , INTENT(in   )                               ::  kjpt     ! number of tracers 
    208       REAL(wp)        , INTENT(inout), DIMENSION(jpi,jpj,jpk,kjpt)  ::  ptb      ! before tracer fields 
    209       REAL(wp)        , INTENT(inout), DIMENSION(jpi,jpj,jpk,kjpt)  ::  ptn      ! now tracer fields 
    210       REAL(wp)        , INTENT(inout), DIMENSION(jpi,jpj,jpk,kjpt)  ::  pta      ! tracer trend 
    211       !! 
     204      INTEGER         , INTENT(in   )                               ::   kt       ! ocean time-step index 
     205      CHARACTER(len=3), INTENT(in   )                               ::   cdtype   ! =TRA or TRC (tracer indicator) 
     206      INTEGER         , INTENT(in   )                               ::   kjpt     ! number of tracers 
     207      REAL(wp)        , INTENT(inout), DIMENSION(jpi,jpj,jpk,kjpt)  ::   ptb      ! before tracer fields 
     208      REAL(wp)        , INTENT(inout), DIMENSION(jpi,jpj,jpk,kjpt)  ::   ptn      ! now tracer fields 
     209      REAL(wp)        , INTENT(inout), DIMENSION(jpi,jpj,jpk,kjpt)  ::   pta      ! tracer trend 
     210      ! 
    212211      INTEGER  ::   ji, jj, jk, jn   ! dummy loop indices 
    213212      LOGICAL  ::   ll_tra_hpg       ! local logical 
     
    270269      !!              - (ta,sa) time averaged (t,s)   (ln_dynhpg_imp = T) 
    271270      !!---------------------------------------------------------------------- 
    272       INTEGER         , INTENT(in   )                               ::  kt       ! ocean time-step index 
    273       CHARACTER(len=3), INTENT(in   )                               ::  cdtype   ! =TRA or TRC (tracer indicator) 
    274       INTEGER         , INTENT(in   )                               ::  kjpt     ! number of tracers 
    275       REAL(wp)        , INTENT(inout), DIMENSION(jpi,jpj,jpk,kjpt)  ::  ptb      ! before tracer fields 
    276       REAL(wp)        , INTENT(inout), DIMENSION(jpi,jpj,jpk,kjpt)  ::  ptn      ! now tracer fields 
    277       REAL(wp)        , INTENT(inout), DIMENSION(jpi,jpj,jpk,kjpt)  ::  pta      ! tracer trend 
     271      INTEGER         , INTENT(in   )                               ::   kt       ! ocean time-step index 
     272      CHARACTER(len=3), INTENT(in   )                               ::   cdtype   ! =TRA or TRC (tracer indicator) 
     273      INTEGER         , INTENT(in   )                               ::   kjpt     ! number of tracers 
     274      REAL(wp)        , INTENT(inout), DIMENSION(jpi,jpj,jpk,kjpt)  ::   ptb      ! before tracer fields 
     275      REAL(wp)        , INTENT(inout), DIMENSION(jpi,jpj,jpk,kjpt)  ::   ptn      ! now tracer fields 
     276      REAL(wp)        , INTENT(inout), DIMENSION(jpi,jpj,jpk,kjpt)  ::   pta      ! tracer trend 
    278277      !!      
    279278      LOGICAL  ::   ll_tra, ll_tra_hpg, ll_traqsr   ! local logical 
    280279      INTEGER  ::   ji, jj, jk, jn              ! dummy loop indices 
    281       REAL(wp) ::   ztc_a , ztc_n , ztc_b       ! local scalar 
    282       REAL(wp) ::   ztc_f , ztc_d               !   -      - 
    283       REAL(wp) ::   ze3t_b, ze3t_n, ze3t_a      !   -      - 
    284       REAL(wp) ::   ze3t_f, ze3t_d              !   -      - 
    285       REAL(wp) ::   zfact1, zfact2              !   -      - 
     280      REAL(wp) ::   zfact1, ztc_a , ztc_n , ztc_b , ztc_f , ztc_d    ! local scalar 
     281      REAL(wp) ::   zfact2, ze3t_b, ze3t_n, ze3t_a, ze3t_f, ze3t_d   !   -      - 
    286282      !!---------------------------------------------------------------------- 
    287283 
Note: See TracChangeset for help on using the changeset viewer.