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 771 – NEMO

Changeset 771


Ignore:
Timestamp:
2007-12-17T11:51:41+01:00 (16 years ago)
Author:
gm
Message:

dev_001_GM - small error corrections

Location:
branches/dev_001_GM/NEMO/TOP_SRC
Files:
14 edited

Legend:

Unmodified
Added
Removed
  • branches/dev_001_GM/NEMO/TOP_SRC/LOBSTER/par_lobster.F90

    r769 r771  
    4848 
    4949   ! Starting/ending LOBSTER do-loop indices (N.B. no LOBSTER : jpl_lob < jpf_lob the do-loop are never done) 
    50    INTEGER, PUBLIC, PARAMETER ::   jpf_lob =          1       !: First index of LOBSTER tracers 
    51    INTEGER, PUBLIC, PARAMETER ::   jpl_lob = jp_lobster       !: Last  index of LOBSTER tracers 
     50   INTEGER, PUBLIC, PARAMETER ::   jp_lob0 =          1       !: First index of LOBSTER tracers 
     51   INTEGER, PUBLIC, PARAMETER ::   jp_lob1 = jp_lobster       !: Last  index of LOBSTER tracers 
    5252 
    5353   !!====================================================================== 
  • branches/dev_001_GM/NEMO/TOP_SRC/LOBSTER/trcini_lobster.F90

    r766 r771  
    1818   USE par_trc         ! TOP parameters 
    1919   USE trccfc          ! CFC sms trends 
     20   USE sms             ! Source Minus Sink variables 
     21   USE oce_trc         ! ocean variables 
    2022 
    2123   IMPLICIT NONE 
     
    2830   !!---------------------------------------------------------------------- 
    2931   !! NEMO/TOP 2.0 , LOCEAN-IPSL (2007)  
    30    !! $Id:$  
     32   !! $Id$  
    3133   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
    3234   !!---------------------------------------------------------------------- 
     
    4042      !!---------------------------------------------------------------------- 
    4143      INTEGER  ::   ji, jj, jk, jn 
    42       REAL(wp) ::   zdm0(jpi,jpj,jpk), zrro(jpi,jpj), zfluo, zfluu 
    4344      REAL(wp) ::   ztest, zfluo, zfluu 
    4445      REAL(wp), DIMENSION(jpi,jpj)     ::   zrro 
  • branches/dev_001_GM/NEMO/TOP_SRC/MY_TRC/par_my_trc.F90

    r769 r771  
    4646 
    4747   ! Starting/ending PISCES do-loop indices (N.B. no PISCES : jpl_pcs < jpf_pcs the do-loop are never done) 
    48    INTEGER, PUBLIC, PARAMETER ::   jpf_myt = jp_lpc + 1           !: First index of CFC passive tracers 
    49    INTEGER, PUBLIC, PARAMETER ::   jpl_myt = jp_lpc + jp_my_trc   !: Last  index of CFC passive tracers 
     48   INTEGER, PUBLIC, PARAMETER ::   jp_myt0 = jp_lpc + 1           !: First index of CFC passive tracers 
     49   INTEGER, PUBLIC, PARAMETER ::   jp_myt1 = jp_lpc + jp_my_trc   !: Last  index of CFC passive tracers 
    5050 
    5151   !!====================================================================== 
  • branches/dev_001_GM/NEMO/TOP_SRC/PISCES/par_pisces.F90

    r769 r771  
    107107 
    108108   ! Starting/ending PISCES do-loop indices (N.B. no PISCES : jpl_pcs < jpf_pcs the do-loop are never done) 
    109    INTEGER, PUBLIC, PARAMETER ::   jpf_pcs = jp_l + 1           !: First index of CFC passive tracers 
    110    INTEGER, PUBLIC, PARAMETER ::   jpl_pcs = jp_l + jp_pisces   !: Last  index of CFC passive tracers 
     109   INTEGER, PUBLIC, PARAMETER ::   jp_pcs0 = jp_l + 1           !: First index of CFC passive tracers 
     110   INTEGER, PUBLIC, PARAMETER ::   jp_pcs1 = jp_l + jp_pisces   !: Last  index of CFC passive tracers 
    111111 
    112112   !!====================================================================== 
  • branches/dev_001_GM/NEMO/TOP_SRC/PISCES/trcini_pisces.F90

    r766 r771  
    1010   !!             2.0  !  2007-12  (C. Ethe, G. Madec) from trcini.pisces.h90 
    1111   !!---------------------------------------------------------------------- 
    12 #if defined key_trc_pisces  &&  defined key_trc_kriest 
    13    !!--------------------------------------------------------------------- 
    14    !!   'key_trc_pisces' & 'key_trc_kriest'         PISCES bio-model + ??? 
    15    !!--------------------------------------------------------------------- 
     12#if defined key_trc_pisces 
     13   !!---------------------------------------------------------------------- 
     14   !!   'key_trc_pisces'                                   PISCES bio-model 
     15   !!---------------------------------------------------------------------- 
    1616   !! trc_ini_pisces   : PISCES biochemical model initialisation 
    1717   !!---------------------------------------------------------------------- 
    1818   USE par_trc         ! TOP parameters 
    1919   USE trccfc          ! CFC sms trends 
     20   USE sms             ! Source Minus Sink variables 
    2021   USE iom 
    2122 
     
    2930   !!---------------------------------------------------------------------- 
    3031   !! NEMO/TOP 2.0 , LOCEAN-IPSL (2007)  
    31    !! $Id:$  
     32   !! $Id$  
    3233   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
    3334   !!---------------------------------------------------------------------- 
     
    4142      !! ** Purpose :   Initialisation of the PISCES biochemical model 
    4243      !!---------------------------------------------------------------------- 
    43       INTEGER :: ji, jj, jk, jm 
    44       INTEGER :: ichl, iband 
    45       INTEGER , PARAMETER ::   jpmois = 12, jpan   = 1  
    46  
    47       REAL(wp) :: zcoef 
    48       REAL(wp) :: ztoto,expide,denitide,ztra,zmaskt 
    49       REAL(wp) , DIMENSION (jpi,jpj) :: riverdoc,river,ndepo 
    50       REAL(wp) , DIMENSION (jpi,jpj,jpk) :: cmask 
     44      INTEGER ::   ji, jj, jk, jm 
     45      INTEGER ::   ichl, iband 
     46      INTEGER , PARAMETER ::   jpmois = 12, jpan = 1  
     47 
     48      REAL(wp) ::   zcoef 
     49      REAL(wp) ::   ztoto, expide, denitide,zmaskt 
     50      REAL(wp) , DIMENSION (jpi,jpj)     ::   riverdoc, river, ndepo 
     51      REAL(wp) , DIMENSION (jpi,jpj,jpk) ::   cmask 
    5152 
    5253      INTEGER :: numriv, numdust, numbath, numdep 
     
    5657      INTEGER  ::   jn, kiter 
    5758      REAL(wp) ::   znum, zdiv 
    58       REAL(wp) ::   zws,zwr, zwl,wmax, xnummax, & 
     59      REAL(wp) ::   zws, zwr, zwl,wmax, xnummax 
    5960      REAL(wp) ::   zmin, zmax, zl, zr, xacc 
    6061#endif 
     
    201202 
    202203#if defined key_trc_kriest 
    203       !---------------------------------------------------------------------- 
     204      !!--------------------------------------------------------------------- 
     205      !!    'key_trc_kriest'                                              ??? 
     206      !!--------------------------------------------------------------------- 
    204207      !  COMPUTATION OF THE VERTICAL PROFILE OF MAXIMUM SINKING SPEED 
    205208      !  Search of the maximum number of particles in aggregates for each k-level.   
     
    569572   !!====================================================================== 
    570573END MODULE trcini_pisces 
    571  
  • branches/dev_001_GM/NEMO/TOP_SRC/TRP/trcrad.F90

    r719 r771  
    44   !! Ocean passive tracers:  correction of negative concentrations 
    55   !!====================================================================== 
     6   !! History :   -   !  01-01  (O. Aumont & E. Kestenare)  Original code 
     7   !!            1.0  !  04-03  (C. Ethe)  free form F90 
     8   !!---------------------------------------------------------------------- 
    69#if defined key_passivetrc 
     10   !!---------------------------------------------------------------------- 
     11   !!   'key_passivetrc'                                    Passive tracers 
    712   !!---------------------------------------------------------------------- 
    813   !!   trc_rad    : correction of negative concentrations 
    914   !!---------------------------------------------------------------------- 
    10    !! * Modules used 
    1115   USE oce_trc             ! ocean dynamics and tracers variables 
    1216   USE trc                 ! ocean passive tracers variables 
     
    1721   PRIVATE 
    1822 
    19    !! * Routine accessibility 
    2023   PUBLIC trc_rad        ! routine called by trcstp.F90 
     24 
    2125   !! * Substitutions 
    2226#  include "passivetrc_substitute.h90" 
    2327   !!---------------------------------------------------------------------- 
    24    !!   TOP 1.0 , LOCEAN-IPSL (2005)  
    25    !! $Header$  
    26    !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt  
     28   !! NEMO/TOP 1.0 , LOCEAN-IPSL (2005)  
     29   !! $Id:$  
     30   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
    2731   !!---------------------------------------------------------------------- 
     32    
    2833CONTAINS 
    2934 
     
    3237      !!                  ***  ROUTINE trc_rad  *** 
    3338      !! 
    34       !! ** Purpose : "crappy" routine to correct artificial negative 
    35       !!      concentrations due to isopycnal scheme 
     39      !! ** Purpose :   "crappy" routine to correct artificial negative 
     40      !!              concentrations due to isopycnal scheme 
    3641      !! 
    37       !! ** Method  : Set negative concentrations to zero 
    38       !!              compute the corresponding mass added to the tracers 
    39       !!              and remove it when possible  
     42      !! ** Method  : - PISCES or LOBSTER: Set negative concentrations to zero 
     43      !!                while computing the corresponding tracer content that 
     44      !!                is added to the tracers. Then, adjust the tracer  
     45      !!                concentration using a multiplicative factor so that  
     46      !!                the total tracer concentration is preserved. 
     47      !!              - CFC: simply set to zero the negative CFC concentration 
     48      !!                (the total CFC content is not strictly preserved) 
     49      !!---------------------------------------------------------------------- 
     50      INTEGER, INTENT( in ) ::   kt   ! ocean time-step index       
    4051      !! 
    41       !! History : 
    42       !!   8.2  !  01-01  (O. Aumont & E. Kestenare)  Original code 
    43       !!   9.0  !  04-03  (C. Ethe)  free form F90 
    44       !!---------------------------------------------------------------------- 
    45       !! * Arguments 
    46       INTEGER, INTENT( in ) ::   kt       ! ocean time-step index 
    47        
    48       !! * Local declarations 
    49       INTEGER ::  ji, jj, jk, jn             ! dummy loop indices 
    50 #if defined key_trc_pisces || defined key_trc_lobster1 
    51       REAL(wp) :: zvolk, trcorb, trmasb ,trcorn, trmasn   
    52 #endif 
     52      INTEGER  ::  ji, jj, jk, jn     ! dummy loop indices 
     53      REAL(wp) :: zvolk, ztrcorb, ztrmasb   ! temporary scalars 
     54      REAL(wp) :: zcoef, ztrcorn, ztrmasn   !    "         " 
    5355      CHARACTER (len=22) :: charout 
    5456      !!---------------------------------------------------------------------- 
     
    6062      ENDIF 
    6163 
    62  
    63 #if defined key_cfc 
    64       DO jn = 1, jptra 
    65          DO jk = 1, jpkm1 
    66             DO jj = 1, jpj 
    67                DO ji = 1, jpi 
    68                   trn(ji,jj,jk,jn) = MAX( 0. , trn(ji,jj,jk,jn) ) 
    69                   trb(ji,jj,jk,jn) = MAX( 0. , trb(ji,jj,jk,jn) ) 
    70                END DO 
    71             END DO 
    72          END DO 
    73       END DO 
    74        
    75 #elif defined key_trc_pisces || defined key_trc_lobster1 
    76  
    77       DO jn = 1, jptra 
    78          trcorb = 0. 
    79          trmasb = 0. 
    80          trcorn = 0. 
    81          trmasn = 0. 
    82          DO jk = 1, jpkm1 
    83             DO jj = 1, jpj 
    84                DO ji = 1, jpi 
    85                   zvolk = e1t(ji,jj) * e2t(ji,jj) * fse3t(ji,jj,jk) & 
    86 #if defined key_off_degrad 
    87                   &  * facvol(ji,jj,jk) & 
    88 #endif 
    89                   &  * tmask(ji,jj,jk) * tmask_i(ji,jj) 
    90  
    91                   trcorb = trcorb + MIN( 0., trb(ji,jj,jk,jn) )  * zvolk 
    92                   trcorn = trcorn + MIN( 0., trn(ji,jj,jk,jn) )  * zvolk 
    93  
    94                   trb(ji,jj,jk,jn) = MAX( 0. , trb(ji,jj,jk,jn) ) 
    95                   trn(ji,jj,jk,jn) = MAX( 0. , trn(ji,jj,jk,jn) ) 
    96  
    97                   trmasb = trmasb + trb(ji,jj,jk,jn) * zvolk 
    98                   trmasn = trmasn + trn(ji,jj,jk,jn) * zvolk 
    99                END DO 
    100             END DO 
    101          END DO 
    102  
    103          IF( lk_mpp ) THEN 
    104            CALL mpp_sum( trcorb )   ! sum over the global domain 
    105            CALL mpp_sum( trcorn )   ! sum over the global domain 
    106            CALL mpp_sum( trmasb )   ! sum over the global domain 
    107            CALL mpp_sum( trmasn )   ! sum over the global domain 
    108          ENDIF 
    109  
    110          IF( trcorb /= 0 ) THEN 
    111             DO jk = 1, jpkm1 
    112                DO jj = 1, jpj 
    113                   DO ji = 1, jpi 
    114                      trb(ji,jj,jk,jn) = MAX( 0. , trb(ji,jj,jk,jn) ) 
    115                      trb(ji,jj,jk,jn) = trb(ji,jj,jk,jn) * ( 1. + trcorb/trmasb ) * tmask(ji,jj,jk) 
    116                   END DO 
    117                END DO 
    118             END DO 
    119          ENDIF 
    120  
    121          IF( trcorn /= 0) THEN 
     64      IF( lk_trc_cfc ) THEN                             ! CFC model 
     65         DO jn = 1, jptra 
    12266            DO jk = 1, jpkm1 
    12367               DO jj = 1, jpj 
    12468                  DO ji = 1, jpi 
    12569                     trn(ji,jj,jk,jn) = MAX( 0. , trn(ji,jj,jk,jn) ) 
    126                      trn(ji,jj,jk,jn) = trn(ji,jj,jk,jn) * ( 1. + trcorn/trmasn ) * tmask(ji,jj,jk) 
     70                     trb(ji,jj,jk,jn) = MAX( 0. , trb(ji,jj,jk,jn) ) 
    12771                  END DO 
    12872               END DO 
    12973            END DO 
    130          ENDIF 
     74         END DO 
     75      ENDIF  
    13176 
    132       END DO 
    133       
    134 #endif 
     77      IF( lk_trc_pisces .OR. lk_trc_lobster ) THEN      ! PISCES or LOBSTER bio-model 
     78         DO jn = 1, jptra 
     79            ztrcorb = 0.e0 
     80            ztrmasb = 0.e0 
     81            ztrcorn = 0.e0 
     82            ztrmasn = 0.e0 
     83            DO jk = 1, jpkm1 
     84               DO jj = 1, jpj 
     85                  DO ji = 1, jpi 
     86                     zvolk  = e1t(ji,jj) * e2t(ji,jj) * fse3t(ji,jj,jk)   & 
     87# if defined key_off_degrad 
     88                        &   * facvol(ji,jj,jk)   & 
     89# endif 
     90                        &   * tmask(ji,jj,jk) * tmask_i(ji,jj) 
    13591 
    136       IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     92                     ztrcorb = ztrcorb + MIN( 0., trb(ji,jj,jk,jn) )  * zvolk 
     93                     ztrcorn = ztrcorn + MIN( 0., trn(ji,jj,jk,jn) )  * zvolk 
     94 
     95                     trb(ji,jj,jk,jn) = MAX( 0. , trb(ji,jj,jk,jn) ) 
     96                     trn(ji,jj,jk,jn) = MAX( 0. , trn(ji,jj,jk,jn) ) 
     97 
     98                     ztrmasb = ztrmasb + trb(ji,jj,jk,jn) * zvolk 
     99                     ztrmasn = ztrmasn + trn(ji,jj,jk,jn) * zvolk 
     100                  END DO 
     101               END DO 
     102            END DO 
     103            IF( lk_mpp ) THEN 
     104               CALL mpp_sum( ztrcorb )      ! sum over the global domain 
     105               CALL mpp_sum( ztrcorn )      ! sum over the global domain 
     106               CALL mpp_sum( ztrmasb )      ! sum over the global domain 
     107               CALL mpp_sum( ztrmasn )      ! sum over the global domain 
     108            ENDIF 
     109 
     110            IF( ztrcorb /= 0 ) THEN 
     111               zcoef = 1. + ztrcorb / ztrmasb 
     112               DO jk = 1, jpkm1 
     113                  DO jj = 1, jpj 
     114                     DO ji = 1, jpi 
     115                         trb(ji,jj,jk,jn) = MAX( 0. , trb(ji,jj,jk,jn) )               !!gm bug already done just above 
     116                        trb(ji,jj,jk,jn) = trb(ji,jj,jk,jn) * zcoef * tmask(ji,jj,jk) 
     117                     END DO 
     118                  END DO 
     119               END DO 
     120            ENDIF 
     121 
     122            IF( ztrcorn /= 0 ) THEN 
     123               zcoef = 1. + ztrcorn / ztrmasn 
     124               DO jk = 1, jpkm1 
     125                  DO jj = 1, jpj 
     126                     DO ji = 1, jpi 
     127                        trn(ji,jj,jk,jn) = MAX( 0. , trn(ji,jj,jk,jn) )                !!gm bug already done just above 
     128                        trn(ji,jj,jk,jn) = trn(ji,jj,jk,jn) * zcoef * tmask(ji,jj,jk) 
     129                     END DO 
     130                  END DO 
     131               END DO 
     132            ENDIF 
     133            ! 
     134         END DO 
     135         ! 
     136      ENDIF 
     137      ! 
     138      IF(ln_ctl) THEN      ! print mean trends (used for debugging) 
    137139         WRITE(charout, FMT="('rad')") 
    138          CALL prt_ctl_trc_info(charout) 
    139          CALL prt_ctl_trc(tab4d=trn, mask=tmask, clinfo=ctrcnm) 
     140         CALL prt_ctl_trc_info( charout ) 
     141         CALL prt_ctl_trc( tab4d=trn, mask=tmask, clinfo=ctrcnm ) 
    140142      ENDIF 
    141  
    142        
     143      ! 
    143144   END SUBROUTINE trc_rad 
    144145 
    145146#else 
    146147   !!---------------------------------------------------------------------- 
    147    !!   Dummy module :                      NO passive tracer 
     148   !!   Dummy module :                                         NO TOP model 
    148149   !!---------------------------------------------------------------------- 
    149150CONTAINS 
    150    SUBROUTINE trc_rad (kt )              ! Empty routine 
    151       INTEGER, INTENT(in) :: kt 
     151   SUBROUTINE trc_rad( kt )              ! Empty routine 
     152      INTEGER, INTENT(in) ::   kt 
    152153      WRITE(*,*) 'trc_rad: You should not have seen this print! error?', kt 
    153154   END SUBROUTINE trc_rad 
  • branches/dev_001_GM/NEMO/TOP_SRC/TRP/trctrp.F90

    r719 r771  
    44   !! Ocean Physics    : manage the passive tracer transport 
    55   !!====================================================================== 
     6   !! History :   1.0  !  2004-03 (C. Ethe) Original code 
     7   !!---------------------------------------------------------------------- 
    68#if defined key_passivetrc 
     9   !!---------------------------------------------------------------------- 
     10   !!   'key_passivetrc'                                         TOP models 
    711   !!---------------------------------------------------------------------- 
    812   !!   trc_trp        : passive tracer transport 
    913   !!---------------------------------------------------------------------- 
    10    !! * Modules used 
    1114   USE oce_trc         ! ocean dynamics and active tracers variables 
    1215   USE trc             ! ocean passive tracers variables  
    13  
    14    USE trctrp_lec      ! passive tracers transport 
     16   USE trctrp_lec      ! passive tracers transport parameters 
    1517 
    1618   USE trcbbl          ! bottom boundary layer               (trc_bbl routine) 
     
    4042   USE zpshde_trc      ! partial step: hor. derivative   (zps_hde_trc routine) 
    4143 
    42  
    4344   IMPLICIT NONE 
    4445   PRIVATE 
    4546 
    46    !! * Routine accessibility 
    47    PUBLIC trc_trp            ! called by trc_stp 
     47   PUBLIC   trc_trp    ! called by trc_stp 
    4848 
    4949   !! * Substitutions 
    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   !! NEMO/TOP 1.0 , LOCEAN-IPSL (2005)  
     53   !! $Id$  
     54   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
    5555   !!---------------------------------------------------------------------- 
    5656 
     
    6161      !!                     ***  ROUTINE trc_trp  *** 
    6262      !!                       
    63       !! ** Purpose : Management of passive tracers transport 
     63      !! ** Purpose :   Management of passive tracers transport 
    6464      !!  
    65       !! ** Method  :  
    66       !!              Compute the passive tracers trends  
    67       !!              Update the passive tracers 
    68       !! 
    69       !! History : 
    70       !!   9.0  !  04-03  (C. Ethe)  Original 
     65      !! ** Method  : - Compute the passive tracers trends  
     66      !!              - Update the passive tracers 
    7167      !!---------------------------------------------------------------------- 
    72       !! * Arguments 
    7368      INTEGER, INTENT( in ) ::  kt  ! ocean time-step index 
    7469      !! --------------------------------------------------------------------- 
    7570 
    76       !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
    77       ! Passitive tracers 
    78       !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    79       !----------------------------------------------------------------------- 
    80  
    81   
    8271                               CALL trc_sbc( kt )            ! surface boundary condition 
    8372# if defined key_trcbbc 
     73!!gm bug : this should be control during the initialisation phase, not here! 
    8474       CALL ctl_stop( '  Bottom heat flux not yet implemented with passive tracer         ' & 
    8575           &          '  Check in trc_trp routine ' ) 
    8676# endif  
    8777      !                                                      ! bottom boundary condition 
    88       IF( lk_trcbbl_dif    )   CALL trc_bbl_dif( kt )                ! diffusive bottom boundary layer scheme 
    89       IF( lk_trcbbl_adv    )   CALL trc_bbl_adv( kt )                ! advective (and/or diffusive) bottom boundary layer scheme 
     78      IF( lk_trcbbl_dif    )   CALL trc_bbl_dif( kt )            ! diffusive bottom boundary layer scheme 
     79      IF( lk_trcbbl_adv    )   CALL trc_bbl_adv( kt )            ! advective (and/or diffusive) bottom boundary layer scheme 
    9080 
    9181      IF( lk_trcdmp        )   CALL trc_dmp( kt )            ! internal damping trends 
    9282 
    9383      !                                                      ! horizontal & vertical advection 
    94       IF( ln_trcadv_cen2   )   CALL trc_adv_cen2  ( kt )             ! 2nd order centered scheme 
    95       IF( ln_trcadv_muscl  )   CALL trc_adv_muscl ( kt )             ! MUSCL scheme 
    96       IF( ln_trcadv_muscl2 )   CALL trc_adv_muscl2( kt )             ! MUSCL2 scheme 
    97       IF( ln_trcadv_tvd    )   CALL trc_adv_tvd   ( kt )             ! TVD scheme 
    98       IF( ln_trcadv_smolar )   CALL trc_adv_smolar( kt )             ! SMOLARKIEWICZ scheme 
     84      IF( ln_trcadv_cen2   )   CALL trc_adv_cen2  ( kt )         ! 2nd order centered scheme 
     85      IF( ln_trcadv_muscl  )   CALL trc_adv_muscl ( kt )         ! MUSCL scheme 
     86      IF( ln_trcadv_muscl2 )   CALL trc_adv_muscl2( kt )         ! MUSCL2 scheme 
     87      IF( ln_trcadv_tvd    )   CALL trc_adv_tvd   ( kt )         ! TVD scheme 
     88      IF( ln_trcadv_smolar )   CALL trc_adv_smolar( kt )         ! SMOLARKIEWICZ scheme 
    9989 
    10090  
    10191      IF( n_cla == 1   ) THEN 
     92!!gm bug : this should be control during the initialisation phase, not here! 
    10293         WRITE(ctmp1,*) ' Cross Land Advection not yet implemented with passive tracer n_cla = ',n_cla 
    103          CALL ctl_stop(ctmp1) 
     94         CALL ctl_stop( ctmp1 ) 
    10495      ENDIF 
    10596 
    10697      !                                                      ! lateral mixing  
    107       IF( l_trcldf_bilapg  )   CALL trc_ldf_bilapg ( kt )            ! s-coord. horizontal bilaplacian 
    108       IF( l_trcldf_bilap   )   CALL trc_ldf_bilap  ( kt )            ! iso-level bilaplacian  
    109       IF( l_trcldf_iso     )   CALL trc_ldf_iso    ( kt )            ! iso-neutral laplacian  
    110       IF( l_trcldf_iso_zps )   CALL trc_ldf_iso_zps( kt )            ! partial step iso-neutral laplacian 
    111       IF( l_trcldf_lap     )   CALL trc_ldf_lap    ( kt )            ! iso-level laplacian 
     98      IF( l_trcldf_bilapg  )   CALL trc_ldf_bilapg ( kt )        ! s-coord. horizontal bilaplacian 
     99      IF( l_trcldf_bilap   )   CALL trc_ldf_bilap  ( kt )        ! iso-level bilaplacian  
     100      IF( l_trcldf_iso     )   CALL trc_ldf_iso    ( kt )        ! iso-neutral laplacian  
     101      IF( l_trcldf_iso_zps )   CALL trc_ldf_iso_zps( kt )        ! partial step iso-neutral laplacian 
     102      IF( l_trcldf_lap     )   CALL trc_ldf_lap    ( kt )        ! iso-level laplacian 
    112103  
    113104      !                                                      ! vertical diffusion 
    114       IF( l_trczdf_exp     )   CALL trc_zdf_exp( kt )                ! explicit time stepping (time splitting scheme) 
    115       IF( l_trczdf_imp     )   CALL trc_zdf_imp( kt )                ! implicit time stepping (euler backward) 
    116       IF( l_trczdf_iso     )   CALL trc_zdf_iso( kt )                ! isopycnal 
    117       IF( l_trczdf_iso_vo  )   CALL trc_zdf_iso_vopt( kt )           ! vector opt. isopycnal 
     105      IF( l_trczdf_exp     )   CALL trc_zdf_exp     ( kt )       ! explicit time stepping (time splitting scheme) 
     106      IF( l_trczdf_imp     )   CALL trc_zdf_imp     ( kt )       ! implicit time stepping (euler backward) 
     107      IF( l_trczdf_iso     )   CALL trc_zdf_iso     ( kt )       ! isopycnal 
     108      IF( l_trczdf_iso_vo  )   CALL trc_zdf_iso_vopt( kt )       ! vector opt. isopycnal 
    118109 
    119110                               CALL trc_nxt( kt )            ! tracer fields at next time step 
    120111  
    121                                CALL trc_rad( kt )            ! Correct artificial negative concentrations for isopycnal scheme 
     112                               CALL trc_rad( kt )            ! Correct artificial negative concentrations 
     113      !                                                      ! especially useful when isopycnal mixing is used 
    122114      !                                                       
    123115 
    124       IF( ln_zps .AND. .NOT. lk_trccfg_1d ) & 
    125          &                     CALL zps_hde_trc( kt, trb, gtru, gtrv )  ! Partial steps: now horizontal gradient 
    126       !                                                                 ! of passive tracers at the bottom ocean level 
    127  
    128  
    129     END SUBROUTINE trc_trp 
     116      IF( ln_zps .AND. .NOT. lk_trccfg_1d )   &              ! Partial steps: now horizontal gradient of passive 
     117         &                     CALL zps_hde_trc( kt, trb, gtru, gtrv )       ! tracers at the bottom ocean level 
     118      ! 
     119      IF(ln_ctl) THEN      ! print mean trends (used for debugging) 
     120         WRITE(charout, FMT="('TRP')") 
     121         CALL prt_ctl_trc_info( charout ) 
     122         CALL prt_ctl_trc( tab4d=tra, mask=tmask, clinfo=ctrcnm ) 
     123      ENDIF 
     124      ! 
     125   END SUBROUTINE trc_trp 
    130126 
    131127#else 
    132128   !!---------------------------------------------------------------------- 
    133    !!   Dummy module :                      NO passive tracers 
     129   !!   Dummy module :                                        No TOP models 
    134130   !!---------------------------------------------------------------------- 
    135131CONTAINS 
    136    SUBROUTINE trc_trp (kt )              ! Empty routine 
    137       INTEGER, INTENT(in) :: kt 
     132   SUBROUTINE trc_trp( kt )              ! Empty routine 
     133      INTEGER, INTENT(in) ::   kt 
    138134      WRITE(*,*) 'trc_trp: You should not have seen this print! error?', kt 
    139135   END SUBROUTINE trc_trp 
  • branches/dev_001_GM/NEMO/TOP_SRC/TRP/trctrp_ctl.F90

    r719 r771  
    11MODULE trctrp_ctl 
    2    !!============================================================================== 
     2   !!====================================================================== 
    33   !!                       ***  MODULE  trctrp_ctl  *** 
    4    !! Ocean passive tracers:  transport option control 
    5    !!============================================================================== 
     4   !! TOP :   transport option control 
     5   !!====================================================================== 
     6   !! History :   1.0  !  2004-03 (C. Ethe) Original code 
     7   !!---------------------------------------------------------------------- 
    68#if defined key_passivetrc 
    79   !!---------------------------------------------------------------------- 
     10   !!   'key_passivetrc'                                         TOP models 
     11   !!---------------------------------------------------------------------- 
    812   !!   trc_trp_ctl  : control the different options of transport 
    9    !!---------------------------------------------------------------------- 
    10    !! * Modules used 
    11    USE oce_trc             ! ocean dynamics and active tracers variables 
    12    USE trc                 ! ocean passive tracers variables 
    13    USE trctrp_lec          ! passive tracers transport 
     13   !!   trc_adv_ctl  : control the different options of the advection 
     14   !!   trc_ldf_ctl  : control the different options of the lateral diffusion 
     15   !!   trc_zdf_ctl  : control the different options of the vertical diffusion 
     16   !!   trc_dmp_ctl  : control the different options of the internal damping 
     17   !!---------------------------------------------------------------------- 
     18   USE oce_trc       ! ocean dynamics and active tracers variables 
     19   USE trc           ! ocean passive tracers variables 
     20   USE trctrp_lec    ! passive tracers transport 
    1421 
    1522   IMPLICIT NONE 
    1623   PRIVATE 
    1724 
    18    !! * Accessibility 
    19    PUBLIC trc_trp_ctl    
    20  
    21    !! * Module variable 
     25   PUBLIC   trc_trp_ctl   ! called by ??? 
     26 
    2227#if defined key_trcldf_eiv 
    2328      LOGICAL, PARAMETER ::   lk_trcldf_eiv   = .TRUE.   !: eddy induced velocity flag 
     
    2530      LOGICAL, PARAMETER ::   lk_trcldf_eiv   = .FALSE.  !: eddy induced velocity flag 
    2631#endif 
    27  
    28    !!---------------------------------------------------------------------- 
    29    !!   TOP 1.0 , LOCEAN-IPSL (2005)  
    30    !! $Header$  
    31    !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt  
     32   !!---------------------------------------------------------------------- 
     33   !! NEMO/TOP 1.0 , LOCEAN-IPSL (2005)  
     34   !! $Id$  
     35   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
    3236   !!---------------------------------------------------------------------- 
    3337 
     
    3539 
    3640   SUBROUTINE trc_trp_ctl 
    37       !!--------------------------------------------------------------------- 
     41      !!---------------------------------------------------------------------- 
    3842      !!                  ***  ROUTINE trc_trp_ctl  *** 
    3943      !!                 
    4044      !! ** Purpose :   Control the consistency between cpp options for  
    4145      !!                tracer transport 
    42       !! 
    43       !! History : 
    44       !!   9.0  !  04-0.  (C. Ethe)  
    45       !!---------------------------------------------------------------------- 
    46  
    47       !!---------------------------------------------------------------------- 
    48       !!  TOP 1.0 , LOCEAN-IPSL (2005)  
    49       !!---------------------------------------------------------------------- 
    50  
    51       !! Control of Advection scheme options 
    52       CALL trc_adv_ctl 
    53  
    54       !! Control of Lateral diffusion scheme options 
    55       CALL trc_ldf_ctl 
    56  
    57       !! Control of Vertival diffusion scheme options 
    58       CALL trc_zdf_ctl 
    59  
    60       !! Control of Newtonian damping  options 
     46      !!---------------------------------------------------------------------- 
     47      !!---------------------------------------------------------------------- 
     48 
     49      CALL trc_adv_ctl      ! Control of Advection scheme options 
     50 
     51      CALL trc_ldf_ctl      ! Control of Lateral diffusion scheme options 
     52 
     53      CALL trc_zdf_ctl      ! Control of Vertival diffusion scheme options 
     54 
     55      !                     ! Control of Newtonian damping  options 
    6156      IF(lwp) THEN 
     57         WRITE(numout,*) 
    6258         WRITE(numout,*) ' *** Tracer damping option' 
    63          WRITE(numout,*) 
    64       ENDIF 
    65  
     59      ENDIF 
    6660#if defined key_trcdmp 
    67       IF(lwp) THEN  
    68          WRITE(numout,*)' key_trcdmp is defined' 
    69          WRITE(numout,*)' Check trcdmp ROUTINE ' 
    70          WRITE(numout,*)'  ' 
    71       ENDIF  
     61      IF(lwp) WRITE(numout,*) '     key_trcdmp is defined:   Check trcdmp ROUTINE ' 
    7262      CALL trc_dmp_ctl 
    7363#else 
    74       IF (lwp) WRITE(numout,*) ' No tracer damping' 
    75 #endif 
    76  
    77  
     64      IF(lwp) WRITE(numout,*) '     No tracer damping' 
     65#endif 
     66      ! 
    7867   END SUBROUTINE trc_trp_ctl 
     68 
    7969 
    8070   SUBROUTINE trc_adv_ctl 
     
    8373      !!                 
    8474      !! ** Purpose :   Control the consistency between cpp options for  
    85       !!      tracer advection schemes 
    86       !! 
    87       !! History : 
    88       !!   8.5  !  02-11  (G. Madec)  Original code 
    89       !!   9.0  !  04-0.  (C. Ethe)  adapted for passive tracers 
    90       !!---------------------------------------------------------------------- 
    91  
    92       !! * Local declarations 
     75      !!              tracer advection schemes 
     76      !!---------------------------------------------------------------------- 
    9377      INTEGER ::   ioptio 
    94  
    95  
    96       !!---------------------------------------------------------------------- 
    97       !!  TOP 1.0 , LOCEAN-IPSL (2005)  
    9878      !!---------------------------------------------------------------------- 
    9979 
     
    127107            &    CALL ctl_stop( '    cross-land advection only with 2nd order advection scheme ' ) 
    128108      ENDIF 
    129  
     109      ! 
    130110   END SUBROUTINE trc_adv_ctl 
     111 
    131112 
    132113   SUBROUTINE trc_ldf_ctl 
     
    136117      !! ** Purpose :   Control the consistency between cpp options for  
    137118      !!      tracer lateral diffusion  
    138       !! 
    139       !! History : 
    140       !!   9.0  !  03-04  (C. Ethe)  
    141       !!---------------------------------------------------------------------- 
    142       !! * Local declarations 
     119      !!---------------------------------------------------------------------- 
    143120      INTEGER ::   ioptio               ! ??? 
    144121      LOGICAL ::   ll_print = .FALSE.   ! =T print eddy coef. in numout       
    145  
    146       !!---------------------------------------------------------------------- 
    147       !!  TOP 1.0 , LOCEAN-IPSL (2005)  
    148122      !!---------------------------------------------------------------------- 
    149123 
     
    161135         IF( ln_trcldf_lap   )   ioptio = ioptio + 1 
    162136         IF( ln_trcldf_bilap )   ioptio = ioptio + 1 
    163          IF( ioptio /= 1 )  & 
    164             &   CALL ctl_stop( '    use ONE of the 2 lap/bilap operator type on tracer' ) 
     137         IF( ioptio /= 1 )   CALL ctl_stop( '    use ONE of the 2 lap/bilap operator type on tracer' ) 
    165138          
    166139         ioptio = 0 
     
    168141         IF( ln_trcldf_hor   )   ioptio = ioptio + 1 
    169142         IF( ln_trcldf_iso   )   ioptio = ioptio + 1 
    170          IF( ioptio /= 1 ) & 
    171             &   CALL ctl_stop( '   use only ONE direction (level/hor/iso)' ) 
     143         IF( ioptio /= 1 )   CALL ctl_stop( '   use only ONE direction (level/hor/iso)' ) 
    172144          
    173145         ! ... Choice of the lateral scheme used 
     
    195167         l_trcldf_bilapg  =  ln_trcldf_bilap .AND. ln_trcldf_hor       ! geopotential bilap. (s-coord) 
    196168         l_trcldf_iso     =  ln_trcldf_lap   .AND.                  &  ! laplacian operator 
    197             &                   ( ln_trcldf_iso   .OR.  ln_trcldf_hor )  &  ! iso-neutral (z-coord) or horizontal (s-coord) 
     169            &              ( ln_trcldf_iso   .OR.  ln_trcldf_hor )  &  ! iso-neutral (z-coord) or horizontal (s-coord) 
    198170            &                                     .AND. .NOT.ln_zps 
    199          l_trcldf_iso_zps =       ln_trcldf_lap   .AND.                  &  ! laplacian operator 
    200             &                   ( ln_trcldf_iso   .OR.  ln_trcldf_hor )  &  ! iso-neutral (partial steps) 
    201             &                                     .AND. ln_zps              ! or geopotential in mixed partial steps/s-coord 
     171         l_trcldf_iso_zps =  ln_trcldf_lap   .AND.                  &  ! laplacian operator 
     172            &              ( ln_trcldf_iso   .OR.  ln_trcldf_hor )  &  ! iso-neutral (partial steps) 
     173            &                                .AND. ln_zps              ! or geopotential in mixed partial steps/s-coord 
    202174         l_trczdf_iso    = .FALSE. 
    203175         l_trczdf_iso_vo = .FALSE. 
     
    211183#endif 
    212184          
    213           
    214185         ioptio = 0 
    215186         IF( l_trcldf_lap     )   ioptio = ioptio + 1 
     
    261232         ENDIF 
    262233      ENDIF 
    263  
     234      ! 
    264235   END SUBROUTINE trc_ldf_ctl 
     236 
    265237 
    266238   SUBROUTINE trc_zdf_ctl 
     
    268240      !!                  ***  ROUTINE trc_zdf_ctl  *** 
    269241      !!  
    270       !! ** Purpose :     Control the consistency between cpp options for  
    271       !!      tracer vertical diffusion 
    272       !! 
    273       !!   9.0  !  04-03  (C. Ethe)   
    274       !!---------------------------------------------------------------------- 
    275       !! * Local declarations 
    276  
    277       !!---------------------------------------------------------------------- 
    278       !!  TOP 1.0 , LOCEAN-IPSL (2005)  
     242      !! ** Purpose :   Control the consistency between cpp options for  
     243      !!              tracer vertical diffusion 
     244      !!---------------------------------------------------------------------- 
    279245      !!---------------------------------------------------------------------- 
    280246 
     
    305271      l_trczdf_imp = .TRUE. 
    306272#endif 
    307  
    308  
     273      ! 
    309274   END SUBROUTINE trc_zdf_ctl 
     275 
    310276 
    311277   SUBROUTINE trc_dmp_ctl 
     
    314280      !!  
    315281      !! ** Purpose :    Control the consistency between cpp options for  
    316       !!      tracer newtonian damping  
    317       !! 
    318       !! 
    319       !! History : 
    320       !!   9.0  !  04-03  (C. Ethe)  
     282      !!              tracer newtonian damping  
    321283      !!---------------------------------------------------------------------- 
    322284#if defined key_trcdmp 
    323285 
    324286      SELECT CASE ( ndmptr ) 
    325  
     287      ! 
    326288      CASE ( -1 )               ! ORCA: damping in Red & Med Seas only 
    327289         IF(lwp) WRITE(numout,*) '          tracer damping in the Med & Red seas only' 
    328  
     290         ! 
    329291      CASE ( 1:90 )             ! Damping poleward of 'ndmptr' degrees 
    330292         IF(lwp) WRITE(numout,*) '          tracer damping poleward of', ndmptr, ' degrees' 
    331  
     293         ! 
    332294      CASE DEFAULT 
    333  
    334295         WRITE(ctmp1,*) '          bad flag value for nmldmp = ', ndmptr 
    335296         CALL ctl_stop(ctmp1) 
    336  
     297         ! 
    337298      END SELECT 
    338299 
    339  
    340300      SELECT CASE ( nmldmptr ) 
    341  
     301      ! 
    342302      CASE ( 0 )                ! newtonian damping throughout the water column 
    343303         IF(lwp) WRITE(numout,*) '          tracer damping throughout the water column' 
    344  
     304         ! 
    345305      CASE ( 1 )                ! no damping in the turbocline (avt > 5 cm2/s) 
    346306         IF(lwp) WRITE(numout,*) '          no tracer damping in the turbocline' 
    347  
     307         ! 
    348308      CASE ( 2 )                ! no damping in the mixed layer  
    349309         IF(lwp) WRITE(numout,*) '          no tracer damping in the mixed layer' 
    350  
     310         ! 
    351311      CASE DEFAULT 
    352312         WRITE(ctmp1,*) '          bad flag value for nmldmp = ', nmldmptr 
    353313         CALL ctl_stop(ctmp1) 
    354  
     314         ! 
    355315      END SELECT 
    356316#endif 
    357   
     317      ! 
    358318   END SUBROUTINE trc_dmp_ctl 
    359319 
    360320#else 
    361321   !!---------------------------------------------------------------------- 
    362    !!   Dummy module :                      NO passive tracer 
     322   !!   Dummy module :                                        No TOP models 
    363323   !!---------------------------------------------------------------------- 
    364324CONTAINS 
  • branches/dev_001_GM/NEMO/TOP_SRC/TRP/trctrp_lec.F90

    r770 r771  
    11MODULE trctrp_lec 
    2    !!============================================================================== 
     2   !!====================================================================== 
    33   !!                       ***  MODULE  trctrp_lec  *** 
    4    !! Ocean passive tracers:  namelist read options for transport 
    5    !!============================================================================== 
     4   !! TOP :   namelist read options for transport 
     5   !!====================================================================== 
    66   !! History :   1.0  !  2004-03  (C. Ethe)  Original code 
    77   !!             2.0  !  2007-12  (C. Ethe, G. Madec)  revised architecture 
     
    99#if defined key_passivetrc 
    1010   !!---------------------------------------------------------------------- 
    11    !!   'key_passivetrc'                                          TOP model 
     11   !!   'key_passivetrc'                                         TOP models 
    1212   !!---------------------------------------------------------------------- 
    1313   !!   trc_trp_lec  : read the passive tracer namelist for transport 
     
    9696      !!---------------------------------------------------------------------- 
    9797 
    98       ! Read Namelist namtrcadv : tracer advection scheme 
    99       ! ------------------------- 
    100       REWIND( numnat ) 
     98      IF(lwp) WRITE(numout,*) 
     99      IF(lwp) WRITE(numout,*) ' trc_trp_lec: read namelist for tracer transport' 
     100      IF(lwp) WRITE(numout,*) ' ~~~~~~~~~~~' 
     101 
     102      !                                ! tracer advection scheme 
     103      REWIND( numnat )                 !   ! Read Namelist namtrcadv 
    101104      READ  ( numnat, namtrcadv ) 
    102105 
    103       ! Parameter control and print 
    104       ! --------------------------- 
    105       ! Control print 
    106       IF(lwp) THEN 
     106      IF(lwp) THEN                     !   ! Control print 
    107107         WRITE(numout,*) 
    108          WRITE(numout,*) 'choice/control of the tracer advection scheme' 
    109          WRITE(numout,*) '~~~~~~~~~~~' 
    110          WRITE(numout,*) '          Namelist namtrcadv : chose a advection scheme for tracers' 
    111          WRITE(numout,*) 
    112          WRITE(numout,*) '             2nd order advection scheme     ln_trcadv_cen2   = ', ln_trcadv_cen2 
    113          WRITE(numout,*) '             TVD advection scheme           ln_trcadv_tvd    = ', ln_trcadv_tvd 
    114          WRITE(numout,*) '             MUSCL  advection scheme        ln_trcadv_muscl  = ', ln_trcadv_muscl 
    115          WRITE(numout,*) '             MUSCL2 advection scheme        ln_trcadv_muscl2 = ', ln_trcadv_muscl2 
    116          WRITE(numout,*) '             SMOLARKIEWICZ advection scheme ln_trcadv_smolar = ', ln_trcadv_smolar 
     108         WRITE(numout,*) '   Namelist namtrcadv : chose a advection scheme for tracers' 
     109         WRITE(numout,*) '      2nd order advection scheme     ln_trcadv_cen2   = ', ln_trcadv_cen2 
     110         WRITE(numout,*) '      TVD advection scheme           ln_trcadv_tvd    = ', ln_trcadv_tvd 
     111         WRITE(numout,*) '      MUSCL  advection scheme        ln_trcadv_muscl  = ', ln_trcadv_muscl 
     112         WRITE(numout,*) '      MUSCL2 advection scheme        ln_trcadv_muscl2 = ', ln_trcadv_muscl2 
     113         WRITE(numout,*) '      SMOLARKIEWICZ advection scheme ln_trcadv_smolar = ', ln_trcadv_smolar 
    117114      ENDIF 
    118115 
    119116#if  defined key_trcbbl_dif 
    120       ! Read Namelist namtrcbbl : Bottom boundary layer coef 
    121       ! -------------------------------------------------- 
    122       REWIND( numnat ) 
     117      !                                ! Bottom boundary layer  
     118      REWIND( numnat )                 !   ! Read Namelist namtrcbbl 
    123119      READ  ( numnat, namtrcbbl ) 
    124120 
    125       ! Parameter control and print 
    126       ! --------------------------- 
    127       IF(lwp) THEN 
    128          WRITE(numout,*) ' Diffusive Bottom Boundary Layer' 
    129          WRITE(numout,*) '~~~~~~~~' 
    130          WRITE(numout,*) ' bottom boundary layer coef.    atrcbbl = ', atrcbbl 
     121      IF(lwp) THEN                     !   ! Control print 
     122         WRITE(numout,*) 
     123         WRITE(numout,*) '   Namelist namtrcbbl : set Diffusive Bottom Boundary Layer parameters' 
     124         WRITE(numout,*) '      bottom boundary layer coef.    atrcbbl = ', atrcbbl 
    131125# if defined key_trcbbl_adv 
    132          WRITE(numout,*) ' * Advective Bottom Boundary Layer' 
     126         WRITE(numout,*) '   * Advective Bottom Boundary Layer' 
    133127# endif 
    134          WRITE(numout,*) 
    135128      ENDIF 
    136129#endif 
    137130 
    138       !  Define the lateral tracer physics parameters 
    139       ! ============================================= 
    140      
    141       ! Read Namelist namtrcldf : Lateral physics on tracers 
    142       REWIND( numnat ) 
     131      !                                ! Lateral physics on tracers    
     132      REWIND( numnat )                 !   ! Read Namelist namtrcldf 
    143133      READ  ( numnat, namtrcldf ) 
    144134 
    145       IF(lwp) THEN 
     135      IF(lwp) THEN                     !   ! Control print 
    146136         WRITE(numout,*) 
    147          WRITE(numout,*) 'lateral passive tracer physics' 
    148          WRITE(numout,*) '~~~~~~~' 
    149137         WRITE(numout,*) '   Namelist namtrcldf : set lateral mixing parameters (type, direction, coefficients)' 
    150          WRITE(numout,*) '     perform lateral diffusion or not               ln_trcldf_diff  = ', ln_trcldf_diff 
    151          WRITE(numout,*) '     laplacian operator                             ln_trcldf_lap   = ', ln_trcldf_lap 
    152          WRITE(numout,*) '     bilaplacian operator                           ln_trcldf_bilap = ', ln_trcldf_bilap 
    153          WRITE(numout,*) '     iso-level                                      ln_trcldf_level = ', ln_trcldf_level 
    154          WRITE(numout,*) '     horizontal (geopotential)                      ln_trcldf_hor   = ', ln_trcldf_hor 
    155          WRITE(numout,*) '     iso-neutral                                    ln_trcldf_iso   = ', ln_trcldf_iso 
    156          WRITE(numout,*) '     lateral eddy diffusivity                              ahtrc0   = ', ahtrc0 
    157          WRITE(numout,*) '     background hor. diffusivity                            ahtrb0  = ', ahtrb0 
    158          WRITE(numout,*) '     eddy induced velocity coef.                           aeivtr0  = ', aeivtr0 
    159          WRITE(numout,*) '     ratio between passive and active tracer diffusion coef  trcrat = ', trcrat 
     138         WRITE(numout,*) '      perform lateral diffusion or not               ln_trcldf_diff  = ', ln_trcldf_diff 
     139         WRITE(numout,*) '      laplacian operator                             ln_trcldf_lap   = ', ln_trcldf_lap 
     140         WRITE(numout,*) '      bilaplacian operator                           ln_trcldf_bilap = ', ln_trcldf_bilap 
     141         WRITE(numout,*) '      iso-level                                      ln_trcldf_level = ', ln_trcldf_level 
     142         WRITE(numout,*) '      horizontal (geopotential)                      ln_trcldf_hor   = ', ln_trcldf_hor 
     143         WRITE(numout,*) '      iso-neutral                                    ln_trcldf_iso   = ', ln_trcldf_iso 
     144         WRITE(numout,*) '      lateral eddy diffusivity                              ahtrc0   = ', ahtrc0 
     145         WRITE(numout,*) '      background hor. diffusivity                            ahtrb0  = ', ahtrb0 
     146         WRITE(numout,*) '      eddy induced velocity coef.                           aeivtr0  = ', aeivtr0 
     147         WRITE(numout,*) '      ratio between passive and active tracer diffusion coef  trcrat = ', trcrat 
    160148      ENDIF 
    161149 
    162       ! Read namtrczdf namelist : vertical mixing parameters 
    163       ! -------------------- 
    164       REWIND( numnat ) 
     150      !                                ! Vertical mixing 
     151      REWIND( numnat )                 !   ! Read namtrczdf namelist 
    165152      READ  ( numnat, namtrczdf ) 
    166153 
    167       ! Parameter print 
    168       ! --------------- 
    169       IF(lwp) THEN 
     154      IF(lwp) THEN                     !   ! Control print 
    170155         WRITE(numout,*) 
    171          WRITE(numout,*) 'vertical physics' 
    172          WRITE(numout,*) '~~~~~~~~' 
    173          WRITE(numout,*) '          Namelist namtrczdf : set vertical diffusion parameters' 
    174          WRITE(numout,*) '             time splitting / backward scheme ln_trczdf_exp = ', ln_trczdf_exp 
    175          WRITE(numout,*) '             number of time step               n_trczdf_exp = ', n_trczdf_exp 
     156         WRITE(numout,*) '   Namelist namtrczdf : set vertical diffusion parameters' 
     157         WRITE(numout,*) '      time splitting / backward scheme ln_trczdf_exp = ', ln_trczdf_exp 
     158         WRITE(numout,*) '      number of time step               n_trczdf_exp = ', n_trczdf_exp 
    176159      ENDIF 
    177160 
    178161# if defined key_trcdmp 
    179       ! Read Namelist namtdp : passive tracres damping term 
    180       ! -------------------- 
    181       REWIND( numnat ) 
     162      !                                ! passive tracres damping term 
     163      REWIND( numnat )                 !   ! Read Namelist namtdp 
    182164      READ  ( numnat, namtrcdmp ) 
    183       IF( lzoom )   nmldmptr = 0      ! restoring to climatology at closed north or south boundaries 
     165      IF( lzoom )   nmldmptr = 0           ! restoring to climatology at closed north or south boundaries 
    184166 
    185       ! Parameter control and print 
    186       ! --------------------------- 
    187       IF(lwp) THEN 
     167      IF(lwp) THEN                     !   ! Control print 
    188168         WRITE(numout,*) 
    189          WRITE(numout,*) 'newtonian damping' 
    190          WRITE(numout,*) '~~~~~~~' 
    191          WRITE(numout,*) '          Namelist namtrcdmp : set damping parameter' 
    192          WRITE(numout,*) '             tracers damping option         ndmptr   = ', ndmptr 
    193          WRITE(numout,*) '             create a damping.coeff file    ndmpftr  = ', ndmpftr 
    194          WRITE(numout,*) '             mixed layer damping option     nmldmptr = ', nmldmptr, '(zoom: forced to 0)' 
    195          WRITE(numout,*) '             surface time scale (days)      sdmptr   = ', sdmptr 
    196          WRITE(numout,*) '             bottom time scale (days)       bdmptr   = ', bdmptr 
    197          WRITE(numout,*) '             depth of transition (meters)   hdmptr   = ', hdmptr 
    198          WRITE(numout,*) 
     169         WRITE(numout,*) '   Namelist namtrcdmp : set damping parameter' 
     170         WRITE(numout,*) '      tracers damping option         ndmptr   = ', ndmptr 
     171         WRITE(numout,*) '      create a damping.coeff file    ndmpftr  = ', ndmpftr 
     172         WRITE(numout,*) '      mixed layer damping option     nmldmptr = ', nmldmptr, '(zoom: forced to 0)' 
     173         WRITE(numout,*) '      surface time scale (days)      sdmptr   = ', sdmptr 
     174         WRITE(numout,*) '      bottom time scale (days)       bdmptr   = ', bdmptr 
     175         WRITE(numout,*) '      depth of transition (meters)   hdmptr   = ', hdmptr 
    199176      ENDIF 
    200177#endif 
  • branches/dev_001_GM/NEMO/TOP_SRC/trcdit.F90

    r768 r771  
    197197   END SUBROUTINE trcdit_wr 
    198198 
    199  
    200199# if defined key_trc_diatrd 
    201200 
     
    435434   END SUBROUTINE trcdid_wr 
    436435 
     436# else 
     437   SUBROUTINE trcdid_wr( kt, kindic )                      ! Dummy routine 
     438      INTEGER, INTENT ( in ) ::   kt, kindic 
     439      WRITE(*,*) 'trcdid_wr: You should not have seen this print! error?', kt, kindic 
     440   END SUBROUTINE trcdid_wr 
    437441# endif 
    438442 
     
    580584END SUBROUTINE trcdii_wr 
    581585 
     586# else 
     587   SUBROUTINE trcdii_wr( kt, kindic )                      ! Dummy routine 
     588      INTEGER, INTENT ( in ) :: kt, kindic 
     589      WRITE(*,*) 'trcdii_wr: You should not have seen this print! error?', kt, kindic 
     590   END SUBROUTINE trcdii_wr 
    582591# endif 
    583592 
     
    701710   END SUBROUTINE trcdib_wr 
    702711 
     712# else 
     713   SUBROUTINE trcdib_wr( kt, kindic )                      ! Dummy routine 
     714      INTEGER, INTENT ( in ) ::   kt, kindic 
     715      WRITE(*,*) 'trcdib_wr: You should not have seen this print! error?', kt, kindic 
     716   END SUBROUTINE trcdib_wr 
    703717# endif  
    704718 
  • branches/dev_001_GM/NEMO/TOP_SRC/trcrst.F90

    r768 r771  
    261261                  &   +             0.5e-3               * ( 1.- tmask(ji,jj,jk) ) 
    262262               bicarb = 2.* trn(ji,jj,jk,jpdic) - caralk 
    263                hi(ji,jj,jk) = ( ak23(ji,jj,jk) * bicarb / co3 )   *       tmask(ji,jj,jk) 
     263               hi(ji,jj,jk) = ( ak23(ji,jj,jk) * bicarb / co3 )   *       tmask(ji,jj,jk)   & 
    264264                  &         +             1.0e-9                  * ( 1.- tmask(ji,jj,jk) ) 
    265265            END DO 
  • branches/dev_001_GM/NEMO/TOP_SRC/trcsms.F90

    r765 r771  
    8888      ! ------------------------ 
    8989 
    90       CALL p4zprg(kt)      ! main program of PISCES  
     90      CALL p4zprg( kt )      ! main program of PISCES  
    9191 
    9292 
    93       !                    ! split in  SMS to be DONE here 
     93      !                      ! split in  SMS to be DONE here 
    9494 
    9595#elif defined key_cfc 
     
    102102#endif 
    103103 
    104       IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     104      IF(ln_ctl) THEN      ! print mean trends (used for debugging) 
    105105         WRITE(charout, FMT="('SMS')") 
    106          CALL prt_ctl_trc_info(charout) 
    107          CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm) 
     106         CALL prt_ctl_trc_info( charout ) 
     107         CALL prt_ctl_trc( tab4d=tra, mask=tmask, clinfo=ctrcnm ) 
    108108      ENDIF 
    109109      ! 
  • branches/dev_001_GM/NEMO/TOP_SRC/trcstp.F90

    r768 r771  
    22   !!====================================================================== 
    33   !!                       ***  MODULE trcstp  *** 
    4    !! Time-stepping    : time loop of opa for passive tracer 
     4   !! TOP :   time stepping of TOP models (passive tracers) 
    55   !!====================================================================== 
     6   !! History :   1.0  !  2004-03 (C. Ethe) Original code 
     7   !!---------------------------------------------------------------------- 
    68#if defined key_passivetrc 
    79   !!---------------------------------------------------------------------- 
    8    !!   trc_stp      : passive tracer system time-stepping 
     10   !!   'key_passivetrc'                                         TOP models 
    911   !!---------------------------------------------------------------------- 
    10    !! * Modules used 
    11    USE oce_trc          ! ocean dynamics and active tracers variables 
    12    USE trc              ! ocean passive tracers variables  
    13    USE trctrp           ! passive tracers transport 
    14    USE trcsms           ! passive tracers sources and sinks 
    15    USE prtctl_trc       ! Print control for debbuging 
    16    USE trcdia 
    17    USE trcdit 
    18    USE trcrst 
     12   !!   trc_stp       : passive tracer system time-stepping 
     13   !!---------------------------------------------------------------------- 
     14   USE oce_trc        ! ocean dynamics and active tracers variables 
     15   USE trc            ! ocean passive tracers variables  
     16   USE trctrp         ! passive tracers transport 
     17   USE trcsms         ! passive tracers sources and sinks 
     18   USE prtctl_trc     ! Print control for debbuging 
     19   USE trcdia         ! passive tracer diagnostics 
     20   USE trcdit         ! ??? 
     21   USE trcrst         ! ??? 
    1922 
    2023   IMPLICIT NONE 
    2124   PRIVATE 
    2225 
    23    !! * Routine accessibility 
    24    PUBLIC trc_stp           ! called by step 
     26   PUBLIC   trc_stp   ! called in step.F90 module 
     27 
    2528   !!---------------------------------------------------------------------- 
    26    !!   TOP 1.0 , LOCEAN-IPSL (2005)  
    27    !! $Header$  
    28    !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt  
     29   !! NEMO/TOP 1.0 , LOCEAN-IPSL (2005)  
     30   !! $Id$  
     31   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
    2932   !!---------------------------------------------------------------------- 
    3033 
     
    3235 
    3336   SUBROUTINE trc_stp( kt, kindic ) 
    34       !!------------------------------------------------------------------- 
     37      !!---------------------------------------------------------------------- 
    3538      !!                     ***  ROUTINE trc_stp  *** 
    3639      !!                       
    37       !! ** Purpose : Time loop of opa for passive tracer 
     40      !! ** Purpose :   Time loop of TOP passive tracer 
    3841      !!  
    39       !! ** Method  :  
    40       !!              Compute the passive tracers trends  
    41       !!              Update the passive tracers 
    42       !! 
    43       !! History : 
    44       !!   9.0  !  04-03  (C. Ethe)  Original 
    45       !!------------------------------------------------------------------- 
    46       !! * Arguments 
    47       INTEGER, INTENT( in ) ::  kt  ! ocean time-step index 
    48       INTEGER, INTENT( in ) ::  kindic 
     42      !! ** Method  :   Compute the passive tracers trends  
     43      !!                Update the passive tracers 
     44      !!---------------------------------------------------------------------- 
     45      INTEGER, INTENT( in ) ::   kt       ! ocean time-step index 
     46      INTEGER, INTENT( in ) ::   kindic   ! ??? 
    4947      CHARACTER (len=25) :: charout 
     48      !!---------------------------------------------------------------------- 
    5049 
    51       ! this ROUTINE is called only every ndttrc time step 
    52       IF( MOD( kt , ndttrc ) /= 0 ) RETURN 
     50      IF( MOD( kt, ndttrc ) /= 0 )   RETURN            ! routine called only every ndttrc time step 
    5351 
    54       CALL trc_rst_opn( kt )      ! Open tracer restart file  
    55  
    56        ! tracers: sink and source  
    5752      IF(ln_ctl) THEN 
    5853         WRITE(charout,FMT="('kt =', I4,'  d/m/y =',I2,I2,I4)") kt, nday, nmonth, nyear 
     
    6055      ENDIF 
    6156 
    62       CALL trc_sms( kt ) 
     57                       CALL trc_rst_opn( kt )          ! Open tracer restart file  
    6358 
    64       IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
    65          WRITE(charout, FMT="('SMS')") 
    66          CALL prt_ctl_trc_info(charout) 
    67          CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm) 
    68       ENDIF 
     59                       CALL trc_sms( kt )              ! sink and source of passive tracers 
    6960 
    70       ! transport of passive tracers 
    71       CALL trc_trp( kt ) 
     61                       CALL trc_trp( kt )              ! transport of passive tracers 
    7262 
    73       IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
    74          WRITE(charout, FMT="('TRP')") 
    75          CALL prt_ctl_trc_info(charout) 
    76          CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm) 
    77       ENDIF 
     63      IF( lrst_trc )   CALL trc_rst_wri( kt )          ! write tracer restart file 
    7864 
    79       IF( lrst_trc ) CALL trc_rst_wri( kt )  ! write tracer restart file 
    80  
    81       CALL trc_dia( kt, kindic )     ! diagnostics 
    82  
    83  
     65                       CALL trc_dia( kt, kindic )      ! diagnostics 
     66      ! 
    8467   END SUBROUTINE trc_stp 
    8568 
    8669#else 
    8770   !!---------------------------------------------------------------------- 
    88    !!   Default key                                     NO passive tracers 
     71   !!   Dummy module                                          No TOP models 
    8972   !!---------------------------------------------------------------------- 
    9073CONTAINS 
  • branches/dev_001_GM/NEMO/TOP_SRC/trp_trc.F90

    r765 r771  
    1212#if defined key_passivetrc 
    1313   !!---------------------------------------------------------------------- 
    14    !!   'key_passivetrc'                                    Passive tracers 
     14   !!   'key_passivetrc'                                          TOP model 
    1515   !!---------------------------------------------------------------------- 
    1616 
Note: See TracChangeset for help on using the changeset viewer.