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 334 for trunk/NEMO/TOP_SRC – NEMO

Changeset 334 for trunk/NEMO/TOP_SRC


Ignore:
Timestamp:
2005-11-14T12:53:13+01:00 (18 years ago)
Author:
opalod
Message:

nemo_v1_update_022 : CE + RB + CT : add print control possibility

Location:
trunk/NEMO/TOP_SRC/TRP
Files:
26 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMO/TOP_SRC/TRP/trcadv_cen2.F90

    r274 r334  
    1414   USE trc                 ! ocean passive tracers variables 
    1515   USE trcbbl              ! advective passive tracers in the BBL 
     16   USE prtctl_trc 
    1617 
    1718   IMPLICIT NONE 
     
    2425#  include "passivetrc_substitute.h90" 
    2526   !!---------------------------------------------------------------------- 
    26    !!  TOP 1.0,  LOCEAN-IPSL (2005)  
    27    !! $Header$  
    28    !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt  
     27   !!   OPA 9.0 , LODYC-IPSL (2003) 
    2928   !!---------------------------------------------------------------------- 
    3029 
     
    133132         zfui1, zfvj1                          !    "         " 
    134133#endif 
     134      CHARACTER (len=22) :: charout 
    135135      !!---------------------------------------------------------------------- 
    136136 
     
    154154 
    155155 
    156       DO jn = 1, jptra 
    157  
    158156      ! Upstream / centered scheme indicator 
    159157      ! ------------------------------------ 
    160158  
    161          DO jk = 1, jpk 
    162             DO jj = 1, jpj 
    163                DO ji = 1, jpi 
    164                   zind(ji,jj,jk) =  MAX ( upsrnfh(ji,jj) * upsrnfz(jk),     &  ! changing advection scheme near runoff 
    165                      &                    upsadv(ji,jj)                     &  ! in the vicinity of some straits 
     159      DO jk = 1, jpk 
     160         DO jj = 1, jpj 
     161            DO ji = 1, jpi 
     162               zind(ji,jj,jk) =  MAX ( upsrnfh(ji,jj) * upsrnfz(jk),     &  ! changing advection scheme near runoff 
     163                  &                    upsadv(ji,jj)                     &  ! in the vicinity of some straits 
    166164#if defined key_ice_lim 
    167                      &                  , tmask(ji,jj,jk)                   &  ! half upstream tracer fluxes 
    168                      &                  * MAX( 0., SIGN( 1., fzptn(ji,jj)   &  ! if tn < ("freezing"+0.1 ) 
    169                      &                                +0.1-tn(ji,jj,jk) ) ) & 
    170 #endif 
    171                      &                  ) 
    172                END DO 
     165                  &                  , tmask(ji,jj,jk)                   &  ! half upstream tracer fluxes 
     166                  &                  * MAX( 0., SIGN( 1., fzptn(ji,jj)   &  ! if tn < ("freezing"+0.1 ) 
     167                  &                                +0.1-tn(ji,jj,jk) ) ) & 
     168#endif 
     169                  &                  ) 
    173170            END DO 
    174171         END DO 
    175  
    176  
     172      END DO 
     173 
     174 
     175      DO jn = 1, jptra 
    177176         ! I. Horizontal advective fluxes 
    178177         ! ------------------------------ 
     
    256255         END DO                                           !   End of slab 
    257256         !                                                ! =============== 
    258  
    259          IF(ln_ctl) THEN         ! print mean trends (used for debugging) 
    260             ztra = SUM( tra(2:nictle,2:njctle,1:jpkm1,jn) * tmask(2:nictle,2:njctle,1:jpkm1) ) 
    261             WRITE(numout,*) ' trc/had - ',ctrcnm(jn),' : ', ztra-tra_ctl(jn)  
    262             tra_ctl(jn) = ztra  
    263          ENDIF 
    264  
    265          ! II. Vertical advection 
    266          ! ---------------------- 
     257      ENDDO 
     258 
     259      IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     260         WRITE(charout, FMT="('centered2 - had')") 
     261         CALL prt_ctl_trc_info(charout) 
     262         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm,clinfo2='trd') 
     263      ENDIF 
     264       
     265      ! II. Vertical advection 
     266      ! ---------------------- 
     267      DO jn = 1, jptra 
    267268 
    268269         ! Bottom value : flux set to zero 
     
    320321         END DO 
    321322 
    322          IF(ln_ctl) THEN         ! print mean trends (used for debugging) 
    323             ztra = SUM( tra(2:nictle,2:njctle,1:jpkm1,jn) * tmask(2:nictle,2:njctle,1:jpkm1) ) 
    324             WRITE(numout,*) ' trc/zad - ',ctrcnm(jn),' : ', ztra-tra_ctl(jn), ' centered2'  
    325             tra_ctl(jn) = ztra  
    326          ENDIF 
    327  
    328323      END DO 
    329324 
     325      IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     326         WRITE(charout, FMT="('centered - zad')") 
     327         CALL prt_ctl_trc_info(charout) 
     328         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm,clinfo2='trd') 
     329      ENDIF 
    330330 
    331331   END SUBROUTINE trc_adv_cen2 
  • trunk/NEMO/TOP_SRC/TRP/trcadv_muscl.F90

    r274 r334  
    1515   USE trcbbl          ! advective passive tracers in the BBL 
    1616   USE lib_mpp 
     17   USE prtctl_trc      ! Print control for debbuging 
    1718 
    1819   IMPLICIT NONE 
     
    2526#  include "passivetrc_substitute.h90" 
    2627   !!---------------------------------------------------------------------- 
    27    !!  TOP 1.0,  LOCEAN-IPSL (2005)  
    28    !! $Header$  
    29    !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt  
     28   !!   OPA 9.0 , LODYC-IPSL (2003) 
    3029   !!---------------------------------------------------------------------- 
    3130 
     
    7978      REAL(wp) ::   zfui, zfvj 
    8079#endif 
    81  
     80      CHARACTER (len=22) :: charout 
    8281      !!---------------------------------------------------------------------- 
    8382 
     
    231230            END DO 
    232231         END DO 
    233  
    234          IF(ln_ctl) THEN         ! print mean trends (used for debugging) 
    235             ztra = SUM( tra(2:nictle,2:njctle,1:jpkm1,jn) * tmask(2:nictle,2:njctle,1:jpkm1) ) 
    236             WRITE(numout,*) ' trc/had  - ',ctrcnm(jn),' : ', ztra-tra_ctl(jn), ' muscl'  
    237             tra_ctl(jn) = ztra  
    238          ENDIF 
     232      ENDDO 
     233 
     234      IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     235         WRITE(charout, FMT="('muscl - had')") 
     236         CALL prt_ctl_trc_info(charout) 
     237         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm,clinfo2='trd') 
     238      ENDIF 
    239239 
    240240         ! II. Vertical advective fluxes 
    241241         ! ----------------------------- 
    242242 
     243      DO jn = 1, jptra 
    243244         ! First guess of the slope 
    244245         ! interior values 
     
    317318         END DO 
    318319 
    319          IF(ln_ctl) THEN         ! print mean trends (used for debugging) 
    320             ztra = SUM( tra(2:nictle,2:njctle,1:jpkm1,jn) * tmask(2:nictle,2:njctle,1:jpkm1) ) 
    321             WRITE(numout,*) ' trc/zad  - ',ctrcnm(jn),' : ', ztra-tra_ctl(jn), ' muscl'  
    322             tra_ctl(jn) = ztra  
    323          ENDIF 
    324  
    325320      END DO 
     321 
     322      IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     323         WRITE(charout, FMT="('muscl - zad')") 
     324         CALL prt_ctl_trc_info(charout) 
     325         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm,clinfo2='trd') 
     326      ENDIF 
    326327 
    327328END SUBROUTINE trc_adv_muscl 
  • trunk/NEMO/TOP_SRC/TRP/trcadv_muscl2.F90

    r274 r334  
    1414   USE lbclnk          ! ocean lateral boundary conditions (or mpp link) 
    1515   USE trcbbl          ! advective passive tracers in the BBL 
     16   USE prtctl_trc          ! Print control for debbuging 
    1617 
    1718   IMPLICIT NONE 
     
    2829#  include "passivetrc_substitute.h90" 
    2930   !!---------------------------------------------------------------------- 
    30    !!  TOP 1.0,  LOCEAN-IPSL (2005)  
    31    !! $Header$  
    32    !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt  
     31   !!   OPA 9.0 , LODYC-IPSL (2003) 
    3332   !!---------------------------------------------------------------------- 
    3433 
     
    8281      REAL(wp) ::   zfui, zfvj 
    8382#endif 
     83      CHARACTER (len=22) :: charout 
    8484      !!---------------------------------------------------------------------- 
    8585 
     
    279279            END DO 
    280280         END DO 
    281  
    282          IF(ln_ctl) THEN         ! print mean trends (used for debugging) 
    283             ztra = SUM( tra(2:nictle,2:njctle,1:jpkm1,jn) * tmask(2:nictle,2:njctle,1:jpkm1) ) 
    284             WRITE(numout,*) ' trc/had  - ',ctrcnm(jn),' : ', ztra-tra_ctl(jn), ' muscl'  
    285             tra_ctl(jn) = ztra  
    286          ENDIF 
    287  
    288          ! II. Vertical advective fluxes 
    289          ! ----------------------------- 
     281      ENDDO 
     282 
     283      IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     284         WRITE(charout, FMT="('muscl2 - had')") 
     285         CALL prt_ctl_trc_info(charout) 
     286         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm,clinfo2='trd') 
     287      ENDIF 
     288 
     289      ! II. Vertical advective fluxes 
     290      ! ----------------------------- 
     291 
     292      DO jn = 1, jptra 
    290293 
    291294         ! First guess of the slope 
     
    379382         END DO 
    380383 
    381          IF(ln_ctl) THEN         ! print mean trends (used for debugging) 
    382             ztra = SUM( tra(2:nictle,2:njctle,1:jpkm1,jn) * tmask(2:nictle,2:njctle,1:jpkm1) ) 
    383             WRITE(numout,*) ' trc/zad  - ',ctrcnm(jn),' : ', ztra-tra_ctl(jn), ' muscl2'  
    384             tra_ctl(jn) = ztra  
    385          ENDIF 
    386  
    387384      END DO 
     385 
     386      IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     387         WRITE(charout, FMT="('muscl2 - zad')") 
     388         CALL prt_ctl_trc_info(charout) 
     389         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm,clinfo2='trd') 
     390      ENDIF 
    388391 
    389392   END SUBROUTINE trc_adv_muscl2 
  • trunk/NEMO/TOP_SRC/TRP/trcadv_smolar.F90

    r274 r334  
    1515   USE lbclnk              ! ocean lateral boundary conditions (or mpp link) 
    1616   USE trcbbl              ! advective passive tracers in the BBL 
     17   USE prtctl_trc      ! Print control for debbuging 
    1718 
    1819   IMPLICIT NONE 
     
    2930#  include "passivetrc_substitute.h90" 
    3031   !!---------------------------------------------------------------------- 
    31    !!  TOP 1.0,  LOCEAN-IPSL (2005)  
    32    !! $Header$  
    33    !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt  
     32   !!   OPA 9.0 , LODYC-IPSL (2003) 
    3433   !!---------------------------------------------------------------------- 
    3534CONTAINS 
     
    9695         zbuf 
    9796 
     97#if defined key_trc_diatrd 
     98      REAL(wp) :: zgm, zgz 
     99#endif 
     100 
    98101      REAL(wp) :: zbtr, ztra 
    99102      REAL(wp) :: zfp_ui, zfp_vj, zfm_ui, zfm_vj, zfp_w, zfm_w 
    100  
     103      CHARACTER (len=22) :: charout 
    101104      !!---------------------------------------------------------------------- 
    102105 
     
    496499        ! Lateral boundary conditions on trtrd: 
    497500 
    498         CALL lbc_lnk( trtrd(1,1,1,jn,1), 'T', 1. ) 
    499         CALL lbc_lnk( trtrd(1,1,1,jn,2), 'T', 1. ) 
    500         CALL lbc_lnk( trtrd(1,1,1,jn,3), 'T', 1. ) 
    501 #endif 
    502  
    503         IF(ln_ctl) THEN         ! print mean trends (used for debugging) 
    504            ztra = SUM( tra(2:nictle,2:njctle,1:jpkm1,jn) * tmask(2:nictle,2:njctle,1:jpkm1) ) 
    505            WRITE(numout,*) ' trc/zad  - ',ctrcnm(jn),' : ', ztra-tra_ctl(jn), ' smolar'  
    506            tra_ctl(jn) = ztra  
    507         ENDIF 
     501        CALL lbc_lnk( trtrd(:,:,:,jn,1), 'T', 1. ) 
     502        CALL lbc_lnk( trtrd(:,:,:,jn,2), 'T', 1. ) 
     503        CALL lbc_lnk( trtrd(:,:,:,jn,3), 'T', 1. ) 
     504#endif 
     505 
     506  
    508507        ! END of tracer loop 
    509508        ! ================== 
    510509     ENDDO 
     510 
     511      IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     512         WRITE(charout, FMT="('smolar - adv')") 
     513         CALL prt_ctl_trc_info(charout) 
     514         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm,clinfo2='trd') 
     515      ENDIF 
    511516      
    512517  END SUBROUTINE trc_adv_smolar 
  • trunk/NEMO/TOP_SRC/TRP/trcadv_tvd.F90

    r274 r334  
    1616   USE lbclnk              ! ocean lateral boundary conditions (or mpp link) 
    1717   USE trcbbl              ! advective passive tracers in the BBL 
     18   USE prtctl_trc      ! Print control for debbuging 
    1819 
    1920   IMPLICIT NONE 
     
    2627#  include "passivetrc_substitute.h90" 
    2728   !!---------------------------------------------------------------------- 
    28    !!  TOP 1.0,  LOCEAN-IPSL (2005)  
    29    !! $Header$  
    30    !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt  
     29   !!   OPA 9.0 , LODYC-IPSL (2003) 
    3130   !!---------------------------------------------------------------------- 
    3231 
     
    7978         zfp_ui, zfp_vj, zfp_wk,         &  !    "         " 
    8079         zfm_ui, zfm_vj, zfm_wk             !    "         " 
     80 
     81      CHARACTER (len=22) :: charout 
    8182      !!---------------------------------------------------------------------- 
    8283 
     
    234235         END DO 
    235236 
    236          IF(ln_ctl) THEN         ! print mean trends (used for debugging) 
    237             ztra = SUM( tra(2:nictle,2:njctle,1:jpkm1,jn) * tmask(2:nictle,2:njctle,1:jpkm1) ) 
    238             WRITE(numout,*) ' trc/zad  - ',ctrcnm(jn),' : ', ztra-tra_ctl(jn), ' tvd'  
    239             tra_ctl(jn) = ztra  
    240          ENDIF 
    241  
    242       END DO 
     237      END DO 
     238 
     239      IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     240         WRITE(charout, FMT="('tvd - adv')") 
     241         CALL prt_ctl_trc_info(charout) 
     242         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm,clinfo2='trd') 
     243      ENDIF 
    243244 
    244245   END SUBROUTINE trc_adv_tvd 
     
    289290      ! -------------------- 
    290291      ! large negative value (-zbig) inside land 
    291       WHERE( tmask(:,:,:) == 0. ) 
    292          pbef(:,:,:) = -zbig 
    293          paft(:,:,:) = -zbig 
    294       ENDWHERE  
     292      ! large negative value (-zbig) inside land 
     293      pbef(:,:,:) = pbef(:,:,:) * tmask(:,:,:) - zbig * ( 1.e0 - tmask(:,:,:) ) 
     294      paft(:,:,:) = paft(:,:,:) * tmask(:,:,:) - zbig * ( 1.e0 - tmask(:,:,:) ) 
    295295      ! search maximum in neighbourhood 
    296296      DO jk = 1, jpkm1 
     
    309309      END DO 
    310310      ! large positive value (+zbig) inside land 
    311       WHERE( tmask(:,:,:) == 0. ) 
    312          pbef(:,:,:) = +zbig 
    313          paft(:,:,:) = +zbig 
    314       ENDWHERE 
     311      pbef(:,:,:) = pbef(:,:,:) * tmask(:,:,:) + zbig * ( 1.e0 - tmask(:,:,:) ) 
     312      paft(:,:,:) = paft(:,:,:) * tmask(:,:,:) + zbig * ( 1.e0 - tmask(:,:,:) ) 
    315313      ! search minimum in neighbourhood 
    316314      DO jk = 1, jpkm1 
  • trunk/NEMO/TOP_SRC/TRP/trcbbc.F90

    r274 r334  
    1414   USE oce_trc             ! ocean dynamics and active tracers variables 
    1515   USE trc                 ! ocean passive tracers variables 
     16   USE prtctl_trc          ! Print control for debbuging 
    1617  
    1718   IMPLICIT NONE 
     
    3940#  include "passivetrc_substitute.h90" 
    4041   !!---------------------------------------------------------------------- 
    41    !!  TOP 1.0,  LOCEAN-IPSL (2005)  
    42    !! $Header$  
    43    !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt  
     42   !!  OPA 9.0 , LODYC-IPSL (2003) 
    4443   !!---------------------------------------------------------------------- 
    4544 
     
    8382#endif 
    8483      REAL(wp) ::   ztra                ! temporary scalar 
     84      CHARACTER (len=22) :: charout 
    8585      !!---------------------------------------------------------------------- 
    8686 
     
    106106            END DO 
    107107#endif 
    108             IF(ln_ctl) THEN         ! print mean trends (used for debugging) 
    109                ztra = SUM( tra(2:nictle,2:njctle,1:jpkm1,jn) * tmask(2:nictle,2:njctle,1:jpkm1) ) 
    110                WRITE(numout,*) ' trc/bbc  - ',ctrcnm(jn),' : ', ztra-tra_ctl(jn)  
    111                tra_ctl(jn) = ztra  
    112             ENDIF 
    113          END DO 
    114  
     108         END DO 
     109 
     110         IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     111            WRITE(charout, FMT="('bbc')") 
     112            CALL prt_ctl_trc_info(charout) 
     113            CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm,clinfo2='trd') 
     114         ENDIF 
    115115      END SELECT 
    116116 
  • trunk/NEMO/TOP_SRC/TRP/trcbbl.F90

    r274 r334  
    1818   USE oce_trc             ! ocean dynamics and active tracers variables 
    1919   USE trc                 ! ocean passive tracers variables 
     20   USE prtctl_trc          ! Print control for debbuging 
    2021 
    2122   IMPLICIT NONE 
     
    4849#  include "passivetrc_substitute.h90" 
    4950   !!---------------------------------------------------------------------- 
    50    !!  TOP 1.0,  LOCEAN-IPSL (2005)  
    51    !! $Header$  
    52    !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt  
     51   !!   OPA 9.0 , LODYC-IPSL (2003) 
    5352   !!---------------------------------------------------------------------- 
    5453 
     
    117116        ztnb, zsnb, zdep,                & 
    118117        ztrb, zahu, zahv 
     118      CHARACTER (len=22) :: charout 
    119119      REAL(wp) ::   & 
    120120         fsalbt, pft, pfs, pfh              ! statement function 
     
    204204#  endif 
    205205 
     206!! 
     207!!     OFFLINE VERSION OF DIFFUSIVE BBL 
     208!! 
     209#if defined key_off_tra 
     210 
     211      ! 2. Additional second order diffusive trends 
     212      ! ------------------------------------------- 
     213 
     214      DO jn = 1, jptra 
     215         ! first derivative (gradient) 
     216          
     217#  if defined key_vectopt_loop   &&   ! defined key_autotasking 
     218         jj = 1 
     219         DO ji = 1, jpij   ! vector opt. (forced unrolling) 
     220#  else 
     221         DO jj = 1, jpj 
     222            DO ji = 1, jpi 
     223#  endif 
     224               ik = mbkt(ji,jj)  
     225               ztrb(ji,jj) = trb(ji,jj,ik,jn) * tmask(ji,jj,1) 
     226#  if ! defined key_vectopt_loop   ||   defined key_autotasking 
     227            END DO 
     228#  endif 
     229         END DO 
     230 
     231#  if defined key_vectopt_loop   &&   ! defined key_autotasking 
     232         jj = 1 
     233         DO ji = 1, jpij-jpi   ! vector opt. (forced unrolling) 
     234#  else 
     235         DO jj = 1, jpjm1 
     236            DO ji = 1, jpim1 
     237#  endif 
     238               zkx(ji,jj) = bblx(ji,jj) * zahu(ji,jj) * ( ztrb(ji+1,jj) - ztrb(ji,jj) ) 
     239               zky(ji,jj) = bbly(ji,jj) * zahv(ji,jj) * ( ztrb(ji,jj+1) - ztrb(ji,jj) ) 
     240#  if ! defined key_vectopt_loop   ||   defined key_autotasking 
     241            END DO 
     242#  endif 
     243         END DO 
     244!! 
     245!!  ONLINE VERSION OF DIFFUSIVE BBL 
     246!! 
     247#else 
    206248      ! 1. Criteria of additional bottom diffusivity: grad(rho).grad(h)<0 
    207249      ! -------------------------------------------- 
     
    257299      END DO 
    258300 
    259  
    260301      ! 2. Additional second order diffusive trends 
    261302      ! ------------------------------------------- 
     
    263304      DO jn = 1, jptra 
    264305         ! first derivative (gradient) 
    265           
     306 
    266307#  if defined key_vectopt_loop   &&   ! defined key_autotasking 
    267308         jj = 1 
     
    271312            DO ji = 1, jpi 
    272313#  endif 
    273                ik = mbkt(ji,jj)  
     314               ik = mbkt(ji,jj) 
    274315               ztrb(ji,jj) = trb(ji,jj,ik,jn) * tmask(ji,jj,1) 
    275316#  if ! defined key_vectopt_loop   ||   defined key_autotasking 
     
    277318#  endif 
    278319         END DO 
    279  
    280320#  if defined key_vectopt_loop   &&   ! defined key_autotasking 
    281321         jj = 1 
     
    291331#  endif 
    292332         END DO 
     333 
     334#endif 
    293335 
    294336         IF( cp_cfg == "orca" ) THEN 
     
    341383#  endif 
    342384         END DO 
    343          IF(ln_ctl) THEN         ! print mean trends (used for debugging) 
    344             ztra = SUM( tra(2:nictle,2:njctle,1:jpkm1,jn) * tmask(2:nictle,2:njctle,1:jpkm1) ) 
    345             WRITE(numout,*) ' trc/bbl  - ',ctrcnm(jn),' : ', ztra-tra_ctl(jn)  
    346             tra_ctl(jn) = ztra  
    347          ENDIF 
    348       END DO 
    349  
     385 
     386      END DO 
     387 
     388      IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     389         WRITE(charout, FMT="('bbl - dif')") 
     390         CALL prt_ctl_trc_info(charout) 
     391         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm,clinfo2='trd') 
     392      ENDIF 
    350393 
    351394   END SUBROUTINE trc_bbl_dif 
  • trunk/NEMO/TOP_SRC/TRP/trcbbl_adv.h90

    r274 r334  
    44 
    55   !!---------------------------------------------------------------------- 
    6    !!  TOP 1.0,  LOCEAN-IPSL (2005)  
    7    !! $Header$  
    8    !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt  
     6   !!   OPA 9.0 , LODYC-IPSL  (2003) 
    97   !!---------------------------------------------------------------------- 
    108 
     
    7977      REAL(wp) ::   & 
    8078         fsalbt, pft, pfs, pfh             ! statement function 
     79      CHARACTER (len=22) :: charout 
    8180      !!---------------------------------------------------------------------- 
    8281      ! ratio alpha/beta 
     
    384383#endif 
    385384          END DO 
    386           IF(ln_ctl) THEN         ! print mean trends (used for debugging) 
    387              ztra = SUM( tra(2:nictle,2:njctle,1:jpkm1,jn) * tmask(2:nictle,2:njctle,1:jpkm1) ) 
    388              WRITE(numout,*) ' trc/bbl  - ',ctrcnm(jn),' : ', ztra-tra_ctl(jn)  
    389              tra_ctl(jn) = ztra  
    390           ENDIF 
    391  
    392        END DO 
    393            
     385 
     386       END DO 
     387 
     388      IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     389         WRITE(charout, FMT="('bbl - adv')") 
     390         CALL prt_ctl_trc_info(charout) 
     391         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm,clinfo2='trd') 
     392      ENDIF          
    394393       ! 6. Vertical advection velocities 
    395394       ! -------------------------------- 
  • trunk/NEMO/TOP_SRC/TRP/trcdmp.F90

    r274 r334  
    1919   USE trctrp_lec      ! passive tracers transport 
    2020   USE trcdta 
     21   USE prtctl_trc      ! Print control for debbuging 
    2122 
    2223   IMPLICIT NONE 
     
    3536#  include "passivetrc_substitute.h90" 
    3637   !!---------------------------------------------------------------------- 
    37    !!  TOP 1.0,  LOCEAN-IPSL (2005)  
    38    !! $Header$  
    39    !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt  
     38   !!   OPA 9.0 , LODYC-IPSL (2003) 
    4039   !!---------------------------------------------------------------------- 
    4140 
     
    7473      INTEGER  ::   ji, jj, jk, jn     ! dummy loop indices 
    7574      REAL(wp) ::   ztest, ztra, zdt   ! temporary scalars 
     75      CHARACTER (len=22) :: charout 
    7676      !!---------------------------------------------------------------------- 
    7777 
     
    157157         ENDIF 
    158158 
    159          IF(ln_ctl) THEN         ! print mean trends (used for debugging) 
    160             ztra = SUM( tra(2:nictle,2:njctle,1:jpkm1,jn) * tmask(2:nictle,2:njctle,1:jpkm1) ) 
    161             WRITE(numout,*) ' trc/dmp  - ',ctrcnm(jn),' : ', ztra-tra_ctl(jn)  
    162             tra_ctl(jn) = ztra  
    163          ENDIF 
    164  
    165159      END DO 
    166     
     160 
     161     IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     162         WRITE(charout, FMT="('dmp')") 
     163         CALL prt_ctl_trc_info(charout) 
     164         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm,clinfo2='trd') 
     165      ENDIF 
     166   
    167167      trb(:,:,:,:) = trn(:,:,:,:) 
    168168    
  • trunk/NEMO/TOP_SRC/TRP/trcldf_bilap.F90

    r274 r334  
    1313   USE trc             ! ocean passive tracers variables 
    1414   USE lbclnk          ! ocean lateral boundary conditions (or mpp link) 
     15   USE prtctl_trc      ! Print control for debbuging 
    1516 
    1617   IMPLICIT NONE 
     
    2324#  include "passivetrc_substitute.h90" 
    2425   !!---------------------------------------------------------------------- 
    25    !!  TOP 1.0,  LOCEAN-IPSL (2005)  
    26    !! $Header$  
    27    !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt  
     26   !!   OPA 9.0 , LODYC-IPSL (2003) 
    2827   !!---------------------------------------------------------------------- 
    2928 
     
    9594      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   &  
    9695         ztu, ztv                              ! workspace 
     96      CHARACTER (len=22) :: charout 
    9797      !!---------------------------------------------------------------------- 
    9898 
     
    203203#if defined key_trc_diatrd 
    204204         ! Lateral boundary conditions on the laplacian zlt   (unchanged sgn) 
    205          CALL lbc_lnk( trtrd(1,1,1,jn,5), 'T', 1. )   
    206 #endif 
    207          IF(ln_ctl) THEN         ! print mean trends (used for debugging) 
    208             ztra = SUM( tra(2:nictle,2:njctle,1:jpkm1,jn) * tmask(2:nictle,2:njctle,1:jpkm1) ) 
    209             WRITE(numout,*) ' trc/ldf  - ',ctrcnm(jn),' : ', ztra-tra_ctl(jn) 
    210             tra_ctl(jn) = ztra  
    211          ENDIF 
    212  
     205         CALL lbc_lnk( trtrd(:,:,:,jn,5), 'T', 1. )   
     206#endif 
    213207      END DO 
     208 
     209     IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     210         WRITE(charout, FMT="('ldf - bilap')") 
     211         CALL prt_ctl_trc_info(charout) 
     212         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm,clinfo2='trd') 
     213      ENDIF 
    214214 
    215215   END SUBROUTINE trc_ldf_bilap 
  • trunk/NEMO/TOP_SRC/TRP/trcldf_bilapg.F90

    r274 r334  
    1616   USE trc                 ! ocean passive tracers variables 
    1717   USE lbclnk              ! ocean lateral boundary condition (or mpp link) 
     18   USE prtctl_trc          ! Print control for debbuging 
    1819 
    1920   IMPLICIT NONE 
     
    2627#  include "passivetrc_substitute.h90" 
    2728   !!---------------------------------------------------------------------- 
    28    !!  TOP 1.0,  LOCEAN-IPSL (2005)  
    29    !! $Header$  
    30    !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt  
     29   !!   OPA 9.0 , LODYC-IPSL (2003) 
    3130   !!---------------------------------------------------------------------- 
    3231    
     
    7170         wk1, wk2               ! work array used for rotated biharmonic 
    7271                                ! operator on tracers and/or momentum 
     72      CHARACTER (len=22) :: charout 
    7373      !!---------------------------------------------------------------------- 
    7474 
     
    118118         !                                                ! =============== 
    119119 
    120          IF(ln_ctl) THEN         ! print mean trends (used for debugging) 
    121             ztra = SUM( tra(2:nictle,2:njctle,1:jpkm1,jn) * tmask(2:nictle,2:njctle,1:jpkm1) ) 
    122             WRITE(numout,*) ' trc/ldf  - ',ctrcnm(jn),' : ', ztra-tra_ctl(jn) 
    123             tra_ctl(jn) = ztra  
    124          ENDIF 
    125  
    126120      END DO 
     121 
     122     IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     123         WRITE(charout, FMT="('ldf - bilapg')") 
     124         CALL prt_ctl_trc_info(charout) 
     125         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm,clinfo2='trd') 
     126      ENDIF 
    127127 
    128128   END SUBROUTINE trc_ldf_bilapg 
  • trunk/NEMO/TOP_SRC/TRP/trcldf_iso.F90

    r274 r334  
    1515   USE oce_trc      ! ocean dynamics and tracers variables 
    1616   USE trc          ! ocean passive tracers variables 
     17   USE prtctl_trc   ! Print control for debbuging 
    1718 
    1819   IMPLICIT NONE 
     
    2425   !! * Substitutions 
    2526#  include "passivetrc_substitute.h90" 
    26    !!---------------------------------------------------------------------- 
    27    !!  TOP 1.0,  LOCEAN-IPSL (2005)  
    28    !! $Header$ 
    29    !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt 
    3027   !!---------------------------------------------------------------------- 
    3128 
     
    9895      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   & 
    9996         zftv                       ! workspace 
     97      CHARACTER (len=22) :: charout 
    10098      !!---------------------------------------------------------------------- 
    10199 
     
    203201         END DO                                        !   End of slab   
    204202         !                                             ! =============== 
    205          IF(ln_ctl) THEN         ! print mean trends (used for debugging) 
    206             ztra = SUM( tra(2:nictle,2:njctle,1:jpkm1,jn) * tmask(2:nictle,2:njctle,1:jpkm1) ) 
    207             WRITE(numout,*) ' trc/ldf  - ',ctrcnm(jn),' : ', ztra-tra_ctl(jn) 
    208             tra_ctl(jn) = ztra  
    209          ENDIF 
    210203 
    211204      END DO 
     205 
     206      IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     207         WRITE(charout, FMT="('ldf - iso')") 
     208         CALL prt_ctl_trc_info(charout) 
     209         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm,clinfo2='trd') 
     210      ENDIF 
    212211 
    213212   END SUBROUTINE trc_ldf_iso 
  • trunk/NEMO/TOP_SRC/TRP/trcldf_iso_zps.F90

    r274 r334  
    1414   USE oce_trc             ! ocean dynamics and active tracers variables 
    1515   USE trc                 ! ocean passive tracers variables 
     16   USE prtctl_trc          ! Print control for debbuging 
    1617 
    1718   IMPLICIT NONE 
     
    2425#  include "passivetrc_substitute.h90" 
    2526   !!---------------------------------------------------------------------- 
    26    !!  TOP 1.0,  LOCEAN-IPSL (2005)  
    27    !! $Header$  
    28    !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt  
     27   !!   OPA 9.0 , LODYC-IPSL (2003) 
    2928   !!---------------------------------------------------------------------- 
    3029 
     
    102101         zcg1,zcg2 
    103102#endif 
    104  
     103      CHARACTER (len=22) :: charout 
    105104      !!---------------------------------------------------------------------- 
    106105 
     
    240239         END DO                                        !   End of slab   
    241240         !                                             ! =============== 
    242          IF(ln_ctl) THEN         ! print mean trends (used for debugging) 
    243             ztra = SUM( tra(2:nictle,2:njctle,1:jpkm1,jn) * tmask(2:nictle,2:njctle,1:jpkm1) ) 
    244             WRITE(numout,*) ' trc/ldf  - ',ctrcnm(jn),' : ', ztra-tra_ctl(jn) 
    245             tra_ctl(jn) = ztra  
    246          ENDIF 
    247  
    248241      END DO 
     242 
     243      IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     244         WRITE(charout, FMT="('ldf - iso/zps')") 
     245         CALL prt_ctl_trc_info(charout) 
     246         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm,clinfo2='trd') 
     247      ENDIF 
    249248 
    250249   END SUBROUTINE trc_ldf_iso_zps 
  • trunk/NEMO/TOP_SRC/TRP/trcldf_lap.F90

    r274 r334  
    1212   USE oce_trc             ! ocean dynamics and active tracers variables 
    1313   USE trc                 ! ocean passive tracers variables 
     14   USE prtctl_trc          ! Print control for debbuging 
    1415 
    1516   IMPLICIT NONE 
     
    2223#  include "passivetrc_substitute.h90" 
    2324   !!---------------------------------------------------------------------- 
    24    !!  TOP 1.0,  LOCEAN-IPSL (2005)  
    25    !! $Header$  
    26    !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt  
     25   !!   OPA 9.0 , LODYC-IPSL (2003) 
    2726   !!---------------------------------------------------------------------- 
    2827    
     
    7978      REAL(wp) ::   & 
    8079         ztra, ztrax, ztray              ! workspace 
     80      CHARACTER (len=22) :: charout 
    8181      !!---------------------------------------------------------------------- 
    8282       
     
    139139         !                                                  ! ============= 
    140140 
    141          IF(ln_ctl) THEN         ! print mean trends (used for debugging) 
    142             ztra = SUM( tra(2:nictle,2:njctle,1:jpkm1,jn) * tmask(2:nictle,2:njctle,1:jpkm1) ) 
    143             WRITE(numout,*) ' trc/ldf  - ',ctrcnm(jn),' : ', ztra-tra_ctl(jn) 
    144             tra_ctl(jn) = ztra  
    145          ENDIF 
     141      END DO 
    146142 
    147       END DO 
     143     IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     144         WRITE(charout, FMT="('ldf - lap')") 
     145         CALL prt_ctl_trc_info(charout) 
     146         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm,clinfo2='trd') 
     147      ENDIF 
    148148 
    149149   END SUBROUTINE trc_ldf_lap 
  • trunk/NEMO/TOP_SRC/TRP/trcnxt.F90

    r274 r334  
    1313   USE lbclnk          ! ocean lateral boundary conditions (or mpp link) 
    1414   USE trctrp_lec      ! pasive tracers transport 
     15   USE prtctl_trc      ! Print control for debbuging 
    1516 
    1617   IMPLICIT NONE 
     
    2021   PUBLIC trc_nxt          ! routine called by step.F90 
    2122   !!---------------------------------------------------------------------- 
    22    !!  TOP 1.0,  LOCEAN-IPSL (2005)  
    23    !! $Header$  
    24    !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt  
     23   !!   OPA 9.0 , LODYC-IPSL   (2003) 
    2524   !!---------------------------------------------------------------------- 
    2625 
     
    6766      INTEGER ::   ji, jj, jk,jn   ! dummy loop indices 
    6867      REAL(wp) ::   zfact, ztra    ! temporary scalar 
     68      CHARACTER (len=22) :: charout 
    6969      !!---------------------------------------------------------------------- 
    7070 
     
    139139         END DO                                           !   End of slab 
    140140         !                                                ! =============== 
    141          IF(ln_ctl) THEN         ! print mean field (used for debugging) 
    142             ztra = SUM( trn(2:nictle,2:njctle,1:jpkm1,jn)*tmask(2:nictle,2:njctle,1:jpkm1) )  
    143             WRITE(numout,*) ' trc/nxt  - ',ctrcnm(jn),' : ', ztra 
    144          ENDIF 
     141      END DO 
    145142 
    146       END DO 
     143      IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     144         WRITE(charout, FMT="('nxt')") 
     145         CALL prt_ctl_trc_info(charout) 
     146         CALL prt_ctl_trc(tab4d=trn, mask=tmask, clinfo=ctrcnm) 
     147      ENDIF 
     148 
    147149 
    148150   END SUBROUTINE trc_nxt 
  • trunk/NEMO/TOP_SRC/TRP/trcrad.F90

    r274 r334  
    1212   USE trc                 ! ocean passive tracers variables 
    1313   USE lib_mpp 
     14   USE prtctl_trc          ! Print control for debbuging 
    1415 
    1516   IMPLICIT NONE 
     
    2122#  include "passivetrc_substitute.h90" 
    2223   !!---------------------------------------------------------------------- 
    23    !!  TOP 1.0,  LOCEAN-IPSL (2005)  
    24    !! $Header$  
    25    !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt  
     24   !!   OPA 9.0 , LODYC-IPSL   (2003) 
    2625   !!---------------------------------------------------------------------- 
    2726CONTAINS 
     
    4746      !! * Local declarations 
    4847      INTEGER ::  ji, jj, jk, jn             ! dummy loop indices 
    49       REAL(wp) :: ztra 
    50 #if defined key_trc_hamocc3 || defined key_trc_pisces 
     48#if defined key_trc_pisces 
    5149      REAL(wp) :: zvolk, trcorb, trmasb ,trcorn, trmasn   
    5250#endif 
     51      CHARACTER (len=22) :: charout 
    5352      !!---------------------------------------------------------------------- 
    5453 
     
    5958      ENDIF 
    6059 
    61 #if defined key_trc_hamocc3 
    62       DO jn = 1, jptra 
    63          trcorb = 0. 
    64          trmasb = 0. 
    65          trcorn = 0. 
    66          trmasn = 0. 
    67          DO jk = 1, jpkm1 
    68             DO jj = 2, jpjm1 
    69                DO ji = 2, jpim1 
    70                   zvolk = e1t(ji,jj) * e2t(ji,jj) * fse3t(ji,jj,jk) & 
    71 #if defined key_off_degrad 
    72                   &  * facvol(ji,jj,jk) & 
    73 #endif 
    74                   &  * tmask(ji,jj,jk)   
    7560 
    76                   trcorb = trcorb + MIN( 0., trb(ji,jj,jk,jn) )  * zvolk 
    77                   trcorn = trcorn + MIN( 0., trn(ji,jj,jk,jn) )  * zvolk 
    78  
    79                   trb(ji,jj,jk,jn) = MAX( 0. , trb(ji,jj,jk,jn) ) 
    80                   trn(ji,jj,jk,jn) = MAX( 0. , trn(ji,jj,jk,jn) ) 
    81  
    82                   trmasb = trmasb + trb(ji,jj,jk,jn) * zvolk 
    83                   trmasn = trmasn + trn(ji,jj,jk,jn) * zvolk 
    84                END DO 
    85             END DO 
    86          END DO 
    87  
    88          IF( lk_mpp ) THEN 
    89            CALL mpp_sum( trcorb )   ! sum over the global domain 
    90            CALL mpp_sum( trcorn )   ! sum over the global domain 
    91            CALL mpp_sum( trmasb )   ! sum over the global domain 
    92            CALL mpp_sum( trmasn )   ! sum over the global domain 
    93          ENDIF 
    94  
    95          DO jk = 1, jpkm1 
    96             DO jj = 1, jpj 
    97                DO ji = 1, jpi 
    98                   trb(ji,jj,jk,jn) = MAX( 0., trb(ji,jj,jk,jn) ) 
    99                   trb(ji,jj,jk,jn) = trb(ji,jj,jk,jn) * ( 1. + trcorb/trmasb ) * tmask(ji,jj,jk) 
    100                   trn(ji,jj,jk,jn) = MAX( 0., trn(ji,jj,jk,jn) ) 
    101                   trn(ji,jj,jk,jn) = trn(ji,jj,jk,jn) * ( 1. + trcorb/trmasb ) * tmask(ji,jj,jk) 
    102                END DO 
    103             END DO 
    104          END DO 
    105       END DO 
    106  
    107 #elif defined key_trc_age || defined key_trc_lobster1 
     61#if defined key_trc_lobster1 || defined key_cfc 
    10862      DO jn = 1, jptra 
    10963         DO jk = 1, jpkm1 
     
    151105         ENDIF 
    152106 
    153          IF( trcorb /= 0) THEN 
     107         IF( trcorb /= 0 ) THEN 
    154108            DO jk = 1, jpkm1 
    155109               DO jj = 1, jpj 
     
    176130      
    177131#endif 
    178       DO jn = 1, jptra 
    179          IF(ln_ctl) THEN         ! print mean field (used for debugging) 
    180             ztra = SUM( trn(2:nictle,2:njctle,1:jpkm1,jn) * tmask(2:nictle,2:njctle,1:jpkm1) )  
    181             WRITE(numout,*) ' trc/rad  - ',ctrcnm(jn),' : ', ztra 
    182          ENDIF 
    183       ENDDO 
     132 
     133      IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     134         WRITE(charout, FMT="('rad')") 
     135         CALL prt_ctl_trc_info(charout) 
     136         CALL prt_ctl_trc(tab4d=trn, mask=tmask, clinfo=ctrcnm) 
     137      ENDIF 
    184138 
    185139       
  • trunk/NEMO/TOP_SRC/TRP/trcsbc.F90

    r274 r334  
    1111   USE oce_trc             ! ocean dynamics and active tracers variables 
    1212   USE trc                 ! ocean  passive tracers variables 
     13   USE prtctl_trc          ! Print control for debbuging 
     14 
    1315 
    1416   IMPLICIT NONE 
     
    2123#  include "passivetrc_substitute.h90" 
    2224   !!---------------------------------------------------------------------- 
    23    !!  TOP 1.0,  LOCEAN-IPSL (2005)  
    24    !! $Header$  
    25    !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt  
     25   !!   OPA 9.0 , LODYC-IPSL (2003) 
    2626   !!---------------------------------------------------------------------- 
    2727 
     
    6060      INTEGER  ::   ji, jj, jn           ! dummy loop indices 
    6161      REAL(wp) ::   ztra, zsrau, zse3t   ! temporary scalars 
     62      CHARACTER (len=22) :: charout 
    6263      !!---------------------------------------------------------------------- 
    6364 
     
    8990         END DO 
    9091          
    91          IF(ln_ctl) THEN         ! print mean trends (used for debugging) 
    92             ztra = SUM( tra(2:nictle,2:njctle,1:jpkm1,jn) * tmask(2:nictle,2:njctle,1:jpkm1) ) 
    93             WRITE(numout,*) ' trc/sbc  - ',ctrcnm(jn),' : ', ztra-tra_ctl(jn) 
    94             tra_ctl(jn) = ztra  
    95          ENDIF 
    9692      END DO 
     93 
     94      IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     95         WRITE(charout, FMT="('sbc')") 
     96         CALL prt_ctl_trc_info(charout) 
     97         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm,clinfo2='trd') 
     98      ENDIF 
    9799 
    98100   END SUBROUTINE trc_sbc 
  • trunk/NEMO/TOP_SRC/TRP/trcstp.F90

    r276 r334  
    1313   USE trctrp           ! passive tracers transport 
    1414   USE trcsms           ! passive tracers sources and sinks 
    15    USE trcdia          ! passive tracer diagnostics        (trc_dia routine) 
    16    USE trcrst          ! restart for passive tracers 
     15   USE prtctl_trc          ! Print control for debbuging 
     16   USE trcdia 
     17   USE trcrst 
    1718 
    1819   IMPLICIT NONE 
     
    2223   PUBLIC trc_stp           ! called by step 
    2324   !!---------------------------------------------------------------------- 
    24    !!  TOP 1.0,  LOCEAN-IPSL (2005)  
    25    !! $Header$  
    26    !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt  
     25   !!   OPA 9.0 , LODYC-IPSL (2003) 
    2726   !!---------------------------------------------------------------------- 
    2827 
    2928CONTAINS 
    3029 
    31    SUBROUTINE trc_stp( kt ) 
     30   SUBROUTINE trc_stp( kt, kindic ) 
    3231      !!------------------------------------------------------------------- 
    3332      !!                     ***  ROUTINE trc_stp  *** 
     
    4443      !! * Arguments 
    4544      INTEGER, INTENT( in ) ::  kt  ! ocean time-step index 
    46       INTEGER :: jn 
    47       REAL(wp) :: ztra 
     45      INTEGER, INTENT( in ) ::  kindic 
     46      CHARACTER (len=25) :: charout 
    4847 
    49       !! * local declarations 
    50       INTEGER ::   indic    ! error indicator if < 0 
    51       !! --------------------------------------------------------------------- 
     48      IF( kt == nit000 )    CALL trc_dia( kt, kindic )     ! diagnostics init. 
    5249 
    53       indic = 1                    ! reset to no error condition 
     50      ! this ROUTINE is called only every ndttrc time step 
     51      IF( MOD( kt , ndttrc ) /= 0 ) RETURN 
     52 
     53      ! tracers: sink and source  
     54      IF(ln_ctl) THEN 
     55         WRITE(charout,FMT="('kt =', I4,'  d/m/y =',I2,I2,I4)") kt, nday, nmonth, nyear 
     56         CALL prt_ctl_trc_info(charout) 
     57      ENDIF 
    5458 
    5559 
     60      CALL trc_sms( kt ) 
    5661 
    57       ! diagnostics init 
    58  
    59       IF( kt == nit000 )   CALL trc_dia( kt, indic ) 
    60  
    61       ! these ROUTINES are called only every ndttrc time step 
    62       IF( MOD( kt , ndttrc ) == 0 ) THEN 
    63  
    64          ! tracers: sink and source  
    65  
    66          CALL trc_sms( kt ) 
    67  
    68          DO jn = 1, jptra 
    69             IF(ln_ctl) THEN         ! print mean trends (used for debugging) 
    70                ztra = SUM( tra(2:nictle,2:njctle,1:jpkm1,jn) * tmask(2:nictle,2:njctle,1:jpkm1) ) 
    71                WRITE(numout,*) ' trc/sms  - ',ctrcnm(jn),' : ', ztra-tra_ctl(jn) 
    72                tra_ctl(jn) = ztra 
    73             ENDIF 
    74          END DO 
    75  
     62      IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     63         WRITE(charout, FMT="('sms')") 
     64         CALL prt_ctl_trc_info(charout) 
     65         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm) 
     66      ENDIF 
    7667  
    7768 
    78          ! transport of passive tracers 
     69      ! transport of passive tracers 
    7970 
    80          CALL trc_trp( kt ) 
     71      CALL trc_trp( kt ) 
    8172 
    82          DO jn = 1, jptra 
    83             IF(ln_ctl) THEN         ! print mean trends (used for debugging) 
    84                ztra = SUM( tra(2:nictle,2:njctle,1:jpkm1,jn) * tmask(2:nictle,2:njctle,1:jpkm1) ) 
    85                WRITE(numout,*) ' trc/trp  - ',ctrcnm(jn),' : ', ztra-tra_ctl(jn) 
    86                tra_ctl(jn) = ztra 
    87             ENDIF 
    88          END DO 
     73      CALL trc_wri( kt )            ! outputs 
    8974 
    90       ENDIF 
    91  
    92        
    93  
    94       ! outputs 
    95  
    96       CALL trc_wri( kt )  
    97  
    98  
    99  
    100       ! diagnostics 
    101   
    102       CALL trc_dia( kt, indic ) 
    103  
     75      CALL trc_dia( kt, kindic )     ! diagnostics 
    10476 
    10577 
  • trunk/NEMO/TOP_SRC/TRP/trctrp.F90

    r274 r334  
    2424  
    2525   USE trcnxt          ! time-stepping                       (trc_nxt routine) 
    26 !   USE trcrad          ! positivity                          (trc_rad routine) 
     26   USE trcrad          ! positivity                          (trc_rad routine) 
    2727 
    2828   USE trcadv_cen2     ! 2nd order centered advection   (trc_adv_cen2 routine) 
     
    5050#  include "domzgr_substitute.h90" 
    5151   !!---------------------------------------------------------------------- 
    52    !!  TOP 1.0,  LOCEAN-IPSL (2005)  
    53    !! $Header$  
    54    !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt  
     52   !!   OPA 9.0 , LODYC-IPSL (2003) 
    5553   !!---------------------------------------------------------------------- 
    5654 
     
    125123                               CALL trc_nxt( kt )            ! tracer fields at next time step 
    126124  
    127        !!                       CALL trc_rad( kt )            ! Correct artificial negative concentrations  
     125                               CALL trc_rad( kt )            ! Correct artificial negative concentrations  
    128126      !                                                      ! for isopycnal scheme 
    129127 
    130       ! IF( lk_zps           )   CALL zps_hde_trc( kt, trb, gtru, gtrv )  ! Partial steps: now horizontal gradient 
     128      IF( lk_zps           )   CALL zps_hde_trc( kt, trb, gtru, gtrv )  ! Partial steps: now horizontal gradient 
    131129      !                                                                 ! of passive tracers at the bottom ocean level 
    132130 
  • trunk/NEMO/TOP_SRC/TRP/trctrp_ctl.F90

    r281 r334  
    2727 
    2828   !!---------------------------------------------------------------------- 
    29    !!  TOP 1.0,  LOCEAN-IPSL (2005)  
    30    !! $Header$  
    31    !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt  
     29   !!   OPA 9.0 , LODYC-IPSL (2003) 
    3230   !!---------------------------------------------------------------------- 
    3331 
     
    312310      l_trczdf_imp = .TRUE.  
    313311#else 
    314       IF( l_trazdf_exp  ) THEN   
     312      IF( ln_zdfexp  ) THEN   
    315313         l_trczdf_exp = .TRUE.           ! use explicit scheme 
    316314         l_trczdf_imp = .FALSE. 
  • trunk/NEMO/TOP_SRC/TRP/trctrp_lec.F90

    r274 r334  
    7070#endif 
    7171   !!---------------------------------------------------------------------- 
    72    !!  TOP 1.0,  LOCEAN-IPSL (2005)  
    73    !! $Header$  
    74    !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt  
     72   !!   OPA 9.0 , LODYC-IPSL (2003) 
    7573   !!---------------------------------------------------------------------- 
    7674 
  • trunk/NEMO/TOP_SRC/TRP/trczdf_exp.F90

    r274 r334  
    1414   USE trc              ! ocean passive tracers variables 
    1515   USE trctrp_lec       ! passive tracers transport 
     16   USE prtctl_trc          ! Print control for debbuging 
    1617 
    1718   IMPLICIT NONE 
     
    2829#  include "passivetrc_substitute.h90" 
    2930   !!---------------------------------------------------------------------- 
    30    !!  TOP 1.0,  LOCEAN-IPSL (2005)  
    31    !! $Header$ 
    32    !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt 
     31   !!  OPA 9.0, LODYC-IPSL (2003) 
    3332   !!---------------------------------------------------------------------- 
    3433 
     
    8180      REAL(wp), DIMENSION(jpi,jpk) ::   & 
    8281         zwx, zwy 
     82      CHARACTER (len=22) :: charout 
    8383      !!--------------------------------------------------------------------- 
    8484 
     
    161161      END DO 
    162162 
     163      IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     164         WRITE(charout, FMT="('zdf - exp')") 
     165         CALL prt_ctl_trc_info(charout) 
     166         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm,clinfo2='trd') 
     167      ENDIF 
     168 
    163169   END SUBROUTINE trc_zdf_exp 
    164170 
  • trunk/NEMO/TOP_SRC/TRP/trczdf_imp.F90

    r274 r334  
    1313   USE trc                 ! ocean passive tracers variables 
    1414   USE trctrp_lec          ! passive tracers transport 
     15   USE prtctl_trc 
    1516 
    1617   IMPLICIT NONE 
     
    2728#  include "passivetrc_substitute.h90" 
    2829   !!---------------------------------------------------------------------- 
    29    !!  TOP 1.0,  LOCEAN-IPSL (2005)  
    30    !! $Header$  
    31    !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt  
     30   !!   OPA 9.0 , LODYC-IPSL (2003) 
    3231   !!---------------------------------------------------------------------- 
    3332 
     
    8180      REAL(wp), DIMENSION(jpi,jpj,jpk,jptra) ::   & 
    8281         ztrd 
     82      CHARACTER (len=22) :: charout 
    8383      !!--------------------------------------------------------------------- 
    8484 
     
    183183         END DO 
    184184 
    185          IF(ln_ctl) THEN  
     185         IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     186            ztrd(:,:,:,:) = 0. 
    186187            DO jk = 1, jpkm1 
    187188               DO jj = 2, jpjm1 
     
    192193            END DO 
    193194         ENDIF 
    194        
    195          IF(ln_ctl) THEN         ! print mean trends (used for debugging) 
    196             ztra = SUM( ztrd(2:nictle,2:njctle,1:jpkm1,jn) * tmask(2:nictle,2:njctle,1:jpkm1) ) 
    197             WRITE(numout,*) ' trc/zdf  - ',ctrcnm(jn),' : ', ztra-tra_ctl(jn) 
    198             tra_ctl(jn) = ztra  
    199          ENDIF 
    200           
     195 
    201196      END DO 
     197 
     198      IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     199         WRITE(charout, FMT="('zdf - imp')") 
     200         CALL prt_ctl_trc_info(charout) 
     201         CALL prt_ctl_trc(tab4d=ztrd, mask=tmask, clinfo=ctrcnm,clinfo2='trd') 
     202      ENDIF 
    202203 
    203204   END SUBROUTINE trc_zdf_imp 
  • trunk/NEMO/TOP_SRC/TRP/trczdf_iso.F90

    r274 r334  
    1717   USE lbclnk           ! ocean lateral boundary conditions (or mpp link) 
    1818   USE trctrp_lec       ! passive tracers transport 
     19   USE prtctl_trc          ! Print control for debbuging 
    1920 
    2021   IMPLICIT NONE 
     
    3031   !! * Substitutions 
    3132#  include "passivetrc_substitute.h90" 
    32    !!---------------------------------------------------------------------- 
    33    !!  TOP 1.0,  LOCEAN-IPSL (2005)  
    34    !! $Header$ 
    35    !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt 
    3633   !!---------------------------------------------------------------------- 
    3734 
     
    148145         zuwki, zvwki 
    149146#endif 
     147      CHARACTER (len=22) :: charout 
    150148      !!--------------------------------------------------------------------- 
    151149      !!  OPA 8.5, LODYC-IPSL (2002) 
     
    349347         !                                                ! =============== 
    350348 
    351          IF(ln_ctl) THEN         ! print mean trends (used for debugging) 
    352             ztra = SUM( tra(2:nictle,2:njctle,1:jpkm1,jn) * tmask(2:nictle,2:njctle,1:jpkm1) ) 
    353             WRITE(numout,*) ' trc/zdf 1  - ',ctrcnm(jn),' : ', ztra-tra_ctl(jn) 
    354             tra_ctl(jn) = ztra  
    355          ENDIF 
    356  
    357349      END DO 
    358350 
     351      IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     352         WRITE(charout, FMT="('zdf - 1')") 
     353         CALL prt_ctl_trc_info(charout) 
     354         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm,clinfo2='trd') 
     355      ENDIF 
    359356 
    360357      DO jn = 1, jptra 
     
    439436         !                                                ! =============== 
    440437 
    441  
    442          IF(ln_ctl) THEN         ! print mean trends (used for debugging) 
    443             ztra = SUM( tra(2:nictle,2:njctle,1:jpkm1,jn) * tmask(2:nictle,2:njctle,1:jpkm1) ) 
    444             WRITE(numout,*) ' trc/zdf 2  - ',ctrcnm(jn),' : ', ztra-tra_ctl(jn) 
    445             tra_ctl(jn) = ztra  
    446          ENDIF 
    447  
    448438      END DO 
     439 
     440      IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     441         WRITE(charout, FMT="('zdf - 2')") 
     442         CALL prt_ctl_trc_info(charout) 
     443         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm,clinfo2='trd') 
     444      ENDIF 
    449445 
    450446   END SUBROUTINE trc_zdf_iso 
  • trunk/NEMO/TOP_SRC/TRP/trczdf_iso_vopt.F90

    r274 r334  
    2020   USE lbclnk          ! ocean lateral boundary conditions (or mpp link) 
    2121   USE trctrp_lec      ! passive tracers transport 
     22   USE prtctl_trc          ! Print control for debbuging 
    2223 
    2324   IMPLICIT NONE 
     
    3334   !! * Substitutions 
    3435#  include "passivetrc_substitute.h90" 
    35    !!---------------------------------------------------------------------- 
    36    !!  TOP 1.0,  LOCEAN-IPSL (2005) 
    37    !! $Header$ 
    38    !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt 
    3936   !!---------------------------------------------------------------------- 
    4037 
     
    5552      !! * Arguments 
    5653      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index 
     54      CHARACTER (len=22) :: charout 
    5755      !!--------------------------------------------------------------------- 
    5856      !!  OPA 8.5, LODYC-IPSL (2002) 
     
    7472      CALL trc_zdf_iso 
    7573 
     74      IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     75         WRITE(charout, FMT="('zdf - 1')") 
     76         CALL prt_ctl_trc_info(charout) 
     77         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm,clinfo2='trd') 
     78      ENDIF 
    7679 
    7780      ! II. vertical diffusion (including the vertical diagonal part of the rotated tensor) 
     
    8083      CALL trc_zdf_zdf( kt ) 
    8184 
     85      IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     86         WRITE(charout, FMT="('zdf - 2')") 
     87         CALL prt_ctl_trc_info(charout) 
     88         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm,clinfo2='trd') 
     89      ENDIF 
    8290 
    8391   END SUBROUTINE trc_zdf_iso_vopt 
     
    318326#  endif 
    319327#endif 
    320          IF(ln_ctl) THEN         ! print mean trends (used for debugging) 
    321             ztra = SUM( tra(2:nictle,2:njctle,1:jpkm1,jn) * tmask(2:nictle,2:njctle,1:jpkm1) ) 
    322             WRITE(numout,*) ' trc/zdf 1 - ',ctrcnm(jn),' : ', ztra-tra_ctl(jn) 
    323             tra_ctl(jn) = ztra  
    324          ENDIF 
    325328 
    326329      END DO 
     
    405408      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   & 
    406409         zwz, zwt, ztfw             ! temporary workspace arrays 
    407       REAL(wp) ::    ztra              !temporary scalars 
     410 
    408411      !!--------------------------------------------------------------------- 
    409412      !!  OPA 8.5, LODYC-IPSL (2002) 
     
    552555         END DO 
    553556 
    554          IF(ln_ctl) THEN         ! print mean trends (used for debugging) 
    555             ztra = SUM( tra(2:nictle,2:njctle,1:jpkm1,jn) * tmask(2:nictle,2:njctle,1:jpkm1) ) 
    556             WRITE(numout,*) ' trc/zdf 2 - ',ctrcnm(jn),' : ', ztra-tra_ctl(jn) 
    557             tra_ctl(jn) = ztra  
    558          ENDIF 
    559  
    560557      END DO 
    561558 
  • trunk/NEMO/TOP_SRC/TRP/zpshde_trc.F90

    r274 r334  
    2828   !! * Substitutions 
    2929#  include "passivetrc_substitute.h90" 
    30    !!---------------------------------------------------------------------- 
    31    !!  TOP 1.0,  LOCEAN-IPSL (2005) 
    32    !! $Header$ 
    33    !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt 
    3430   !!---------------------------------------------------------------------- 
    3531 
Note: See TracChangeset for help on using the changeset viewer.