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 2026 for branches/DEV_r2006_merge_TRA_TRC – NEMO

Ignore:
Timestamp:
2010-07-29T13:09:48+02:00 (14 years ago)
Author:
cetlod
Message:

Encapsulate active and passive trends in one module, see ticket:694

Location:
branches/DEV_r2006_merge_TRA_TRC/NEMO/OPA_SRC/TRD
Files:
2 added
3 edited

Legend:

Unmodified
Added
Removed
  • branches/DEV_r2006_merge_TRA_TRC/NEMO/OPA_SRC/TRD/trdicp.F90

    r1708 r2026  
    5555CONTAINS 
    5656 
    57    SUBROUTINE trd_2d( ptrd2dx, ptrd2dy, ktrd , ctype, clpas ) 
     57   SUBROUTINE trd_2d( ptrd2dx, ptrd2dy, ktrd , ctype ) 
    5858      !!--------------------------------------------------------------------- 
    5959      !!                  ***  ROUTINE trd_2d  *** 
     
    6666      INTEGER                     , INTENT(in   ) ::   ktrd                ! tracer trend index 
    6767      CHARACTER(len=3)            , INTENT(in   ) ::   ctype               ! momentum ('DYN') or tracers ('TRA') trends 
    68       CHARACTER(len=3)            , INTENT(in   ), OPTIONAL ::   clpas     ! number of passage 
    6968      !! 
    7069      INTEGER  ::   ji, jj                                                 ! loop indices 
    71       CHARACTER(len=3) ::   cpas                                           ! number of passage 
    7270      REAL(wp) ::   zmsku, zbtu, zbt                                       ! temporary scalars 
    7371      REAL(wp) ::   zmskv, zbtv                                            !    "         " 
    7472      !!---------------------------------------------------------------------- 
    7573 
    76       ! Control of optional arguments 
    77       cpas = 'fst' 
    78       IF( PRESENT(clpas) )  cpas = clpas 
    7974 
    8075      ! 1. Mask trends 
     
    123118         ! 
    124119      CASE( 'TRA' )              ! Tracers 
    125          IF( cpas == 'fst' )   THEN 
    126             tmo(ktrd) = 0.e0 
    127             smo(ktrd) = 0.e0 
    128          ENDIF 
     120         tmo(ktrd) = 0.e0 
     121         smo(ktrd) = 0.e0 
    129122         DO jj = 1, jpj 
    130123            DO ji = 1, jpi 
     
    156149         ! 
    157150      CASE( 'TRA' )              ! Tracers 
    158          IF( cpas == 'fst' )   THEN 
    159             t2(ktrd) = 0.e0 
    160             s2(ktrd) = 0.e0 
    161          ENDIF 
     151         t2(ktrd) = 0.e0 
     152         s2(ktrd) = 0.e0 
    162153         DO jj = 1, jpj 
    163154            DO ji = 1, jpi 
     
    173164 
    174165 
    175    SUBROUTINE trd_3d( ptrd3dx, ptrd3dy, ktrd, ctype, clpas ) 
     166   SUBROUTINE trd_3d( ptrd3dx, ptrd3dy, ktrd, ctype ) 
    176167      !!--------------------------------------------------------------------- 
    177168      !!                  ***  ROUTINE trd_3d  *** 
     
    184175      INTEGER,                          INTENT(in   ) ::   ktrd               ! momentum or tracer trend index 
    185176      CHARACTER(len=3),                 INTENT(in   ) ::   ctype              ! momentum ('DYN') or tracers ('TRA') trends 
    186       CHARACTER(len=3),                 INTENT(in   ), OPTIONAL ::   clpas    ! number of passage 
    187177      !! 
    188178      INTEGER ::   ji, jj, jk 
    189       CHARACTER(len=3) ::   cpas                                              ! number of passage 
    190179      REAL(wp) ::   zbt, zbtu, zbtv, zmsku, zmskv                             ! temporary scalars 
    191180      !!---------------------------------------------------------------------- 
    192  
    193       ! Control of optional arguments 
    194       cpas = 'fst' 
    195       IF( PRESENT(clpas) )  cpas = clpas 
    196181 
    197182      ! 1. Mask the trends 
     
    242227         ! 
    243228      CASE( 'TRA' )              ! Tracers 
    244          IF( cpas == 'fst' )   THEN 
    245             tmo(ktrd) = 0.e0 
    246             smo(ktrd) = 0.e0 
    247          ENDIF 
     229         tmo(ktrd) = 0.e0 
     230         smo(ktrd) = 0.e0 
    248231         DO jk = 1, jpkm1 
    249232            DO jj = 1, jpj 
     
    279262         ! 
    280263      CASE( 'TRA' )              ! Tracers 
    281          IF( cpas == 'fst' )   THEN 
    282             t2(ktrd) = 0.e0 
    283             s2(ktrd) = 0.e0 
    284          ENDIF 
     264         t2(ktrd) = 0.e0 
     265         s2(ktrd) = 0.e0 
    285266         DO jk = 1, jpk 
    286267            DO jj = 1, jpj 
     
    600581            WRITE (numout,*) 
    601582            WRITE (numout,9400) kt 
    602             WRITE (numout,9401) (tmo(jpicpt_xad)+tmo(jpicpt_yad))/ tvolt, (smo(jpicpt_xad)+smo(jpicpt_yad))/ tvolt 
     583            WRITE (numout,9401)  tmo(jpicpt_xad) / tvolt, smo(jpicpt_xad) / tvolt 
     584            WRITE (numout,9411)  tmo(jpicpt_yad) / tvolt, smo(jpicpt_yad) / tvolt 
    603585            WRITE (numout,9402)  tmo(jpicpt_zad) / tvolt, smo(jpicpt_zad) / tvolt 
    604586            WRITE (numout,9403)  tmo(jpicpt_ldf) / tvolt, smo(jpicpt_ldf) / tvolt 
     
    6175999400     FORMAT(' tracer trend at it= ',i6,' :     temperature',   & 
    618600              '              salinity',/' ============================') 
    619 9401     FORMAT(' horizontal advection        ',e20.13,'     ',e20.13) 
     6019401     FORMAT(' zonal      advection        ',e20.13,'     ',e20.13) 
     6029411     FORMAT(' meridional advection        ',e20.13,'     ',e20.13) 
    6206039402     FORMAT(' vertical advection          ',e20.13,'     ',e20.13) 
    6216049403     FORMAT(' horizontal diffusion        ',e20.13,'     ',e20.13) 
     
    633616            WRITE (numout,*) 
    634617            WRITE (numout,9420) kt 
    635             WRITE (numout,9421) ( t2(jpicpt_xad)+t2(jpicpt_yad) )/ tvolt, ( s2(jpicpt_xad)+s2(jpicpt_yad) )/ tvolt 
     618            WRITE (numout,9421)   t2(jpicpt_xad) / tvolt, s2(jpicpt_xad) / tvolt 
     619            WRITE (numout,9431)   t2(jpicpt_yad) / tvolt, s2(jpicpt_yad) / tvolt 
    636620            WRITE (numout,9422)   t2(jpicpt_zad) / tvolt, s2(jpicpt_zad) / tvolt 
    637621            WRITE (numout,9423)   t2(jpicpt_ldf) / tvolt, s2(jpicpt_ldf) / tvolt 
     
    6506349420     FORMAT(' tracer**2 trend at it= ', i6, ' :      temperature',   & 
    651635            '               salinity', /, ' ===============================') 
    652 9421     FORMAT(' horizontal advection      * t   ', e20.13, '     ', e20.13) 
     6369421     FORMAT(' zonal      advection      * t   ', e20.13, '     ', e20.13) 
     6379431     FORMAT(' meridional advection      * t   ', e20.13, '     ', e20.13) 
    6536389422     FORMAT(' vertical advection        * t   ', e20.13, '     ', e20.13) 
    6546399423     FORMAT(' horizontal diffusion      * t   ', e20.13, '     ', e20.13) 
     
    705690 
    706691CONTAINS 
    707    SUBROUTINE trd_2d( ptrd2dx, ptrd2dy, ktrd , ctype, clpas )       ! Empty routine 
     692   SUBROUTINE trd_2d( ptrd2dx, ptrd2dy, ktrd , ctype )       ! Empty routine 
    708693      REAL, DIMENSION(:,:) ::   ptrd2dx, ptrd2dy 
    709694      INTEGER                     , INTENT(in   ) ::   ktrd         ! tracer trend index 
    710695      CHARACTER(len=3)            , INTENT(in   ) ::   ctype        ! momentum ('DYN') or tracers ('TRA') trends 
    711       CHARACTER(len=3), INTENT(in), OPTIONAL ::   clpas             ! number of passage 
    712696      WRITE(*,*) 'trd_2d: You should not have seen this print! error ?', & 
    713           &       ptrd2dx(1,1), ptrd2dy(1,1), ktrd, ctype, clpas 
     697          &       ptrd2dx(1,1), ptrd2dy(1,1), ktrd, ctype 
    714698   END SUBROUTINE trd_2d 
    715    SUBROUTINE trd_3d( ptrd3dx, ptrd3dy, ktrd , ctype, clpas )       ! Empty routine 
     699   SUBROUTINE trd_3d( ptrd3dx, ptrd3dy, ktrd , ctype )       ! Empty routine 
    716700      REAL, DIMENSION(:,:,:) ::   ptrd3dx, ptrd3dy 
    717701      INTEGER                     , INTENT(in   ) ::   ktrd         ! tracer trend index 
    718702      CHARACTER(len=3)            , INTENT(in   ) ::   ctype        ! momentum ('DYN') or tracers ('TRA') trends 
    719       CHARACTER(len=3), INTENT(in), OPTIONAL ::   clpas             ! number of passage 
    720703      WRITE(*,*) 'trd_3d: You should not have seen this print! error ?', & 
    721           &       ptrd3dx(1,1,1), ptrd3dy(1,1,1), ktrd, ctype, clpas 
     704          &       ptrd3dx(1,1,1), ptrd3dy(1,1,1), ktrd, ctype 
    722705   END SUBROUTINE trd_3d 
    723706   SUBROUTINE trd_icp_init               ! Empty routine 
  • branches/DEV_r2006_merge_TRA_TRC/NEMO/OPA_SRC/TRD/trdmod.F90

    r1708 r2026  
    4343CONTAINS 
    4444 
    45    SUBROUTINE trd_mod( ptrdx, ptrdy, ktrd, ctype, kt, cnbpas ) 
     45   SUBROUTINE trd_mod( ptrdx, ptrdy, ktrd, ctype, kt ) 
    4646      !!--------------------------------------------------------------------- 
    4747      !!                  ***  ROUTINE trd_mod  *** 
     
    5353      INTEGER, INTENT( in ) ::   ktrd                              ! tracer trend index 
    5454      CHARACTER(len=3), INTENT( in ) ::   ctype                    ! momentum or tracers trends type 'DYN'/'TRA' 
    55       CHARACTER(len=3), INTENT( in ), OPTIONAL ::   cnbpas         ! number of passage 
    5655      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT( inout ) ::   ptrdx ! Temperature or U trend  
    5756      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT( inout ) ::   ptrdy ! Salinity    or V trend 
    5857      !! 
    5958      INTEGER ::   ji, jj 
    60       CHARACTER(len=3) ::   ccpas                                  ! number of passage 
    6159      REAL(wp), DIMENSION(jpi,jpj) ::   ztswu, ztswv               ! 2D workspace 
    6260      REAL(wp), DIMENSION(jpi,jpj) ::   ztbfu, ztbfv               ! 2D workspace 
     
    6563 
    6664      z2dx(:,:)   = 0.e0   ;   z2dy(:,:)   = 0.e0                  ! initialization of workspace arrays 
    67  
    68       ! Control of optional arguments 
    69       ccpas = 'fst' 
    70       IF( PRESENT(cnbpas) )  ccpas = cnbpas 
    7165 
    7266      IF( neuler == 0 .AND. kt == nit000    ) THEN   ;   r2dt =      rdt      ! = rdtra (restarting with Euler time stepping) 
     
    9589            CASE ( jptra_trd_yad )   ;   CALL trd_icp( ptrdx, ptrdy, jpicpt_yad, ctype )   ! y- horiz adv 
    9690            CASE ( jptra_trd_zad )                                                         ! z- vertical adv  
    97                CALL trd_icp( ptrdx, ptrdy, jpicpt_zad, ctype, clpas=ccpas )    
     91               CALL trd_icp( ptrdx, ptrdy, jpicpt_zad, ctype )    
    9892               ! compute the surface flux condition wn(:,:,1)*tn(:,:,1) 
    9993               z2dx(:,:) = wn(:,:,1)*tn(:,:,1)/fse3t(:,:,1) 
     
    235229 
    236230CONTAINS 
    237    SUBROUTINE trd_mod(ptrd3dx, ptrd3dy, ktrd , ctype, kt, cnbpas)   ! Empty routine 
     231   SUBROUTINE trd_mod(ptrd3dx, ptrd3dy, ktrd , ctype, kt )   ! Empty routine 
    238232      REAL, DIMENSION(:,:,:), INTENT( in ) ::   & 
    239233          ptrd3dx,                     &                           ! Temperature or U trend  
     
    242236      INTEGER, INTENT( in ) ::   kt                                ! Time step 
    243237      CHARACTER(len=3), INTENT( in ) ::  ctype                     ! momentum or tracers trends type 
    244       CHARACTER(len=3), INTENT( in ), OPTIONAL ::   cnbpas         ! number of passage 
    245238      WRITE(*,*) 'trd_3d: You should not have seen this print! error ?', ptrd3dx(1,1,1) 
    246239      WRITE(*,*) ' "   ": You should not have seen this print! error ?', ptrd3dy(1,1,1) 
     
    248241      WRITE(*,*) ' "   ": You should not have seen this print! error ?', ctype 
    249242      WRITE(*,*) ' "   ": You should not have seen this print! error ?', kt 
    250       WRITE(*,*) ' "   ": You should not have seen this print! error ?', cnbpas 
    251243   END SUBROUTINE trd_mod 
    252244#   endif 
  • branches/DEV_r2006_merge_TRA_TRC/NEMO/OPA_SRC/TRD/trdmod_oce.F90

    r1601 r2026  
    2424 
    2525# if defined key_trdtra   ||   defined key_trdmld 
    26    LOGICAL , PUBLIC ::   l_trdtra = .TRUE.              !: tracers  trend flag 
     26   LOGICAL , PUBLIC ::   l_trdtra = .TRUE.                !: tracers  trend flag 
    2727# else 
    28    LOGICAL , PUBLIC ::   l_trdtra = .FALSE.             !: tracers  trend flag 
     28   LOGICAL , PUBLIC ::   l_trdtra = .FALSE.               !: tracers  trend flag 
    2929# endif 
    3030# if defined key_trddyn   ||   defined key_trdvor 
    31    LOGICAL , PUBLIC ::   l_trddyn = .TRUE.              !: momentum trend flag 
     31   LOGICAL , PUBLIC ::   l_trddyn = .TRUE.                !: momentum trend flag 
    3232# else 
    33    LOGICAL , PUBLIC ::   l_trddyn = .FALSE.             !: momentum trend flag 
     33   LOGICAL , PUBLIC ::   l_trddyn = .FALSE.               !: momentum trend flag 
    3434# endif 
    35  
     35# if ( defined key_trdtrc && defined key_iomput )  ||  defined key_trdmld_trc 
     36   LOGICAL , PUBLIC ::   l_trdtrc = .TRUE.                !: tracers  trend flag 
     37# else 
     38   LOGICAL , PUBLIC ::   l_trdtrc = .FALSE.               !: tracers  trend flag 
     39# endif 
    3640   !                                                   !!! Active tracers trends indexes 
    3741   INTEGER, PUBLIC, PARAMETER ::   jptra_trd_xad =  1   !: x- horizontal advection 
     
    4751   INTEGER, PUBLIC, PARAMETER ::   jptra_trd_nsr = 11   !: non solar radiation 
    4852   INTEGER, PUBLIC, PARAMETER ::   jptra_trd_atf = 12   !: Asselin correction 
     53#if defined key_top 
     54   !!* Passive tracers trends indexes 
     55   INTEGER, PUBLIC, PARAMETER ::   jptra_trd_sms  = 13   !: sources m. sinks 
     56   INTEGER, PUBLIC, PARAMETER ::   jptra_trd_radn = 14   !: corr. trn<0 in trcrad 
     57   INTEGER, PUBLIC, PARAMETER ::   jptra_trd_radb = 15   !: corr. trb<0 in trcrad (like atf) 
     58#endif 
    4959    
    5060   !                                                   !!! Momentum trends indexes 
Note: See TracChangeset for help on using the changeset viewer.