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 503 for trunk/NEMO/OPA_SRC/TRD – NEMO

Changeset 503 for trunk/NEMO/OPA_SRC/TRD


Ignore:
Timestamp:
2006-09-27T10:52:29+02:00 (18 years ago)
Author:
opalod
Message:

nemo_v1_update_064 : CT : general trends update including the addition of mean windows analysis possibility in the mixed layer

Location:
trunk/NEMO/OPA_SRC/TRD
Files:
1 added
8 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMO/OPA_SRC/TRD/trdicp.F90

    r249 r503  
    44   !! Ocean diagnostics:  ocean tracers and dynamic trends 
    55   !!===================================================================== 
     6   !! History :       !  91-12 (G. Madec) 
     7   !!                 !  92-06 (M. Imbard) add time step frequency 
     8   !!                 !  96-01 (G. Madec)  terrain following coordinates 
     9   !!            8.5  !  02-06 (G. Madec)  F90: Free form and module 
     10   !!            9.0  !  04-08 (C. Talandier) New trends organization 
     11   !!---------------------------------------------------------------------- 
    612#if  defined key_trdtra   ||   defined key_trddyn   ||   defined key_esopa 
    713   !!---------------------------------------------------------------------- 
     
    915   !!   'key_trddyn'                            momentum trends diagnostics 
    1016   !!---------------------------------------------------------------------- 
    11  
    12    !!---------------------------------------------------------------------- 
    13    !!   trd              : verify the basin averaged properties for tra/dyn  
     17   !!---------------------------------------------------------------------- 
     18   !!   trd_icp          : compute the basin averaged properties for tra/dyn  
    1419   !!   trd_dwr          : print dynmaic trends in ocean.output file 
    1520   !!   trd_twr          : print tracers trends in ocean.output file 
    1621   !!   trd_icp_init     : initialization step 
    1722   !!---------------------------------------------------------------------- 
    18    !! * Modules used 
    1923   USE oce             ! ocean dynamics and tracers variables 
    2024   USE dom_oce         ! ocean space and time domain variables 
     
    3135   PRIVATE 
    3236 
    33    !! * Interfaces 
    34    INTERFACE trd 
     37   INTERFACE trd_icp 
    3538      MODULE PROCEDURE trd_2d, trd_3d 
    3639   END INTERFACE 
    3740 
    38    !! * Routine accessibility 
    39    PUBLIC trd                   ! called by step.F90 
    40    PUBLIC trd_dwr               ! called by step.F90 
    41    PUBLIC trd_twr               ! called by step.F90 
    42    PUBLIC trd_icp_init          ! called by opa.F90 
    43  
    44    !! * Shared module variables 
    45 #if  defined key_trdtra   &&   defined key_trddyn    ||   defined key_esopa 
    46    LOGICAL, PUBLIC, PARAMETER ::   lk_trdtra = .TRUE.    !: tracers  trend flag 
    47    LOGICAL, PUBLIC, PARAMETER ::   lk_trddyn = .TRUE.    !: momentum trend flag 
    48 #elif  defined key_trdtra 
    49    LOGICAL, PUBLIC, PARAMETER ::   lk_trdtra = .TRUE.    !: tracers  trend flag 
    50    LOGICAL, PUBLIC, PARAMETER ::   lk_trddyn = .FALSE.   !: momentum trend flag 
    51 #elif  defined key_trddyn 
    52    LOGICAL, PUBLIC, PARAMETER ::   lk_trdtra = .FALSE.   !: tracers  trend flag 
    53    LOGICAL, PUBLIC, PARAMETER ::   lk_trddyn = .TRUE.    !: momentum trend flag 
    54 #endif 
     41   PUBLIC   trd_icp       ! called by trdmod.F90 
     42   PUBLIC   trd_dwr       ! called by step.F90 
     43   PUBLIC   trd_twr       ! called by step.F90 
     44   PUBLIC   trd_icp_init  ! called by opa.F90 
    5545 
    5646   !! * Substitutions 
     
    6050   !!   OPA 9.0 , LOCEAN-IPSL (2005)  
    6151   !! $Header$  
    62    !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt  
     52   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
    6353   !!---------------------------------------------------------------------- 
    6454 
    6555CONTAINS 
    6656 
    67    SUBROUTINE trd_2d(ptrd2dx, ptrd2dy, ktrd , ctype) 
     57   SUBROUTINE trd_2d( ptrd2dx, ptrd2dy, ktrd , ctype, clpas ) 
    6858      !!--------------------------------------------------------------------- 
    6959      !!                  ***  ROUTINE trd_2d  *** 
     
    7161      !! ** Purpose : verify the basin averaged properties of tracers and/or 
    7262      !!              momentum equations at every time step frequency ntrd. 
     63      !!---------------------------------------------------------------------- 
     64      REAL(wp), DIMENSION(jpi,jpj), INTENT(inout) ::   ptrd2dx             ! Temperature or U trend  
     65      REAL(wp), DIMENSION(jpi,jpj), INTENT(inout) ::   ptrd2dy             ! Salinity    or V trend 
     66      INTEGER                     , INTENT(in   ) ::   ktrd                ! tracer trend index 
     67      CHARACTER(len=3)            , INTENT(in   ) ::   ctype               ! momentum ('DYN') or tracers ('TRA') trends 
     68      CHARACTER(len=3)            , INTENT(in   ), OPTIONAL ::   clpas     ! number of passage 
    7369      !! 
    74       !! ** Method : 
    75       !! 
    76       !! History : 
    77       !!        !  91-12 (G. Madec) 
    78       !!        !  92-06 (M. Imbard) add time step frequency 
    79       !!        !  96-01 (G. Madec)  terrain following coordinates 
    80       !!   8.5  !  02-06 (G. Madec)  F90: Free form and module 
    81       !!   9.0  !  04-08 (C. Talandier) New trends organization 
    82       !!---------------------------------------------------------------------- 
    83       !! * Arguments 
    84       REAL(wp), DIMENSION(jpi,jpj), INTENT( inout ) ::   & 
    85          ptrd2dx,                      &   ! Temperature or U trend  
    86          ptrd2dy                           ! Salinity    or V trend 
    87  
    88       INTEGER, INTENT( in ) ::   ktrd      ! tracer trend index 
    89  
    90       CHARACTER(len=3), INTENT( in ) ::   & 
    91          ctype                             ! momentum or tracers trends type 
    92          !                                 ! 'DYN' or 'TRA' 
    93  
    94       !! * Local declarations 
    95       INTEGER ::   ji, jj        ! loop indices 
    96       REAL(wp) ::   & 
    97          zbt, zbtu, zbtv,     &  ! temporary scalars 
    98          zmsku, zmskv            !    "         " 
    99       !!---------------------------------------------------------------------- 
    100  
    101       ! 1. Advective trends and forcing trend 
    102       ! ------------------------------------- 
    103  
    104       ! 1.1 Mask the forcing trend and substract it from the vertical diffusion trend 
    105       SELECT CASE (ctype) 
    106  
    107       CASE ('DYN')              ! Momentum 
     70      INTEGER  ::   ji, jj                                                 ! loop indices 
     71      CHARACTER(len=3) ::   cpas                                           ! number of passage 
     72      REAL(wp) ::   zmsku, zbtu, zbt                                       ! temporary scalars 
     73      REAL(wp) ::   zmskv, zbtv                                            !    "         " 
     74      !!---------------------------------------------------------------------- 
     75 
     76      ! Control of optional arguments 
     77      cpas = 'fst' 
     78      IF( PRESENT(clpas) )  cpas = clpas 
     79 
     80      ! 1. Mask trends 
     81      ! -------------- 
     82 
     83      SELECT CASE( ctype ) 
     84      ! 
     85      CASE( 'DYN' )              ! Momentum 
    10886         DO jj = 1, jpjm1 
    10987            DO ji = 1, jpim1 
     
    11694         ptrd2dx(jpi, : ) = 0.e0      ;      ptrd2dy(jpi, : ) = 0.e0 
    11795         ptrd2dx( : ,jpj) = 0.e0      ;      ptrd2dy( : ,jpj) = 0.e0 
    118  
    119       CASE ('TRA')              ! Tracers 
     96         ! 
     97      CASE( 'TRA' )              ! Tracers 
    12098         ptrd2dx(:,:) = ptrd2dx(:,:) * tmask_i(:,:) 
    12199         ptrd2dy(:,:) = ptrd2dy(:,:) * tmask_i(:,:) 
    122  
     100         ! 
    123101      END SELECT 
    124102       
    125       ! 2. Basin averaged tracer trend 
    126       ! ------------------------------ 
    127  
    128       SELECT CASE (ctype) 
    129  
    130       CASE ('DYN')              ! Momentum 
     103      ! 2. Basin averaged tracer/momentum trends 
     104      ! ---------------------------------------- 
     105 
     106      SELECT CASE( ctype ) 
     107      ! 
     108      CASE( 'DYN' )              ! Momentum 
    131109         umo(ktrd) = 0.e0 
    132110         vmo(ktrd) = 0.e0 
    133  
    134          SELECT CASE (ktrd) 
    135  
    136          CASE (jpdtdswf)         ! surface forcing 
     111         ! 
     112         SELECT CASE( ktrd ) 
     113         ! 
     114         CASE( jpdyn_trd_swf )         ! surface forcing 
    137115            DO jj = 1, jpj 
    138116               DO ji = 1, jpi 
     
    141119               END DO 
    142120            END DO 
    143  
    144          CASE (jpdtdbfr)         ! bottom friction fluxes 
     121            ! 
     122         CASE( jpdyn_trd_bfr )         ! bottom friction fluxes 
    145123            DO jj = 1, jpj 
    146124               DO ji = 1, jpi 
     
    149127               END DO 
    150128            END DO 
    151  
     129            ! 
    152130         END SELECT 
    153  
    154       CASE ('TRA')              ! Tracers 
    155          tmo(ktrd) = 0.e0 
    156          smo(ktrd) = 0.e0 
     131         ! 
     132      CASE( 'TRA' )              ! Tracers 
     133         IF( cpas == 'fst' )   THEN 
     134            tmo(ktrd) = 0.e0 
     135            smo(ktrd) = 0.e0 
     136         ENDIF 
    157137         DO jj = 1, jpj 
    158138            DO ji = 1, jpi 
     
    162142            END DO 
    163143         END DO 
    164  
     144         ! 
    165145      END SELECT 
    166146       
    167       ! 3. Basin averaged tracer square trend 
    168       ! ------------------------------------- 
     147      ! 3. Basin averaged tracer/momentum square trends 
     148      ! ---------------------------------------------- 
    169149      ! c a u t i o n: field now 
    170150       
    171       SELECT CASE (ctype) 
    172  
    173       CASE ('DYN')              ! Momentum 
     151      SELECT CASE( ctype ) 
     152      ! 
     153      CASE( 'DYN' )              ! Momentum 
    174154         hke(ktrd) = 0.e0 
    175155         DO jj = 1, jpj 
     
    182162            END DO 
    183163         END DO 
    184  
    185       CASE ('TRA')              ! Tracers 
    186          t2(ktrd) = 0.e0 
    187          s2(ktrd) = 0.e0 
     164         ! 
     165      CASE( 'TRA' )              ! Tracers 
     166         IF( cpas == 'fst' )   THEN 
     167            t2(ktrd) = 0.e0 
     168            s2(ktrd) = 0.e0 
     169         ENDIF 
    188170         DO jj = 1, jpj 
    189171            DO ji = 1, jpi 
     
    193175            END DO 
    194176         END DO 
    195        
     177         !       
    196178      END SELECT 
    197  
     179      ! 
    198180   END SUBROUTINE trd_2d 
    199181 
    200182 
    201  
    202    SUBROUTINE trd_3d(ptrd3dx, ptrd3dy, ktrd, ctype) 
     183   SUBROUTINE trd_3d( ptrd3dx, ptrd3dy, ktrd, ctype, clpas ) 
    203184      !!--------------------------------------------------------------------- 
    204185      !!                  ***  ROUTINE trd_3d  *** 
     
    206187      !! ** Purpose : verify the basin averaged properties of tracers and/or 
    207188      !!              momentum equations at every time step frequency ntrd. 
     189      !!---------------------------------------------------------------------- 
     190      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(inout) ::   ptrd3dx            ! Temperature or U trend  
     191      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(inout) ::   ptrd3dy            ! Salinity    or V trend 
     192      INTEGER,                          INTENT(in   ) ::   ktrd               ! momentum or tracer trend index 
     193      CHARACTER(len=3),                 INTENT(in   ) ::   ctype              ! momentum ('DYN') or tracers ('TRA') trends 
     194      CHARACTER(len=3),                 INTENT(in   ), OPTIONAL ::   clpas    ! number of passage 
    208195      !! 
    209       !! ** Method : 
    210       !! 
    211       !! History : 
    212       !!        !  91-12 (G. Madec) 
    213       !!        !  92-06 (M. Imbard) add time step frequency 
    214       !!        !  96-01 (G. Madec)  terrain following coordinates 
    215       !!   8.5  !  02-06 (G. Madec)  F90: Free form and module 
    216       !!   9.0  !  04-08 (C. Talandier) New trends organization 
    217       !!---------------------------------------------------------------------- 
    218       !! * Arguments 
    219       REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT( inout ) ::   & 
    220           ptrd3dx,                     &   ! Temperature or U trend  
    221           ptrd3dy                          ! Salinity    or V trend 
    222  
    223       INTEGER, INTENT( in ) ::   ktrd      ! momentum or tracer trend index 
    224  
    225       CHARACTER(len=3), INTENT( in ) ::   & 
    226          ctype                             ! momentum or tracers trends type 
    227          !                                 ! 'DYN' or 'TRA' 
    228  
    229       !! * Local declarations 
    230196      INTEGER ::   ji, jj, jk 
    231       REAL(wp) ::   & 
    232          zbt, zbtu, zbtv,               &  ! temporary scalars 
    233          zmsku, zmskv 
    234       !!---------------------------------------------------------------------- 
    235  
    236       ! 1. Advective trends and forcing trend 
    237       ! ------------------------------------- 
    238  
    239       ! Mask the trends 
    240       SELECT CASE (ctype) 
    241  
    242       CASE ('DYN')              ! Momentum         
     197      CHARACTER(len=3) ::   cpas                                              ! number of passage 
     198      REAL(wp) ::   zbt, zbtu, zbtv, zmsku, zmskv                             ! temporary scalars 
     199      !!---------------------------------------------------------------------- 
     200 
     201      ! Control of optional arguments 
     202      cpas = 'fst' 
     203      IF( PRESENT(clpas) )  cpas = clpas 
     204 
     205      ! 1. Mask the trends 
     206      ! ------------------ 
     207 
     208      SELECT CASE( ctype ) 
     209      ! 
     210      CASE( 'DYN' )              ! Momentum         
    243211         DO jk = 1, jpk 
    244212            DO jj = 1, jpjm1 
     
    248216                  ptrd3dx(ji,jj,jk) = ptrd3dx(ji,jj,jk) * zmsku 
    249217                  ptrd3dy(ji,jj,jk) = ptrd3dy(ji,jj,jk) * zmskv 
    250                ENDDO 
    251             ENDDO 
    252          ENDDO 
    253  
     218               END DO 
     219            END DO 
     220         END DO 
    254221         ptrd3dx(jpi, : ,:) = 0.e0      ;      ptrd3dy(jpi, : ,:) = 0.e0 
    255222         ptrd3dx( : ,jpj,:) = 0.e0      ;      ptrd3dy( : ,jpj,:) = 0.e0 
    256  
    257       CASE ('TRA')              ! Tracers 
     223         ! 
     224      CASE( 'TRA' )              ! Tracers 
    258225         DO jk = 1, jpk 
    259226            ptrd3dx(:,:,jk) = ptrd3dx(:,:,jk) * tmask(:,:,jk) * tmask_i(:,:) 
    260227            ptrd3dy(:,:,jk) = ptrd3dy(:,:,jk) * tmask(:,:,jk) * tmask_i(:,:) 
    261          ENDDO 
    262  
     228         END DO 
     229         ! 
    263230      END SELECT    
    264231 
    265       ! 2. Basin averaged tracer/momentum trend 
    266       ! --------------------------------------- 
     232      ! 2. Basin averaged tracer/momentum trends 
     233      ! ---------------------------------------- 
    267234       
    268       SELECT CASE (ctype) 
    269  
    270       CASE ('DYN')              ! Momentum 
     235      SELECT CASE( ctype ) 
     236      ! 
     237      CASE( 'DYN' )              ! Momentum 
    271238         umo(ktrd) = 0.e0 
    272239         vmo(ktrd) = 0.e0 
     
    281248            END DO 
    282249         END DO 
    283  
    284       CASE ('TRA')              ! Tracers 
    285          tmo(ktrd) = 0.e0 
    286          smo(ktrd) = 0.e0 
     250         ! 
     251      CASE( 'TRA' )              ! Tracers 
     252         IF( cpas == 'fst' )   THEN 
     253            tmo(ktrd) = 0.e0 
     254            smo(ktrd) = 0.e0 
     255         ENDIF 
    287256         DO jk = 1, jpkm1 
    288257            DO jj = 1, jpj 
     
    294263            END DO 
    295264         END DO 
    296  
     265         ! 
    297266      END SELECT 
    298267 
    299       ! 3. Basin averaged tracer/momentum square trend 
    300       ! ---------------------------------------------- 
     268      ! 3. Basin averaged tracer/momentum square trends 
     269      ! ----------------------------------------------- 
    301270      ! c a u t i o n: field now 
    302271       
    303       SELECT CASE (ctype) 
    304  
    305       CASE ('DYN')              ! Momentum 
     272      SELECT CASE( ctype ) 
     273      ! 
     274      CASE( 'DYN' )              ! Momentum 
    306275         hke(ktrd) = 0.e0 
    307276         DO jk = 1, jpk 
     
    316285            END DO 
    317286         END DO 
    318  
    319       CASE ('TRA')              ! Tracers 
    320          t2(ktrd) = 0.e0 
    321          s2(ktrd) = 0.e0 
     287         ! 
     288      CASE( 'TRA' )              ! Tracers 
     289         IF( cpas == 'fst' )   THEN 
     290            t2(ktrd) = 0.e0 
     291            s2(ktrd) = 0.e0 
     292         ENDIF 
    322293         DO jk = 1, jpk 
    323294            DO jj = 1, jpj 
     
    329300            END DO 
    330301         END DO 
    331  
     302         ! 
    332303      END SELECT 
    333  
     304      ! 
    334305   END SUBROUTINE trd_3d 
    335306 
     
    340311      !!                  ***  ROUTINE trd_icp_init  *** 
    341312      !!  
    342       !! ** Purpose :    
    343       !! 
    344       !! ** Method  : 
    345       !! 
    346       !! History : 
    347       !!   9.0  !  03-09 (G. Madec)  Original code 
    348       !!        !  04-08 (C. Talandier) New trends organization 
    349       !!---------------------------------------------------------------------- 
    350       !! * Local declarations 
    351       INTEGER :: ji, jj, jk 
    352  
     313      !! ** Purpose :   Read the namtrd namelist 
     314      !!---------------------------------------------------------------------- 
     315      INTEGER  ::   ji, jj, jk 
    353316      REAL(wp) ::   zmskt 
    354317#if  defined key_trddyn 
    355       REAL(wp) ::   zmsku,zmskv 
     318      REAL(wp) ::   zmsku, zmskv 
    356319#endif 
    357  
    358       NAMELIST/namtrd/ ntrd, nctls 
    359       !!---------------------------------------------------------------------- 
    360  
    361       ! namelist namtrd : trend diagnostic 
    362       REWIND( numnam ) 
    363       READ  ( numnam, namtrd ) 
     320      !!---------------------------------------------------------------------- 
    364321 
    365322      IF(lwp) THEN 
     
    367324         WRITE(numout,*) 'trd_icp_init : integral constraints properties trends' 
    368325         WRITE(numout,*) '~~~~~~~~~~~~~' 
    369          WRITE(numout,*) ' ' 
    370          WRITE(numout,*) '          Namelist namtrd : ' 
    371          WRITE(numout,*) '             time step frequency trend       ntrd  = ', ntrd 
    372326      ENDIF 
    373  
    374       ! initialisation of BBL tracers lateral diffusion to zero 
    375       tldfbbl(:,:) = 0.e0   ;   sldfbbl(:,:) = 0.e0   
    376       ! initialisation of BBL tracers lateral advection to zero 
    377       tladbbl(:,:) = 0.e0   ;   sladbbl(:,:) = 0.e0   
    378       ! initialisation of workspace 
    379       tladi(:,:,:) = 0.e0  ;  tladj(:,:,:) = 0.e0 
    380       sladi(:,:,:) = 0.e0  ;  sladj(:,:,:) = 0.e0 
    381327 
    382328      ! Total volume at t-points: 
     
    392338      IF( lk_mpp )   CALL mpp_sum( tvolt )   ! sum over the global domain 
    393339 
    394       IF(lwp) THEN 
    395          WRITE(numout,*) 
    396          WRITE(numout,*) '          total ocean volume at T-point   tvolt = ',tvolt 
    397       ENDIF 
     340      IF(lwp) WRITE(numout,*) '                total ocean volume at T-point   tvolt = ',tvolt 
    398341 
    399342#if  defined key_trddyn 
     
    419362 
    420363      IF(lwp) THEN 
    421          WRITE(numout,*) '          total ocean volume at U-point   tvolu = ',tvolu 
    422          WRITE(numout,*) '          total ocean volume at V-point   tvolv = ',tvolv 
    423          WRITE(numout,*) ' ' 
     364         WRITE(numout,*) '                total ocean volume at U-point   tvolu = ',tvolu 
     365         WRITE(numout,*) '                total ocean volume at V-point   tvolv = ',tvolv 
    424366      ENDIF 
    425367#endif 
    426  
     368      ! 
    427369   END SUBROUTINE trd_icp_init 
    428  
    429370 
    430371 
     
    434375      !!  
    435376      !! ** Purpose :  write dynamic trends in ocean.output  
     377      !!---------------------------------------------------------------------- 
     378      INTEGER, INTENT(in) ::   kt                                  ! ocean time-step index 
    436379      !! 
    437       !! ** Method  : 
    438       !! 
    439       !! History : 
    440       !!   9.0  !  03-09  (G. Madec)  Original code 
    441       !!        !  04-08  (C. Talandier)  New trends organization 
    442       !!---------------------------------------------------------------------- 
    443       !! * Arguments 
    444       INTEGER, INTENT( in ) ::   kt      ! ocean time-step index 
    445       INTEGER ::   ji, jj, jk 
    446       REAL(wp) ::   & 
    447          ze1e2w,zcof,        &  !    "         " 
    448          zbe1ru, zbe2rv,     &  !    "         " 
    449          zbtr, ztz, zth  
    450  
    451       REAL(wp), DIMENSION(jpi,jpj,jpk) ::   & 
    452                zkepe, zkx, zky, zkz              ! temporary arrays 
     380      INTEGER  ::   ji, jj, jk 
     381      REAL(wp) ::   ze1e2w, zcof, zbe1ru, zbe2rv, zbtr, ztz, zth   !    "      scalars 
     382      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   zkepe, zkx, zky, zkz   ! temporary arrays 
    453383      !!---------------------------------------------------------------------- 
    454384 
     
    462392         ! c a u t i o n here, trends are computed at kt+1 (now , but after the swap) 
    463393 
    464          zkx(:,:,:) = 0.e0 
    465          zky(:,:,:) = 0.e0 
    466          zkz(:,:,:) = 0.e0 
     394         zkx(:,:,:)   = 0.e0 
     395         zky(:,:,:)   = 0.e0 
     396         zkz(:,:,:)   = 0.e0 
    467397         zkepe(:,:,:) = 0.e0 
    468398    
    469399         CALL eos( tn, sn, rhd, rhop )       ! now potential and in situ densities 
    470400 
    471          ! 4.1 Density flux at w-point 
     401         ! Density flux at w-point 
    472402         DO jk = 2, jpk 
    473403            DO jj = 1, jpj 
     
    478408            END DO 
    479409         END DO 
    480          zkz  (:,:, 1 ) = 0.e0 
     410         zkz(:,:,1) = 0.e0 
    481411          
    482412         ! Density flux at u and v-points 
     
    524454         ! --------------------------------- 
    525455         IF( lk_mpp ) THEN 
    526                CALL mpp_sum( peke ) 
    527                CALL mpp_sum( umo , 11 ) 
    528                CALL mpp_sum( vmo , 11 ) 
    529                CALL mpp_sum( hke , 10 ) 
    530          END IF 
     456            CALL mpp_sum( peke ) 
     457            CALL mpp_sum( umo , jptot_dyn ) 
     458            CALL mpp_sum( vmo , jptot_dyn ) 
     459            CALL mpp_sum( hke , jptot_dyn ) 
     460         ENDIF 
    531461 
    532462         ! I.2 Print dynamic trends in the ocean.output file 
     
    537467            WRITE (numout,*) 
    538468            WRITE (numout,9500) kt 
    539             WRITE (numout,9501) umo( 1) / tvolu, vmo( 1) / tvolv 
    540             WRITE (numout,9502) umo( 2) / tvolu, vmo( 2) / tvolv 
    541             WRITE (numout,9503) umo( 3) / tvolu, vmo( 3) / tvolv 
    542             WRITE (numout,9504) umo( 4) / tvolu, vmo( 4) / tvolv 
    543             WRITE (numout,9505) umo( 5) / tvolu, vmo( 5) / tvolv 
    544             WRITE (numout,9506) umo( 6) / tvolu, vmo( 6) / tvolv 
    545             WRITE (numout,9507) umo( 7) / tvolu, vmo( 7) / tvolv 
    546             WRITE (numout,9508) umo( 8) / tvolu, vmo( 8) / tvolv 
    547             WRITE (numout,9509) umo(10) / tvolu, vmo(10) / tvolv 
    548             WRITE (numout,9510) umo( 9) / tvolu, vmo( 9) / tvolv 
    549             WRITE (numout,9511) umo(11) / tvolu, vmo(11) / tvolv 
     469            WRITE (numout,9501) umo(jpicpd_hpg) / tvolu, vmo(jpicpd_hpg) / tvolv 
     470            WRITE (numout,9502) umo(jpicpd_keg) / tvolu, vmo(jpicpd_keg) / tvolv 
     471            WRITE (numout,9503) umo(jpicpd_rvo) / tvolu, vmo(jpicpd_rvo) / tvolv 
     472            WRITE (numout,9504) umo(jpicpd_pvo) / tvolu, vmo(jpicpd_pvo) / tvolv 
     473            WRITE (numout,9505) umo(jpicpd_ldf) / tvolu, vmo(jpicpd_ldf) / tvolv 
     474            WRITE (numout,9506) umo(jpicpd_zad) / tvolu, vmo(jpicpd_zad) / tvolv 
     475            WRITE (numout,9507) umo(jpicpd_zdf) / tvolu, vmo(jpicpd_zdf) / tvolv 
     476            WRITE (numout,9508) umo(jpicpd_spg) / tvolu, vmo(jpicpd_spg) / tvolv 
     477            WRITE (numout,9509) umo(jpicpd_swf) / tvolu, vmo(jpicpd_swf) / tvolv 
     478            WRITE (numout,9510) umo(jpicpd_dat) / tvolu, vmo(jpicpd_dat) / tvolv 
     479            WRITE (numout,9511) umo(jpicpd_bfr) / tvolu, vmo(jpicpd_bfr) / tvolv 
    550480            WRITE (numout,9512) 
    551481            WRITE (numout,9513)                                                 & 
    552             &     (  umo(1) + umo(2) + umo(3) + umo( 4) + umo( 5) + umo(6)    & 
    553             &      + umo(7) + umo(8) + umo(9) + umo(10) + umo(11) ) / tvolu,   & 
    554             &     (  vmo(1) + vmo(2) + vmo(3) + vmo( 4) + vmo( 5) + vmo(6)    & 
    555             &      + vmo(7) + vmo(8) + vmo(9) + vmo(10) + vmo(11) ) / tvolv 
     482            &     (  umo(jpicpd_hpg) + umo(jpicpd_keg) + umo(jpicpd_rvo) + umo(jpicpd_pvo) + umo(jpicpd_ldf)   & 
     483            &      + umo(jpicpd_zad) + umo(jpicpd_zdf) + umo(jpicpd_spg) + umo(jpicpd_dat) + umo(jpicpd_swf)   & 
     484            &      + umo(jpicpd_bfr) ) / tvolu,   & 
     485            &     (  vmo(jpicpd_hpg) + vmo(jpicpd_keg) + vmo(jpicpd_rvo) + vmo(jpicpd_pvo) + vmo(jpicpd_ldf)   & 
     486            &      + vmo(jpicpd_zad) + vmo(jpicpd_zdf) + vmo(jpicpd_spg) + vmo(jpicpd_dat) + vmo(jpicpd_swf)   & 
     487            &      + vmo(jpicpd_bfr) ) / tvolv 
    556488         ENDIF 
    557489 
     
    565497 9507    FORMAT(' vertical diffusion         u= ', e20.13, '    v= ', e20.13) 
    566498 9508    FORMAT(' surface pressure gradient  u= ', e20.13, '    v= ', e20.13) 
    567  9509    FORMAT(' forcing term               u= ', e20.13, '    v= ', e20.13) 
     499 9509    FORMAT(' surface wind forcing       u= ', e20.13, '    v= ', e20.13) 
    568500 9510    FORMAT(' dampimg term               u= ', e20.13, '    v= ', e20.13) 
    569501 9511    FORMAT(' bottom flux                u= ', e20.13, '    v= ', e20.13) 
     
    575507            WRITE (numout,*) 
    576508            WRITE (numout,9520) kt 
    577             WRITE (numout,9521) hke( 1) / tvolt 
    578             WRITE (numout,9522) hke( 2) / tvolt 
    579             WRITE (numout,9523) hke( 3) / tvolt 
    580             WRITE (numout,9524) hke( 4) / tvolt 
    581             WRITE (numout,9525) hke( 5) / tvolt 
    582             WRITE (numout,9526) hke( 6) / tvolt 
    583             WRITE (numout,9527) hke( 7) / tvolt 
    584             WRITE (numout,9528) hke( 8) / tvolt 
    585             WRITE (numout,9529) hke(10) / tvolt 
    586             WRITE (numout,9530) hke( 9) / tvolt 
     509            WRITE (numout,9521) hke(jpicpd_hpg) / tvolt 
     510            WRITE (numout,9522) hke(jpicpd_keg) / tvolt 
     511            WRITE (numout,9523) hke(jpicpd_rvo) / tvolt 
     512            WRITE (numout,9524) hke(jpicpd_pvo) / tvolt 
     513            WRITE (numout,9525) hke(jpicpd_ldf) / tvolt 
     514            WRITE (numout,9526) hke(jpicpd_zad) / tvolt 
     515            WRITE (numout,9527) hke(jpicpd_zdf) / tvolt 
     516            WRITE (numout,9528) hke(jpicpd_spg) / tvolt 
     517            WRITE (numout,9529) hke(jpicpd_swf) / tvolt 
     518            WRITE (numout,9530) hke(jpicpd_dat) / tvolt 
    587519            WRITE (numout,9531) 
    588520            WRITE (numout,9532)   & 
    589             &     (  hke(1) + hke(2) + hke(3) + hke(4) + hke(5) + hke(6)   & 
    590             &      + hke(7) + hke(8) + hke(9) + hke(10) ) / tvolt 
     521            &     (  hke(jpicpd_hpg) + hke(jpicpd_keg) + hke(jpicpd_rvo) + hke(jpicpd_pvo) + hke(jpicpd_ldf)   & 
     522            &      + hke(jpicpd_zad) + hke(jpicpd_zdf) + hke(jpicpd_spg) + hke(jpicpd_dat) + hke(jpicpd_swf) ) / tvolt 
    591523         ENDIF 
    592524 
     
    600532 9527    FORMAT(' vertical diffusion        u2= ', e20.13) 
    601533 9528    FORMAT(' surface pressure gradient u2= ', e20.13) 
    602  9529    FORMAT(' forcing term              u2= ', e20.13) 
     534 9529    FORMAT(' surface wind forcing      u2= ', e20.13) 
    603535 9530    FORMAT(' dampimg term              u2= ', e20.13) 
    604536 9531    FORMAT(' --------------------------------------------------') 
     
    609541            WRITE (numout,*) 
    610542            WRITE (numout,9540) kt 
    611             WRITE (numout,9541) ( hke(2) + hke(3) + hke(6) ) / tvolt 
    612             WRITE (numout,9542) ( hke(2) + hke(6) ) / tvolt 
    613             WRITE (numout,9543) ( hke(4) ) / tvolt 
    614             WRITE (numout,9544) ( hke(3) ) / tvolt 
    615             WRITE (numout,9545) ( hke(8) ) / tvolt 
    616             WRITE (numout,9546) ( hke(5) ) / tvolt 
    617             WRITE (numout,9547) ( hke(7) ) / tvolt 
    618             WRITE (numout,9548) ( hke(1) ) / tvolt, rpktrd / tvolt 
     543            WRITE (numout,9541) ( hke(jpicpd_keg) + hke(jpicpd_rvo) + hke(jpicpd_zad) ) / tvolt 
     544            WRITE (numout,9542) ( hke(jpicpd_keg) + hke(jpicpd_zad) ) / tvolt 
     545            WRITE (numout,9543) ( hke(jpicpd_pvo) ) / tvolt 
     546            WRITE (numout,9544) ( hke(jpicpd_rvo) ) / tvolt 
     547            WRITE (numout,9545) ( hke(jpicpd_spg) ) / tvolt 
     548            WRITE (numout,9546) ( hke(jpicpd_ldf) ) / tvolt 
     549            WRITE (numout,9547) ( hke(jpicpd_zdf) ) / tvolt 
     550            WRITE (numout,9548) ( hke(jpicpd_hpg) ) / tvolt, rpktrd / tvolt 
     551            WRITE (numout,*) 
     552            WRITE (numout,*) 
    619553         ENDIF 
    620554 
    621555 9540    FORMAT(' energetic consistency at it= ', i6, ' :', /' =========================================') 
    622556 9541    FORMAT(' 0 = non linear term(true if key_vorenergy or key_combined): ', e20.13) 
    623  9542    FORMAT(' 0 = ke gradient + vertical advection              : ', e20.13) 
     557 9542    FORMAT(' 0 = ke gradient + vertical advection                      : ', e20.13) 
    624558 9543    FORMAT(' 0 = coriolis term  (true if key_vorenergy or key_combined): ', e20.13) 
    625  9544    FORMAT(' 0 = uh.( rot(u) x uh ) (true if enstrophy conser.)    : ', e20.13) 
    626  9545    FORMAT(' 0 = surface pressure gradient                     : ', e20.13) 
    627  9546    FORMAT(' 0 > horizontal diffusion                          : ', e20.13) 
    628  9547    FORMAT(' 0 > vertical diffusion                            : ', e20.13) 
    629  9548    FORMAT(' pressure gradient u2 = - 1/rau0 u.dz(rhop)        : ', e20.13, '  u.dz(rhop) =', e20.13) 
    630  
     559 9544    FORMAT(' 0 = uh.( rot(u) x uh ) (true if enstrophy conser.)        : ', e20.13) 
     560 9545    FORMAT(' 0 = surface pressure gradient                             : ', e20.13) 
     561 9546    FORMAT(' 0 > horizontal diffusion                                  : ', e20.13) 
     562 9547    FORMAT(' 0 > vertical diffusion                                    : ', e20.13) 
     563 9548    FORMAT(' pressure gradient u2 = - 1/rau0 u.dz(rhop)                : ', e20.13, '  u.dz(rhop) =', e20.13) 
     564         ! 
    631565         ! Save potential to kinetic energy conversion for next time step 
    632566         rpktrd = peke 
    633  
     567         ! 
    634568      ENDIF 
    635  
     569      ! 
    636570   END SUBROUTINE trd_dwr 
    637  
    638  
    639571 
    640572 
     
    644576      !!  
    645577      !! ** Purpose :  write active tracers trends in ocean.output  
    646       !! 
    647       !! ** Method  : 
    648       !! 
    649       !! History : 
    650       !!   9.0  !  03-09  (G. Madec)  Original code 
    651       !!        !  04-08  (C. Talandier)  New trends organization 
    652       !!---------------------------------------------------------------------- 
    653       !! * Arguments 
    654       INTEGER, INTENT( in ) ::   kt      ! ocean time-step index 
    655  
     578      !!---------------------------------------------------------------------- 
     579      INTEGER, INTENT(in) ::   kt   ! ocean time-step index 
    656580      !!---------------------------------------------------------------------- 
    657581 
     
    664588         ! ------------------------------- 
    665589         IF( lk_mpp ) THEN 
    666             CALL mpp_sum( tmo, 10 )    
    667             CALL mpp_sum( smo, 10 ) 
    668             CALL mpp_sum( t2 , 10 ) 
    669             CALL mpp_sum( s2 , 10 ) 
     590            CALL mpp_sum( tmo, jptot_tra )    
     591            CALL mpp_sum( smo, jptot_tra ) 
     592            CALL mpp_sum( t2 , jptot_tra ) 
     593            CALL mpp_sum( s2 , jptot_tra ) 
    670594         ENDIF 
    671595 
     
    677601            WRITE (numout,*) 
    678602            WRITE (numout,9400) kt 
    679             WRITE (numout,9401) tmo(1) / tvolt, smo(1) / tvolt 
    680             WRITE (numout,9402) tmo(2) / tvolt, smo(2) / tvolt 
    681             WRITE (numout,9403) tmo(3) / tvolt, smo(3) / tvolt 
    682             WRITE (numout,9404) tmo(4) / tvolt, smo(4) / tvolt 
    683             WRITE (numout,9405) tmo(5) / tvolt, smo(5) / tvolt 
    684             WRITE (numout,9406) tmo(6) / tvolt, smo(6) / tvolt 
    685             WRITE (numout,9407) tmo(7) / tvolt 
    686             WRITE (numout,9408) tmo(8) / tvolt, smo(8) / tvolt 
    687             WRITE (numout,9409) 
    688             WRITE (numout,9410) (  tmo(1) + tmo(2) + tmo(3) + tmo(4)              & 
    689             &                    + tmo(5) + tmo(6) + tmo(7) + tmo(8) ) / tvolt,   & 
    690             &                   (  smo(1) + smo(2) + smo(3) + smo(4)              & 
    691             &                    + smo(5) + smo(6)           + smo(8) ) / tvolt 
     603            WRITE (numout,9401) (tmo(jpicpt_xad)+tmo(jpicpt_yad))/ tvolt, (smo(jpicpt_xad)+smo(jpicpt_yad))/ tvolt 
     604            WRITE (numout,9402)  tmo(jpicpt_zad) / tvolt, smo(jpicpt_zad) / tvolt 
     605            WRITE (numout,9403)  tmo(jpicpt_ldf) / tvolt, smo(jpicpt_ldf) / tvolt 
     606            WRITE (numout,9404)  tmo(jpicpt_zdf) / tvolt, smo(jpicpt_zdf) / tvolt 
     607            WRITE (numout,9405)  tmo(jpicpt_npc) / tvolt, smo(jpicpt_npc) / tvolt 
     608            WRITE (numout,9406)  tmo(jpicpt_dmp) / tvolt, smo(jpicpt_dmp) / tvolt 
     609            WRITE (numout,9407)  tmo(jpicpt_qsr) / tvolt 
     610            WRITE (numout,9408)  tmo(jpicpt_nsr) / tvolt, smo(jpicpt_nsr) / tvolt 
     611            WRITE (numout,9409)  
     612            WRITE (numout,9410) (  tmo(jpicpt_xad) + tmo(jpicpt_yad) + tmo(jpicpt_zad) + tmo(jpicpt_ldf) + tmo(jpicpt_zdf)   & 
     613            &                    + tmo(jpicpt_npc) + tmo(jpicpt_dmp) + tmo(jpicpt_qsr) + tmo(jpicpt_nsr) ) / tvolt,   & 
     614            &                   (  smo(jpicpt_xad) + smo(jpicpt_yad) + smo(jpicpt_zad) + smo(jpicpt_ldf) + smo(jpicpt_zdf)   & 
     615            &                    + smo(jpicpt_npc) + smo(jpicpt_dmp)                   + smo(jpicpt_nsr) ) / tvolt 
    692616         ENDIF 
    693617 
     
    6986229403     FORMAT(' horizontal diffusion        ',e20.13,'     ',e20.13) 
    6996239404     FORMAT(' vertical diffusion          ',e20.13,'     ',e20.13) 
    700 9405     FORMAT(' STATIC instability mixing   ',e20.13,'     ',e20.13) 
     6249405     FORMAT(' static instability mixing   ',e20.13,'     ',e20.13) 
    7016259406     FORMAT(' damping term                ',e20.13,'     ',e20.13) 
    702 9407     FORMAT(' penetrative qsr             ',e20.13,'     ',e20.13) 
    703 9408     FORMAT(' forcing term                ',e20.13,'     ',e20.13) 
     6269407     FORMAT(' penetrative qsr             ',e20.13) 
     6279408     FORMAT(' non solar radiation         ',e20.13,'     ',e20.13) 
    7046289409     FORMAT(' -------------------------------------------------------------------------') 
    7056299410     FORMAT(' total trend                 ',e20.13,'     ',e20.13) 
     
    710634            WRITE (numout,*) 
    711635            WRITE (numout,9420) kt 
    712             WRITE (numout,9421) t2(1) / tvolt, s2(1) / tvolt 
    713             WRITE (numout,9422) t2(2) / tvolt, s2(2) / tvolt 
    714             WRITE (numout,9423) t2(3) / tvolt, s2(3) / tvolt 
    715             WRITE (numout,9424) t2(4) / tvolt, s2(4) / tvolt 
    716             WRITE (numout,9425) t2(5) / tvolt, s2(5) / tvolt 
    717             WRITE (numout,9426) t2(6) / tvolt, s2(6) / tvolt 
    718             WRITE (numout,9427) t2(7) / tvolt 
    719             WRITE (numout,9428) t2(8) / tvolt, s2(8) / tvolt 
     636            WRITE (numout,9421) ( t2(jpicpt_xad)+t2(jpicpt_yad) )/ tvolt, ( s2(jpicpt_xad)+s2(jpicpt_yad) )/ tvolt 
     637            WRITE (numout,9422)   t2(jpicpt_zad) / tvolt, s2(jpicpt_zad) / tvolt 
     638            WRITE (numout,9423)   t2(jpicpt_ldf) / tvolt, s2(jpicpt_ldf) / tvolt 
     639            WRITE (numout,9424)   t2(jpicpt_zdf) / tvolt, s2(jpicpt_zdf) / tvolt 
     640            WRITE (numout,9425)   t2(jpicpt_npc) / tvolt, s2(jpicpt_npc) / tvolt 
     641            WRITE (numout,9426)   t2(jpicpt_dmp) / tvolt, s2(jpicpt_dmp) / tvolt 
     642            WRITE (numout,9427)   t2(jpicpt_qsr) / tvolt 
     643            WRITE (numout,9428)   t2(jpicpt_nsr) / tvolt, s2(jpicpt_nsr) / tvolt 
    720644            WRITE (numout,9429) 
    721             WRITE (numout,9430) (  t2(1) + t2(2) + t2(3) + t2(4)              & 
    722             &                    + t2(5) + t2(6) + t2(7) + t2(8) ) / tvolt,   & 
    723             &                   (  s2(1) + s2(2) + s2(3) + s2(4)              & 
    724             &                    + s2(5) + s2(6)          + s2(8) ) / tvolt 
     645            WRITE (numout,9430) (  t2(jpicpt_xad) + t2(jpicpt_yad) + t2(jpicpt_zad) + t2(jpicpt_ldf) + t2(jpicpt_zdf)   & 
     646            &                    + t2(jpicpt_npc) + t2(jpicpt_dmp) + t2(jpicpt_qsr) + t2(jpicpt_nsr) ) / tvolt,   & 
     647            &                   (  s2(jpicpt_xad) + s2(jpicpt_yad) + s2(jpicpt_zad) + s2(jpicpt_ldf) + s2(jpicpt_zdf)   & 
     648            &                    + s2(jpicpt_npc) + s2(jpicpt_dmp)                  + s2(jpicpt_nsr) ) / tvolt 
    725649         ENDIF 
    726650 
     
    7316559423     FORMAT(' horizontal diffusion      * t   ', e20.13, '     ', e20.13) 
    7326569424     FORMAT(' vertical diffusion        * t   ', e20.13, '     ', e20.13) 
    733 9425     FORMAT(' STATIC instability mixing * t   ', e20.13, '     ', e20.13) 
     6579425     FORMAT(' static instability mixing * t   ', e20.13, '     ', e20.13) 
    7346589426     FORMAT(' damping term              * t   ', e20.13, '     ', e20.13) 
    735 9427     FORMAT(' penetrative qsr           * t   ', e20.13, '     ', e20.13) 
    736 9428     FORMAT(' forcing term              * t   ', e20.13, '     ', e20.13) 
     6599427     FORMAT(' penetrative qsr           * t   ', e20.13) 
     6609428     FORMAT(' non solar radiation       * t   ', e20.13, '     ', e20.13) 
    7376619429     FORMAT(' -----------------------------------------------------------------------------') 
    7386629430     FORMAT(' total trend                *t = ', e20.13, '  *s = ', e20.13) 
     
    743667            WRITE (numout,*) 
    744668            WRITE (numout,9440) kt 
    745             WRITE (numout,9441) ( tmo(1)+tmo(2) )/tvolt, ( smo(1)+smo(2) )/tvolt 
    746             WRITE (numout,9442)   tmo(3)/tvolt,  smo(3)/tvolt 
    747             WRITE (numout,9443)   tmo(4)/tvolt,  smo(4)/tvolt 
    748             WRITE (numout,9444)   tmo(5)/tvolt,  smo(5)/tvolt 
    749             WRITE (numout,9445) ( t2(1)+t2(2) )/tvolt, ( s2(1)+s2(2) )/tvolt 
    750             WRITE (numout,9446)   t2(3)/tvolt,   s2(3)/tvolt 
    751             WRITE (numout,9447)   t2(4)/tvolt,   s2(4)/tvolt 
    752             WRITE (numout,9448)   t2(5)/tvolt,   s2(5)/tvolt 
     669            WRITE (numout,9441) ( tmo(jpicpt_xad)+tmo(jpicpt_yad)+tmo(jpicpt_zad) )/tvolt,   & 
     670            &                   ( smo(jpicpt_xad)+smo(jpicpt_yad)+smo(jpicpt_zad) )/tvolt 
     671            WRITE (numout,9442)   tmo(jpicpt_zl1)/tvolt,  smo(jpicpt_zl1)/tvolt 
     672            WRITE (numout,9443)   tmo(jpicpt_ldf)/tvolt,  smo(jpicpt_ldf)/tvolt 
     673            WRITE (numout,9444)   tmo(jpicpt_zdf)/tvolt,  smo(jpicpt_zdf)/tvolt 
     674            WRITE (numout,9445)   tmo(jpicpt_npc)/tvolt,  smo(jpicpt_npc)/tvolt 
     675            WRITE (numout,9446) ( t2(jpicpt_xad)+t2(jpicpt_yad)+t2(jpicpt_zad) )/tvolt,    & 
     676            &                   ( s2(jpicpt_xad)+s2(jpicpt_yad)+s2(jpicpt_zad) )/tvolt 
     677            WRITE (numout,9447)   t2(jpicpt_ldf)/tvolt,   s2(jpicpt_ldf)/tvolt 
     678            WRITE (numout,9448)   t2(jpicpt_zdf)/tvolt,   s2(jpicpt_zdf)/tvolt 
     679            WRITE (numout,9449)   t2(jpicpt_npc)/tvolt,   s2(jpicpt_npc)/tvolt 
    753680         ENDIF 
    754681 
     
    756683            ' :         temperature','                salinity',/,   & 
    757684            ' ==================================') 
    758 9441     FORMAT(' 0 = horizontal+vertical advection      ',e20.13,'       ',e20.13) 
    759 9442     FORMAT(' 0 = horizontal diffusion               ',e20.13,'       ',e20.13) 
    760 9443     FORMAT(' 0 = vertical diffusion                 ',e20.13,'       ',e20.13) 
    761 9444     FORMAT(' 0 = static instability mixing          ',e20.13,'       ',e20.13) 
    762 9445     FORMAT(' 0 = horizontal+vertical advection * t  ',e20.13,'       ',e20.13) 
    763 9446     FORMAT(' 0 > horizontal diffusion          * t  ',e20.13,'       ',e20.13) 
    764 9447     FORMAT(' 0 > vertical diffusion            * t  ',e20.13,'       ',e20.13) 
    765 9448     FORMAT(' 0 > static instability mixing     * t  ',e20.13,'       ',e20.13) 
    766  
     6859441     FORMAT(' 0 = horizontal+vertical advection +    ',e20.13,'       ',e20.13) 
     6869442     FORMAT('     1st lev vertical advection         ',e20.13,'       ',e20.13) 
     6879443     FORMAT(' 0 = horizontal diffusion               ',e20.13,'       ',e20.13) 
     6889444     FORMAT(' 0 = vertical diffusion                 ',e20.13,'       ',e20.13) 
     6899445     FORMAT(' 0 = static instability mixing          ',e20.13,'       ',e20.13) 
     6909446     FORMAT(' 0 = horizontal+vertical advection * t  ',e20.13,'       ',e20.13) 
     6919447     FORMAT(' 0 > horizontal diffusion          * t  ',e20.13,'       ',e20.13) 
     6929448     FORMAT(' 0 > vertical diffusion            * t  ',e20.13,'       ',e20.13) 
     6939449     FORMAT(' 0 > static instability mixing     * t  ',e20.13,'       ',e20.13) 
     694         ! 
    767695      ENDIF 
    768  
     696      ! 
    769697   END SUBROUTINE trd_twr 
    770698 
     
    773701   !!   Default case :                                         Empty module 
    774702   !!---------------------------------------------------------------------- 
    775    LOGICAL, PUBLIC, PARAMETER ::   lk_trdtra = .FALSE.   !: tracers  trend flag 
    776    LOGICAL, PUBLIC, PARAMETER ::   lk_trddyn = .FALSE.   !: momentum trend flag 
    777703CONTAINS 
    778    SUBROUTINE trd_2d(ptrd2dx, ptrd2dy, ktrd , ctype)       ! Empty routine 
    779       REAL, DIMENSION(:,:,:), INTENT( inout ) ::   & 
    780           ptrd2dx,                     &   ! Temperature or U trend  
    781           ptrd2dy                          ! Salinity    or V trend 
    782       INTEGER, INTENT( in ) ::   ktrd      ! momentum or tracer trend index 
    783       CHARACTER(len=3), INTENT( in ) ::   & 
    784          ctype                             ! momentum or tracers trends type 
    785       WRITE(*,*) 'trd_2d: You should not have seen this print! error ?', ptrd2dx(1,1,1) 
    786       WRITE(*,*) ' "   ": You should not have seen this print! error ?', ptrd2dy(1,1,1) 
    787       WRITE(*,*) ' "   ": You should not have seen this print! error ?', ktrd 
    788       WRITE(*,*) ' "   ": You should not have seen this print! error ?', ctype 
     704   SUBROUTINE trd_2d( ptrd2dx, ptrd2dy, ktrd , ctype )       ! Empty routine 
     705      REAL, DIMENSION(:,:) ::   ptrd2dx, ptrd2dy 
     706      WRITE(*,*) 'trd_2d: You should not have seen this print! error ?', ptrd2dx(1,1), ptrd2dy(1,1), ktrd, ctype 
    789707   END SUBROUTINE trd_2d 
    790    SUBROUTINE trd_3d(ptrd3dx, ptrd3dy, ktrd , ctype)       ! Empty routine 
    791       REAL, DIMENSION(:,:,:), INTENT( inout ) ::   & 
    792           ptrd3dx,                     &   ! Temperature or U trend  
    793           ptrd3dy                          ! Salinity    or V trend 
    794       INTEGER, INTENT( in ) ::   ktrd      ! momentum or tracer trend index 
    795       CHARACTER(len=3), INTENT( in ) ::   & 
    796          ctype                             ! momentum or tracers trends type 
    797       WRITE(*,*) 'trd_3d: You should not have seen this print! error ?', ptrd3dx(1,1,1) 
    798       WRITE(*,*) ' "   ": You should not have seen this print! error ?', ptrd3dy(1,1,1) 
    799       WRITE(*,*) ' "   ": You should not have seen this print! error ?', ktrd 
    800       WRITE(*,*) ' "   ": You should not have seen this print! error ?', ctype 
     708   SUBROUTINE trd_3d( ptrd3dx, ptrd3dy, ktrd , ctype )       ! Empty routine 
     709      REAL, DIMENSION(:,:,:) ::   ptrd3dx, ptrd3dy 
     710      WRITE(*,*) 'trd_3d: You should not have seen this print! error ?', ptrd3dx(1,1,1), ptrd3dy(1,1,1), ktrd, ctype 
    801711   END SUBROUTINE trd_3d 
    802712   SUBROUTINE trd_icp_init               ! Empty routine 
    803713   END SUBROUTINE trd_icp_init 
    804714   SUBROUTINE trd_dwr( kt )          ! Empty routine 
    805       INTEGER, INTENT(in) :: kt 
    806715      WRITE(*,*) 'trd_dwr: You should not have seen this print! error ?', kt 
    807716   END SUBROUTINE trd_dwr 
    808717   SUBROUTINE trd_twr( kt )          ! Empty routine 
    809       INTEGER, INTENT(in) :: kt 
    810718      WRITE(*,*) 'trd_twr: You should not have seen this print! error ?', kt 
    811719   END SUBROUTINE trd_twr 
  • trunk/NEMO/OPA_SRC/TRD/trdicp_oce.F90

    r247 r503  
    66 
    77   !!---------------------------------------------------------------------- 
    8    !!  OPA 9.0 , LOCEAN-IPSL (2005)  
    9    !! $Header$  
    10    !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt  
    11    !!---------------------------------------------------------------------- 
    12    !!---------------------------------------------------------------------- 
    138   !!   'key_trdtra'   or                         tracer trends diagnostics 
    149   !!   'key_trddyn'                            momentum trends diagnostics 
    1510   !!---------------------------------------------------------------------- 
    16    !! * Modules used 
    1711   USE par_oce                 ! ocean parameters 
    1812 
     
    2014   PUBLIC 
    2115 
    22    !! Namelist parameters 
    23    !!---------------------------------------------------------------------- 
    24    INTEGER  ::      & !!: namdia :  diagnostics on dynamics and/or tracer trends 
    25       ntrd  = 10 ,  &  !: time step frequency dynamics and tracers trends 
    26       nctls =  0       !: control surface type for trends vertical integration 
     16   !! * Shared module variables 
     17#if  defined key_trdtra   &&   defined key_trddyn    ||   defined key_esopa 
     18   LOGICAL, PARAMETER ::   lk_trdtra = .TRUE.    !: tracers  trend flag 
     19   LOGICAL, PARAMETER ::   lk_trddyn = .TRUE.    !: momentum trend flag 
     20#elif  defined key_trdtra 
     21   LOGICAL, PARAMETER ::   lk_trdtra = .TRUE.    !: tracers  trend flag 
     22   LOGICAL, PARAMETER ::   lk_trddyn = .FALSE.   !: momentum trend flag 
     23#elif  defined key_trddyn 
     24   LOGICAL, PARAMETER ::   lk_trdtra = .FALSE.   !: tracers  trend flag 
     25   LOGICAL, PARAMETER ::   lk_trddyn = .TRUE.    !: momentum trend flag 
     26#else 
     27   LOGICAL, PARAMETER ::   lk_trdtra = .FALSE.   !: tracers  trend flag 
     28   LOGICAL, PARAMETER ::   lk_trddyn = .FALSE.   !: momentum trend flag 
     29#endif 
    2730 
    2831   !! Tracers trends diagnostics parameters 
    2932   !!--------------------------------------------------------------------- 
    30    INTEGER, PARAMETER ::            &  !: trends index 
    31       jpttdlad = 1,   &  !: tracer horizontal advection 
    32       jpttdzad = 2,   &  !: tracer vertical advection 
    33       jpttdldf = 3,   &  !: tracer horizontal diffusion 
    34       jpttdzdf = 4,   &  !: tracer vertical diffusion 
    35       jpttdnpc = 5,   &  !: tracer non penetrative convection 
    36       jpttddoe = 6,   &  !: tracer D.amping O.r vertical E.iv 
    37       jpttdqsr = 7,   &  !: tracer penetrative solar radiation 
    38       jpttdnsr = 8       !: tracer non solar radiation 
     33   INTEGER, PARAMETER ::   &  !: => tracer trends indexes <= 
     34        jpicpt_xad =  1,   &  !: x- horizontal advection 
     35        jpicpt_yad =  2,   &  !: y- horizontal advection 
     36        jpicpt_zad =  3,   &  !: z- vertical   advection 
     37        jpicpt_ldf =  4,   &  !: lateral       diffusion 
     38        jpicpt_zdf =  5,   &  !: vertical diffusion (Kz) 
     39        jpicpt_bbc =  6,   &  !: Bottom Boundary Condition (geoth. flux)  
     40        jpicpt_bbl =  7,   &  !: Bottom Boundary Layer (diffusive/convective) 
     41        jpicpt_npc =  8,   &  !: static instability mixing 
     42        jpicpt_dmp =  9,   &  !: damping 
     43        jpicpt_qsr = 10,   &  !: penetrative solar radiation 
     44        jpicpt_nsr = 11,   &  !: non solar radiation 
     45        jpicpt_zl1 = 12       !: first level vertical flux 
    3946 
     47   INTEGER, PARAMETER ::   &  !: => Total tracer trends indexes <= 
     48        jptot_tra = 12        !: change it when adding/removing one indice above 
     49    
    4050   !! Momentum trends diagnostics parameters 
    4151   !!--------------------------------------------------------------------- 
    42    INTEGER, PARAMETER ::            &  !: trends index 
    43       jpdtdhpg =  1,   &  !: dynamic hydrostatic pressure gradient  
    44       jpdtdkeg =  2,   &  !: dynamic kinetic energy gradient 
    45       jpdtdrvo =  3,   &  !: dynamic relative vorticity 
    46       jpdtdpvo =  4,   &  !: dynamic planetary vorticity 
    47       jpdtdldf =  5,   &  !: dynamic lateral diffusion 
    48       jpdtdzad =  6,   &  !: dynamic vertical advection 
    49       jpdtdzdf =  7,   &  !: dynamic vertical diffusion 
    50       jpdtdspg =  8,   &  !: dynamic surface pressure gradient 
    51       jpdtddat =  9,   &  !: dynamic damping term 
    52       jpdtdswf = 10,   &  !: dynamic surface wind forcing 
    53       jpdtdbfr = 11       !: dynamic bottom friction  
     52   INTEGER, PARAMETER ::   &  !: => dynamic trends indexes <= 
     53        jpicpd_hpg =  1,   &  !: hydrostatic pressure gradient  
     54        jpicpd_keg =  2,   &  !: kinetic energy gradient 
     55        jpicpd_rvo =  3,   &  !: relative vorticity 
     56        jpicpd_pvo =  4,   &  !: planetary vorticity 
     57        jpicpd_ldf =  5,   &  !: lateral diffusion 
     58        jpicpd_zad =  6,   &  !: vertical advection 
     59        jpicpd_zdf =  7,   &  !: vertical diffusion 
     60        jpicpd_spg =  8,   &  !: surface pressure gradient 
     61        jpicpd_dat =  9,   &  !: damping term 
     62        jpicpd_swf = 10,   &  !: surface wind forcing 
     63        jpicpd_bfr = 11       !: bottom friction  
    5464 
    55    REAL, DIMENSION(jpi,jpj) ::   &  !: 
    56       tldfbbl, sldfbbl,          &  ! Temperature/salinity lateral diffusion trends 
    57       !                             ! in the BBL   
    58       tladbbl, sladbbl              ! Temperature/salinity lateral advection trends  
    59       !                             ! in the BBL 
    60  
    61    REAL, DIMENSION(jpi,jpj,jpk) ::   &  !: 
    62       tladi, sladi,                  &  ! Temp./sal. MUSCL OR TVD advection fluxes  
    63       !                                 ! terms along i-  
    64       tladj, sladj                      ! Temp./sal. MUSCL OR TVD advection fluxes  
    65       !                                 ! terms along j-  
    66 #if defined key_ldfslp 
    67    REAL(wp), DIMENSION(jpi,jpj,jpk) ::   &  !: 
    68       uldftrd, vldftrd     !: lateral diffusion trend in isopycnal case 
    69 #endif 
     65   INTEGER, PARAMETER ::   &  !: => Total dynamic trends indexes <= 
     66        jptot_dyn = 11        !: change it when adding/removing one indice above 
     67    
    7068#if   defined key_trdtra   ||   defined key_trddyn   ||   defined key_esopa 
    7169 
    7270   !! Variables used for diagnostics 
    7371   !!--------------------------------------------------------------------- 
    74    REAL(wp) ::   &  !: 
    75       tvolt,     &  !: volume of the whole ocean computed at t-points 
    76       tvolu,     &  !: volume of the whole ocean computed at u-points 
    77       tvolv         !: volume of the whole ocean computed at v-points 
     72   REAL(wp) ::   tvolt        !: volume of the whole ocean computed at t-points 
     73   REAL(wp) ::   tvolu        !: volume of the whole ocean computed at u-points 
     74   REAL(wp) ::   tvolv        !: volume of the whole ocean computed at v-points 
    7875 
    7976   !! Tracers trends diagnostics variables 
    8077   !!--------------------------------------------------------------------- 
    81    REAL(wp), DIMENSION(10) ::   &  !: 
    82       tmo, smo         !: tracers trends average  
    83       !                !  tmo(1) : horizontal advection 
    84       !                !  tmo(2) : vertical advection 
    85       !                !  tmo(3) : horizontal diffusion 
    86       !                !  tmo(4) : vertical diffusion 
    87       !                !  tmo(5) : static instability 
    88       !                !  tmo(6) : damping OR vertical EIV 
    89       !                !  tmo(7) : penetrative solar radiation (T only) 
    90    REAL(wp), DIMENSION(10) ::   &  !: 
    91       t2, s2           !: tracers square trends average  
    92       !                !  t2(1) : horizontal advection 
    93       !                !  t2(2) : vertical advection 
    94       !                !  t2(3) : horizontal diffusion 
    95       !                !  t2(4) : vertical diffusion 
    96       !                !  t2(5) : static instability 
    97       !                !  t2(6) : damping OR vertical EIV 
    98       !                !  t2(7) : penetrative solar radiation (T only) 
     78   REAL(wp), DIMENSION(jptot_tra) ::   tmo, smo         !: tracers trends average  
     79   REAL(wp), DIMENSION(jptot_tra) ::   t2, s2           !: tracers square trends average  
    9980    
    10081   !! Momentum trends diagnostics variables 
    10182   !!--------------------------------------------------------------------- 
    102    REAL(wp), DIMENSION(11) ::   &  !: 
    103       umo, vmo         !: momentum trends average  
    104       !                !  umo(1) : hydrostatic pressure gradient 
    105       !                !  umo(2) : kinetic energy 
    106       !                !  umo(3) : lateral diffusion geo-pot 
    107       !                !  umo(4) :  
    108       !                !  umo(5) : lateral diffusion 
    109       !                !  umo(6) : vertical advection 
    110       !                !  umo(7) : vertical diffusion 
    111       !                !  umo(8) : surface pressure gradient 
    112       !                !  umo(9) :  
    113  
    114    REAL(wp), DIMENSION(10) ::   &  !: 
    115       hke              !: momentum square trends average  
    116       !                !  hke(1) : horizontal advection 
    117       !                !  hke(2) : vertical advection 
    118  
    119    REAL(wp) ::   &  !: 
    120       rpktrd,    &  !: potential to kinetic energy conversion 
    121       peke          !: conversion potential energy - kinetic energy trend 
     83   REAL(wp), DIMENSION(jptot_dyn) ::   umo, vmo         !: momentum trends average  
     84   REAL(wp), DIMENSION(jptot_dyn) ::   hke              !: momentum square trends average  
     85   REAL(wp) ::   rpktrd   !: potential to kinetic energy conversion 
     86   REAL(wp) ::   peke     !: conversion potential energy - kinetic energy trend 
    12287 
    12388#endif 
    124  
    125   !!====================================================================== 
     89   !!---------------------------------------------------------------------- 
     90   !!  OPA 9.0 , LOCEAN-IPSL (2005)  
     91   !! $Header$  
     92   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
     93   !!====================================================================== 
    12694END MODULE trdicp_oce 
  • trunk/NEMO/OPA_SRC/TRD/trdmld.F90

    r352 r503  
    44   !! Ocean diagnostics:  mixed layer T-S trends  
    55   !!===================================================================== 
     6   !! History :       !  95-04  (J. Vialard)    Original code 
     7   !!                 !  97-02  (E. Guilyardi)  Adaptation global + base cmo 
     8   !!                 !  99-09  (E. Guilyardi)  Re-writing + netCDF output 
     9   !!            8.5  !  02-06  (G. Madec)      F90: Free form and module 
     10   !!            9.0  !  04-08  (C. Talandier)  New trends organization 
     11   !!                 !  05-05  (C. Deltel)     Diagnose trends of time averaged ML T & S 
     12   !!---------------------------------------------------------------------- 
    613#if   defined key_trdmld   ||   defined key_esopa 
    714   !!---------------------------------------------------------------------- 
    815   !!   'key_trdmld'                          mixed layer trend diagnostics 
     16   !!---------------------------------------------------------------------- 
    917   !!---------------------------------------------------------------------- 
    1018   !!   trd_mld          : T and S cumulated trends averaged over the mixed layer 
     
    1220   !!   trd_mld_init     : initialization step 
    1321   !!---------------------------------------------------------------------- 
    14    !! * Modules used 
    1522   USE oce             ! ocean dynamics and tracers variables 
    1623   USE dom_oce         ! ocean space and time domain variables 
     
    2835   USE lbclnk          ! ocean lateral boundary conditions (or mpp link) 
    2936   USE diadimg         ! dimg direct access file format output 
     37   USE trdmld_rst , ONLY : trd_mld_rst_read  ! restart for diagnosing the ML trends 
     38   USE prtctl          ! Print control 
    3039 
    3140   IMPLICIT NONE 
    3241   PRIVATE 
    3342 
    34    !! * Accessibility 
    35    PUBLIC trd_mld        ! routine called by step.F90 
    36    PUBLIC trd_mld_init   ! routine called by opa.F90 
    37    PUBLIC trd_mld_zint   ! routine called by tracers routines 
    38  
    39    !! * Shared module variables 
    40    LOGICAL, PUBLIC, PARAMETER ::   lk_trdmld = .TRUE.    !: momentum trend flag 
    41  
    42    !! * Module variables 
    43    INTEGER ::   & 
    44       nh_t, nmoymltrd,             &  ! ??? 
    45       nidtrd,                      & 
    46       ndextrd1(jpi*jpj),           & 
    47       ndimtrd1 
    48    INTEGER, SAVE ::   & 
    49       ionce, icount,               & 
    50       idebug                          ! (0/1) set it to 1 in case of problem to have more print 
    51  
    52    INTEGER, DIMENSION(jpi,jpj) ::   & 
    53       nmld,                         & ! mixed layer depth 
    54       nbol                 
    55  
    56    REAL(wp), DIMENSION(jpi,jpj) ::   & 
    57       rmld   ,          &  ! mld depth (m) corresponding to nmld 
    58       tml    , sml  ,   &  ! average T and S over mixed layer 
    59       tmlb   , smlb ,   &  ! before tml and sml (kt-1) 
    60       tmlbb  , smlbb,   &  ! tml and sml at begining of the nwrite-1  
    61       !                    ! timestep averaging period 
    62       tmlbn  , smlbn,   &  ! after tml and sml at time step after the 
    63       !                    ! begining of the NWRITE-1 timesteps 
    64       tmltrdm, smltrdm     ! 
    65  
    66    REAL(wp), DIMENSION(jpi,jpj,jpk) ::   & 
    67       tmltrd ,          &  ! total cumulative trends of temperature and  
    68       smltrd ,          &  ! salinity over nwrite-1 time steps 
    69       wkx 
    70  
    71    CHARACTER(LEN=80) :: clname 
     43   PUBLIC   trd_mld        ! routine called by step.F90 
     44   PUBLIC   trd_mld_init   ! routine called by opa.F90 
     45   PUBLIC   trd_mld_zint   ! routine called by tracers routines 
     46 
     47   CHARACTER (LEN=40) ::  clhstnam         ! name of the trends NetCDF file 
     48   INTEGER ::   nh_t, nmoymltrd 
     49   INTEGER ::   nidtrd, ndextrd1(jpi*jpj) 
     50   INTEGER ::   ndimtrd1                         
     51   INTEGER, SAVE ::  ionce, icount                    
    7252 
    7353   !! * Substitutions 
     
    8363CONTAINS 
    8464 
    85 SUBROUTINE trd_mld_zint( pttrdmld, pstrdmld, ktrd, ctype ) 
     65   SUBROUTINE trd_mld_zint( pttrdmld, pstrdmld, ktrd, ctype ) 
    8666      !!---------------------------------------------------------------------- 
    8767      !!                  ***  ROUTINE trd_mld_zint  *** 
    8868      !!  
    89       !! ** Purpose :   computation of vertically integrated T and S budgets 
    90       !!                from ocean surface down to control surface  
     69      !! ** Purpose :   Compute the vertical average of the 3D fields given as arguments  
     70      !!                to the subroutine. This vertical average is performed from ocean 
     71      !!                surface down to a chosen control surface. 
    9172      !! 
    9273      !! ** Method/usage : 
    93       !!      integration done over nwrite-1 time steps  
    94       !!      Control surface can be either a mixed layer depth (time varying) 
     74      !!      The control surface can be either a mixed layer depth (time varying) 
    9575      !!      or a fixed surface (jk level or bowl).  
    96       !!      Choose control surface with nctls in namelist NAMDIA. 
    97       !!      nctls = 0  : use mixed layer with density criterion  
    98       !!      nctls = 1  : read index from file 'ctlsurf_idx' 
    99       !!      nctls > 1  : use fixed level surface jk = nctls 
     76      !!      Choose control surface with nctls in namelist NAMTRD : 
     77      !!        nctls = 0  : use mixed layer with density criterion  
     78      !!        nctls = 1  : read index from file 'ctlsurf_idx' 
     79      !!        nctls > 1  : use fixed level surface jk = nctls 
    10080      !!      Note: in the remainder of the routine, the volume between the  
    10181      !!            surface and the control surface is called "mixed-layer" 
    102       !!      Method check : if the control surface is fixed, the residual dh/dt 
    103       !!                     entrainment should be zero 
    104       !! 
    105       !! ** Action : 
    106       !!            /commld/   : rmld         mld depth corresponding to nmld 
    107       !!                         tml          average T over mixed layer 
    108       !!                         tmlb         tml at kt-1 
    109       !!                         tmlbb        tml at begining of the NWRITE-1  
    110       !!                                      time steps averaging period 
    111       !!                         tmlbn        tml at time step after the  
    112       !!                                      begining of the NWRITE-1 time 
    113       !!                                      steps averaging period 
    114       !! 
    115       !!                  mixed layer trends : 
    116       !! 
    117       !!                  tmltrd (,,1) = zonal advection 
    118       !!                  tmltrd (,,2) = meridional advection 
    119       !!                  tmltrd (,,3) = vertical advection 
    120       !!                  tmltrd (,,4) = lateral diffusion (horiz. component+Beckman) 
    121       !!                  tmltrd (,,5) = forcing 
    122       !!                  tmltrd (,,6) = entrainment due to vertical diffusion (TKE) 
    123       !!          if iso  tmltrd (,,7) = lateral diffusion (vertical component) 
    124       !!                  tmltrd (,,8) = eddy induced zonal advection 
    125       !!                  tmltrd (,,9) = eddy induced meridional advection 
    126       !!                  tmltrd (,,10) = eddy induced vertical advection 
    127       !! 
    128       !!                  tmltrdm(,) : total cumulative trends over nwrite-1 time steps 
    129       !!                  ztmltot(,) : dT/dt over the NWRITE-1 time steps  
    130       !!                               averaging period (including Asselin  
    131       !!                               terms) 
    132       !!                  ztmlres(,) : residual = dh/dt entrainment 
    133       !! 
    134       !!      trends output in netCDF format using ioipsl 
    135       !! 
    136       !! History : 
    137       !!        !  95-04  (J. Vialard)  Original code 
    138       !!        !  97-02  (E. Guilyardi)  Adaptation global + base cmo 
    139       !!        !  99-09  (E. Guilyardi)  Re-writing + netCDF output 
    140       !!   8.5  !  02-06  (G. Madec)  F90: Free form and module 
    141       !!   9.0  !  04-08  (C. Talandier) New trends organization 
    14282      !!---------------------------------------------------------------------- 
    143       !! * Arguments 
    144       INTEGER, INTENT( in ) ::   ktrd         ! ocean trend index 
    145  
    146       CHARACTER(len=2), INTENT( in ) ::   & 
    147          ctype                                ! surface/bottom (2D arrays) or 
    148                                               ! interior (3D arrays) physics 
    149  
    150       REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT( in ) ::   & 
    151          pttrdmld,                         &  ! Temperature trend  
    152          pstrdmld                             ! Salinity    trend 
    153  
    154       !! * Local declarations 
     83      INTEGER, INTENT( in ) ::   ktrd                             ! ocean trend index 
     84      CHARACTER(len=2), INTENT( in ) :: ctype                     ! surface/bottom (2D arrays) or 
     85      !                                                           ! interior (3D arrays) physics 
     86      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT( in ) ::  pttrdmld ! temperature trend  
     87      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT( in ) ::  pstrdmld ! salinity trend  
    15588      INTEGER ::   ji, jj, jk, isum 
    156 # if defined key_trabbl_dif 
    157       INTEGER ::   ikb 
    158 # endif 
    159  
    160       REAL(wp), DIMENSION(jpi,jpj) ::   & 
    161          zvlmsk 
     89      REAL(wp), DIMENSION(jpi,jpj) ::  zvlmsk 
    16290      !!---------------------------------------------------------------------- 
    16391 
     92      ! I. Definition of control surface and associated fields 
     93      ! ------------------------------------------------------ 
     94      !            ==> only once per time step <==  
     95 
    16496      IF( icount == 1 ) THEN         
    165  
    166          zvlmsk(:,:)   = 0.e0 
    167          tmltrd(:,:,:) = 0.e0 
    168          smltrd(:,:,:) = 0.e0 
    169           
    170          ! This computation should be done only once per time step 
    171  
    172          !  ======================================================== 
    173          !   I. definition of control surface and associated fields 
    174          !  ======================================================== 
    175  
    176          !    I.1 set nmld(ji,jj) = index of first T point below control surface 
    177          !    -------------------                       or outside mixed-layer 
    178  
    179          IF( nctls == 0 ) THEN 
    180             ! control surface = mixed-layer with density criterion  
    181             ! (array nmln computed in zdfmxl.F90) 
    182             nmld(:,:) = nmln(:,:) 
    183          ELSE IF( nctls == 1 ) THEN 
    184             ! control surface = read index from file  
     97         ! 
     98         tmltrd(:,:,:) = 0.e0    ;    smltrd(:,:,:) = 0.e0    ! <<< reset trend arrays to zero 
     99          
     100         ! ... Set nmld(ji,jj) = index of first T point below control surf. or outside mixed-layer 
     101         IF( nctls == 0 ) THEN       ! * control surface = mixed-layer with density criterion  
     102            nmld(:,:) = nmln(:,:)    ! array nmln computed in zdfmxl.F90 
     103         ELSE IF( nctls == 1 ) THEN  ! * control surface = read index from file  
    185104            nmld(:,:) = nbol(:,:) 
    186          ELSE IF( nctls >= 2 ) THEN 
    187             ! control surface = model level 
     105         ELSE IF( nctls >= 2 ) THEN  ! * control surface = model level 
    188106            nctls = MIN( nctls, jpktrd - 1 ) 
    189107            nmld(:,:) = nctls + 1 
    190108         ENDIF 
    191109 
    192          IF( ionce == 1 ) THEN  ! compute ndextrd1 and ndimtrd1 only once 
    193             ! Check of validity : nmld(ji,jj) =< jpktrd 
    194             isum = 0 
     110         ! ... Compute ndextrd1 and ndimtrd1 only once 
     111         IF( ionce == 1 ) THEN 
     112            ! 
     113            ! Check of validity : nmld(ji,jj) <= jpktrd 
     114            isum        = 0 
     115            zvlmsk(:,:) = 0.e0 
    195116 
    196117            IF( jpktrd < jpk ) THEN  
     
    215136            ENDIF                                 
    216137 
    217             ! no more pass here 
    218             ionce = 0 
    219  
    220          ENDIF 
    221           
    222          IF( idebug /= 0 ) THEN 
    223             ! CALL prihre (zvlmsk,jpi,jpj,1,jpi,2,1,jpj,2,3,numout) 
    224             WRITE(numout,*) ' debuging trd_mld_zint: I.1 done '   
    225             CALL FLUSH(numout) 
    226          ENDIF 
    227  
    228  
    229          ! I.2 probability density function of presence in mixed-layer 
    230          ! -------------------------------- 
    231          ! (i.e. weight of each grid point in vertical integration : wkx(ji,jj,jk) 
    232  
    233  
    234          ! initialize wkx with vertical scale factor in mixed-layer 
    235  
     138            ionce = 0                ! no more pass here 
     139            ! 
     140         END IF 
     141          
     142         ! ... Weights for vertical averaging 
    236143         wkx(:,:,:) = 0.e0 
    237          DO jk = 1, jpktrd 
     144         DO jk = 1, jpktrd             ! initialize wkx with vertical scale factor in mixed-layer 
    238145            DO jj = 1,jpj 
    239146               DO ji = 1,jpi 
    240                   IF( jk - nmld(ji,jj) < 0. )   wkx(ji,jj,jk) = fse3t(ji,jj,jk) * tmask(ji,jj,jk) 
     147                  IF( jk - nmld(ji,jj) < 0.e0 )   wkx(ji,jj,jk) = fse3t(ji,jj,jk) * tmask(ji,jj,jk) 
    241148               END DO 
    242149            END DO 
    243150         END DO 
    244151          
    245          ! compute mixed-layer depth : rmld 
    246           
    247          rmld(:,:) = 0. 
     152         rmld(:,:) = 0.e0                ! compute mixed-layer depth : rmld 
    248153         DO jk = 1, jpktrd 
    249154            rmld(:,:) = rmld(:,:) + wkx(:,:,jk) 
    250155         END DO 
    251156          
    252          ! compute PDF 
    253  
     157         DO jk = 1, jpktrd             ! compute integration weights 
     158            wkx(:,:,jk) = wkx(:,:,jk) / MAX( 1., rmld(:,:) ) 
     159         END DO 
     160 
     161         icount = 0                    ! <<< flag = off : control surface & integr. weights 
     162         !                             !     computed only once per time step 
     163      END IF 
     164 
     165      ! II. Vertical integration of trends in the mixed-layer 
     166      ! ----------------------------------------------------- 
     167 
     168      SELECT CASE (ctype) 
     169      CASE ( '3D' )   ! mean T/S trends in the mixed-layer 
    254170         DO jk = 1, jpktrd 
    255             wkx(:,:,jk) = wkx(:,:,jk) / MAX( 1., rmld(:,:) ) 
    256          END DO 
    257  
    258          IF( idebug /= 0 ) THEN 
    259             WRITE(numout,*) ' debuging trd_mld_zint: I.2 done '   
    260             CALL FLUSH(numout) 
    261          ENDIF 
    262  
    263          ! Set counter icount to 0 to avoid this part at each time step 
    264          icount = 0 
    265  
    266       ENDIF 
    267  
    268  
    269       !  ==================================================== 
    270       !   II. vertical integration of trends in mixed-layer 
    271       !  ==================================================== 
    272  
    273       ! II.1 vertical integration of 3D and 2D trends 
    274       ! --------------------------------------------- 
    275  
    276       SELECT CASE (ctype) 
    277  
    278       CASE ('3D')       ! 3D treatment 
    279  
    280          ! trends terms in the mixed-layer 
    281          DO jk = 1, jpktrd 
    282             ! Temperature 
    283             tmltrd(:,:,ktrd) = tmltrd(:,:,ktrd) + pttrdmld(:,:,jk) * wkx(:,:,jk)    
    284  
    285             ! Salinity 
    286             smltrd(:,:,ktrd) = smltrd(:,:,ktrd) + pstrdmld(:,:,jk) * wkx(:,:,jk)    
    287          ENDDO 
    288  
    289       CASE ('2D')       ! 2D treatment 
    290  
    291          SELECT CASE (ktrd)  
    292  
    293          CASE (jpmldldf) 
    294  
    295 # if defined key_trabbl_dif 
    296                ! trends terms from Beckman over-flow parameterization 
    297                DO jj = 1,jpj 
    298                   DO ji = 1,jpi 
    299                      ikb = MAX( mbathy(ji,jj)-1, 1 ) 
    300                      ! beckmann component -> horiz. part of lateral diffusion 
    301                      tmltrd(ji,jj,ktrd) = tmltrd(ji,jj,ktrd) + pttrdmld(ji,jj,1) * wkx(ji,jj,ikb) 
    302                      smltrd(ji,jj,ktrd) = smltrd(ji,jj,ktrd) + pstrdmld(ji,jj,1) * wkx(ji,jj,ikb) 
    303                   END DO 
    304                END DO 
    305 # endif 
    306  
    307          CASE DEFAULT 
    308  
    309             ! trends terms at upper boundary of mixed-layer 
    310  
    311             ! forcing term (non penetrative) 
    312             ! Temperature 
    313             tmltrd(:,:,ktrd) = tmltrd(:,:,ktrd) + pttrdmld(:,:,1) * wkx(:,:,1)    
    314  
    315             ! forcing term 
    316             ! Salinity 
    317             smltrd(:,:,ktrd) = smltrd(:,:,ktrd) + pstrdmld(:,:,1) * wkx(:,:,1)    
    318  
    319          END SELECT 
    320  
     171            tmltrd(:,:,ktrd) = tmltrd(:,:,ktrd) + pttrdmld(:,:,jk) * wkx(:,:,jk)   ! temperature 
     172            smltrd(:,:,ktrd) = smltrd(:,:,ktrd) + pstrdmld(:,:,jk) * wkx(:,:,jk)   ! salinity 
     173         END DO 
     174      CASE ( '2D' )   ! forcing at upper boundary of the mixed-layer 
     175         tmltrd(:,:,ktrd) = tmltrd(:,:,ktrd) + pttrdmld(:,:,1) * wkx(:,:,1)        ! non penetrative 
     176         smltrd(:,:,ktrd) = smltrd(:,:,ktrd) + pstrdmld(:,:,1) * wkx(:,:,1)             
    321177      END SELECT 
    322  
    323       IF( idebug /= 0 ) THEN 
    324          IF(lwp) WRITE(numout,*) ' debuging trd_mld_zint: II.1 done'   
    325          CALL FLUSH(numout) 
    326       ENDIF 
    327  
     178      ! 
    328179   END SUBROUTINE trd_mld_zint 
    329  
    330  
     180     
    331181 
    332182   SUBROUTINE trd_mld( kt ) 
     
    334184      !!                  ***  ROUTINE trd_mld  *** 
    335185      !!  
    336       !! ** Purpose :  computation of cumulated trends over analysis period 
    337       !!               and make outputs (NetCDF or DIMG format) 
     186      !! ** Purpose :  Compute and cumulate the mixed layer trends over an analysis 
     187      !!               period, and write NetCDF (or dimg) outputs. 
    338188      !! 
    339189      !! ** Method/usage : 
     190      !!          The stored trends can be chosen twofold (according to the ln_trdmld_instant  
     191      !!          logical namelist variable) : 
     192      !!          1) to explain the difference between initial and final  
     193      !!             mixed-layer T & S (where initial and final relate to the 
     194      !!             current analysis window, defined by ntrd in the namelist) 
     195      !!          2) to explain the difference between the current and previous  
     196      !!             TIME-AVERAGED mixed-layer T & S (where time-averaging is 
     197      !!             performed over each analysis window). 
    340198      !! 
    341       !! History : 
    342       !!   9.0  !  04-08  (C. Talandier) New trends organization 
     199      !! ** Consistency check :  
     200      !!        If the control surface is fixed ( nctls > 1 ), the residual term (dh/dt 
     201      !!        entrainment) should be zero, at machine accuracy. Note that in the case 
     202      !!        of time-averaged mixed-layer fields, this residual WILL NOT BE ZERO 
     203      !!        over the first two analysis windows (except if restart). 
     204      !!        N.B. For ORCA2_LIM, use e.g. ntrd=5, ucf=1., nctls=8 
     205      !!             for checking residuals. 
     206      !!             On a NEC-SX5 computer, this typically leads to: 
     207      !!                   O(1.e-20) temp. residuals (tml_res) when ln_trdmld_instant=.false. 
     208      !!                   O(1.e-21) temp. residuals (tml_res) when ln_trdmld_instant=.true. 
     209      !! 
     210      !! ** Action : 
     211      !!       At each time step, mixed-layer averaged trends are stored in the  
     212      !!       tmltrd(:,:,jpmld_xxx) array (see trdmld_oce.F90 for definitions of jpmld_xxx). 
     213      !!       This array is known when trd_mld is called, at the end of the stp subroutine,  
     214      !!       except for the purely vertical K_z diffusion term, which is embedded in the 
     215      !!       lateral diffusion trend. 
     216      !! 
     217      !!       In I), this K_z term is diagnosed and stored, thus its contribution is removed 
     218      !!       from the lateral diffusion trend. 
     219      !!       In II), the instantaneous mixed-layer T & S are computed, and misc. cumulative 
     220      !!       arrays are updated. 
     221      !!       In III), called only once per analysis window, we compute the total trends, 
     222      !!       along with the residuals and the Asselin correction terms. 
     223      !!       In IV), the appropriate trends are written in the trends NetCDF file. 
     224      !! 
     225      !! References : 
     226      !!       - Vialard & al. 
     227      !!       - See NEMO documentation (in preparation) 
    343228      !!---------------------------------------------------------------------- 
    344       !! * Arguments 
    345229      INTEGER, INTENT( in ) ::   kt   ! ocean time-step index 
    346  
    347       !! * Local declarations 
     230      !! 
    348231      INTEGER :: ji, jj, jk, jl, ik, it 
    349  
    350       REAL(wp) :: zmean, zavt 
    351  
    352       REAL(wp) ,DIMENSION(jpi,jpj) ::   & 
    353          ztmltot, ztmlres,              & 
    354          zsmltot, zsmlres,              &  
    355          z2d 
    356  
     232      LOGICAL :: lldebug = .TRUE. 
     233      REAL(wp) :: zavt, zfn, zfn2 
     234      REAL(wp) ,DIMENSION(jpi,jpj) ::     & 
     235           ztmltot,  zsmltot,             & ! dT/dt over the anlysis window (including Asselin) 
     236           ztmlres,  zsmlres,             & ! residual = dh/dt entrainment term 
     237           ztmlatf,  zsmlatf,             & ! needed for storage only 
     238           ztmltot2, ztmlres2, ztmltrdm2, & ! \  working arrays to diagnose the trends 
     239           zsmltot2, zsmlres2, zsmltrdm2, & !  > associated with the time meaned ML T & S 
     240           ztmlatf2, zsmlatf2               ! / 
     241      REAL(wp), DIMENSION(jpi,jpj,jpltrd) ::  & 
     242           ztmltrd2, zsmltrd2               ! only needed for mean diagnostics 
    357243#if defined key_dimgout 
    358244      INTEGER ::  iyear,imon,iday 
     
    361247      !!---------------------------------------------------------------------- 
    362248 
    363       ! I. trends terms at lower boundary of mixed-layer 
    364       ! ------------------------------------------------ 
    365  
     249      ! ====================================================================== 
     250      ! I. Diagnose the purely vertical (K_z) diffusion trend 
     251      ! ====================================================================== 
     252 
     253      ! ... These terms can be estimated by flux computation at the lower boundary of the ML  
     254      !     (we compute (-1/h) * K_z * d_z( T ) and (-1/h) * K_z * d_z( S )) 
    366255      DO jj = 1,jpj 
    367256         DO ji = 1,jpi 
    368              
    369257            ik = nmld(ji,jj) 
    370              
    371             ! Temperature 
    372             ! entrainment due to vertical diffusion 
    373             !       - due to vertical mixing scheme (TKE) 
    374258            zavt = avt(ji,jj,ik) 
    375             tmltrd(ji,jj,jpmldevd) = - 1. * zavt / fse3w(ji,jj,ik) * tmask(ji,jj,ik)   & 
    376                &                   * ( tn(ji,jj,ik-1) - tn(ji,jj,ik) )   & 
    377                &                   / MAX( 1., rmld(ji,jj) ) * tmask(ji,jj,1) 
    378             ! Salinity 
    379             ! entrainment due to vertical diffusion 
    380             !       - due to vertical mixing scheme (TKE) 
     259            tmltrd(ji,jj,jpmld_zdf) = - zavt / fse3w(ji,jj,ik) * tmask(ji,jj,ik)  & 
     260               &                      * ( tn(ji,jj,ik-1) - tn(ji,jj,ik) )         & 
     261               &                      / MAX( 1., rmld(ji,jj) ) * tmask(ji,jj,1) 
    381262            zavt = fsavs(ji,jj,ik) 
    382             smltrd(ji,jj,jpmldevd) = -1. * zavt / fse3w(ji,jj,ik) * tmask(ji,jj,ik)   & 
    383                &                  * ( sn(ji,jj,ik-1) - sn(ji,jj,ik) )   & 
    384                &                  / MAX( 1., rmld(ji,jj) ) * tmask(ji,jj,1) 
     263            smltrd(ji,jj,jpmld_zdf) = - zavt / fse3w(ji,jj,ik) * tmask(ji,jj,ik)  & 
     264               &                      * ( sn(ji,jj,ik-1) - sn(ji,jj,ik) )         & 
     265               &                      / MAX( 1., rmld(ji,jj) ) * tmask(ji,jj,1) 
    385266         END DO 
    386267      END DO 
    387268 
     269      ! ... Remove this K_z trend from the iso-neutral diffusion term (if any) 
    388270      IF( ln_traldf_iso ) THEN 
    389          ! We substract to the TOTAL vertical diffusion tmltrd(:,:,jpmldzdf)  
    390          ! computed in subroutines trazdf_iso.F90 or trazdf_imp.F90 
    391          ! the vertical part du to the Kz in order to keep only the vertical 
    392          ! isopycnal diffusion (i.e the isopycnal diffusion componant on the vertical): 
    393          tmltrd(:,:,jpmldzdf) = tmltrd(:,:,jpmldzdf) - tmltrd(:,:,jpmldevd)   ! - due to isopycnal mixing scheme (implicit part) 
    394          smltrd(:,:,jpmldzdf) = smltrd(:,:,jpmldzdf) - smltrd(:,:,jpmldevd)   ! - due to isopycnal mixing scheme (implicit part) 
    395       ENDIF 
    396  
    397       ! Boundary conditions 
    398       CALL lbc_lnk( tmltrd, 'T', 1. ) 
    399       CALL lbc_lnk( smltrd, 'T', 1. ) 
    400  
    401       IF( idebug /= 0 ) THEN 
    402          WRITE(numout,*) ' debuging trd_mld: I. done'   
    403          CALL FLUSH(numout) 
    404       ENDIF 
    405  
    406       !  ================================= 
    407       !   II. Cumulated trends 
    408       !  ================================= 
    409  
    410       ! II.1 set before values of vertically average T and S  
    411       ! --------------------------------------------------- 
    412  
     271         tmltrd(:,:,jpmld_ldf) = tmltrd(:,:,jpmld_ldf) - tmltrd(:,:,jpmld_zdf) 
     272         smltrd(:,:,jpmld_ldf) = smltrd(:,:,jpmld_ldf) - smltrd(:,:,jpmld_zdf) 
     273      END IF 
     274 
     275      ! ... Lateral boundary conditions 
     276      DO jl = 1, jpltrd 
     277         CALL lbc_lnk( tmltrd(:,:,jl), 'T', 1. ) 
     278         CALL lbc_lnk( smltrd(:,:,jl), 'T', 1. ) 
     279      END DO 
     280 
     281      ! ====================================================================== 
     282      ! II. Cumulate the trends over the analysis window 
     283      ! ====================================================================== 
     284 
     285      ztmltrd2(:,:,:) = 0.e0   ;    zsmltrd2(:,:,:) = 0.e0  ! <<< reset arrays to zero 
     286      ztmltot2(:,:)   = 0.e0   ;    zsmltot2(:,:)   = 0.e0 
     287      ztmlres2(:,:)   = 0.e0   ;    zsmlres2(:,:)   = 0.e0 
     288      ztmlatf2(:,:)   = 0.e0   ;    zsmlatf2(:,:)   = 0.e0 
     289 
     290      ! II.1 Set before values of vertically average T and S  
     291      ! ---------------------------------------------------- 
    413292      IF( kt > nit000 ) THEN 
    414          tmlb(:,:) = tml(:,:) 
    415          smlb(:,:) = sml(:,:) 
    416       ENDIF 
    417  
    418       ! II.2 vertically integrated T and S 
    419       ! --------------------------------- 
    420  
    421       tml(:,:) = 0. 
    422       sml(:,:) = 0. 
    423  
     293         !   ... temperature ...                    ... salinity ... 
     294         tmlb   (:,:) = tml   (:,:)           ; smlb   (:,:) = sml   (:,:) 
     295         tmlatfn(:,:) = tmltrd(:,:,jpmld_atf) ; smlatfn(:,:) = smltrd(:,:,jpmld_atf) 
     296      END IF 
     297 
     298      ! II.2 Vertically averaged T and S 
     299      ! -------------------------------- 
     300      tml(:,:) = 0.e0   ;   sml(:,:) = 0.e0 
    424301      DO jk = 1, jpktrd - 1 
    425302         tml(:,:) = tml(:,:) + wkx(:,:,jk) * tn(:,:,jk) 
     
    427304      END DO 
    428305 
    429       IF(idebug /= 0) THEN 
    430          WRITE(numout,*) ' debuging trd_mld: II.2 done'   
    431          CALL FLUSH(numout) 
    432       ENDIF 
    433  
    434       ! II.3 set `before' mixed layer values for kt = nit000+1 
    435       ! -------------------------------------------------------- 
    436  
    437       IF( kt == nit000+1 ) THEN 
    438          tmlbb(:,:) = tmlb(:,:) 
    439          tmlbn(:,:) = tml (:,:) 
    440          smlbb(:,:) = smlb(:,:) 
    441          smlbn(:,:) = sml (:,:) 
    442       ENDIF 
    443  
    444       IF( idebug /= 0 ) THEN 
    445          WRITE(numout,*) ' debuging trd_mld: II.3 done'   
    446          CALL FLUSH(numout) 
    447       ENDIF 
    448  
    449       ! II.4 cumulated trends over analysis period (kt=2 to nwrite) 
    450       ! ----------------------------------------------------------- 
    451  
    452       ! trends cumulated over nwrite-2 time steps 
    453  
    454       IF( kt >= nit000+2 ) THEN 
     306      ! II.3 Initialize mixed-layer "before" arrays for the 1rst analysis window     
     307      ! ------------------------------------------------------------------------ 
     308      IF( kt == 2 ) THEN  !  i.e. ( .NOT. ln_rstart ).AND.( kt == nit000 + 1) 
     309         ! 
     310         !   ... temperature ...                ... salinity ... 
     311         tmlbb  (:,:) = tmlb   (:,:)   ;   smlbb  (:,:) = smlb   (:,:) 
     312         tmlbn  (:,:) = tml    (:,:)   ;   smlbn  (:,:) = sml    (:,:) 
     313         tmlatfb(:,:) = tmlatfn(:,:)   ;   smlatfb(:,:) = smlatfn(:,:) 
     314          
     315         tmltrd_csum_ub (:,:,:) = 0.e0  ;   smltrd_csum_ub (:,:,:) = 0.e0 
     316         tmltrd_atf_sumb(:,:)   = 0.e0  ;   smltrd_atf_sumb(:,:)   = 0.e0 
     317 
     318         rmldbn(:,:) = rmld(:,:) 
     319 
     320         IF( ln_ctl ) THEN 
     321            WRITE(numout,*) '             we reach kt == nit000 + 1 = ', nit000+1 
     322            CALL prt_ctl(tab2d_1=tmlbb   , clinfo1=' tmlbb   -   : ', mask1=tmask, ovlap=1) 
     323            CALL prt_ctl(tab2d_1=tmlbn   , clinfo1=' tmlbn   -   : ', mask1=tmask, ovlap=1) 
     324            CALL prt_ctl(tab2d_1=tmlatfb , clinfo1=' tmlatfb -   : ', mask1=tmask, ovlap=1) 
     325         END IF 
     326         ! 
     327      END IF 
     328 
     329      IF( ( ln_rstart ) .AND. ( kt == nit000 ) .AND. ( ln_ctl ) ) THEN 
     330         IF( ln_trdmld_instant ) THEN 
     331            WRITE(numout,*) '             restart from kt == nit000 = ', nit000 
     332            CALL prt_ctl(tab2d_1=tmlbb   , clinfo1=' tmlbb   -   : ', mask1=tmask, ovlap=1) 
     333            CALL prt_ctl(tab2d_1=tmlbn   , clinfo1=' tmlbn   -   : ', mask1=tmask, ovlap=1) 
     334            CALL prt_ctl(tab2d_1=tmlatfb , clinfo1=' tmlatfb -   : ', mask1=tmask, ovlap=1) 
     335         ELSE 
     336            WRITE(numout,*) '             restart from kt == nit000 = ', nit000 
     337            CALL prt_ctl(tab2d_1=tmlbn          , clinfo1=' tmlbn           -  : ', mask1=tmask, ovlap=1) 
     338            CALL prt_ctl(tab2d_1=rmldbn         , clinfo1=' rmldbn          -  : ', mask1=tmask, ovlap=1) 
     339            CALL prt_ctl(tab2d_1=tml_sumb       , clinfo1=' tml_sumb        -  : ', mask1=tmask, ovlap=1) 
     340            CALL prt_ctl(tab2d_1=tmltrd_atf_sumb, clinfo1=' tmltrd_atf_sumb -  : ', mask1=tmask, ovlap=1) 
     341            CALL prt_ctl(tab3d_1=tmltrd_csum_ub , clinfo1=' tmltrd_csum_ub  -  : ', mask1=tmask, ovlap=1, kdim=1) 
     342         END IF 
     343      END IF 
     344 
     345      ! II.4 Cumulated trends over the analysis period 
     346      ! ---------------------------------------------- 
     347      ! 
     348      !         [  1rst analysis window ] [     2nd analysis window     ]                        
     349      ! 
     350      !     o---[--o-----o-----o-----o--]-[--o-----o-----o-----o-----o--]---o-----o--> time steps 
     351      !                            ntrd                             2*ntrd       etc. 
     352      !     1      2     3     4    =5 e.g.                          =10 
     353      ! 
     354      IF( ( kt >= 2 ).OR.( ln_rstart ) ) THEN 
     355         ! 
    455356         nmoymltrd = nmoymltrd + 1 
     357          
     358         ! ... Cumulate over BOTH physical contributions AND over time steps 
    456359         DO jl = 1, jpltrd 
    457360            tmltrdm(:,:) = tmltrdm(:,:) + tmltrd(:,:,jl) 
    458361            smltrdm(:,:) = smltrdm(:,:) + smltrd(:,:,jl) 
    459362         END DO 
    460       ENDIF 
    461  
    462       IF( idebug /= 0 ) THEN 
    463          WRITE(numout,*) ' debuging trd_mld: II.4 done'   
    464          CALL FLUSH(numout) 
    465       ENDIF 
    466  
    467       !  ============================================= 
    468       !   III. Output in netCDF + residual computation 
    469       !  ============================================= 
    470  
    471       ztmltot(:,:) = 0. 
    472       zsmltot(:,:) = 0. 
    473       ztmlres(:,:) = 0. 
    474       zsmlres(:,:) = 0. 
    475  
    476       IF( MOD( kt - nit000+1, nwrite ) == 0 ) THEN 
    477  
    478          ! III.1 compute total trend  
    479          ! ------------------------ 
    480  
    481          zmean = float(nmoymltrd) 
    482           
    483          ztmltot(:,:) = ( tml(:,:) - tmlbn(:,:) + tmlb(:,:) - tmlbb(:,:) ) /  (zmean * 2. * rdt) 
    484          zsmltot(:,:) = ( sml(:,:) - smlbn(:,:) + smlb(:,:) - smlbb(:,:) ) /  (zmean * 2. * rdt) 
    485  
    486          IF(idebug /= 0) THEN 
    487             WRITE(numout,*) ' zmean = ',zmean   
    488             WRITE(numout,*) ' debuging trd_mld: III.1 done'   
    489             CALL FLUSH(numout) 
    490          ENDIF 
    491            
    492  
    493          ! III.2 compute residual  
    494          ! --------------------- 
    495  
    496          ztmlres(:,:) = ztmltot(:,:) - tmltrdm(:,:) / zmean 
    497          zsmlres(:,:) = zsmltot(:,:) - smltrdm(:,:) / zmean 
    498  
    499  
    500          ! Boundary conditions 
    501  
    502          CALL lbc_lnk( ztmltot, 'T', 1. ) 
    503          CALL lbc_lnk( ztmlres, 'T', 1. ) 
    504          CALL lbc_lnk( zsmltot, 'T', 1. ) 
    505          CALL lbc_lnk( zsmlres, 'T', 1. ) 
    506  
    507          IF( idebug /= 0 ) THEN 
    508             WRITE(numout,*) ' debuging trd_mld: III.2 done'   
    509             CALL FLUSH(numout) 
    510          ENDIF 
    511  
    512  
    513          ! III.3 time evolution array swap 
    514          ! ------------------------------ 
    515  
    516          tmlbb(:,:) = tmlb(:,:) 
    517          tmlbn(:,:) = tml (:,:) 
    518          smlbb(:,:) = smlb(:,:) 
    519          smlbn(:,:) = sml (:,:) 
    520  
    521          IF( idebug /= 0 ) THEN 
    522             WRITE(numout,*) ' debuging trd_mld: III.3 done'   
    523             CALL FLUSH(numout) 
    524          ENDIF 
    525  
    526  
    527          ! III.4 zero cumulative array 
    528          ! --------------------------- 
    529  
    530           nmoymltrd = 0 
    531  
    532           tmltrdm(:,:) = 0. 
    533           smltrdm(:,:) = 0. 
    534  
    535           IF(idebug /= 0) THEN 
    536               WRITE(numout,*) ' debuging trd_mld: III.4 done'   
    537               CALL FLUSH(numout) 
    538           ENDIF 
    539            
    540       ENDIF 
    541  
    542       ! III.5 write trends to output 
    543       ! --------------------------- 
     363 
     364         ! ... Special handling of the Asselin trend  
     365         tmlatfm(:,:) = tmlatfm(:,:) + tmlatfn(:,:) 
     366         smlatfm(:,:) = smlatfm(:,:) + smlatfn(:,:) 
     367 
     368         ! ... Trends associated with the time mean of the ML T/S 
     369         tmltrd_sum    (:,:,:) = tmltrd_sum    (:,:,:) + tmltrd    (:,:,:) ! tem 
     370         tmltrd_csum_ln(:,:,:) = tmltrd_csum_ln(:,:,:) + tmltrd_sum(:,:,:) 
     371         tml_sum       (:,:)   = tml_sum       (:,:)   + tml       (:,:) 
     372         smltrd_sum    (:,:,:) = smltrd_sum    (:,:,:) + smltrd    (:,:,:) ! sal 
     373         smltrd_csum_ln(:,:,:) = smltrd_csum_ln(:,:,:) + smltrd_sum(:,:,:) 
     374         sml_sum       (:,:)   = sml_sum       (:,:)   + sml       (:,:) 
     375         rmld_sum      (:,:)   = rmld_sum      (:,:)   + rmld      (:,:)   ! rmld 
     376         ! 
     377      END IF 
     378 
     379      ! ====================================================================== 
     380      ! III. Prepare fields for output (get here ONCE PER ANALYSIS PERIOD) 
     381      ! ====================================================================== 
     382 
     383      ! Convert to appropriate physical units 
     384      ! N.B. It may be useful to check IOIPSL time averaging with : 
     385      !      tmltrd (:,:,:) = 1. ; smltrd (:,:,:) = 1. 
     386      tmltrd(:,:,:) = tmltrd(:,:,:) * ucf   ! (actually needed for 1:jpltrd-1, but trdmld(:,:,jpltrd) 
     387      smltrd(:,:,:) = smltrd(:,:,:) * ucf   !  is no longer used, and is reset to 0. at next time step) 
     388       
     389      MODULO_NTRD : IF( MOD( kt, ntrd ) == 0 ) THEN        ! nitend MUST be multiple of ntrd 
     390         ! 
     391         ztmltot (:,:) = 0.e0   ;   zsmltot (:,:) = 0.e0   ! reset arrays to zero 
     392         ztmlres (:,:) = 0.e0   ;   zsmlres (:,:) = 0.e0 
     393         ztmltot2(:,:) = 0.e0   ;   zsmltot2(:,:) = 0.e0 
     394         ztmlres2(:,:) = 0.e0   ;   zsmlres2(:,:) = 0.e0 
     395       
     396         zfn  = float(nmoymltrd)    ;    zfn2 = zfn * zfn 
     397          
     398         ! III.1 Prepare fields for output ("instantaneous" diagnostics)  
     399         ! ------------------------------------------------------------- 
     400          
     401         !-- Compute total trends 
     402         ztmltot(:,:) = ( tml(:,:) - tmlbn(:,:) + tmlb(:,:) - tmlbb(:,:) ) / ( 2.*rdt ) 
     403         zsmltot(:,:) = ( sml(:,:) - smlbn(:,:) + smlb(:,:) - smlbb(:,:) ) / ( 2.*rdt ) 
     404          
     405         !-- Compute residuals 
     406         ztmlres(:,:) = ztmltot(:,:) - ( tmltrdm(:,:) - tmlatfn(:,:) + tmlatfb(:,:) ) 
     407         zsmlres(:,:) = zsmltot(:,:) - ( smltrdm(:,:) - smlatfn(:,:) + smlatfb(:,:) ) 
     408       
     409         !-- Diagnose Asselin trend over the analysis window  
     410         ztmlatf(:,:) = tmlatfm(:,:) - tmlatfn(:,:) + tmlatfb(:,:) 
     411         zsmlatf(:,:) = smlatfm(:,:) - smlatfn(:,:) + smlatfb(:,:) 
     412          
     413         !-- Lateral boundary conditions 
     414         !         ... temperature ...                    ... salinity ... 
     415         CALL lbc_lnk( ztmltot , 'T', 1. )  ;   CALL lbc_lnk( zsmltot , 'T', 1. ) 
     416         CALL lbc_lnk( ztmlres , 'T', 1. )  ;   CALL lbc_lnk( zsmlres , 'T', 1. ) 
     417         CALL lbc_lnk( ztmlatf , 'T', 1. )  ;   CALL lbc_lnk( zsmlatf , 'T', 1. ) 
     418 
     419#if defined key_diainstant 
     420         CALL ctl_stop( 'tml_trd : key_diainstant was never checked within trdmld. Comment this to proceed.') 
     421#endif 
     422         ! III.2 Prepare fields for output ("mean" diagnostics)  
     423         ! ---------------------------------------------------- 
     424          
     425         !-- Update the ML depth time sum (to build the Leap-Frog time mean) 
     426         rmld_sum(:,:) = rmldbn(:,:) + 2 * ( rmld_sum(:,:) - rmld(:,:) ) + rmld(:,:) 
     427 
     428         !-- Compute temperature total trends 
     429         tml_sum (:,:) = tmlbn(:,:) + 2 * ( tml_sum(:,:) - tml(:,:) ) + tml(:,:) 
     430         ztmltot2(:,:) = ( tml_sum(:,:) - tml_sumb(:,:) ) /  ( 2.*rdt )    ! now in degC/s 
     431          
     432         !-- Compute salinity total trends 
     433         sml_sum (:,:) = smlbn(:,:) + 2 * ( sml_sum(:,:) - sml(:,:) ) + sml(:,:) 
     434         zsmltot2(:,:) = ( sml_sum(:,:) - sml_sumb(:,:) ) /  ( 2.*rdt )    ! now in psu/s 
     435          
     436         !-- Compute temperature residuals 
     437         DO jl = 1, jpltrd 
     438            ztmltrd2(:,:,jl) = tmltrd_csum_ub(:,:,jl) + tmltrd_csum_ln(:,:,jl) 
     439         END DO 
     440 
     441         ztmltrdm2(:,:) = 0.e0 
     442         DO jl = 1, jpltrd 
     443            ztmltrdm2(:,:) = ztmltrdm2(:,:) + ztmltrd2(:,:,jl) 
     444         END DO 
     445 
     446         ztmlres2(:,:) =  ztmltot2(:,:)  -       & 
     447              ( ztmltrdm2(:,:) - tmltrd_sum(:,:,jpmld_atf) + tmltrd_atf_sumb(:,:) ) 
     448          
     449         !-- Compute salinity residuals 
     450         DO jl = 1, jpltrd 
     451            zsmltrd2(:,:,jl) = smltrd_csum_ub(:,:,jl) + smltrd_csum_ln(:,:,jl) 
     452         END DO 
     453 
     454         zsmltrdm2(:,:) = 0. 
     455         DO jl = 1, jpltrd 
     456            zsmltrdm2(:,:) = zsmltrdm2(:,:) + zsmltrd2(:,:,jl) 
     457         END DO 
     458 
     459         zsmlres2(:,:) =  zsmltot2(:,:)  -       & 
     460              ( zsmltrdm2(:,:) - smltrd_sum(:,:,jpmld_atf) + smltrd_atf_sumb(:,:) ) 
     461          
     462         !-- Diagnose Asselin trend over the analysis window 
     463         ztmlatf2(:,:) = ztmltrd2(:,:,jpmld_atf) - tmltrd_sum(:,:,jpmld_atf) + tmltrd_atf_sumb(:,:) 
     464         zsmlatf2(:,:) = zsmltrd2(:,:,jpmld_atf) - smltrd_sum(:,:,jpmld_atf) + smltrd_atf_sumb(:,:) 
     465 
     466         !-- Lateral boundary conditions 
     467         !         ... temperature ...                    ... salinity ... 
     468         CALL lbc_lnk( ztmltot2, 'T', 1. )  ;   CALL lbc_lnk( zsmltot2, 'T', 1. ) 
     469         CALL lbc_lnk( ztmlres2, 'T', 1. )  ;   CALL lbc_lnk( zsmlres2, 'T', 1. ) 
     470         DO jl = 1, jpltrd 
     471            CALL lbc_lnk( ztmltrd2(:,:,jl), 'T', 1. ) ! \  these will be output 
     472            CALL lbc_lnk( zsmltrd2(:,:,jl), 'T', 1. ) ! /  in the NetCDF trends file 
     473         END DO 
     474          
     475         ! III.3 Time evolution array swap 
     476         ! ------------------------------- 
     477          
     478         ! For T/S instantaneous diagnostics  
     479         !   ... temperature ...               ... salinity ... 
     480         tmlbb  (:,:) = tmlb   (:,:)  ;   smlbb  (:,:) = smlb   (:,:) 
     481         tmlbn  (:,:) = tml    (:,:)  ;   smlbn  (:,:) = sml    (:,:) 
     482         tmlatfb(:,:) = tmlatfn(:,:)  ;   smlatfb(:,:) = smlatfn(:,:) 
     483 
     484         ! For T mean diagnostics  
     485         tmltrd_csum_ub (:,:,:) = zfn * tmltrd_sum(:,:,:) - tmltrd_csum_ln(:,:,:) 
     486         tml_sumb       (:,:)   = tml_sum(:,:) 
     487         tmltrd_atf_sumb(:,:)   = tmltrd_sum(:,:,jpmld_atf) 
     488          
     489         ! For S mean diagnostics  
     490         smltrd_csum_ub (:,:,:) = zfn * smltrd_sum(:,:,:) - smltrd_csum_ln(:,:,:) 
     491         sml_sumb       (:,:)   = sml_sum(:,:) 
     492         smltrd_atf_sumb(:,:)   = smltrd_sum(:,:,jpmld_atf) 
     493          
     494         ! ML depth 
     495         rmldbn         (:,:)   = rmld    (:,:) 
     496          
     497         IF( ln_ctl ) THEN 
     498            IF( ln_trdmld_instant ) THEN 
     499               CALL prt_ctl(tab2d_1=tmlbb   , clinfo1=' tmlbb   -   : ', mask1=tmask, ovlap=1) 
     500               CALL prt_ctl(tab2d_1=tmlbn   , clinfo1=' tmlbn   -   : ', mask1=tmask, ovlap=1) 
     501               CALL prt_ctl(tab2d_1=tmlatfb , clinfo1=' tmlatfb -   : ', mask1=tmask, ovlap=1) 
     502            ELSE 
     503               CALL prt_ctl(tab2d_1=tmlbn          , clinfo1=' tmlbn           -  : ', mask1=tmask, ovlap=1) 
     504               CALL prt_ctl(tab2d_1=rmldbn         , clinfo1=' rmldbn          -  : ', mask1=tmask, ovlap=1) 
     505               CALL prt_ctl(tab2d_1=tml_sumb       , clinfo1=' tml_sumb        -  : ', mask1=tmask, ovlap=1) 
     506               CALL prt_ctl(tab2d_1=tmltrd_atf_sumb, clinfo1=' tmltrd_atf_sumb -  : ', mask1=tmask, ovlap=1) 
     507               CALL prt_ctl(tab3d_1=tmltrd_csum_ub , clinfo1=' tmltrd_csum_ub  -  : ', mask1=tmask, ovlap=1, kdim=1) 
     508            END IF 
     509         END IF 
     510 
     511         ! III.4 Convert to appropriate physical units 
     512         ! ------------------------------------------- 
     513 
     514         !    ... temperature ...                         ... salinity ... 
     515         ztmltot (:,:)   = ztmltot(:,:)   * ucf/zfn  ; zsmltot (:,:)   = zsmltot(:,:)   * ucf/zfn 
     516         ztmlres (:,:)   = ztmlres(:,:)   * ucf/zfn  ; zsmlres (:,:)   = zsmlres(:,:)   * ucf/zfn 
     517         ztmlatf (:,:)   = ztmlatf(:,:)   * ucf/zfn  ; zsmlatf (:,:)   = zsmlatf(:,:)   * ucf/zfn 
     518 
     519         tml_sum (:,:)   = tml_sum (:,:)  /  (2*zfn) ; sml_sum (:,:)   = sml_sum (:,:)  /  (2*zfn) 
     520         ztmltot2(:,:)   = ztmltot2(:,:)  * ucf/zfn2 ; zsmltot2(:,:)   = zsmltot2(:,:)  * ucf/zfn2 
     521         ztmltrd2(:,:,:) = ztmltrd2(:,:,:)* ucf/zfn2 ; zsmltrd2(:,:,:) = zsmltrd2(:,:,:)* ucf/zfn2 
     522         ztmlatf2(:,:)   = ztmlatf2(:,:)  * ucf/zfn2 ; zsmlatf2(:,:)   = zsmlatf2(:,:)  * ucf/zfn2 
     523         ztmlres2(:,:)   = ztmlres2(:,:)  * ucf/zfn2 ; zsmlres2(:,:)   = zsmlres2(:,:)  * ucf/zfn2 
     524 
     525         rmld_sum(:,:)   = rmld_sum(:,:)  /  (2*zfn)  ! similar to tml_sum and sml_sum 
     526 
     527         ! * Debugging information * 
     528         IF( lldebug ) THEN 
     529            ! 
     530            WRITE(numout,*) 
     531            WRITE(numout,*) 'trd_mld : write trends in the Mixed Layer for debugging process:' 
     532            WRITE(numout,*) '~~~~~~~  ' 
     533            WRITE(numout,*) '          TRA kt = ', kt, 'nmoymltrd = ', nmoymltrd 
     534            WRITE(numout,*) 
     535            WRITE(numout,*) '          >>>>>>>>>>>>>>>>>>  TRA TEMPERATURE <<<<<<<<<<<<<<<<<<' 
     536            WRITE(numout,*) '          TRA ztmlres    : ', SUM(ztmlres(:,:)) 
     537            WRITE(numout,*) '          TRA ztmltot    : ', SUM(ztmltot(:,:)) 
     538            WRITE(numout,*) '          TRA tmltrdm    : ', SUM(tmltrdm(:,:)) 
     539            WRITE(numout,*) '          TRA tmlatfb    : ', SUM(tmlatfb(:,:)) 
     540            WRITE(numout,*) '          TRA tmlatfn    : ', SUM(tmlatfn(:,:)) 
     541            DO jl = 1, jpltrd 
     542               WRITE(numout,*) '          * TRA TREND INDEX jpmld_xxx = jl = ', jl, & 
     543                    & ' tmltrd : ', SUM(tmltrd(:,:,jl)) 
     544            END DO 
     545            WRITE(numout,*) '          TRA ztmlres (jpi/2,jpj/2) : ', ztmlres (jpi/2,jpj/2) 
     546            WRITE(numout,*) '          TRA ztmlres2(jpi/2,jpj/2) : ', ztmlres2(jpi/2,jpj/2) 
     547            WRITE(numout,*) 
     548            WRITE(numout,*) '          >>>>>>>>>>>>>>>>>>  TRA SALINITY <<<<<<<<<<<<<<<<<<' 
     549            WRITE(numout,*) '          TRA zsmlres    : ', SUM(zsmlres(:,:)) 
     550            WRITE(numout,*) '          TRA zsmltot    : ', SUM(zsmltot(:,:)) 
     551            WRITE(numout,*) '          TRA smltrdm    : ', SUM(smltrdm(:,:)) 
     552            WRITE(numout,*) '          TRA smlatfb    : ', SUM(smlatfb(:,:)) 
     553            WRITE(numout,*) '          TRA smlatfn    : ', SUM(smlatfn(:,:)) 
     554            DO jl = 1, jpltrd 
     555               WRITE(numout,*) '          * TRA TREND INDEX jpmld_xxx = jl = ', jl, & 
     556                    & ' smltrd : ', SUM(smltrd(:,:,jl)) 
     557            END DO 
     558            WRITE(numout,*) '          TRA zsmlres (jpi/2,jpj/2) : ', zsmlres (jpi/2,jpj/2) 
     559            WRITE(numout,*) '          TRA zsmlres2(jpi/2,jpj/2) : ', zsmlres2(jpi/2,jpj/2) 
     560            ! 
     561         END IF 
     562         ! 
     563      END IF MODULO_NTRD 
     564 
     565      ! ====================================================================== 
     566      ! IV. Write trends in the NetCDF file 
     567      ! ====================================================================== 
     568 
     569      ! IV.1 Code for dimg mpp output 
     570      ! ----------------------------- 
    544571 
    545572#if defined key_dimgout 
    546 ! code for dimg mpp output 
    547       IF ( MOD(kt,nwrite) == 0 ) THEN 
    548          WRITE(clmode,'(f5.1,a)' ) nwrite*rdt/86400.,' days average' 
    549          iyear = ndastp/10000 
    550          imon = (ndastp-iyear*10000)/100 
    551          iday = ndastp - imon*100 - iyear*10000 
     573 
     574      IF( MOD( kt, ntrd ) == 0 ) THEN 
     575         iyear =  ndastp/10000 
     576         imon  = (ndastp-iyear*10000)/100 
     577         iday  =  ndastp - imon*100 - iyear*10000 
    552578         WRITE(clname,9000) TRIM(cexper),'MLDiags',iyear,imon,iday 
    553          cltext=TRIM(cexper)//' mld diags'//TRIM(clmode) 
     579         WRITE(clmode,'(f5.1,a)') ntrd*rdt/86400.,' days average' 
     580         cltext = TRIM(cexper)//' mld diags'//TRIM(clmode) 
    554581         CALL dia_wri_dimg (clname, cltext, smltrd, jpltrd, '2') 
    555   9000   FORMAT(a,"_",a,"_y",i4.4,"m",i2.2,"d",i2.2,".dimgproc") 
    556        END IF 
     582      END IF 
     583 
     5849000  FORMAT(a,"_",a,"_y",i4.4,"m",i2.2,"d",i2.2,".dimgproc") 
    557585 
    558586#else 
    559       IF( kt >=  nit000+1 ) THEN 
    560  
    561          ! define time axis 
    562          it= kt-nit000+1 
    563          IF( lwp .AND. MOD( kt, nwrite ) == 0 ) THEN 
    564             WRITE(numout,*) '     trd_mld : write NetCDF fields' 
    565          ENDIF 
    566           
    567          CALL histwrite( nidtrd,"somlttml",it,rmld          ,ndimtrd1,ndextrd1) ! Mixed-layer depth 
    568           
    569          ! Temperature trends 
    570          ! ------------------ 
    571          CALL histwrite( nidtrd,"somltemp",it,tml           ,ndimtrd1,ndextrd1) ! Mixed-layer temperature 
    572          CALL histwrite( nidtrd,"somlttto",it,ztmltot       ,ndimtrd1,ndextrd1) ! total  
    573          CALL histwrite( nidtrd,"somlttax",it,tmltrd(:,:, 1),ndimtrd1,ndextrd1) ! i- adv. 
    574          CALL histwrite( nidtrd,"somlttay",it,tmltrd(:,:, 2),ndimtrd1,ndextrd1) ! j- adv. 
    575          CALL histwrite( nidtrd,"somlttaz",it,tmltrd(:,:, 3),ndimtrd1,ndextrd1) ! vertical adv. 
    576          CALL histwrite( nidtrd,"somlttdh",it,tmltrd(:,:, 4),ndimtrd1,ndextrd1) ! hor. lateral diff. 
    577          CALL histwrite( nidtrd,"somlttfo",it,tmltrd(:,:, 5),ndimtrd1,ndextrd1) ! forcing 
    578  
    579          CALL histwrite( nidtrd,"somlbtdz",it,tmltrd(:,:, 6),ndimtrd1,ndextrd1) ! vert. diffusion  
    580          CALL histwrite( nidtrd,"somlbtdt",it,ztmlres       ,ndimtrd1,ndextrd1) ! dh/dt entrainment (residual) 
    581          IF( ln_traldf_iso ) THEN 
    582             CALL histwrite( nidtrd,"somlbtdv",it,tmltrd(:,:, 7),ndimtrd1,ndextrd1) ! vert. lateral diff. 
    583          ENDIF 
    584 #if defined key_traldf_eiv 
    585          CALL histwrite( nidtrd,"somlgtax",it,tmltrd(:,:, 8),ndimtrd1,ndextrd1) ! i- adv. (eiv) 
    586          CALL histwrite( nidtrd,"somlgtay",it,tmltrd(:,:, 9),ndimtrd1,ndextrd1) ! j- adv. (eiv) 
    587          CALL histwrite( nidtrd,"somlgtaz",it,tmltrd(:,:,10),ndimtrd1,ndextrd1) ! vert. adv. (eiv) 
    588          z2d(:,:) = tmltrd(:,:,8) + tmltrd(:,:,9) + tmltrd(:,:,10) 
    589          CALL histwrite( nidtrd,"somlgtat",it,z2d           ,ndimtrd1,ndextrd1) ! total adv. (eiv) 
    590 #endif    
    591  
    592          ! Salinity trends 
    593          ! --------------- 
    594          CALL histwrite( nidtrd,"somlsalt",it,sml           ,ndimtrd1,ndextrd1) ! Mixed-layer salinity 
    595          CALL histwrite( nidtrd,"somltsto",it,zsmltot       ,ndimtrd1,ndextrd1) ! total  
    596          CALL histwrite( nidtrd,"somltsax",it,smltrd(:,:, 1),ndimtrd1,ndextrd1) ! i- adv. 
    597          CALL histwrite( nidtrd,"somltsay",it,smltrd(:,:, 2),ndimtrd1,ndextrd1) ! j- adv. 
    598          CALL histwrite( nidtrd,"somltsaz",it,smltrd(:,:, 3),ndimtrd1,ndextrd1) ! vert. adv. 
    599          CALL histwrite( nidtrd,"somltsdh",it,smltrd(:,:, 4),ndimtrd1,ndextrd1) ! hor. lateral diff. 
    600          CALL histwrite( nidtrd,"somltsfo",it,smltrd(:,:, 5),ndimtrd1,ndextrd1) ! forcing 
    601          CALL histwrite( nidtrd,"somlbsdz",it,smltrd(:,:, 6),ndimtrd1,ndextrd1) ! vert. diff. 
    602          CALL histwrite( nidtrd,"somlbsdt",it,zsmlres       ,ndimtrd1,ndextrd1) ! dh/dt entrainment (residual) 
    603          IF( ln_traldf_iso ) THEN 
    604             CALL histwrite( nidtrd,"somlbsdv",it,smltrd(:,:, 7),ndimtrd1,ndextrd1) ! vert. lateral diff; 
    605          ENDIF 
    606 #if defined key_traldf_eiv 
    607          CALL histwrite( nidtrd,"somlgsax",it,smltrd(:,:, 8),ndimtrd1,ndextrd1) ! i-adv. (eiv) 
    608          CALL histwrite( nidtrd,"somlgsay",it,smltrd(:,:, 9),ndimtrd1,ndextrd1) ! j-adv. (eiv) 
    609          CALL histwrite( nidtrd,"somlgsaz",it,smltrd(:,:,10),ndimtrd1,ndextrd1) ! vert. adv. (eiv) 
    610          z2d(:,:) = smltrd(:,:,8) + smltrd(:,:,9) + smltrd(:,:,10) 
    611          CALL histwrite( nidtrd,"somlgsat",it,z2d           ,ndimtrd1,ndextrd1) ! total adv. (eiv) 
     587       
     588      ! IV.2 Code for IOIPSL/NetCDF output 
     589      ! ---------------------------------- 
     590 
     591      IF( lwp .AND. MOD( kt , ntrd ) == 0 ) THEN 
     592         WRITE(numout,*) ' ' 
     593         WRITE(numout,*) 'trd_mld : write trends in the NetCDF file :' 
     594         WRITE(numout,*) '~~~~~~~  ' 
     595         WRITE(numout,*) '          ', TRIM(clhstnam), ' at kt = ', kt 
     596         WRITE(numout,*) '          N.B. nmoymltrd = ', nmoymltrd 
     597         WRITE(numout,*) ' ' 
     598      END IF 
     599          
     600      it = kt - nit000 + 1 
     601 
     602      !-- Write the trends for T/S instantaneous diagnostics  
     603      IF( ln_trdmld_instant ) THEN            
     604 
     605         CALL histwrite( nidtrd, "mxl_depth", it, rmld(:,:), ndimtrd1, ndextrd1 ) 
     606          
     607         !................................. ( ML temperature ) ................................... 
     608          
     609         !-- Output the fields 
     610         CALL histwrite( nidtrd, "tml"     , it, tml    (:,:), ndimtrd1, ndextrd1 )  
     611         CALL histwrite( nidtrd, "tml_tot" , it, ztmltot(:,:), ndimtrd1, ndextrd1 )  
     612         CALL histwrite( nidtrd, "tml_res" , it, ztmlres(:,:), ndimtrd1, ndextrd1 )  
     613          
     614         DO jl = 1, jpltrd - 1 
     615            CALL histwrite( nidtrd, trim("tml"//ctrd(jl,2)),            & 
     616                 &          it, tmltrd (:,:,jl), ndimtrd1, ndextrd1 ) 
     617         END DO 
     618          
     619         CALL histwrite( nidtrd, trim("tml"//ctrd(jpmld_atf,2)),        & 
     620              &          it, ztmlatf(:,:), ndimtrd1, ndextrd1 ) 
     621          
     622         !.................................. ( ML salinity ) ..................................... 
     623          
     624         !-- Output the fields 
     625         CALL histwrite( nidtrd, "sml"     , it, sml    (:,:), ndimtrd1, ndextrd1 )  
     626         CALL histwrite( nidtrd, "sml_tot" , it, zsmltot(:,:), ndimtrd1, ndextrd1 )  
     627         CALL histwrite( nidtrd, "sml_res" , it, zsmlres(:,:), ndimtrd1, ndextrd1 )  
     628          
     629         DO jl = 1, jpltrd - 1 
     630            CALL histwrite( nidtrd, trim("sml"//ctrd(jl,2)),            & 
     631                 &          it, smltrd(:,:,jl), ndimtrd1, ndextrd1 ) 
     632         END DO 
     633          
     634         CALL histwrite( nidtrd, trim("sml"//ctrd(jpmld_atf,2)),        & 
     635              &          it, zsmlatf(:,:), ndimtrd1, ndextrd1 ) 
     636          
     637         IF( kt == nitend )   CALL histclo( nidtrd ) 
     638 
     639      !-- Write the trends for T/S mean diagnostics  
     640      ELSE 
     641          
     642         CALL histwrite( nidtrd, "mxl_depth", it, rmld_sum(:,:), ndimtrd1, ndextrd1 )  
     643          
     644         !................................. ( ML temperature ) ................................... 
     645          
     646         !-- Output the fields 
     647         CALL histwrite( nidtrd, "tml"     , it, tml_sum (:,:), ndimtrd1, ndextrd1 )  
     648         CALL histwrite( nidtrd, "tml_tot" , it, ztmltot2(:,:), ndimtrd1, ndextrd1 )  
     649         CALL histwrite( nidtrd, "tml_res" , it, ztmlres2(:,:), ndimtrd1, ndextrd1 )  
     650          
     651         DO jl = 1, jpltrd - 1 
     652            CALL histwrite( nidtrd, trim("tml"//ctrd(jl,2)),            & 
     653                 &          it, ztmltrd2(:,:,jl), ndimtrd1, ndextrd1 ) 
     654         END DO 
     655          
     656         CALL histwrite( nidtrd, trim("tml"//ctrd(jpmld_atf,2)),        & 
     657              &          it, ztmlatf2(:,:), ndimtrd1, ndextrd1 ) 
     658          
     659         !.................................. ( ML salinity ) ..................................... 
     660                      
     661         !-- Output the fields 
     662         CALL histwrite( nidtrd, "sml"     , it, sml_sum (:,:), ndimtrd1, ndextrd1 )  
     663         CALL histwrite( nidtrd, "sml_tot" , it, zsmltot2(:,:), ndimtrd1, ndextrd1 )  
     664         CALL histwrite( nidtrd, "sml_res" , it, zsmlres2(:,:), ndimtrd1, ndextrd1 )  
     665          
     666         DO jl = 1, jpltrd - 1 
     667            CALL histwrite( nidtrd, trim("sml"//ctrd(jl,2)),            & 
     668                 &          it, zsmltrd2(:,:,jl), ndimtrd1, ndextrd1 ) 
     669         END DO 
     670          
     671         CALL histwrite( nidtrd, trim("sml"//ctrd(jpmld_atf,2)),        & 
     672              &          it, zsmlatf2(:,:), ndimtrd1, ndextrd1 ) 
     673          
     674         IF( kt == nitend )   CALL histclo( nidtrd ) 
     675 
     676      END IF 
     677       
     678      ! Compute the control surface (for next time step) : flag = on 
     679      icount = 1 
     680      ! 
    612681#endif 
    613682 
    614          IF( idebug /= 0 ) THEN 
    615             WRITE(numout,*) ' debuging trd_mld: III.5 done'   
    616             CALL FLUSH(numout) 
    617          ENDIF 
    618  
    619          ! set counter icount to one to allow the calculation 
    620          ! of the surface control in the next time step in the trd_mld_zint subroutine 
    621          icount = 1 
    622  
    623       ENDIF 
    624  
    625       ! At the end of the 1st time step, set icount to 1 to be 
    626       ! able to compute the surface control at the beginning of 
    627       ! the second time step 
    628       IF( kt == nit000 )   icount = 1 
    629  
    630       IF( kt == nitend )   CALL histclo( nidtrd ) 
    631 #endif 
     683      IF( MOD( kt , ntrd ) == 0 ) THEN 
     684         ! 
     685         ! III.5 Reset cumulative arrays to zero 
     686         ! ------------------------------------- 
     687         nmoymltrd = 0 
     688          
     689         !   ... temperature ...               ... salinity ... 
     690         tmltrdm        (:,:)   = 0.e0   ;   smltrdm        (:,:)   = 0.e0 
     691         tmlatfm        (:,:)   = 0.e0   ;   smlatfm        (:,:)   = 0.e0 
     692         tml_sum        (:,:)   = 0.e0   ;   sml_sum        (:,:)   = 0.e0 
     693         tmltrd_csum_ln (:,:,:) = 0.e0   ;   smltrd_csum_ln (:,:,:) = 0.e0 
     694         tmltrd_sum     (:,:,:) = 0.e0   ;   smltrd_sum     (:,:,:) = 0.e0 
     695 
     696         rmld_sum       (:,:)   = 0.e0 
     697         ! 
     698      END IF 
    632699 
    633700   END SUBROUTINE trd_mld 
     
    642709      !!      from ocean surface down to control surface (NetCDF output) 
    643710      !! 
    644       !! ** Method/usage : 
    645       !! 
    646       !! History : 
    647       !!        !  95-04  (J. Vialard)  Original code 
    648       !!        !  97-02  (E. Guilyardi)  Adaptation global + base cmo 
    649       !!        !  99-09  (E. Guilyardi)  Re-writing + netCDF output 
    650       !!   8.5  !  02-06  (G. Madec)  F90: Free form and module 
    651       !!   9.0  !  04-08  (C. Talandier) New trends organization 
    652711      !!---------------------------------------------------------------------- 
    653712      !! * Local declarations 
    654       INTEGER :: ilseq 
     713      INTEGER :: ilseq, jl 
    655714 
    656715      REAL(wp) ::   zjulian, zsto, zout 
    657716 
    658       CHARACTER (LEN=21) ::   & 
     717      CHARACTER (LEN=21) ::    & 
    659718         clold ='OLD'        , & ! open specifier (direct access files) 
    660719         clunf ='UNFORMATTED', & ! open specifier (direct access files) 
    661720         clseq ='SEQUENTIAL'     ! open specifier (direct access files) 
    662       CHARACTER (LEN=40) ::   clhstnam 
    663721      CHARACTER (LEN=40) ::   clop 
    664       CHARACTER (LEN=12) ::   clmxl 
    665  
    666       NAMELIST/namtrd/ ntrd, nctls 
     722      CHARACTER (LEN=12) ::   clmxl, cltu, clsu 
     723 
    667724      !!---------------------------------------------------------------------- 
    668725 
    669       !  =================== 
    670       !   I. initialization 
    671       !  =================== 
    672  
    673       ! Open specifier 
    674       ilseq  = 1 
    675       idebug = 0      ! set it to 1 in case of problem to have more print 
    676       icount = 1       
    677       ionce  = 1 
    678  
    679       ! namelist namtrd : trend diagnostic 
    680       REWIND( numnam ) 
    681       READ  ( numnam, namtrd ) 
     726      ! ====================================================================== 
     727      ! I. initialization 
     728      ! ====================================================================== 
    682729 
    683730      IF(lwp) THEN 
    684          WRITE(numout,*) ' ' 
    685          WRITE(numout,*) 'trd_mld_init: mixed layer heat & freshwater budget trends' 
    686          WRITE(numout,*) '~~~~~~~~~~~~~' 
    687          WRITE(numout,*) ' ' 
    688          WRITE(numout,*) '          Namelist namtrd : ' 
    689          WRITE(numout,*) '             control surface for trends      nctls = ',nctls 
    690          WRITE(numout,*) ' ' 
    691       ENDIF 
    692  
    693       ! cumulated trends array init 
     731         WRITE(numout,*) 
     732         WRITE(numout,*) ' trd_mld_init : Mixed-layer trends' 
     733         WRITE(numout,*) ' ~~~~~~~~~~~~~' 
     734         WRITE(numout,*) '                namelist namtrd read in trd_mod_init                        ' 
     735         WRITE(numout,*) 
     736      END IF 
     737 
     738      ! I.1 Check consistency of user defined preferences 
     739      ! ------------------------------------------------- 
     740 
     741      IF( ( lk_trdmld ) .AND. ( MOD( nitend, ntrd ) /= 0 ) ) THEN 
     742         WRITE(numout,cform_err) 
     743         WRITE(numout,*) '                Your nitend parameter, nitend = ', nitend 
     744         WRITE(numout,*) '                is no multiple of the trends diagnostics frequency        ' 
     745         WRITE(numout,*) '                          you defined, ntrd   = ', ntrd 
     746         WRITE(numout,*) '                This will not allow you to restart from this simulation.  ' 
     747         WRITE(numout,*) '                You should reconsider this choice.                        '  
     748         WRITE(numout,*)  
     749         WRITE(numout,*) '                N.B. the nitend parameter is also constrained to be a     ' 
     750         WRITE(numout,*) '                multiple of the sea-ice frequency parameter (typically 5) ' 
     751         nstop = nstop + 1 
     752      END IF 
     753 
     754      IF( ( lk_trdmld ) .AND. ( n_cla == 1 ) ) THEN 
     755         WRITE(numout,cform_war) 
     756         WRITE(numout,*) '                You set n_cla = 1. Note that the Mixed-Layer diagnostics  ' 
     757         WRITE(numout,*) '                are not exact along the corresponding straits.            ' 
     758         nwarn = nwarn + 1 
     759      END IF 
     760 
     761      ! I.2 Initialize arrays to zero or read a restart file 
     762      ! ---------------------------------------------------- 
     763 
    694764      nmoymltrd = 0 
    695       tmltrdm(:,:) = 0.e0 
    696       smltrdm(:,:) = 0.e0 
    697  
    698       !  read control surface from file ctlsurf_idx 
    699  
     765 
     766      !     ... temperature ...                  ... salinity ... 
     767      tml            (:,:)   = 0.e0    ;    sml            (:,:)   = 0.e0     ! inst. 
     768      tmltrdm        (:,:)   = 0.e0    ;    smltrdm        (:,:)   = 0.e0 
     769      tmlatfm        (:,:)   = 0.e0    ;    smlatfm        (:,:)   = 0.e0 
     770      tml_sum        (:,:)   = 0.e0    ;    sml_sum        (:,:)   = 0.e0     ! mean 
     771      tmltrd_sum     (:,:,:) = 0.e0    ;    smltrd_sum     (:,:,:) = 0.e0 
     772      tmltrd_csum_ln (:,:,:) = 0.e0    ;    smltrd_csum_ln (:,:,:) = 0.e0 
     773 
     774      rmld           (:,:)   = 0.e0             
     775      rmld_sum       (:,:)   = 0.e0 
     776 
     777      IF( ln_rstart .AND. ln_trdmld_restart ) THEN 
     778         CALL trd_mld_rst_read 
     779      ELSE 
     780         !     ... temperature ...                  ... salinity ... 
     781         tmlb           (:,:)   = 0.e0    ;    smlb           (:,:)   = 0.e0  ! inst. 
     782         tmlbb          (:,:)   = 0.e0    ;    smlbb          (:,:)   = 0.e0   
     783         tmlbn          (:,:)   = 0.e0    ;    smlbn          (:,:)   = 0.e0   
     784         tml_sumb       (:,:)   = 0.e0    ;    sml_sumb       (:,:)   = 0.e0  ! mean 
     785         tmltrd_csum_ub (:,:,:) = 0.e0    ;    smltrd_csum_ub (:,:,:) = 0.e0 
     786         tmltrd_atf_sumb(:,:)   = 0.e0    ;    smltrd_atf_sumb(:,:)   = 0.e0   
     787      END IF 
     788 
     789      ilseq  = 1   ;   icount = 1   ;   ionce  = 1                            ! open specifier 
     790 
     791      ! I.3 Read control surface from file ctlsurf_idx 
     792      ! ---------------------------------------------- 
     793  
    700794      IF( nctls == 1 ) THEN 
    701          clname ='ctlsurf_idx' 
    702          CALL ctlopn(numbol,clname,clold,clunf,clseq,   & 
    703               ilseq,numout,lwp,1) 
    704          REWIND (numbol) 
    705          READ(numbol) nbol 
    706       ENDIF 
    707  
    708  
    709       IF( idebug /= 0 ) THEN 
    710          WRITE(numout,*) ' debuging trd_mld_init: 0. done '   
    711          CALL FLUSH(numout) 
    712       ENDIF 
    713  
    714       !  =================================== 
    715       !   II. netCDF output initialization 
    716       !  =================================== 
     795         clname = 'ctlsurf_idx' 
     796         CALL ctlopn( numbol, clname, clold, clunf, clseq, ilseq, numout, lwp, 1 ) 
     797         REWIND( numbol ) 
     798         READ  ( numbol ) nbol 
     799      END IF 
     800 
     801      ! ====================================================================== 
     802      ! II. netCDF output initialization 
     803      ! ====================================================================== 
    717804 
    718805#if defined key_dimgout  
    719  
     806      ??? 
    720807#else 
    721       !     clmxl = legend root for netCDF output 
    722       IF( nctls == 0 ) THEN 
    723          ! control surface = mixed-layer with density criterion  
    724          ! (array nmln computed in zdfmxl.F90) 
    725          clmxl = 'Mixed Layer ' 
    726       ELSE IF( nctls == 1 ) THEN 
    727          ! control surface = read index from file  
     808      ! clmxl = legend root for netCDF output 
     809      IF( nctls == 0 ) THEN      ! control surface = mixed-layer with density criterion 
     810         clmxl = 'Mixed Layer '  !                   (array nmln computed in zdfmxl.F90) 
     811      ELSE IF( nctls == 1 ) THEN ! control surface = read index from file  
    728812         clmxl = '      Bowl ' 
    729       ELSE IF( nctls >= 2 ) THEN 
    730          ! control surface = model level 
    731          WRITE(clmxl,'(A9,I2,1X)') 'Levels 1-', nctls 
    732       ENDIF 
    733  
    734       !----------------------------------------- 
     813      ELSE IF( nctls >= 2 ) THEN ! control surface = model level 
     814         WRITE(clmxl,'(A10,I2,1X)') 'Levels 1 -', nctls 
     815      END IF 
     816 
    735817      ! II.1 Define frequency of output and means 
    736818      ! ----------------------------------------- 
    737  
    738 #if defined key_diainstant 
    739       zsto = nwrite*rdt 
    740       clop ="inst(x)" 
    741 #else 
    742       zsto = rdt 
    743       clop ="ave(x)" 
    744 #endif 
    745       zout = nwrite*rdt 
    746  
    747       IF(lwp) WRITE (numout,*) ' trdmld_ncinit: netCDF initialization' 
     819#  if defined key_diainstant 
     820      IF( .NOT. ln_trdmld_instant ) THEN 
     821         CALL ctl_stop( 'trd_mld : this was never checked. Comment this line to proceed...' ) 
     822      END IF 
     823      zsto = ntrd * rdt 
     824      clop ="inst(only(x))" 
     825#  else 
     826      IF( ln_trdmld_instant ) THEN 
     827         zsto = rdt                 ! inst. diags : we use IOIPSL time averaging 
     828      ELSE 
     829         zsto = ntrd * rdt          ! mean  diags : we DO NOT use any IOIPSL time averaging 
     830      END IF 
     831      clop ="ave(only(x))" 
     832#  endif 
     833      zout = ntrd * rdt 
     834 
     835      IF(lwp) WRITE (numout,*) '                netCDF initialization' 
    748836 
    749837      ! II.2 Compute julian date from starting date of the run 
    750       ! ------------------------ 
    751  
     838      ! ------------------------------------------------------ 
    752839      CALL ymds2ju( nyear, nmonth, nday, 0.e0, zjulian ) 
    753       IF (lwp) WRITE(numout,*)' '   
    754       IF (lwp) WRITE(numout,*)' Date 0 used :',nit000   & 
    755            ,' YEAR ', nyear,' MONTH ', nmonth,' DAY ', nday   & 
    756            ,'Julian day : ', zjulian 
     840      IF(lwp) WRITE(numout,*)' '   
     841      IF(lwp) WRITE(numout,*)'                Date 0 used :',nit000,    & 
     842         &                   ' YEAR ', nyear,' MONTH '      , nmonth,   & 
     843         &                   ' DAY ' , nday, 'Julian day : ', zjulian 
    757844 
    758845 
    759846      ! II.3 Define the T grid trend file (nidtrd) 
    760       ! --------------------------------- 
    761  
    762       CALL dia_nam( clhstnam, nwrite, 'trends' )                  ! filename 
     847      ! ------------------------------------------ 
     848      !-- Define long and short names for the NetCDF output variables 
     849      !       ==> choose them according to trdmld_oce.F90 <== 
     850 
     851      ctrd(jpmld_xad,1) = " Zonal advection"                  ;   ctrd(jpmld_xad,2) = "_xad" 
     852      ctrd(jpmld_yad,1) = " Meridional advection"             ;   ctrd(jpmld_yad,2) = "_yad" 
     853      ctrd(jpmld_zad,1) = " Vertical advection"               ;   ctrd(jpmld_zad,2) = "_zad" 
     854      ctrd(jpmld_ldf,1) = " Lateral diffusion"                ;   ctrd(jpmld_ldf,2) = "_ldf" 
     855      ctrd(jpmld_for,1) = " Forcing"                          ;   ctrd(jpmld_for,2) = "_for" 
     856      ctrd(jpmld_zdf,1) = " Vertical diff. (Kz)"              ;   ctrd(jpmld_zdf,2) = "_zdf" 
     857      ctrd(jpmld_bbc,1) = " Geothermal flux"                  ;   ctrd(jpmld_bbc,2) = "_bbc" 
     858      ctrd(jpmld_bbl,1) = " Adv/diff. Bottom boundary layer"  ;   ctrd(jpmld_bbl,2) = "_bbl" 
     859      ctrd(jpmld_dmp,1) = " Tracer damping"                   ;   ctrd(jpmld_dmp,2) = "_dmp" 
     860      ctrd(jpmld_npc,1) = " Non penetrative convec. adjust."  ;   ctrd(jpmld_npc,2) = "_npc" 
     861      ctrd(jpmld_atf,1) = " Asselin time filter"              ;   ctrd(jpmld_atf,2) = "_atf" 
     862                                                                   
     863      !-- Create a NetCDF file and enter the define mode  
     864      CALL dia_nam( clhstnam, ntrd, 'trends' ) 
    763865      IF(lwp) WRITE(numout,*) ' Name of NETCDF file ', clhstnam 
    764       CALL histbeg( clhstnam, jpi, glamt, jpj, gphit,1, jpi,   &  ! Horizontal grid : glamt and gphit 
    765          &          1, jpj, 0, zjulian, rdt, nh_t, nidtrd, domain_id=nidom ) 
    766  
    767       ! Declare output fields as netCDF variables 
    768  
    769       ! Mixed layer Depth 
    770       CALL histdef( nidtrd, "somlttml", clmxl//"Depth"              , "m"   ,   &  ! hmlp 
    771          &          jpi, jpj, nh_t, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    772  
    773       ! Temperature 
    774       CALL histdef( nidtrd, "somltemp", clmxl//"Temperature"        , "C"   ,   &  ! ??? 
    775          &          jpi, jpj, nh_t, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    776       ! Temperature trends 
    777       CALL histdef( nidtrd, "somlttto", clmxl//"T Total"             , "C/s",   &  ! total 
    778          &          jpi, jpj, nh_t, 1  , 1, 1  , -99 , 32, clop, zout, zout ) 
    779       CALL histdef( nidtrd, "somlttax", clmxl//"T Zonal Advection", "C/s",       & ! i-adv. 
    780          &          jpi, jpj, nh_t, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    781       CALL histdef( nidtrd, "somlttay", clmxl//"T Meridional Advection", "C/s",   & ! j-adv. 
    782          &          jpi, jpj, nh_t, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    783       CALL histdef( nidtrd, "somlttaz", clmxl//"T Vertical Advection", "C/s",   & ! vert. adv. 
    784          &          jpi, jpj, nh_t, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    785       CALL histdef( nidtrd, "somlttdh", clmxl//"T Horizontal Diffusion ", "C/s",   & ! hor. lateral diff. 
    786          &          jpi, jpj, nh_t, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    787       CALL histdef( nidtrd, "somlttfo", clmxl//"T Forcing", "C/s",   & ! forcing 
    788          &          jpi, jpj, nh_t, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    789       CALL histdef( nidtrd, "somlbtdz", clmxl//"T Vertical Diffusion", "C/s",   & ! vert. diff. 
    790          &          jpi, jpj, nh_t, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    791       CALL histdef( nidtrd, "somlbtdt", clmxl//"T dh/dt Entrainment (Residual)", "C/s",   & ! T * dh/dt  
    792          &          jpi, jpj, nh_t, 1  , 1, 1  , -99 , 32, clop, zout, zout ) 
    793       IF( ln_traldf_iso ) THEN 
    794       CALL histdef( nidtrd, "somlbtdv", clmxl//"T Vert. lateral Diffusion","C/s",   & ! vertical diffusion entrainment (ISO) 
    795          &          jpi, jpj, nh_t, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    796       ENDIF 
    797 #if defined key_traldf_eiv 
    798       CALL histdef( nidtrd, "somlgtax", clmxl//"T Zonal EIV Advection", "C/s",   & ! i-adv. (eiv) 
    799          &          jpi, jpj, nh_t, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    800       CALL histdef( nidtrd, "somlgtay", clmxl//"T Meridional EIV Advection", "C/s",   & ! j-adv. (eiv) 
    801          &          jpi, jpj, nh_t, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    802       CALL histdef( nidtrd, "somlgtaz", clmxl//"T Vertical EIV Advection", "C/s",   & ! vert. adv. (eiv) 
    803          &          jpi, jpj, nh_t, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    804       CALL histdef( nidtrd, "somlgtat", clmxl//"T Total EIV Advection", "C/s",   & ! total advection (eiv) 
    805          &          jpi, jpj, nh_t, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    806 #endif 
    807       ! Salinity 
    808       CALL histdef( nidtrd, "somlsalt", clmxl//"Salinity", "PSU",   & ! Mixed-layer salinity 
    809          &          jpi, jpj, nh_t, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    810       ! Salinity trends 
    811       CALL histdef( nidtrd, "somltsto", clmxl//"S Total", "PSU/s",   & ! total  
    812          &          jpi, jpj, nh_t, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    813       CALL histdef( nidtrd, "somltsax", clmxl//"S Zonal Advection", "PSU/s",   & ! i-advection 
    814          &          jpi, jpj, nh_t, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    815       CALL histdef( nidtrd, "somltsay", clmxl//"S Meridional Advection", "PSU/s",   & ! j-advection 
    816          &          jpi, jpj, nh_t, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    817       CALL histdef( nidtrd, "somltsaz", clmxl//"S Vertical Advection", "PSU/s",   & ! vertical advection 
    818          &          jpi, jpj, nh_t, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    819       CALL histdef( nidtrd, "somltsdh", clmxl//"S Horizontal Diffusion ", "PSU/s",   & ! hor. lat. diff. 
    820          &          jpi, jpj, nh_t, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    821       CALL histdef( nidtrd, "somltsfo", clmxl//"S Forcing", "PSU/s",   & ! forcing 
    822          &          jpi, jpj, nh_t, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    823  
    824       CALL histdef( nidtrd, "somlbsdz", clmxl//"S Vertical Diffusion", "PSU/s",   & ! vert. diff. 
    825          &          jpi, jpj, nh_t, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    826       CALL histdef( nidtrd, "somlbsdt", clmxl//"S dh/dt Entrainment (Residual)", "PSU/s",   & ! S * dh/dt  
    827          &          jpi, jpj, nh_t, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    828       IF( ln_traldf_iso ) THEN 
    829       ! vertical diffusion entrainment (ISO) 
    830       CALL histdef( nidtrd, "somlbsdv", clmxl//"S Vertical lateral Diffusion", "PSU/s",   & ! vert. lat. diff. 
    831          &          jpi, jpj, nh_t, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    832       ENDIF 
    833 #if defined key_traldf_eiv 
    834       CALL histdef( nidtrd, "somlgsax", clmxl//"S Zonal EIV Advection", "PSU/s",   & ! i-advection (eiv) 
    835          &          jpi, jpj, nh_t, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    836       CALL histdef( nidtrd, "somlgsay", clmxl//"S Meridional EIV Advection", "PSU/s",   & ! j-advection (eiv) 
    837          &          jpi, jpj, nh_t, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    838       CALL histdef( nidtrd, "somlgsaz", clmxl//"S Vertical EIV Advection", "PSU/s",   & ! vert. adv. (eiv) 
    839          &          jpi, jpj, nh_t, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    840       CALL histdef( nidtrd, "somlgsat", clmxl//"S Total EIV Advection", "PSU/s",   & ! total adv. (eiv) 
    841          &          jpi, jpj, nh_t, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    842 #endif 
     866      CALL histbeg( clhstnam, jpi, glamt, jpj, gphit,                                            & 
     867      &             1, jpi, 1, jpj, 0, zjulian, rdt, nh_t, nidtrd, domain_id=nidom ) 
     868 
     869      !-- Define the ML depth variable 
     870      CALL histdef(nidtrd, "mxl_depth", clmxl//"  Mixed Layer Depth"              , "m",         & 
     871                   jpi, jpj, nh_t, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
     872 
     873      !-- Define physical units 
     874      IF( ucf == 1. ) THEN 
     875         cltu = "degC/s"     ;   clsu = "p.s.u./s" 
     876      ELSEIF ( ucf == 3600.*24.) THEN 
     877         cltu = "degC/day"   ;   clsu = "p.s.u./day" 
     878      ELSE 
     879         cltu = "unknown?"   ;   clsu = "unknown?" 
     880      END IF 
     881 
     882      !-- Define miscellaneous T and S mixed-layer variables  
     883 
     884      IF( jpltrd /= jpmld_atf ) CALL ctl_stop( 'Error : jpltrd /= jpmld_atf' ) ! see below 
     885 
     886      !................................. ( ML temperature ) ................................... 
     887 
     888      CALL histdef(nidtrd, "tml"      , clmxl//" T Mixed Layer Temperature"       ,  "C",        & 
     889                   jpi, jpj, nh_t, 1  , 1, 1  , -99 , 32, clop, zsto, zout )            
     890      CALL histdef(nidtrd, "tml_tot",   clmxl//" T Total trend"                   , cltu,        &  
     891                   jpi, jpj, nh_t, 1  , 1, 1  , -99 , 32, clop, zout, zout )               
     892      CALL histdef(nidtrd, "tml_res",   clmxl//" T dh/dt Entrainment (Resid.)"    , cltu,        &  
     893                   jpi, jpj, nh_t, 1  , 1, 1  , -99 , 32, clop, zout, zout )                    
     894       
     895      DO jl = 1, jpltrd - 1      ! <== only true if jpltrd == jpmld_atf 
     896         CALL histdef(nidtrd, trim("tml"//ctrd(jl,2)), clmxl//" T"//ctrd(jl,1), cltu,            &  
     897                   jpi, jpj, nh_t, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) ! IOIPSL: time mean 
     898      END DO                                                                 ! if zsto=rdt above 
     899       
     900      CALL histdef(nidtrd, trim("tml"//ctrd(jpmld_atf,2)), clmxl//" T"//ctrd(jpmld_atf,1), cltu, &  
     901                   jpi, jpj, nh_t, 1  , 1, 1  , -99 , 32, clop, zout, zout ) ! IOIPSL: NO time mean 
     902       
     903      !.................................. ( ML salinity ) ..................................... 
     904      
     905      CALL histdef(nidtrd, "sml"      , clmxl//" S Mixed Layer Salinity"          , "p.s.u.",       & 
     906                   jpi, jpj, nh_t, 1  , 1, 1  , -99 , 32, clop, zsto, zout )            
     907      CALL histdef(nidtrd, "sml_tot",   clmxl//" S Total trend"                   , clsu,        &  
     908                   jpi, jpj, nh_t, 1  , 1, 1  , -99 , 32, clop, zout, zout )               
     909      CALL histdef(nidtrd, "sml_res",   clmxl//" S dh/dt Entrainment (Resid.)"    , clsu,        &  
     910                   jpi, jpj, nh_t, 1  , 1, 1  , -99 , 32, clop, zout, zout )                    
     911       
     912      DO jl = 1, jpltrd - 1      ! <== only true if jpltrd == jpmld_atf 
     913         CALL histdef(nidtrd, trim("sml"//ctrd(jl,2)), clmxl//" S"//ctrd(jl,1), clsu,            &  
     914                   jpi, jpj, nh_t, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) ! IOIPSL: time mean 
     915      END DO                                                                 ! if zsto=rdt above 
     916       
     917      CALL histdef(nidtrd, trim("sml"//ctrd(jpmld_atf,2)), clmxl//" S"//ctrd(jpmld_atf,1), clsu, &  
     918                   jpi, jpj, nh_t, 1  , 1, 1  , -99 , 32, clop, zout, zout ) ! IOIPSL: NO time mean 
     919 
     920      !-- Leave IOIPSL/NetCDF define mode 
    843921      CALL histend( nidtrd ) 
    844 #endif 
    845  
    846       IF( idebug /= 0 ) THEN 
    847          WRITE(numout,*) ' debuging trd_mld_init: II. done'   
    848          CALL FLUSH(numout) 
    849       ENDIF 
    850  
    851  
    852       END SUBROUTINE trd_mld_init 
     922 
     923#endif        /* key_dimgout */ 
     924   END SUBROUTINE trd_mld_init 
    853925 
    854926#else 
     
    856928   !!   Default option :                                       Empty module 
    857929   !!---------------------------------------------------------------------- 
    858    LOGICAL, PUBLIC, PARAMETER ::   lk_trdmld = .FALSE.   !: momentum trend flag 
    859930CONTAINS 
    860931   SUBROUTINE trd_mld( kt )             ! Empty routine 
  • trunk/NEMO/OPA_SRC/TRD/trdmld_oce.F90

    r247 r503  
    44   !! Ocean trends :   set tracer and momentum trend variables 
    55   !!====================================================================== 
     6   !! History :  9.0  !  04-08  (C. Talandier)  New trends organization 
    67   !!---------------------------------------------------------------------- 
    7    !!  OPA 9.0 , LOCEAN-IPSL (2005)  
    8    !! $Header$  
    9    !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt  
    10    !!---------------------------------------------------------------------- 
    11    !!---------------------------------------------------------------------- 
    12    !! * Modules used 
    138   USE par_oce         ! ocean parameters 
    149 
    1510   IMPLICIT NONE 
    16    PUBLIC 
     11   PRIVATE 
    1712 
    18    INTEGER, PARAMETER ::            &  !: mixed layer trends index 
    19       jpmldxad = 1,   &  !: zonal advection 
    20       jpmldyad = 2,   &  !: meridionnal advection 
    21       jpmldzad = 3,   &  !: vertical advection 
    22       jpmldldf = 4,   &  !: lateral diffusion (horiz. component+Beckman) 
    23       jpmldfor = 5,   &  !: forcing  
    24       jpmldevd = 6,   &  !: entrainment due to vertical diffusion (TKE) 
    25       jpmldzdf = 7,   &  !: explicit vertical part if isopycnal diffusion 
    26       jpmldxei = 8,   &  !: eddy induced zonal advection 
    27       jpmldyei = 9,   &  !: eddy induced meridional advection 
    28       jpmldzei =10       !: eddy induced vertical advection 
     13#if defined key_trdmld 
     14   LOGICAL, PUBLIC, PARAMETER ::   lk_trdmld = .TRUE.    !: ML trend flag 
     15#else 
     16   LOGICAL, PUBLIC, PARAMETER ::   lk_trdmld = .FALSE.   !: ML trend flag 
     17#endif 
     18   !!* mixed layer trends indices 
     19   INTEGER, PARAMETER, PUBLIC ::   jpltrd = 11    !: number of mixed-layer trends arrays 
     20   INTEGER, PARAMETER, PUBLIC ::   jpktrd = jpk   !: max level for mixed-layer trends diag. 
     21   ! 
     22   INTEGER, PUBLIC, PARAMETER ::   jpmld_xad =  1   !:  zonal      \ 
     23   INTEGER, PUBLIC, PARAMETER ::   jpmld_yad =  2   !:  meridonal   > advection 
     24   INTEGER, PUBLIC, PARAMETER ::   jpmld_zad =  3   !:  vertical   / 
     25   INTEGER, PUBLIC, PARAMETER ::   jpmld_ldf =  4   !:  lateral diffusion (geopot. or iso-neutral) 
     26   INTEGER, PUBLIC, PARAMETER ::   jpmld_for =  5   !:  forcing  
     27   INTEGER, PUBLIC, PARAMETER ::   jpmld_zdf =  6   !:  vertical diffusion (TKE) 
     28   INTEGER, PUBLIC, PARAMETER ::   jpmld_bbc =  7   !:  geothermal flux 
     29   INTEGER, PUBLIC, PARAMETER ::   jpmld_bbl =  8   !:  bottom boundary layer (advective/diffusive) 
     30   INTEGER, PUBLIC, PARAMETER ::   jpmld_dmp =  9   !:  internal restoring trend 
     31   INTEGER, PUBLIC, PARAMETER ::   jpmld_npc = 10   !:  non penetrative convective adjustment 
     32   INTEGER, PUBLIC, PARAMETER ::   jpmld_atf = 11   !:  asselin trend 
     33!! INTEGER, PUBLIC, PARAMETER ::   jpmld_xxx = xx   !:  add here any additional trend (add change jpltrd) 
    2934 
    3035#if   defined  key_trdmld   ||   defined key_esopa 
     
    3338   !!---------------------------------------------------------------------- 
    3439 
    35    !! Trends diagnostics parameters 
     40   !! Arrays used for diagnosing mixed-layer trends  
    3641   !!--------------------------------------------------------------------- 
    37    INTEGER, PARAMETER ::            &  !: 
    38 # if defined key_traldf_eiv 
    39       jpltrd = 10,  &  !: number of mixed-layer trends arrays 
    40       jpktrd = jpk     !: max level for mixed-layer trends diag. 
    41 # else 
    42       jpltrd = 7,   &  !: number of mixed-layer trends arrays 
    43       jpktrd = jpk     !: max level for mixed-layer trends diag. 
    44 # endif 
     42   CHARACTER(LEN=80) , PUBLIC :: clname, ctrd(jpltrd+1,2) 
    4543 
     44   INTEGER , PUBLIC, DIMENSION(jpi,jpj)     ::   nmld   !: mixed layer depth indexes  
     45   INTEGER , PUBLIC, DIMENSION(jpi,jpj)     ::   nbol   !: mixed-layer depth indexes when read from file 
     46 
     47   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk) ::   wkx    !: 
     48 
     49   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::  & 
     50      rmld   ,                      & !: mld depth (m) corresponding to nmld 
     51      tml    , sml  ,               & !: \ "now" mixed layer temperature/salinity 
     52      tmlb   , smlb ,               & !: /  and associated "before" fields 
     53      tmlbb  , smlbb,               & !: \  idem, but valid at the 1rst time step of the 
     54      tmlbn  , smlbn,               & !: /  current analysis window 
     55      tmltrdm, smltrdm,             & !: total cumulative trends over the analysis window 
     56      tml_sum,                      & !: mixed layer T, summed over the current analysis period 
     57      tml_sumb,                     & !: idem, but from the previous analysis period 
     58      tmltrd_atf_sumb,              & !: Asselin trends, summed over the previous analysis period 
     59      sml_sum,                      & !:  
     60      sml_sumb,                     & !:    ( idem for salinity ) 
     61      smltrd_atf_sumb,              & !:  
     62      rmld_sum, rmldbn                !: needed to compute the leap-frog time mean of the ML depth 
     63 
     64   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::  & 
     65      tmlatfb, tmlatfn ,            & !: "before" Asselin contribution at begining of the averaging 
     66      smlatfb, smlatfn,             & !: period (i.e. last contrib. from previous such period) and  
     67                                      !: "now" Asselin contribution to the ML temp. & salinity trends 
     68      tmlatfm, smlatfm                !: accumulator for Asselin trends (needed for storage only) 
     69 
     70   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpltrd) ::  & 
     71      tmltrd,                       & !: \ physical contributions to the total trend (for T/S), 
     72      smltrd,                       & !: / cumulated over the current analysis window 
     73      tmltrd_sum,                   & !: sum of these trends over the analysis period 
     74      tmltrd_csum_ln,               & !: now cumulated sum of the trends over the "lower triangle" 
     75      tmltrd_csum_ub,               & !: before (prev. analysis period) cumulated sum over the upper triangle 
     76      smltrd_sum,                   & !:  
     77      smltrd_csum_ln,               & !:    ( idem for salinity ) 
     78      smltrd_csum_ub                  !:  
    4679#endif 
    47   !!====================================================================== 
     80   !!---------------------------------------------------------------------- 
     81   !!  OPA 9.0 , LOCEAN-IPSL (2005)  
     82   !! $Header$  
     83   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
     84   !!====================================================================== 
    4885END MODULE trdmld_oce 
  • trunk/NEMO/OPA_SRC/TRD/trdmod.F90

    r462 r503  
    44   !! Ocean diagnostics:  ocean tracers and dynamic trends 
    55   !!===================================================================== 
     6   !! History :  9.0  !  04-08  (C. Talandier) Original code 
     7   !!                 !  05-04  (C. Deltel)    Add Asselin trend in the ML budget 
     8   !!---------------------------------------------------------------------- 
    69#if  defined key_trdtra || defined key_trddyn || defined key_trdmld || defined key_trdvor || defined key_esopa 
    710   !!---------------------------------------------------------------------- 
    811   !!   trd_mod          : Call the trend to be computed 
    9    !!---------------------------------------------------------------------- 
    10    !! * Modules used 
     12   !!   trd_mod_init     : Initialization step 
     13   !!---------------------------------------------------------------------- 
     14   USE phycst                  ! physical constants 
    1115   USE oce                     ! ocean dynamics and tracers variables 
    1216   USE dom_oce                 ! ocean space and time domain variables 
     17   USE zdf_oce                 ! ocean vertical physics variables 
    1318   USE trdmod_oce              ! ocean variables trends 
     19   USE ldftra_oce              ! ocean active tracers lateral physics 
    1420   USE trdvor                  ! ocean vorticity trends  
    1521   USE trdicp                  ! ocean bassin integral constraints properties 
    1622   USE trdmld                  ! ocean active mixed layer tracers trends  
    17    USE trabbl                  ! bottom boundary layer variables 
    1823   USE in_out_manager          ! I/O manager 
     24   USE taumod                  ! surface ocean stress 
    1925 
    2026   IMPLICIT NONE 
    2127   PRIVATE 
    2228 
    23    !! * Routine accessibility 
    24    PUBLIC trd_mod        ! called by all dynXX or traXX modules 
     29   REAL(wp) ::   r2dt          ! time-step, = 2 rdttra except at nit000 (=rdttra) if neuler=0 
     30 
     31   PUBLIC trd_mod              ! called by all dynXX or traXX modules 
     32   PUBLIC trd_mod_init         ! called by opa.F90 module 
    2533 
    2634   !! * Substitutions 
     
    3038   !!   OPA 9.0 , LOCEAN-IPSL (2005)  
    3139   !! $Header$  
    32    !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt  
     40   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
    3341   !!---------------------------------------------------------------------- 
    3442 
    3543CONTAINS 
    3644 
    37    SUBROUTINE trd_mod(ptrdx, ptrdy, ktrd, ctype, kt) 
     45   SUBROUTINE trd_mod( ptrdx, ptrdy, ktrd, ctype, kt, cnbpas ) 
    3846      !!--------------------------------------------------------------------- 
    3947      !!                  ***  ROUTINE trd_mod  *** 
    4048      !!  
    4149      !! ** Purpose : Dispatch all trends computation, e.g. vorticity, mld or  
    42       !!              integral constrains 
     50      !!              integral constraints 
     51      !!---------------------------------------------------------------------- 
     52      INTEGER, INTENT( in ) ::   kt                                ! time step 
     53      INTEGER, INTENT( in ) ::   ktrd                              ! tracer trend index 
     54      CHARACTER(len=3), INTENT( in ) ::   ctype                    ! momentum or tracers trends type 'DYN'/'TRA' 
     55      CHARACTER(len=3), INTENT( in ), OPTIONAL ::   cnbpas         ! number of passage 
     56      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT( inout ) ::   ptrdx ! Temperature or U trend  
     57      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT( inout ) ::   ptrdy ! Salinity    or V trend 
    4358      !! 
    44       !! ** Method : 
    45       !! 
    46       !! History : 
    47       !!   9.0  !  04-08  (C. Talandier) New trends organization 
    48       !!---------------------------------------------------------------------- 
    49       !! * Modules used 
    50 #if defined key_trabbl_adv 
    51       REAL(wp), DIMENSION(jpi,jpj,jpk) ::  &  ! temporary arrays 
    52          &         zun, zvn 
    53 #else 
    54       USE oce                , zun => un,  &  ! When no bbl, zun == un 
    55          &                     zvn => vn      ! When no bbl, zvn == vn 
    56 #endif 
    57  
    58       !! * Arguments 
    59       REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT( inout ) ::   & 
    60          ptrdx,                      &   ! Temperature or U trend  
    61          ptrdy                           ! Salinity    or V trend 
    62  
    63       INTEGER, INTENT( in ) ::   & 
    64          kt  ,                   & ! time step 
    65          ktrd                      ! tracer trend index 
    66  
    67       CHARACTER(len=3), INTENT( in ) ::   & 
    68          ctype                             ! momentum or tracers trends type 
    69          !                                 ! 'DYN' or 'TRA' 
    70  
    71       !! * Local save 
    72       REAL(wp), DIMENSION(jpi,jpj), SAVE ::   & 
    73          zbtr2 
    74  
    75       !! * Local declarations 
    76       INTEGER ::   ji, jj, jk    ! loop indices 
    77       REAL(wp) ::   & 
    78          zbtr,            &  ! temporary scalars 
    79          zfui, zfvj,           &  !    "         " 
    80          zfui1, zfvj1             !    "         " 
    81       REAL(wp), DIMENSION(jpi,jpj) ::   & 
    82          z2dx, z2dy                        ! workspace arrays 
    83       REAL(wp), DIMENSION(jpi,jpj,jpk) ::   & 
    84          z3dx, z3dy                            ! workspace arrays 
    85       !!---------------------------------------------------------------------- 
    86  
    87       ! Initialization of workspace arrays 
    88       z3dx(:,:,:) = 0.e0 
    89       z3dy(:,:,:) = 0.e0 
    90       z2dx(:,:) = 0.e0 
    91       z2dy(:,:) = 0.e0 
     59      INTEGER ::   ji, ikbu, ikbum1 
     60      INTEGER ::   jj, ikbv, ikbvm1 
     61      CHARACTER(len=3) ::   clpas                                  ! number of passage 
     62      REAL(wp) ::   zua, zva                                       ! scalars 
     63      REAL(wp), DIMENSION(jpi,jpj) ::   ztswu, ztswv               ! 2D workspace 
     64      REAL(wp), DIMENSION(jpi,jpj) ::   ztbfu, ztbfv               ! 2D workspace 
     65      REAL(wp), DIMENSION(jpi,jpj) ::   z2dx, z2dy                 ! workspace arrays 
     66      !!---------------------------------------------------------------------- 
     67 
     68      z2dx(:,:)   = 0.e0   ;   z2dy(:,:)   = 0.e0                  ! initialization of workspace arrays 
     69 
     70      ! Control of optional arguments 
     71      clpas = 'fst' 
     72      IF( PRESENT(cnbpas) )  clpas = cnbpas 
     73 
     74      IF( neuler == 0 .AND. kt == nit000    ) THEN   ;   r2dt =      rdt      ! = rdtra (restarting with Euler time stepping) 
     75      ELSEIF(               kt <= nit000 + 1) THEN   ;   r2dt = 2. * rdt      ! = 2 rdttra (leapfrog) 
     76      ENDIF 
    9277 
    9378      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
    94       ! I. Bassin averaged properties for momentum and/or tracers trends 
     79      ! I. Integral Constraints Properties for momentum and/or tracers trends 
    9580      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    9681 
    9782      IF( ( mod(kt,ntrd) == 0 .OR. kt == nit000 .OR. kt == nitend) )   THEN 
    98  
    99          ! Active tracers trends  
    100          IF( lk_trdtra .AND. ctype == 'TRA' )   THEN 
    101  
    102             IF( ktrd == jpttdnsr )   THEN 
    103                ! 2D array tracers surface forcing 
    104                z2dx(:,:) = ptrdx(:,:,1) 
    105                z2dy(:,:) = ptrdy(:,:,1) 
    106  
    107                CALL trd(z2dx, z2dy, ktrd, ctype) 
    108             ELSE 
    109                ! 3D array 
    110                CALL trd(ptrdx, ptrdy, ktrd, ctype) 
    111             ENDIF 
    112  
    113          ENDIF 
    114  
    115          ! Momentum trends  
    116          IF( lk_trddyn .AND. ctype == 'DYN' )   THEN 
    117  
    118             IF( ktrd == jpdtdswf .OR. ktrd == jpdtdbfr )   THEN 
    119                ! momentum surface forcing/bottom friction  2D array 
    120                z2dx(:,:) = ptrdx(:,:,1) 
    121                z2dy(:,:) = ptrdy(:,:,1) 
    122  
    123                CALL trd(z2dx, z2dy, ktrd, ctype) 
    124             ELSE 
    125                ! 3D array 
    126                CALL trd(ptrdx, ptrdy, ktrd, ctype) 
    127             ENDIF 
    128  
    129          ENDIF 
    130  
    131       ENDIF 
     83         ! 
     84         IF( lk_trdtra .AND. ctype == 'TRA' )   THEN       ! active tracer trends 
     85            SELECT CASE ( ktrd ) 
     86            CASE ( jptra_trd_ldf )   ;   CALL trd_icp( ptrdx, ptrdy, jpicpt_ldf, ctype )   ! lateral diff 
     87            CASE ( jptra_trd_zdf )   ;   CALL trd_icp( ptrdx, ptrdy, jpicpt_zdf, ctype )   ! vertical diff (Kz) 
     88            CASE ( jptra_trd_bbc )   ;   CALL trd_icp( ptrdx, ptrdy, jpicpt_bbc, ctype )   ! bottom boundary cond 
     89            CASE ( jptra_trd_bbl )   ;   CALL trd_icp( ptrdx, ptrdy, jpicpt_bbl, ctype )   ! bottom boundary layer 
     90            CASE ( jptra_trd_npc )   ;   CALL trd_icp( ptrdx, ptrdy, jpicpt_npc, ctype )   ! static instability mixing 
     91            CASE ( jptra_trd_dmp )   ;   CALL trd_icp( ptrdx, ptrdy, jpicpt_dmp, ctype )   ! damping 
     92            CASE ( jptra_trd_qsr )   ;   CALL trd_icp( ptrdx, ptrdy, jpicpt_qsr, ctype )   ! penetrative solar radiat. 
     93            CASE ( jptra_trd_nsr )    
     94               z2dx(:,:) = ptrdx(:,:,1)   ;   z2dy(:,:) = ptrdy(:,:,1) 
     95               CALL trd_icp( z2dx, z2dy, jpicpt_nsr, ctype )                               ! non solar radiation 
     96            CASE ( jptra_trd_xad )   ;   CALL trd_icp( ptrdx, ptrdy, jpicpt_xad, ctype )   ! x- horiz adv 
     97            CASE ( jptra_trd_yad )   ;   CALL trd_icp( ptrdx, ptrdy, jpicpt_yad, ctype )   ! y- horiz adv 
     98            CASE ( jptra_trd_zad )                                                         ! z- vertical adv  
     99               CALL trd_icp( ptrdx, ptrdy, jpicpt_zad, ctype, clpas )    
     100               ! compute the surface flux condition wn(:,:,1)*tn(:,:,1)                                                                    
     101               z2dx(:,:) = wn(:,:,1)*tn(:,:,1)/fse3t(:,:,1)    
     102               z2dy(:,:) = wn(:,:,1)*sn(:,:,1)/fse3t(:,:,1) 
     103               CALL trd_icp( z2dx , z2dy , jpicpt_zl1, ctype )                             ! 1st z- vertical adv  
     104            END SELECT 
     105         END IF 
     106 
     107         IF( lk_trddyn .AND. ctype == 'DYN' )   THEN       ! momentum trends  
     108            ! 
     109            SELECT CASE ( ktrd ) 
     110            CASE ( jpdyn_trd_hpg )   ;   CALL trd_icp( ptrdx, ptrdy, jpicpd_hpg, ctype )   ! hydrost. pressure grad 
     111            CASE ( jpdyn_trd_keg )   ;   CALL trd_icp( ptrdx, ptrdy, jpicpd_keg, ctype )   ! KE gradient  
     112            CASE ( jpdyn_trd_rvo )   ;   CALL trd_icp( ptrdx, ptrdy, jpicpd_rvo, ctype )   ! relative vorticity  
     113            CASE ( jpdyn_trd_pvo )   ;   CALL trd_icp( ptrdx, ptrdy, jpicpd_pvo, ctype )   ! planetary vorticity 
     114            CASE ( jpdyn_trd_ldf )   ;   CALL trd_icp( ptrdx, ptrdy, jpicpd_ldf, ctype )   ! lateral diffusion  
     115            CASE ( jpdyn_trd_zad )   ;   CALL trd_icp( ptrdx, ptrdy, jpicpd_zad, ctype )   ! vertical advection  
     116            CASE ( jpdyn_trd_spg )   ;   CALL trd_icp( ptrdx, ptrdy, jpicpd_spg, ctype )   ! surface pressure grad. 
     117            CASE ( jpdyn_trd_dat )   ;   CALL trd_icp( ptrdx, ptrdy, jpicpd_dat, ctype )   ! damping term 
     118            CASE ( jpdyn_trd_zdf )                                                         ! vertical diffusion  
     119               ! subtract surface forcing/bottom friction trends  
     120               ! from vertical diffusive momentum trends 
     121               ztswu(:,:) = 0.e0   ;   ztswv(:,:) = 0.e0 
     122               ztbfu(:,:) = 0.e0   ;   ztbfv(:,:) = 0.e0   
     123               DO jj = 2, jpjm1    
     124                  DO ji = fs_2, fs_jpim1   ! vector opt. 
     125                     ! save the surface forcing momentum fluxes 
     126                     ztswu(ji,jj) = taux(ji,jj) / ( fse3u(ji,jj,1)*rau0 ) 
     127                     ztswv(ji,jj) = tauy(ji,jj) / ( fse3v(ji,jj,1)*rau0 ) 
     128                     ! save bottom friction momentum fluxes 
     129                     ikbu   = MIN( mbathy(ji+1,jj  ), mbathy(ji,jj) ) 
     130                     ikbv   = MIN( mbathy(ji  ,jj+1), mbathy(ji,jj) ) 
     131                     ikbum1 = MAX( ikbu-1, 1 ) 
     132                     ikbvm1 = MAX( ikbv-1, 1 ) 
     133                     zua = ua(ji,jj,ikbum1) * r2dt + ub(ji,jj,ikbum1) 
     134                     zva = va(ji,jj,ikbvm1) * r2dt + vb(ji,jj,ikbvm1) 
     135                     ztbfu(ji,jj) = - avmu(ji,jj,ikbu) * zua / ( fse3u(ji,jj,ikbum1)*fse3uw(ji,jj,ikbu) ) 
     136                     ztbfv(ji,jj) = - avmv(ji,jj,ikbv) * zva / ( fse3v(ji,jj,ikbvm1)*fse3vw(ji,jj,ikbv) ) 
     137                     ! 
     138                     ptrdx(ji,jj,1     ) = ptrdx(ji,jj,1     ) - ztswu(ji,jj) 
     139                     ptrdy(ji,jj,1     ) = ptrdy(ji,jj,1     ) - ztswv(ji,jj) 
     140                     ptrdx(ji,jj,ikbum1) = ptrdx(ji,jj,ikbum1) - ztbfu(ji,jj) 
     141                     ptrdy(ji,jj,ikbvm1) = ptrdy(ji,jj,ikbvm1) - ztbfv(ji,jj) 
     142                  END DO 
     143               END DO 
     144               ! 
     145               CALL trd_icp( ptrdx, ptrdy, jpicpd_zdf, ctype )    
     146               CALL trd_icp( ztswu, ztswv, jpicpd_swf, ctype )                               ! wind stress forcing term 
     147               CALL trd_icp( ztbfu, ztbfv, jpicpd_bfr, ctype )                               ! bottom friction term 
     148            END SELECT 
     149            ! 
     150         END IF 
     151         ! 
     152      END IF 
    132153 
    133154      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
     
    136157 
    137158      IF( lk_trdvor .AND. ctype == 'DYN' )   THEN 
    138  
    139          SELECT CASE ( ktrd ) 
    140  
    141          ! Pressure Gradient trend 
    142          CASE ( jpdtdhpg )       
    143             CALL trd_vor_zint(ptrdx, ptrdy, jpvorprg) 
    144  
    145          ! KE Gradient trend 
    146          CASE ( jpdtdkeg )       
    147             CALL trd_vor_zint(ptrdx, ptrdy, jpvorkeg) 
    148  
    149          ! Relative Vorticity trend 
    150          CASE ( jpdtdrvo )       
    151             CALL trd_vor_zint(ptrdx, ptrdy, jpvorrvo) 
    152  
    153          ! Planetary Vorticity Term trend 
    154          CASE ( jpdtdpvo )       
    155             CALL trd_vor_zint(ptrdx, ptrdy, jpvorpvo) 
    156  
    157          ! Horizontal Diffusion trend 
    158          CASE ( jpdtdldf )       
    159             CALL trd_vor_zint(ptrdx, ptrdy, jpvorldf) 
    160  
    161          ! Vertical Advection trend 
    162          CASE ( jpdtdzad )       
    163             CALL trd_vor_zint(ptrdx, ptrdy, jpvorzad) 
    164  
    165          ! Vertical Diffusion trend 
    166          CASE ( jpdtdzdf )       
    167             CALL trd_vor_zint(ptrdx, ptrdy, jpvorzdf) 
    168  
    169          ! Surface Pressure Grad. trend 
    170          CASE ( jpdtdspg )       
    171             CALL trd_vor_zint(ptrdx, ptrdy, jpvorspg) 
    172  
    173          ! Beta V trend  
    174          CASE ( jpdtddat )       
    175             CALL trd_vor_zint(ptrdx, ptrdy, jpvorbev) 
    176  
    177          ! Wind stress forcing term 
    178          CASE ( jpdtdswf )       
    179             z2dx(:,:) = ptrdx(:,:,1) 
    180             z2dy(:,:) = ptrdy(:,:,1) 
    181  
    182             CALL trd_vor_zint(z2dx, z2dy, jpvorswf) 
    183  
    184          ! Bottom friction term 
    185          CASE ( jpdtdbfr )       
    186             z2dx(:,:) = ptrdx(:,:,1) 
    187             z2dy(:,:) = ptrdy(:,:,1) 
    188  
    189             CALL trd_vor_zint(z2dx, z2dy, jpvorbfr) 
    190  
     159         ! 
     160         SELECT CASE ( ktrd )  
     161         CASE ( jpdyn_trd_hpg )   ;   CALL trd_vor_zint( ptrdx, ptrdy, jpvor_prg )   ! Hydrostatique Pressure Gradient  
     162         CASE ( jpdyn_trd_keg )   ;   CALL trd_vor_zint( ptrdx, ptrdy, jpvor_keg )   ! KE Gradient  
     163         CASE ( jpdyn_trd_rvo )   ;   CALL trd_vor_zint( ptrdx, ptrdy, jpvor_rvo )   ! Relative Vorticity  
     164         CASE ( jpdyn_trd_pvo )   ;   CALL trd_vor_zint( ptrdx, ptrdy, jpvor_pvo )   ! Planetary Vorticity Term  
     165         CASE ( jpdyn_trd_ldf )   ;   CALL trd_vor_zint( ptrdx, ptrdy, jpvor_ldf )   ! Horizontal Diffusion  
     166         CASE ( jpdyn_trd_zad )   ;   CALL trd_vor_zint( ptrdx, ptrdy, jpvor_zad )   ! Vertical Advection  
     167         CASE ( jpdyn_trd_spg )   ;   CALL trd_vor_zint( ptrdx, ptrdy, jpvor_spg )   ! Surface Pressure Grad.  
     168         CASE ( jpdyn_trd_dat )   ;   CALL trd_vor_zint( ptrdx, ptrdy, jpvor_bev )   ! Beta V   
     169         CASE ( jpdyn_trd_zdf )                                                      ! Vertical Diffusion  
     170            ! subtract surface forcing/bottom friction trends  
     171            ! from vertical diffusive momentum trends 
     172            ztswu(:,:) = 0.e0   ;   ztswv(:,:) = 0.e0 
     173            ztbfu(:,:) = 0.e0   ;   ztbfv(:,:) = 0.e0   
     174            DO jj = 2, jpjm1    
     175               DO ji = fs_2, fs_jpim1   ! vector opt. 
     176                  ! save the surface forcing momentum fluxes 
     177                  ztswu(ji,jj) = taux(ji,jj) / ( fse3u(ji,jj,1)*rau0 ) 
     178                  ztswv(ji,jj) = tauy(ji,jj) / ( fse3v(ji,jj,1)*rau0 ) 
     179                  ! save bottom friction momentum fluxes 
     180                  ikbu   = MIN( mbathy(ji+1,jj  ), mbathy(ji,jj) ) 
     181                  ikbv   = MIN( mbathy(ji  ,jj+1), mbathy(ji,jj) ) 
     182                  ikbum1 = MAX( ikbu-1, 1 ) 
     183                  ikbvm1 = MAX( ikbv-1, 1 ) 
     184                  zua = ua(ji,jj,ikbum1) * r2dt + ub(ji,jj,ikbum1) 
     185                  zva = va(ji,jj,ikbvm1) * r2dt + vb(ji,jj,ikbvm1) 
     186                  ztbfu(ji,jj) = - avmu(ji,jj,ikbu) * zua / ( fse3u(ji,jj,ikbum1)*fse3uw(ji,jj,ikbu) ) 
     187                  ztbfv(ji,jj) = - avmv(ji,jj,ikbv) * zva / ( fse3v(ji,jj,ikbvm1)*fse3vw(ji,jj,ikbv) ) 
     188                  ! 
     189                  ptrdx(ji,jj,1     ) = ptrdx(ji,jj,1     ) - ztswu(ji,jj) 
     190                  ptrdx(ji,jj,ikbum1) = ptrdx(ji,jj,ikbum1) - ztbfu(ji,jj) 
     191                  ptrdy(ji,jj,1     ) = ptrdy(ji,jj,1     ) - ztswv(ji,jj) 
     192                  ptrdy(ji,jj,ikbvm1) = ptrdy(ji,jj,ikbvm1) - ztbfv(ji,jj) 
     193               END DO 
     194            END DO 
     195            ! 
     196            CALL trd_vor_zint( ptrdx, ptrdy, jpvor_zdf )    
     197            CALL trd_vor_zint( ztswu, ztswv, jpvor_swf )                               ! Wind stress forcing term 
     198            CALL trd_vor_zint( ztbfu, ztbfv, jpvor_bfr )                               ! Bottom friction term 
    191199         END SELECT 
    192  
     200         ! 
    193201      ENDIF 
    194202 
    195203      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
    196       ! III. Mixed layer trends 
     204      ! III. Mixed layer trends for active tracers 
    197205      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    198206 
    199207      IF( lk_trdmld .AND. ctype == 'TRA' )   THEN 
    200208          
     209         !----------------------------------------------------------------------------------------------- 
     210         ! W.A.R.N.I.N.G : 
     211         ! jptra_trd_ldf : called by traldf.F90 
     212         !                 at this stage we store: 
     213         !                  - the lateral geopotential diffusion (here, lateral = horizontal) 
     214         !                  - and the iso-neutral diffusion if activated  
     215         ! jptra_trd_zdf : called by trazdf.F90 
     216         !                 * in case of purely vertical diffusion (and not iso-neutral), 
     217         !                   we do not need to store the corresponding trend here, since it 
     218         !                   is recomputed later (at the basis of the ML, see trd_mld) 
     219         !                 * else (iso-neutral case) we store the vertical diffusion component in the  
     220         !                   lateral trend including the K_z contrib, which will be removed later (see trd_mld) 
     221         !----------------------------------------------------------------------------------------------- 
     222 
    201223         SELECT CASE ( ktrd ) 
    202  
    203          ! horizontal advection trends 
    204          CASE ( jpttdlad )       
    205  
    206 #if defined key_trabbl_adv 
    207             ! Advective bottom boundary layer  
    208             ! ------------------------------- 
    209             zun(:,:,:) = un(:,:,:) - u_bbl(:,:,:) 
    210             zvn(:,:,:) = vn(:,:,:) - v_bbl(:,:,:) 
    211 #endif 
    212             IF( kt == nit000 )   zbtr2(:,:) = 1. / ( e1t(:,:) * e2t(:,:) ) 
    213  
    214             SELECT CASE ( l_adv ) 
    215  
    216             CASE ( 'ce2' ) 
    217  
    218                ! Split horizontal trends into i- and j- compnents for trdmld case  
    219                ! ---------------------------------------------------------------- 
    220  
    221                ! i- advective trend computed as Uh gradh(T) 
    222                DO jk = 1, jpkm1 
    223                   DO jj = 2, jpjm1 
    224                      DO ji = fs_2, fs_jpim1   ! vector opt. 
    225 # if defined key_zco 
    226                         zbtr = zbtr2(ji,jj) 
    227                         zfui = 0.5 * e2u(ji  ,jj) * zun(ji,  jj,jk) 
    228                         zfui1= 0.5 * e2u(ji-1,jj) * zun(ji-1,jj,jk) 
    229 # else          
    230                         zbtr = zbtr2(ji,jj) / fse3t(ji,jj,jk) 
    231                         zfui = 0.5 * e2u(ji  ,jj) * fse3u(ji,  jj,jk) * zun(ji,  jj,jk) 
    232                         zfui1= 0.5 * e2u(ji-1,jj) * fse3u(ji-1,jj,jk) * zun(ji-1,jj,jk) 
    233 # endif 
    234                         ! save i- advective trend  
    235                         z3dx(ji,jj,jk) = - zbtr * ( zfui  * ( tn(ji+1,jj,jk) - tn(ji  ,jj,jk) )    & 
    236                             &                     + zfui1 * ( tn(ji  ,jj,jk) - tn(ji-1,jj,jk) ) ) 
    237                         z3dy(ji,jj,jk) = - zbtr * ( zfui  * ( sn(ji+1,jj,jk) - sn(ji  ,jj,jk) )    & 
    238                             &                     + zfui1 * ( sn(ji  ,jj,jk) - sn(ji-1,jj,jk) ) ) 
    239                      END DO 
    240                   END DO 
    241                END DO 
    242  
    243                ! save the i- horizontal trends for diagnostic 
    244                CALL trd_mld_zint(z3dx, z3dy, jpmldxad, '3D') 
    245  
    246                ! j- advective trend computed as Uh gradh(T) 
    247                DO jk = 1, jpkm1 
    248                   DO jj = 2, jpjm1 
    249                      DO ji = fs_2, fs_jpim1   ! vector opt. 
    250 # if defined key_zco 
    251                         zbtr = zbtr2(ji,jj) 
    252                         zfvj = 0.5 * e1v(ji,jj  ) * zvn(ji,jj  ,jk) 
    253                         zfvj1= 0.5 * e1v(ji,jj-1) * zvn(ji,jj-1,jk) 
    254 # else          
    255                         zbtr = zbtr2(ji,jj) / fse3t(ji,jj,jk) 
    256                         zfvj = 0.5 * e1v(ji,jj  ) * fse3v(ji,jj  ,jk) * zvn(ji,jj  ,jk) 
    257                         zfvj1= 0.5 * e1v(ji,jj-1) * fse3v(ji,jj-1,jk) * zvn(ji,jj-1,jk) 
    258 # endif 
    259                         ! save j- advective trend  
    260                         z3dx(ji,jj,jk) = - zbtr * ( zfvj  * ( tn(ji,jj+1,jk) - tn(ji,jj  ,jk) )   & 
    261                             &                     + zfvj1 * ( tn(ji,jj  ,jk) - tn(ji,jj-1,jk) ) ) 
    262                         z3dy(ji,jj,jk) = - zbtr * ( zfvj  * ( sn(ji,jj+1,jk) - sn(ji,jj  ,jk) )   & 
    263                             &                     + zfvj1 * ( sn(ji,jj  ,jk) - sn(ji,jj-1,jk) ) ) 
    264                      END DO 
    265                   END DO 
    266                END DO 
    267  
    268                ! save the j- horizontal trend for diagnostic 
    269                CALL trd_mld_zint(z3dx, z3dy, jpmldyad, '3D') 
    270  
    271             CASE ( 'tvd' ) 
    272  
    273                ! Recompute the horizontal advection term Div(Uh.T) term  
    274                z3dx(:,:,:) = ptrdx(:,:,:) - tn(:,:,:) * hdivn(:,:,:) 
    275                z3dy(:,:,:) = ptrdy(:,:,:) - sn(:,:,:) * hdivn(:,:,:) 
    276  
    277                ! Deduce the i- horizontal advection in substracting the j- one. 
    278                ! tladj()/sladj() are computed in traadv_tvd.F90 module 
    279                z3dx(:,:,:) = z3dx(:,:,:) - tladj(:,:,:) 
    280                z3dy(:,:,:) = z3dy(:,:,:) - sladj(:,:,:) 
    281  
    282                DO jk = 1, jpkm1 
    283                   DO jj = 2, jpjm1 
    284                      DO ji = fs_2, fs_jpim1 
    285                         zbtr = zbtr2(ji,jj) / fse3t(ji,jj,jk) 
    286  
    287                         ! Compute the zonal et meridional divergence 
    288                         zfui = e2u(ji  ,jj) * fse3u(ji  ,jj,jk) * zun(ji  ,jj,jk)  & 
    289                              - e2u(ji-1,jj) * fse3u(ji-1,jj,jk) * zun(ji-1,jj,jk) 
    290                         zfvj = e1v(ji,jj  ) * fse3v(ji,jj  ,jk) * zvn(ji,jj  ,jk)  & 
    291                              - e1v(ji,jj-1) * fse3v(ji,jj-1,jk) * zvn(ji,jj-1,jk) 
    292  
    293                         ! i- advective trend computed as U gradx(T/S) 
    294                         z3dx(ji,jj,jk) = z3dx(ji,jj,jk) + tn(ji,jj,jk) * zfui * zbtr 
    295                         z3dy(ji,jj,jk) = z3dy(ji,jj,jk) + sn(ji,jj,jk) * zfui * zbtr 
    296  
    297                         ! j- advective trend computed as V grady(T/S) 
    298                         tladj(ji,jj,jk) = tladj(ji,jj,jk) + tn(ji,jj,jk) * zfvj * zbtr 
    299                         sladj(ji,jj,jk) = sladj(ji,jj,jk) + sn(ji,jj,jk) * zfvj * zbtr 
    300  
    301                      END DO 
    302                   END DO 
    303                END DO 
    304  
    305                ! save the i- horizontal trend for diagnostic 
    306                CALL trd_mld_zint(z3dx, z3dy, jpmldxad, '3D') 
    307  
    308                ! save the j- horizontal trend for diagnostic 
    309                CALL trd_mld_zint(tladj, sladi, jpmldyad, '3D') 
    310  
    311             CASE ( 'mus', 'mu2' ) 
    312  
    313                !  Split horizontal trends in i- and j- direction for trdmld case  
    314                ! ---------------------------------------------------------------- 
    315  
    316                ! i- advective trend computed as U gradx(T/S) 
    317                DO jk = 1, jpkm1 
    318                   DO jj = 2, jpjm1       
    319                      DO ji = fs_2, fs_jpim1   ! vector opt. 
    320 # if defined key_zco 
    321                         zbtr = zbtr2(ji,jj) 
    322                         zfui = e2u(ji  ,jj) * zun(ji,  jj,jk)   & 
    323                            & - e2u(ji-1,jj) * zun(ji-1,jj,jk) 
    324 # else       
    325                         zbtr = zbtr2(ji,jj) / fse3t(ji,jj,jk) 
    326                         zfui =  e2u(ji  ,jj) * fse3u(ji,  jj,jk) * zun(ji,  jj,jk)   & 
    327                            & -  e2u(ji-1,jj) * fse3u(ji-1,jj,jk) * zun(ji-1,jj,jk) 
    328 # endif 
    329                         ! save i- advective trend  
    330                         z3dx(ji,jj,jk) = - zbtr * ( tladi(ji,jj,jk) - tladi(ji-1,jj,jk) )   & 
    331                             &                      + tn(ji,jj,jk) * zfui * zbtr 
    332                         z3dy(ji,jj,jk) = - zbtr * ( sladi(ji,jj,jk) - sladi(ji-1,jj,jk) )  & 
    333                             &                      + sn(ji,jj,jk) * zfui * zbtr 
    334                      END DO 
    335                   END DO 
    336                END DO         
    337  
    338                ! save the i- horizontal trends for diagnostic 
    339                CALL trd_mld_zint(z3dx, z3dy, jpmldxad, '3D') 
    340  
    341                ! j- advective trend computed as V grady(T/S) 
    342                DO jk = 1, jpkm1 
    343                   DO jj = 2, jpjm1       
    344                      DO ji = fs_2, fs_jpim1   ! vector opt. 
    345 # if defined key_zco 
    346                         zbtr = zbtr2(ji,jj) 
    347                         zfvj = e1v(ji,jj  ) * zvn(ji,jj  ,jk)   & 
    348                            & - e1v(ji,jj-1) * zvn(ji,jj-1,jk) 
    349 # else       
    350                         zbtr = zbtr2(ji,jj) / fse3t(ji,jj,jk) 
    351                         zfvj =  e1v(ji,jj  ) * fse3v(ji,jj  ,jk) * zvn(ji,jj  ,jk)   & 
    352                            & -  e1v(ji,jj-1) * fse3v(ji,jj-1,jk) * zvn(ji,jj-1,jk) 
    353 # endif 
    354                         ! save j- advective trend  
    355                         z3dx(ji,jj,jk) =  - zbtr * ( tladj(ji,jj,jk) - tladj(ji,jj-1,jk) )   & 
    356                             &                       + tn(ji,jj,jk) * zfvj * zbtr 
    357                         z3dy(ji,jj,jk) =  - zbtr * ( sladj(ji,jj,jk) - sladj(ji,jj-1,jk) )   & 
    358                             &                       + sn(ji,jj,jk) * zfvj * zbtr 
    359                      END DO 
    360                   END DO 
    361                END DO         
    362  
    363                ! save the j- horizontal trends for diagnostic 
    364                CALL trd_mld_zint(z3dx, z3dy, jpmldyad, '3D') 
    365  
    366             END SELECT 
    367  
    368          ! vertical advection trends 
    369          CASE ( jpttdzad )       
    370             CALL trd_mld_zint(ptrdx, ptrdy, jpmldzad, '3D') 
    371  
    372          ! lateral diffusion trends 
    373          CASE ( jpttdldf )       
    374             CALL trd_mld_zint(ptrdx, ptrdy, jpmldldf, '3D') 
    375 # if defined key_traldf_eiv 
    376             ! Save the i- and j- eddy induce velocity trends 
    377             CALL trd_mld_zint(tladi, sladi, jpmldxei, '3D') 
    378             CALL trd_mld_zint(tladj, sladj, jpmldyei, '3D') 
    379 # endif 
    380             IF( lk_trabbl_dif )   THEN 
    381                z3dx(:,:,:) = 0.e0 
    382                z3dy(:,:,:) = 0.e0 
    383                z3dx(:,:,1) = tldfbbl(:,:) 
    384                z3dy(:,:,1) = sldfbbl(:,:) 
    385                CALL trd_mld_zint(z3dx, z3dy, jpmldldf, '2D') 
    386             ENDIF 
    387  
    388          ! vertical diffusion trends 
    389          CASE ( jpttdzdf )       
    390             CALL trd_mld_zint(ptrdx, ptrdy, jpmldzdf, '3D') 
    391  
    392          ! vertical diffusion trends 
    393          CASE ( jpttddoe )       
    394             CALL trd_mld_zint(ptrdx, ptrdy, jpmldzei, '3D') 
    395  
    396          ! penetrative solar radiation trends 
    397          CASE ( jpttdqsr )       
    398             CALL trd_mld_zint(ptrdx, ptrdy, jpmldfor, '3D') 
    399  
    400          ! non penetrative solar radiation trends 
    401          CASE ( jpttdnsr ) 
    402             ptrdx(:,:,2:jpk) = 0.e0 
    403             ptrdy(:,:,2:jpk) = 0.e0 
    404             CALL trd_mld_zint(ptrdx, ptrdy, jpmldfor, '2D') 
    405  
    406          END SELECT    
     224         CASE ( jptra_trd_xad )   ;   CALL trd_mld_zint( ptrdx, ptrdy, jpmld_xad, '3D' )   ! merid. advection 
     225         CASE ( jptra_trd_yad )   ;   CALL trd_mld_zint( ptrdx, ptrdy, jpmld_yad, '3D' )   ! zonal  advection 
     226         CASE ( jptra_trd_zad )   ;   CALL trd_mld_zint( ptrdx, ptrdy, jpmld_zad, '3D' )   ! vertical advection 
     227         CASE ( jptra_trd_ldf )   ;   CALL trd_mld_zint( ptrdx, ptrdy, jpmld_ldf, '3D' )   ! lateral diffusive 
     228         CASE ( jptra_trd_bbl )   ;   CALL trd_mld_zint( ptrdx, ptrdy, jpmld_bbl, '3D' )   ! bottom boundary layer 
     229         CASE ( jptra_trd_zdf ) 
     230            IF( ln_traldf_iso )       CALL trd_mld_zint( ptrdx, ptrdy, jpmld_ldf, '3D' )   ! vertical diffusion (K_z) 
     231         CASE ( jptra_trd_dmp )   ;   CALL trd_mld_zint( ptrdx, ptrdy, jpmld_dmp, '3D' )   ! internal 3D restoring (tradmp) 
     232         CASE ( jptra_trd_qsr )   ;   CALL trd_mld_zint( ptrdx, ptrdy, jpmld_for, '3D' )   ! air-sea : penetrative sol radiat 
     233         CASE ( jptra_trd_nsr ) 
     234            ptrdx(:,:,2:jpk) = 0.e0   ;   ptrdy(:,:,2:jpk) = 0.e0 
     235            CALL trd_mld_zint( ptrdx, ptrdy, jpmld_for, '2D' )                             ! air-sea : non penetr sol radiat 
     236         CASE ( jptra_trd_bbc )   ;   CALL trd_mld_zint( ptrdx, ptrdy, jpmld_bbc, '3D' )   ! bottom bound cond (geoth flux) 
     237         CASE ( jptra_trd_atf )   ;   CALL trd_mld_zint( ptrdx, ptrdy, jpmld_atf, '3D' )   ! asselin numerical 
     238         CASE ( jptra_trd_npc )   ;   CALL trd_mld_zint( ptrdx, ptrdy, jpmld_npc, '3D' )   ! non penetr convect adjustment 
     239         END SELECT 
    407240 
    408241      ENDIF 
    409  
    410242 
    411243   END SUBROUTINE trd_mod 
     
    434266#   endif 
    435267 
     268   SUBROUTINE trd_mod_init 
     269      !!---------------------------------------------------------------------- 
     270      !!                  ***  ROUTINE trd_mod_init  *** 
     271      !!  
     272      !! ** Purpose :   Initialization of activated trends 
     273      !!---------------------------------------------------------------------- 
     274      USE in_out_manager          ! I/O manager 
     275 
     276      NAMELIST/namtrd/ ntrd, nctls, ln_trdmld_restart, ucf, ln_trdmld_instant 
     277      !!---------------------------------------------------------------------- 
     278 
     279      IF( l_trdtra .OR. l_trddyn )   THEN 
     280         REWIND( numnam ) 
     281         READ  ( numnam, namtrd )      ! namelist namtrd : trends diagnostic 
     282 
     283         IF(lwp) THEN 
     284            WRITE(numout,*) 
     285            WRITE(numout,*) ' trd_mod_init : Momentum/Tracers trends' 
     286            WRITE(numout,*) ' ~~~~~~~~~~~~~' 
     287            WRITE(numout,*) '       Namelist namtrd : set trends parameters' 
     288            WRITE(numout,*) '           * frequency of trends diagnostics   ntrd               = ', ntrd 
     289            WRITE(numout,*) '           * control surface type              nctls              = ', nctls 
     290            WRITE(numout,*) '           * restart for ML diagnostics        ln_trdmld_restart  = ', ln_trdmld_restart 
     291            WRITE(numout,*) '           * instantaneous or mean ML T/S      ln_trdmld_instant  = ', ln_trdmld_instant 
     292            WRITE(numout,*) '           * unit conversion factor            ucf                = ', ucf 
     293        ENDIF 
     294      ENDIF 
     295      ! 
     296      IF( lk_trddyn .OR. lk_trdtra )    CALL trd_icp_init       ! integral constraints trends 
     297      IF( lk_trdmld                )    CALL trd_mld_init       ! mixed-layer trends (active  tracers)   
     298      IF( lk_trdvor                )    CALL trd_vor_init       ! vorticity trends         
     299      ! 
     300   END SUBROUTINE trd_mod_init 
     301 
    436302   !!====================================================================== 
    437303END MODULE trdmod 
  • trunk/NEMO/OPA_SRC/TRD/trdmod_oce.F90

    r247 r503  
    44   !! Ocean trends :   set tracer and momentum trend variables 
    55   !!====================================================================== 
     6   !! History :  9.0  !  04-08  (C. Talandier) Original code 
    67   !!---------------------------------------------------------------------- 
    7    !!  OPA 9.0 , LOCEAN-IPSL (2005)  
    8    !! $Header$  
    9    !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt  
    10    !!---------------------------------------------------------------------- 
    11    !! * Modules used 
    128   USE trdicp_oce              ! ocean momentum/tracers bassin properties trends variables 
    139   USE trdmld_oce              ! ocean active mixed layer tracers trends variables 
    1410   USE trdvor_oce              ! ocean vorticity trends variables 
    1511 
    16    !! Control parameters 
     12   IMPLICIT NONE 
     13   PUBLIC 
     14 
     15   !!* Namelist namtrd:  diagnostics on dynamics/tracer trends 
     16   INTEGER , PUBLIC ::    ntrd  = 10                    !: time step frequency dynamics and tracers trends 
     17   INTEGER , PUBLIC ::    nctls =  0                    !: control surface type for trends vertical integration 
     18   REAL(wp), PUBLIC ::    ucf   = 1.                    !: unit conversion factor (for netCDF trends outputs) 
     19                                                        !: =1. (=86400.) for degC/s (degC/day) and psu/s (psu/day) 
     20   LOGICAL , PUBLIC ::    ln_trdmld_instant = .FALSE.   !: flag to diagnose inst./mean ML T/S trends 
     21   LOGICAL , PUBLIC ::    ln_trdmld_restart = .FALSE.   !: flag to restart mixed-layer diagnostics 
     22 
     23   !!* Control parameters 
     24# if defined key_trdtra   ||   defined key_trdmld 
     25   LOGICAL , PUBLIC ::   l_trdtra = .TRUE.              !: tracers  trend flag 
     26# else 
     27   LOGICAL , PUBLIC ::   l_trdtra = .FALSE.             !: tracers  trend flag 
     28# endif 
     29# if defined key_trddyn   ||   defined key_trdvor 
     30   LOGICAL , PUBLIC ::   l_trddyn = .TRUE.              !: momentum trend flag 
     31# else 
     32   LOGICAL , PUBLIC ::   l_trddyn = .FALSE.             !: momentum trend flag 
     33# endif 
     34 
     35   !!* Active tracers trends indexes 
     36   INTEGER, PUBLIC, PARAMETER ::   jptra_trd_xad =  1   !: x- horizontal advection 
     37   INTEGER, PUBLIC, PARAMETER ::   jptra_trd_yad =  2   !: y- horizontal advection 
     38   INTEGER, PUBLIC, PARAMETER ::   jptra_trd_zad =  3   !: z- vertical   advection 
     39   INTEGER, PUBLIC, PARAMETER ::   jptra_trd_ldf =  4   !: lateral       diffusion 
     40   INTEGER, PUBLIC, PARAMETER ::   jptra_trd_zdf =  5   !: vertical diffusion (Kz) 
     41   INTEGER, PUBLIC, PARAMETER ::   jptra_trd_bbc =  6   !: Bottom Boundary Condition (geoth. flux)  
     42   INTEGER, PUBLIC, PARAMETER ::   jptra_trd_bbl =  7   !: Bottom Boundary Layer (diffusive/convective) 
     43   INTEGER, PUBLIC, PARAMETER ::   jptra_trd_npc =  8   !: static instability mixing 
     44   INTEGER, PUBLIC, PARAMETER ::   jptra_trd_dmp =  9   !: damping 
     45   INTEGER, PUBLIC, PARAMETER ::   jptra_trd_qsr = 10   !: penetrative solar radiation 
     46   INTEGER, PUBLIC, PARAMETER ::   jptra_trd_nsr = 11   !: non solar radiation 
     47   INTEGER, PUBLIC, PARAMETER ::   jptra_trd_atf = 12   !: Asselin correction 
     48    
     49   !!* Momentum trends indexes 
     50   INTEGER, PUBLIC, PARAMETER ::   jpdyn_trd_hpg =  1   !: hydrostatic pressure gradient  
     51   INTEGER, PUBLIC, PARAMETER ::   jpdyn_trd_keg =  2   !: kinetic energy gradient 
     52   INTEGER, PUBLIC, PARAMETER ::   jpdyn_trd_rvo =  3   !: relative vorticity 
     53   INTEGER, PUBLIC, PARAMETER ::   jpdyn_trd_pvo =  4   !: planetary vorticity 
     54   INTEGER, PUBLIC, PARAMETER ::   jpdyn_trd_ldf =  5   !: lateral diffusion 
     55   INTEGER, PUBLIC, PARAMETER ::   jpdyn_trd_zad =  6   !: vertical advection 
     56   INTEGER, PUBLIC, PARAMETER ::   jpdyn_trd_zdf =  7   !: vertical diffusion 
     57   INTEGER, PUBLIC, PARAMETER ::   jpdyn_trd_spg =  8   !: surface pressure gradient 
     58   INTEGER, PUBLIC, PARAMETER ::   jpdyn_trd_dat =  9   !: damping term 
     59   INTEGER, PUBLIC, PARAMETER ::   jpdyn_trd_swf = 10   !: surface wind forcing 
     60   INTEGER, PUBLIC, PARAMETER ::   jpdyn_trd_bfr = 11   !: bottom friction  
     61 
    1762   !!---------------------------------------------------------------------- 
    18    LOGICAL, PUBLIC ::   l_trdtra = .FALSE.    !: tracers  trend flag 
    19    LOGICAL, PUBLIC ::   l_trddyn = .FALSE.    !: momentum trend flag 
    20  
    21   !!====================================================================== 
     63   !!  OPA 9.0 , LOCEAN-IPSL (2006)  
     64   !! $Header$  
     65   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
     66   !!====================================================================== 
    2267END MODULE trdmod_oce 
  • trunk/NEMO/OPA_SRC/TRD/trdvor.F90

    r462 r503  
    44   !! Ocean diagnostics:  momentum trends 
    55   !!===================================================================== 
    6     
     6   !! History :  9.0  !  04-06  (L. Brunier, A-M. Treguier) Original code  
     7   !!                 !  04-08  (C. Talandier) New trends organization 
     8   !!---------------------------------------------------------------------- 
    79#if defined key_trdvor   ||   defined key_esopa 
    810   !!---------------------------------------------------------------------- 
    911   !!   'key_trdvor'   : momentum trend diagnostics 
     12   !!---------------------------------------------------------------------- 
    1013   !!---------------------------------------------------------------------- 
    1114   !!   trd_vor      : momentum trends averaged over the depth 
     
    1316   !!   trd_vor_init : initialization step 
    1417   !!---------------------------------------------------------------------- 
    15    !! * Modules used 
    1618   USE oce             ! ocean dynamics and tracers variables 
    1719   USE dom_oce         ! ocean space and time domain variables 
     
    2729   USE lbclnk          ! ocean lateral boundary conditions (or mpp link) 
    2830 
    29  
    3031   IMPLICIT NONE 
    3132   PRIVATE 
    3233 
    33    !! * Interfaces 
    3434   INTERFACE trd_vor_zint 
    3535      MODULE PROCEDURE trd_vor_zint_2d, trd_vor_zint_3d 
    3636   END INTERFACE 
    3737 
    38    !! * Accessibility 
    39    PUBLIC trd_vor        ! routine called by step.F90 
    40    PUBLIC trd_vor_zint   ! routine called by dynamics routines 
    41    PUBLIC trd_vor_init   ! routine called by opa.F90 
    42  
    43    !! * Shared module variables 
    44    LOGICAL, PUBLIC ::   lk_trdvor = .TRUE.   ! momentum trend flag 
    45  
    46    !! * Module variables 
     38   PUBLIC   trd_vor        ! routine called by step.F90 
     39   PUBLIC   trd_vor_zint   ! routine called by dynamics routines 
     40   PUBLIC   trd_vor_init   ! routine called by opa.F90 
     41 
    4742   INTEGER ::                & 
    4843      nh_t, nmoydpvor  ,     & 
     
    6156     vor_avrres 
    6257 
    63    REAL(wp), DIMENSION(jpi,jpj,jplvor)::   &  !: curl of trends 
    64       vortrd    
    65  
     58   REAL(wp), DIMENSION(jpi,jpj,jpltot_vor)::   vortrd  !: curl of trends 
     59          
    6660   CHARACTER(len=12) ::   cvort 
    6761 
     
    7064#  include "ldfdyn_substitute.h90" 
    7165#  include "vectopt_loop_substitute.h90" 
    72  
    7366   !!---------------------------------------------------------------------- 
    7467   !!   OPA 9.0 , LOCEAN-IPSL (2005)  
    7568   !! $Header$  
    76    !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt  
     69   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
    7770   !!---------------------------------------------------------------------- 
    7871   
     
    8073 
    8174   SUBROUTINE trd_vor_zint_2d( putrdvor, pvtrdvor, ktrd ) 
     75      !!---------------------------------------------------------------------------- 
     76      !!                  ***  ROUTINE trd_vor_zint  *** 
     77      !! 
     78      !! ** Purpose :   computation of vertically integrated vorticity budgets 
     79      !!      from ocean surface down to control surface (NetCDF output) 
     80      !! 
     81      !! ** Method/usage : 
     82      !!      integration done over nwrite-1 time steps 
     83      !! 
     84      !! 
     85      !! ** Action : 
     86      !!            /comvor/   : 
     87      !!                         vor_avr          average 
     88      !!                         vor_avrb         vorticity at kt-1 
     89      !!                         vor_avrbb        vorticity at begining of the NWRITE-1 
     90      !!                                          time steps averaging period 
     91      !!                         vor_avrbn         vorticity at time step after the 
     92      !!                                          begining of the NWRITE-1 time 
     93      !!                                          steps averaging period 
     94      !! 
     95      !!                 trends : 
     96      !! 
     97      !!                  vortrd (,, 1) = Pressure Gradient Trend 
     98      !!                  vortrd (,, 2) = KE Gradient Trend 
     99      !!                  vortrd (,, 3) = Relative Vorticity Trend 
     100      !!                  vortrd (,, 4) = Coriolis Term Trend 
     101      !!                  vortrd (,, 5) = Horizontal Diffusion Trend 
     102      !!                  vortrd (,, 6) = Vertical Advection Trend 
     103      !!                  vortrd (,, 7) = Vertical Diffusion Trend 
     104      !!                  vortrd (,, 8) = Surface Pressure Grad. Trend 
     105      !!                  vortrd (,, 9) = Beta V 
     106      !!                  vortrd (,,10) = forcing term 
     107      !!      vortrd (,,11) = bottom friction term 
     108      !!                  rotot(,) : total cumulative trends over nwrite-1 time steps 
     109      !!                  vor_avrtot(,) : first membre of vrticity equation 
     110      !!                  vor_avrres(,) : residual = dh/dt entrainment 
     111      !! 
     112      !!      trends output in netCDF format using ioipsl 
     113      !! 
     114      !!---------------------------------------------------------------------- 
     115      INTEGER, INTENT( in ) ::   ktrd         ! ocean trend index 
     116      REAL(wp), DIMENSION(jpi,jpj), INTENT( inout ) ::   & 
     117         putrdvor,                         &  ! u vorticity trend  
     118         pvtrdvor                             ! v vorticity trend 
     119      !! 
     120      INTEGER ::   ji, jj 
     121      INTEGER ::   ikbu, ikbum1, ikbv, ikbvm1 
     122      REAL(wp), DIMENSION(jpi,jpj) ::   zudpvor, zvdpvor   ! total cmulative trends 
     123      !!---------------------------------------------------------------------- 
     124 
     125      ! Initialization 
     126      zudpvor(:,:) = 0.e0 
     127      zvdpvor(:,:) = 0.e0 
     128 
     129      CALL lbc_lnk( putrdvor,  'U' , -1. ) 
     130      CALL lbc_lnk( pvtrdvor,  'V' , -1. ) 
     131 
     132      !  ===================================== 
     133      !  I vertical integration of 2D trends 
     134      !  ===================================== 
     135 
     136      SELECT CASE (ktrd)  
     137 
     138      CASE (jpvor_bfr)        ! bottom friction 
     139 
     140         DO jj = 2, jpjm1 
     141            DO ji = fs_2, fs_jpim1  
     142               ikbu   = min( mbathy(ji+1,jj), mbathy(ji,jj) ) 
     143               ikbum1 = max( ikbu-1, 1 ) 
     144               ikbv   = min( mbathy(ji,jj+1), mbathy(ji,jj) ) 
     145               ikbvm1 = max( ikbv-1, 1 ) 
     146             
     147               zudpvor(ji,jj) = putrdvor(ji,jj) * fse3u(ji,jj,ikbum1) * e1u(ji,jj) * umask(ji,jj,ikbum1) 
     148               zvdpvor(ji,jj) = pvtrdvor(ji,jj) * fse3v(ji,jj,ikbvm1) * e2v(ji,jj) * vmask(ji,jj,ikbvm1) 
     149            END DO 
     150         END DO 
     151 
     152      CASE (jpvor_swf)        ! wind stress 
     153 
     154         zudpvor(:,:) = putrdvor(:,:) * fse3u(:,:,1) * e1u(:,:) * umask(:,:,1) 
     155         zvdpvor(:,:) = pvtrdvor(:,:) * fse3v(:,:,1) * e2v(:,:) * vmask(:,:,1) 
     156 
     157      END SELECT 
     158 
     159      ! Average except for Beta.V 
     160      zudpvor(:,:) = zudpvor(:,:) * hur(:,:) 
     161      zvdpvor(:,:) = zvdpvor(:,:) * hvr(:,:) 
     162    
     163      ! Curl 
     164      DO ji=1,jpim1 
     165         DO jj=1,jpjm1 
     166            vortrd(ji,jj,ktrd) = ( zvdpvor(ji+1,jj) - zvdpvor(ji,jj)        & 
     167                 &                - ( zudpvor(ji,jj+1) - zudpvor(ji,jj) ) ) & 
     168                 &               / ( e1f(ji,jj) * e2f(ji,jj) ) 
     169         END DO 
     170      END DO 
     171 
     172      ! Surface mask 
     173      vortrd(:,:,ktrd) = vortrd(:,:,ktrd) * fmask(:,:,1) 
     174 
     175      IF( idebug /= 0 ) THEN 
     176         IF(lwp) WRITE(numout,*) ' debuging trd_vor_zint: I done' 
     177         CALL FLUSH(numout) 
     178      ENDIF 
     179      ! 
     180   END SUBROUTINE trd_vor_zint_2d 
     181 
     182 
     183   SUBROUTINE trd_vor_zint_3d( putrdvor, pvtrdvor, ktrd ) 
    82184      !!---------------------------------------------------------------------------- 
    83185      !!                  ***  ROUTINE trd_vor_zint  *** 
     
    119221      !!      trends output in netCDF format using ioipsl 
    120222      !! 
    121       !! History : 
    122       !!   9.0  !  04-06  (L. Brunier, A-M. Treguier) Original code  
    123       !!        !  04-08  (C. Talandier) New trends organization 
    124       !!---------------------------------------------------------------------- 
    125       !! * Arguments 
     223      !!---------------------------------------------------------------------- 
    126224      INTEGER, INTENT( in ) ::   ktrd         ! ocean trend index 
    127  
    128       REAL(wp), DIMENSION(jpi,jpj), INTENT( inout ) ::   & 
    129          putrdvor,                         &  ! u vorticity trend  
    130          pvtrdvor                             ! v vorticity trend 
    131  
    132       !! * Local declarations 
    133       INTEGER ::   ji, jj 
    134       INTEGER ::   ikbu, ikbum1, ikbv, ikbvm1 
    135       REAL(wp), DIMENSION(jpi,jpj) ::   & 
    136          zudpvor,                       &  ! total cmulative trends 
    137          zvdpvor                           !   "      "        " 
    138       !!---------------------------------------------------------------------- 
    139  
    140       ! Initialization 
    141       zudpvor(:,:) = 0.e0 
    142       zvdpvor(:,:) = 0.e0 
    143  
    144       CALL lbc_lnk( putrdvor,  'U' , -1. ) 
    145       CALL lbc_lnk( pvtrdvor,  'V' , -1. ) 
    146  
    147       !  ===================================== 
    148       !  I vertical integration of 2D trends 
    149       !  ===================================== 
    150  
    151       SELECT CASE (ktrd)  
    152  
    153       CASE (jpvorbfr)        ! bottom friction 
    154  
    155          DO jj = 2, jpjm1 
    156             DO ji = fs_2, fs_jpim1  
    157                ikbu   = min( mbathy(ji+1,jj), mbathy(ji,jj) ) 
    158                ikbum1 = max( ikbu-1, 1 ) 
    159                ikbv   = min( mbathy(ji,jj+1), mbathy(ji,jj) ) 
    160                ikbvm1 = max( ikbv-1, 1 ) 
    161              
    162                zudpvor(ji,jj) = putrdvor(ji,jj) * fse3u(ji,jj,ikbum1) * e1u(ji,jj) * umask(ji,jj,ikbum1) 
    163                zvdpvor(ji,jj) = pvtrdvor(ji,jj) * fse3v(ji,jj,ikbvm1) * e2v(ji,jj) * vmask(ji,jj,ikbvm1) 
    164             END DO 
    165          END DO 
    166  
    167       CASE (jpvorswf)        ! wind stress 
    168  
    169          zudpvor(:,:) = putrdvor(:,:) * fse3u(:,:,1) * e1u(:,:) * umask(:,:,1) 
    170          zvdpvor(:,:) = pvtrdvor(:,:) * fse3v(:,:,1) * e2v(:,:) * vmask(:,:,1) 
    171  
    172       END SELECT 
    173  
    174       ! Average except for Beta.V 
    175       zudpvor(:,:) = zudpvor(:,:) * hur(:,:) 
    176       zvdpvor(:,:) = zvdpvor(:,:) * hvr(:,:) 
    177     
    178       ! Curl 
    179       DO ji=1,jpim1 
    180          DO jj=1,jpjm1 
    181             vortrd(ji,jj,ktrd) = ( zvdpvor(ji+1,jj) - zvdpvor(ji,jj)        & 
    182                  &                - ( zudpvor(ji,jj+1) - zudpvor(ji,jj) ) ) & 
    183                  &               / ( e1f(ji,jj) * e2f(ji,jj) ) 
    184          END DO 
    185       END DO 
    186  
    187       ! Surface mask 
    188       vortrd(:,:,ktrd) = vortrd(:,:,ktrd) * fmask(:,:,1) 
    189  
    190       IF( idebug /= 0 ) THEN 
    191          IF(lwp) WRITE(numout,*) ' debuging trd_vor_zint: I done' 
    192          CALL FLUSH(numout) 
    193       ENDIF 
    194  
    195    END SUBROUTINE trd_vor_zint_2d 
    196  
    197  
    198  
    199    SUBROUTINE trd_vor_zint_3d( putrdvor, pvtrdvor, ktrd ) 
    200       !!---------------------------------------------------------------------------- 
    201       !!                  ***  ROUTINE trd_vor_zint  *** 
    202       !! 
    203       !! ** Purpose :   computation of vertically integrated vorticity budgets 
    204       !!      from ocean surface down to control surface (NetCDF output) 
    205       !! 
    206       !! ** Method/usage : 
    207       !!      integration done over nwrite-1 time steps 
    208       !! 
    209       !! 
    210       !! ** Action : 
    211       !!            /comvor/   : 
    212       !!                         vor_avr          average 
    213       !!                         vor_avrb         vorticity at kt-1 
    214       !!                         vor_avrbb        vorticity at begining of the NWRITE-1 
    215       !!                                          time steps averaging period 
    216       !!                         vor_avrbn         vorticity at time step after the 
    217       !!                                          begining of the NWRITE-1 time 
    218       !!                                          steps averaging period 
    219       !! 
    220       !!                 trends : 
    221       !! 
    222       !!                  vortrd (,,1) = Pressure Gradient Trend 
    223       !!                  vortrd (,,2) = KE Gradient Trend 
    224       !!                  vortrd (,,3) = Relative Vorticity Trend 
    225       !!                  vortrd (,,4) = Coriolis Term Trend 
    226       !!                  vortrd (,,5) = Horizontal Diffusion Trend 
    227       !!                  vortrd (,,6) = Vertical Advection Trend 
    228       !!                  vortrd (,,7) = Vertical Diffusion Trend 
    229       !!                  vortrd (,,8) = Surface Pressure Grad. Trend 
    230       !!                  vortrd (,,9) = Beta V 
    231       !!                  vortrd (,,10) = forcing term 
    232       !!      vortrd (,,11) = bottom friction term 
    233       !!                  rotot(,) : total cumulative trends over nwrite-1 time steps 
    234       !!                  vor_avrtot(,) : first membre of vrticity equation 
    235       !!                  vor_avrres(,) : residual = dh/dt entrainment 
    236       !! 
    237       !!      trends output in netCDF format using ioipsl 
    238       !! 
    239       !! History : 
    240       !!   9.0  !  04-06  (L. Brunier, A-M. Treguier) Original code  
    241       !!        !  04-08  (C. Talandier) New trends organization 
    242       !!---------------------------------------------------------------------- 
    243       !! * Arguments 
    244       INTEGER, INTENT( in ) ::   ktrd         ! ocean trend index 
    245  
    246225      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT( inout ) ::   & 
    247226         putrdvor,                         &  ! u vorticity trend  
    248227         pvtrdvor                             ! v vorticity trend 
    249  
    250       !! * Local declarations 
     228      !! 
    251229      INTEGER ::   ji, jj, jk 
    252  
    253230      REAL(wp), DIMENSION(jpi,jpj) ::   & 
    254231         zubet,                         &  ! u Beta.V case 
     
    279256      ! Save Beta.V term to avoid average before Curl 
    280257      ! Beta.V : intergration, no average 
    281       IF( ktrd == jpvorbev ) THEN  
     258      IF( ktrd == jpvor_bev ) THEN  
    282259         zubet(:,:) = zudpvor(:,:) 
    283260         zvbet(:,:) = zvdpvor(:,:) 
     
    302279      ! Special treatement for the Beta.V term 
    303280      ! Compute the Curl of the Beta.V term which is not averaged 
    304       IF( ktrd == jpvorbev ) THEN 
     281      IF( ktrd == jpvor_bev ) THEN 
    305282         DO ji=1,jpim1 
    306283            DO jj=1,jpjm1 
    307                vortrd(ji,jj,jpvorbev) = (  zvbet(ji+1,jj) - zvbet(ji,jj) -   & 
     284               vortrd(ji,jj,jpvor_bev) = (  zvbet(ji+1,jj) - zvbet(ji,jj) -   & 
    308285                    &                    ( zubet(ji,jj+1) - zubet(ji,jj) ) ) & 
    309286                    &                   / ( e1f(ji,jj) * e2f(ji,jj) ) 
     
    312289 
    313290         ! Average on the Curl 
    314          vortrd(:,:,jpvorbev) = vortrd(:,:,jpvorbev) * hur(:,:) 
     291         vortrd(:,:,jpvor_bev) = vortrd(:,:,jpvor_bev) * hur(:,:) 
    315292 
    316293         ! Surface mask 
    317          vortrd(:,:,jpvorbev) = vortrd(:,:,jpvorbev) * fmask(:,:,1) 
     294         vortrd(:,:,jpvor_bev) = vortrd(:,:,jpvor_bev) * fmask(:,:,1) 
    318295      ENDIF 
    319296    
     
    322299         CALL FLUSH(numout) 
    323300      ENDIF 
    324  
     301      ! 
    325302   END SUBROUTINE trd_vor_zint_3d 
    326  
    327303 
    328304 
     
    333309      !! ** Purpose :  computation of cumulated trends over analysis period 
    334310      !!               and make outputs (NetCDF or DIMG format) 
    335       !! 
    336       !! ** Method/usage : 
    337       !! 
    338       !! History : 
    339       !!   9.0  !  04-06  (L. Brunier, A-M. Treguier) Original code  
    340       !!        !  04-08  (C. Talandier) New trends organization 
    341       !!---------------------------------------------------------------------- 
    342       !! * Arguments 
     311      !!---------------------------------------------------------------------- 
    343312      INTEGER, INTENT( in ) ::   kt   ! ocean time-step index 
    344  
    345       !! * Local declarations 
    346       INTEGER :: ji, jj, jk, jl, it 
    347  
    348       REAL(wp) :: zmean 
    349  
    350       REAL(wp) ,DIMENSION(jpi,jpj) ::   & 
    351          zun, zvn 
     313      !! 
     314      INTEGER  ::   ji, jj, jk, jl, it 
     315      REAL(wp) ::   zmean 
     316      REAL(wp), DIMENSION(jpi,jpj) ::   zun, zvn 
    352317      !!---------------------------------------------------------------------- 
    353318 
     
    424389      IF( kt >= nit000+2 ) THEN 
    425390         nmoydpvor = nmoydpvor + 1 
    426          DO jl = 1, jplvor 
     391         DO jl = 1, jpltot_vor 
    427392            IF( jl /= 9 ) THEN 
    428393               rotot(:,:) = rotot(:,:) + vortrd(:,:,jl) 
     
    490455         it= kt-nit000+1 
    491456         IF( lwp .AND. MOD( kt, ntrd ) == 0 ) THEN 
    492             WRITE(numout,*) '     trdvor_ncwrite : write NetCDF fields' 
     457            WRITE(numout,*) '' 
     458            WRITE(numout,*) 'trd_vor : write trends in the NetCDF file at kt = ', kt 
     459            WRITE(numout,*) '~~~~~~~  ' 
    493460         ENDIF 
    494461  
    495          CALL histwrite( nidvor,"sovortPh",it,vortrd(:,:,1),ndimvor1,ndexvor1)  ! grad Ph 
    496          CALL histwrite( nidvor,"sovortEk",it,vortrd(:,:,2),ndimvor1,ndexvor1)  ! Energy 
    497          CALL histwrite( nidvor,"sovozeta",it,vortrd(:,:,3),ndimvor1,ndexvor1)  ! rel vorticity 
    498          CALL histwrite( nidvor,"sovortif",it,vortrd(:,:,4),ndimvor1,ndexvor1)  ! coriolis 
    499          CALL histwrite( nidvor,"sovodifl",it,vortrd(:,:,5),ndimvor1,ndexvor1)  ! lat diff 
    500          CALL histwrite( nidvor,"sovoadvv",it,vortrd(:,:,6),ndimvor1,ndexvor1)  ! vert adv 
    501          CALL histwrite( nidvor,"sovodifv",it,vortrd(:,:,7),ndimvor1,ndexvor1)  ! vert diff 
    502          CALL histwrite( nidvor,"sovortPs",it,vortrd(:,:,8),ndimvor1,ndexvor1)  ! grad Ps 
    503          CALL histwrite( nidvor,"sovortbv",it,vortrd(:,:,9),ndimvor1,ndexvor1)  ! beta.V 
    504          CALL histwrite( nidvor,"sovowind",it,vortrd(:,:,10),ndimvor1,ndexvor1) ! wind stress 
    505          CALL histwrite( nidvor,"sovobfri",it,vortrd(:,:,11),ndimvor1,ndexvor1) ! bottom friction 
     462         CALL histwrite( nidvor,"sovortPh",it,vortrd(:,:,jpvor_prg),ndimvor1,ndexvor1)  ! grad Ph 
     463         CALL histwrite( nidvor,"sovortEk",it,vortrd(:,:,jpvor_keg),ndimvor1,ndexvor1)  ! Energy 
     464         CALL histwrite( nidvor,"sovozeta",it,vortrd(:,:,jpvor_rvo),ndimvor1,ndexvor1)  ! rel vorticity 
     465         CALL histwrite( nidvor,"sovortif",it,vortrd(:,:,jpvor_pvo),ndimvor1,ndexvor1)  ! coriolis 
     466         CALL histwrite( nidvor,"sovodifl",it,vortrd(:,:,jpvor_ldf),ndimvor1,ndexvor1)  ! lat diff 
     467         CALL histwrite( nidvor,"sovoadvv",it,vortrd(:,:,jpvor_zad),ndimvor1,ndexvor1)  ! vert adv 
     468         CALL histwrite( nidvor,"sovodifv",it,vortrd(:,:,jpvor_zdf),ndimvor1,ndexvor1)  ! vert diff 
     469         CALL histwrite( nidvor,"sovortPs",it,vortrd(:,:,jpvor_spg),ndimvor1,ndexvor1)  ! grad Ps 
     470         CALL histwrite( nidvor,"sovortbv",it,vortrd(:,:,jpvor_bev),ndimvor1,ndexvor1)  ! beta.V 
     471         CALL histwrite( nidvor,"sovowind",it,vortrd(:,:,jpvor_swf),ndimvor1,ndexvor1) ! wind stress 
     472         CALL histwrite( nidvor,"sovobfri",it,vortrd(:,:,jpvor_bfr),ndimvor1,ndexvor1) ! bottom friction 
    506473         CALL histwrite( nidvor,"1st_mbre",it,vor_avrtot    ,ndimvor1,ndexvor1) ! First membre 
    507474         CALL histwrite( nidvor,"sovorgap",it,vor_avrres    ,ndimvor1,ndexvor1) ! gap between 1st and 2 nd mbre 
    508  
     475         ! 
    509476         IF( idebug /= 0 ) THEN 
    510477            WRITE(numout,*) ' debuging trd_vor: III.4 done' 
    511478            CALL FLUSH(numout) 
    512479         ENDIF 
    513  
    514       ENDIF 
    515  
     480         ! 
     481      ENDIF 
     482      ! 
    516483      IF( MOD( kt - nit000+1, ntrd ) == 0 ) rotot(:,:)=0 
    517  
     484      ! 
    518485      IF( kt == nitend )   CALL histclo( nidvor ) 
    519  
     486      ! 
    520487   END SUBROUTINE trd_vor 
    521  
    522488 
    523489 
     
    528494      !! ** Purpose :   computation of vertically integrated T and S budgets 
    529495      !!      from ocean surface down to control surface (NetCDF output) 
    530       !! 
    531       !! ** Method/usage : 
    532       !! 
    533       !! History : 
    534       !!   9.0  !  04-06  (L. Brunier, A-M. Treguier) Original code  
    535       !!        !  04-08  (C. Talandier) New trends organization 
    536       !!---------------------------------------------------------------------- 
    537       !! * Local declarations 
    538       REAL(wp) :: zjulian, zsto, zout 
    539  
     496      !!---------------------------------------------------------------------- 
     497      REAL(wp) ::   zjulian, zsto, zout 
    540498      CHARACTER (len=40) ::   clhstnam 
    541499      CHARACTER (len=40) ::   clop 
    542  
    543       NAMELIST/namtrd/ ntrd,nctls 
    544500      !!---------------------------------------------------------------------- 
    545501 
     
    553509      idebug = 0      ! set it to 1 in case of problem to have more Print 
    554510 
    555       ! namelist namtrd : trend diagnostic 
    556       REWIND( numnam ) 
    557       READ  ( numnam, namtrd ) 
    558  
    559511      IF(lwp) THEN 
    560512         WRITE(numout,*) ' ' 
    561          WRITE(numout,*) 'trd_vor_init: vorticity trends' 
    562          WRITE(numout,*) '~~~~~~~~~~~~~' 
     513         WRITE(numout,*) ' trd_vor_init: vorticity trends' 
     514         WRITE(numout,*) ' ~~~~~~~~~~~~' 
    563515         WRITE(numout,*) ' ' 
    564          WRITE(numout,*) '          Namelist namtrd : ' 
    565          WRITE(numout,*) '             time step frequency trend       ntrd  = ',ntrd 
    566          WRITE(numout,*) ' ' 
    567          WRITE(numout,*) '##########################################################################' 
    568          WRITE(numout,*) ' CAUTION: The interpretation of the vorticity trends is' 
    569          WRITE(numout,*) ' not obvious, please contact Anne-Marie TREGUIER at: treguier@ifremer.fr ' 
    570          WRITE(numout,*) '##########################################################################' 
     516         WRITE(numout,*) '               ##########################################################################' 
     517         WRITE(numout,*) '                CAUTION: The interpretation of the vorticity trends is' 
     518         WRITE(numout,*) '                not obvious, please contact Anne-Marie TREGUIER at: treguier@ifremer.fr ' 
     519         WRITE(numout,*) '               ##########################################################################' 
    571520         WRITE(numout,*) ' ' 
    572521      ENDIF 
     
    599548      zout = ntrd*rdt 
    600549 
    601       IF(lwp) WRITE (numout,*) ' trdvor_ncinit: netCDF initialization' 
     550      IF(lwp) WRITE(numout,*) '              netCDF initialization' 
    602551 
    603552      ! II.2 Compute julian date from starting date of the run 
    604553      ! ------------------------ 
    605554      CALL ymds2ju( nyear, nmonth, nday, 0.e0, zjulian ) 
    606       IF (lwp) WRITE(numout,*)' '   
    607       IF (lwp) WRITE(numout,*)' Date 0 used :',nit000         & 
    608            ,' YEAR ', nyear,' MONTH ', nmonth,' DAY ', nday   & 
    609            ,'Julian day : ', zjulian 
     555      IF(lwp) WRITE(numout,*)' '   
     556      IF(lwp) WRITE(numout,*)'               Date 0 used :',nit000,    & 
     557         &                   ' YEAR ', nyear,' MONTH '      , nmonth,   & 
     558         &                   ' DAY ' , nday, 'Julian day : ', zjulian 
    610559 
    611560      ! II.3 Define the T grid trend file (nidvor) 
     
    650599         CALL FLUSH(numout) 
    651600      ENDIF 
    652  
     601      ! 
    653602   END SUBROUTINE trd_vor_init 
    654603 
     
    657606   !!   Default option :                                       Empty module 
    658607   !!---------------------------------------------------------------------- 
    659    LOGICAL, PUBLIC ::   lk_trdvor = .FALSE.   ! momentum trend flag 
    660  
    661    !! * Interfaces 
    662608   INTERFACE trd_vor_zint 
    663609      MODULE PROCEDURE trd_vor_zint_2d, trd_vor_zint_3d 
    664610   END INTERFACE 
    665  
    666611CONTAINS 
    667612   SUBROUTINE trd_vor( kt )        ! Empty routine 
     
    669614   END SUBROUTINE trd_vor 
    670615   SUBROUTINE trd_vor_zint_2d( putrdvor, pvtrdvor, ktrd ) 
    671       REAL, DIMENSION(:,:), INTENT( inout ) ::   & 
    672          putrdvor, pvtrdvor                  ! U and V momentum trends 
     616      REAL, DIMENSION(:,:), INTENT( inout ) ::   putrdvor, pvtrdvor 
    673617      INTEGER, INTENT( in ) ::   ktrd         ! ocean trend index 
    674618      WRITE(*,*) 'trd_vor_zint_2d: You should not have seen this print! error?', putrdvor(1,1) 
     
    677621   END SUBROUTINE trd_vor_zint_2d 
    678622   SUBROUTINE trd_vor_zint_3d( putrdvor, pvtrdvor, ktrd ) 
    679       REAL, DIMENSION(:,:,:), INTENT( inout ) ::   & 
    680          putrdvor, pvtrdvor                  ! U and V momentum trends 
     623      REAL, DIMENSION(:,:,:), INTENT( inout ) ::   putrdvor, pvtrdvor 
    681624      INTEGER, INTENT( in ) ::   ktrd         ! ocean trend index 
    682625      WRITE(*,*) 'trd_vor_zint_3d: You should not have seen this print! error?', putrdvor(1,1,1) 
  • trunk/NEMO/OPA_SRC/TRD/trdvor_oce.F90

    r247 r503  
    44   !! Ocean trends :   set vorticity trend variables 
    55   !!====================================================================== 
     6   !! History :  9.0  ! ??? 
     7   !!---------------------------------------------------------------------- 
     8 
     9   !!---------------------------------------------------------------------- 
     10   USE par_oce      ! ocean parameters 
     11 
     12   IMPLICIT NONE 
     13   PRIVATE 
     14 
     15#if defined key_trdvor 
     16   LOGICAL, PUBLIC, PARAMETER ::   lk_trdvor = .TRUE.     !: momentum trend flag 
     17#else 
     18   LOGICAL, PUBLIC, PARAMETER ::   lk_trdvor = .FALSE.    !: momentum trend flag 
     19#endif 
     20   !!* vorticity trends index 
     21   INTEGER, PUBLIC, PARAMETER ::   jpltot_vor = 11  !: Number of vorticity trend terms 
     22   ! 
     23   INTEGER, PUBLIC, PARAMETER ::   jpvor_prg =  1   !: Pressure Gradient Trend 
     24   INTEGER, PUBLIC, PARAMETER ::   jpvor_keg =  2   !: KE Gradient Trend 
     25   INTEGER, PUBLIC, PARAMETER ::   jpvor_rvo =  3   !: Relative Vorticity Trend 
     26   INTEGER, PUBLIC, PARAMETER ::   jpvor_pvo =  4   !: Planetary Vorticity Term Trend 
     27   INTEGER, PUBLIC, PARAMETER ::   jpvor_ldf =  5   !: Horizontal Diffusion Trend 
     28   INTEGER, PUBLIC, PARAMETER ::   jpvor_zad =  6   !: Vertical Advection Trend 
     29   INTEGER, PUBLIC, PARAMETER ::   jpvor_zdf =  7   !: Vertical Diffusion Trend 
     30   INTEGER, PUBLIC, PARAMETER ::   jpvor_spg =  8   !: Surface Pressure Grad. Trend 
     31   INTEGER, PUBLIC, PARAMETER ::   jpvor_bev =  9   !: Beta V 
     32   INTEGER, PUBLIC, PARAMETER ::   jpvor_swf = 10   !: wind stress forcing term 
     33   INTEGER, PUBLIC, PARAMETER ::   jpvor_bfr = 11   !: bottom friction term 
     34 
    635   !!---------------------------------------------------------------------- 
    736   !!  OPA 9.0 , LOCEAN-IPSL (2005)  
    837   !! $Header$  
    9    !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt  
    10    !!---------------------------------------------------------------------- 
    11    !!---------------------------------------------------------------------- 
    12    !! * Modules used 
    13    USE par_oce      ! ocean parameters 
    14  
    15    IMPLICIT NONE 
    16    PUBLIC 
    17  
    18    INTEGER,PARAMETER :: jplvor = 11     ! Number of vorticity trend terms 
    19  
    20    INTEGER, PARAMETER ::            &  !: vorticity trends index 
    21       jpvorprg = 1,   &  !: Pressure Gradient Trend 
    22       jpvorkeg = 2,   &  !: KE Gradient Trend 
    23       jpvorrvo = 3,   &  !: Relative Vorticity Trend 
    24       jpvorpvo = 4,   &  !: Planetary Vorticity Term Trend 
    25       jpvorldf = 5,   &  !: Horizontal Diffusion Trend 
    26       jpvorzad = 6,   &  !: Vertical Advection Trend 
    27       jpvorzdf = 7,   &  !: Vertical Diffusion Trend 
    28       jpvorspg = 8,   &  !: Surface Pressure Grad. Trend 
    29       jpvorbev = 9,   &  !: Beta V 
    30       jpvorswf =10,   &  !: wind stress forcing term 
    31       jpvorbfr =11       !: bottom friction term 
    32  
    33   !!====================================================================== 
     38   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
     39   !!====================================================================== 
    3440END MODULE trdvor_oce 
Note: See TracChangeset for help on using the changeset viewer.