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 216 for trunk/NEMO/OPA_SRC/TRD/trdmld.F90 – NEMO

Ignore:
Timestamp:
2005-03-17T15:02:38+01:00 (19 years ago)
Author:
opalod
Message:

CT : UPDATE151 : New trends organization

File:
1 edited

Legend:

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

    r101 r216  
    88   !!   'key_trdmld'                          mixed layer trend diagnostics 
    99   !!---------------------------------------------------------------------- 
    10    !!   trd_mld      : T and S trends averaged over the mixed layer 
     10   !!   trd_mld          : T and S cumulated trends averaged over the mixed layer 
     11   !!   trd_mld_zint     : T and S trends vertical integration 
     12   !!   trd_mld_init     : initialization step 
    1113   !!---------------------------------------------------------------------- 
    1214   !! * Modules used 
    1315   USE oce             ! ocean dynamics and tracers variables 
    1416   USE dom_oce         ! ocean space and time domain variables 
    15    USE ldftra_oce      ! ocean active tracers: lateral physics 
    16    USE trdtra_oce      ! ocean active tracer trend variables 
     17   USE trdmod_oce      ! ocean variables trends 
     18   USE ldftra_oce      ! ocean active tracers lateral physics 
    1719   USE zdf_oce         ! ocean vertical physics 
    1820   USE in_out_manager  ! I/O manager 
    19  
    2021   USE phycst          ! Define parameters for the routines 
    2122   USE daymod          ! calendar 
    2223   USE dianam          ! build the name of file (routine) 
    23    USE ldfslp         ! iso-neutral slopes  
    24    USE zdfmxl 
    25    USE zdfddm 
    26    USE ioipsl 
    27    USE lbclnk 
    28 #if defined key_dimgout 
    29    USE diawri, ONLY : dia_wri_dimg 
    30 #endif 
     24   USE ldfslp          ! iso-neutral slopes  
     25   USE zdfmxl          ! mixed layer depth 
     26   USE zdfddm          ! ocean vertical physics: double diffusion 
     27   USE ioipsl          ! NetCDF library 
     28   USE lbclnk          ! ocean lateral boundary conditions (or mpp link) 
     29   USE diadimg         ! dimg direct access file format output 
    3130 
    3231   IMPLICIT NONE 
     
    3433 
    3534   !! * Accessibility 
    36    PUBLIC trd_mld   ! routine called by step.F90 
     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 
    3738 
    3839   !! * Shared module variables 
     
    4041 
    4142   !! * 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 
    4252   INTEGER, DIMENSION(jpi,jpj) ::   & 
    43       nmld,             &  ! mixed layer depth 
    44       nbol 
    45  
    46    INTEGER ::   & 
    47       nh_t, nmoymltrd,        &  ! ??? 
    48       nidtrd,nhoridtrd,            & 
    49       ndextrd1(jpi*jpj),ndimtrd1  
     53      nmld,                         & ! mixed layer depth 
     54      nbol                 
    5055 
    5156   REAL(wp), DIMENSION(jpi,jpj) ::   & 
     
    5964      tmltrdm, smltrdm     ! 
    6065 
    61 !  REAL(wp), DIMENSION(jpi,jpj,jpltrd) ::   & ! Must be jpk for mpp lbc_lnk 
    62 !                                             TO BE FIXED ??? 
    6366   REAL(wp), DIMENSION(jpi,jpj,jpk) ::   & 
    6467      tmltrd ,          &  ! total cumulative trends of temperature and  
    65       smltrd               ! salinity over nwrite-1 time steps 
    66  
    67    INTEGER ::  iyear,imon,iday 
    68    CHARACTER(LEN=80) :: clname, cltext, clmode 
     68      smltrd ,          &  ! salinity over nwrite-1 time steps 
     69      wkx 
     70 
     71   CHARACTER(LEN=80) :: clname 
    6972 
    7073   !! * Substitutions 
     
    7881CONTAINS 
    7982 
    80    SUBROUTINE trd_mld( kt ) 
     83SUBROUTINE trd_mld_zint( pttrdmld, pstrdmld, ktrd, ctype ) 
    8184      !!---------------------------------------------------------------------- 
    82       !!                  ***  ROUTINE trd_mld  *** 
     85      !!                  ***  ROUTINE trd_mld_zint  *** 
    8386      !!  
    8487      !! ** Purpose :   computation of vertically integrated T and S budgets 
    85       !!      from ocean surface down to control surface (NetCDF output) 
     88      !!                from ocean surface down to control surface  
    8689      !! 
    8790      !! ** Method/usage : 
     
    134137      !!        !  99-09  (E. Guilyardi)  Re-writing + netCDF output 
    135138      !!   8.5  !  02-06  (G. Madec)  F90: Free form and module 
     139      !!   9.0  !  04-08  (C. Talandier) New trends organization 
    136140      !!---------------------------------------------------------------------- 
    137141      !! * Arguments 
    138       INTEGER, INTENT( in ) ::   kt      ! ocean time-step index 
     142      INTEGER, INTENT( in ) ::   ktrd         ! ocean trend index 
     143 
     144      CHARACTER(len=2), INTENT( in ) ::   & 
     145         ctype                                ! surface/bottom (2D arrays) or 
     146                                              ! interior (3D arrays) physics 
     147 
     148      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT( in ) ::   & 
     149         pttrdmld,                         &  ! Temperature trend  
     150         pstrdmld                             ! Salinity    trend 
    139151 
    140152      !! * Local declarations 
    141       INTEGER :: ilseq 
    142       INTEGER :: ji, jj, jk, jl, ik, ikb, idebug, isum, it 
    143       INTEGER, DIMENSION(jpi,jpj) ::  zvlmsk 
    144  
    145       REAL(wp) :: zmean, zavt, zjulian, zsto, zout 
    146       REAL(wp) ,DIMENSION(jpi,jpj,jpktrd) :: zwkx 
    147       REAL(wp) ,DIMENSION(jpi,jpj)        ::  & 
    148            &  ztmltot, ztmlres, z2d, zsmltot, zsmlres 
    149  
    150       CHARACTER (len=21) ::   & 
    151          clold ='OLD'        , & ! open specifier (direct access files) 
    152          clunf ='UNFORMATTED', & ! open specifier (direct access files) 
    153          clseq ='SEQUENTIAL'     ! open specifier (direct access files) 
    154       CHARACTER (len=80) ::   clname 
    155       CHARACTER (len=40) ::   clhstnam 
    156       CHARACTER (len=40) ::   clop 
    157       CHARACTER (len=12) ::   clmxl 
    158  
    159       NAMELIST/namtrd/ ntrd, nctls 
     153      INTEGER ::   ji, jj, jk, isum 
     154# if defined key_trabbl_dif 
     155      INTEGER ::   ikb 
     156# endif 
     157 
     158      REAL(wp), DIMENSION(jpi,jpj) ::   & 
     159         zvlmsk 
    160160      !!---------------------------------------------------------------------- 
    161161 
    162       !  =================== 
    163       !   0. initialization 
    164       !  =================== 
    165  
    166       ! Open specifier 
    167       ilseq = 1 
    168       idebug = 0      ! set it to 1 in case of problem to have more print 
    169  
    170       IF( kt == nit000 ) THEN 
    171          ! namelist namtrd : trend diagnostic 
    172          REWIND( numnam ) 
    173          READ  ( numnam, namtrd ) 
    174  
    175          IF(lwp) THEN 
    176             WRITE(numout,*) 'namtrd' 
    177             WRITE(numout,*) ' ' 
    178             WRITE(numout,*) ' time step frequency trend       ntrd  = ',ntrd 
    179             WRITE(numout,*) ' control surface for trends      nctls = ',nctls 
    180             WRITE(numout,*) ' ' 
    181          ENDIF 
    182  
    183          ! cumulated trends array init 
    184          nmoymltrd = 0 
    185          tmltrdm(:,:) = 0. 
    186          smltrdm(:,:) = 0. 
    187       ENDIF 
    188  
    189       ! set before values of vertically average T and S  
    190  
    191       IF( kt > nit000 ) THEN 
    192          tmlb(:,:) = tml(:,:) 
    193          smlb(:,:) = sml(:,:) 
    194       ENDIF 
    195  
    196       !  read control surface from file ctlsurf_idx 
    197  
    198       IF( kt == nit000 .and. nctls == - 1 ) THEN 
    199          clname ='ctlsurf_idx' 
    200          CALL ctlopn(numbol,clname,clold,clunf,clseq,   & 
    201               ilseq,numout,lwp,1) 
    202          REWIND (numbol) 
    203          READ(numbol) nbol 
    204       ENDIF 
    205  
    206       IF( idebug /= 0 ) THEN 
    207          WRITE(numout,*) ' debuging trd_mld: 0. done '   
    208          CALL FLUSH(numout) 
    209       ENDIF 
    210  
    211  
    212       !  ======================================================== 
    213       !   I. definition of control surface and associated fields 
    214       !  ======================================================== 
    215  
    216       !    I.1 set nmld(ji,jj) = index of first T point below control surface 
    217       !    -------------------                       or outside mixed-layer 
    218  
    219       !     clmxl = legend root for netCDF output 
    220  
    221       IF( nctls == 0 ) THEN 
    222          ! control surface = mixed-layer with density criterion  
    223          ! (array nmln computed in zdfmxl.F90) 
    224          nmld(:,:) = nmln(:,:) 
    225          clmxl = 'Mixed Layer ' 
    226       ELSE IF( nctls == 1 ) THEN 
    227          ! control surface = read index from file  
    228          nmld(:,:) = nbol(:,:) 
    229          clmxl = '      Bowl ' 
    230       ELSE IF( nctls >= 2 ) THEN 
    231          ! control surface = model level 
    232          nctls = MIN( nctls, jpktrd - 1 ) 
    233          nmld(:,:) = nctls + 1 
    234          WRITE(clmxl,'(A9,I2,1X)') 'Levels 1-', nctls 
    235       ENDIF 
    236  
    237       ! Check of validity : nmld(ji,jj) =< jpktrd 
    238       isum = 0 
    239  
    240       IF( jpktrd < jpk ) THEN  
    241          DO jj = 1, jpj 
    242             DO ji = 1, jpi 
    243                IF( nmld(ji,jj) <= jpktrd ) THEN 
    244                   zvlmsk(ji,jj) = tmask(ji,jj,1) 
    245                ELSE 
    246                   isum = isum + 1 
    247                   zvlmsk(ji,jj) = 0. 
    248                ENDIF 
     162      IF( icount == 1 ) THEN         
     163 
     164         zvlmsk(:,:)   = 0.e0 
     165         tmltrd(:,:,:) = 0.e0 
     166         smltrd(:,:,:) = 0.e0 
     167          
     168         ! This computation should be done only once per time step 
     169 
     170         !  ======================================================== 
     171         !   I. definition of control surface and associated fields 
     172         !  ======================================================== 
     173 
     174         !    I.1 set nmld(ji,jj) = index of first T point below control surface 
     175         !    -------------------                       or outside mixed-layer 
     176 
     177         IF( nctls == 0 ) THEN 
     178            ! control surface = mixed-layer with density criterion  
     179            ! (array nmln computed in zdfmxl.F90) 
     180            nmld(:,:) = nmln(:,:) 
     181         ELSE IF( nctls == 1 ) THEN 
     182            ! control surface = read index from file  
     183            nmld(:,:) = nbol(:,:) 
     184         ELSE IF( nctls >= 2 ) THEN 
     185            ! control surface = model level 
     186            nctls = MIN( nctls, jpktrd - 1 ) 
     187            nmld(:,:) = nctls + 1 
     188         ENDIF 
     189 
     190         IF( ionce == 1 ) THEN  ! compute ndextrd1 and ndimtrd1 only once 
     191            ! Check of validity : nmld(ji,jj) =< jpktrd 
     192            isum = 0 
     193 
     194            IF( jpktrd < jpk ) THEN  
     195               DO jj = 1, jpj 
     196                  DO ji = 1, jpi 
     197                     IF( nmld(ji,jj) <= jpktrd ) THEN 
     198                        zvlmsk(ji,jj) = tmask(ji,jj,1) 
     199                     ELSE 
     200                        isum = isum + 1 
     201                        zvlmsk(ji,jj) = 0. 
     202                     ENDIF 
     203                  END DO 
     204               END DO 
     205            ENDIF 
     206 
     207            ! Index of ocean points (2D only) 
     208            IF( isum > 0 ) THEN 
     209               WRITE(numout,*)' Number of invalid points nmld > jpktrd', isum  
     210               CALL wheneq( jpi*jpj, zvlmsk(:,:) , 1, 1., ndextrd1, ndimtrd1 )    ! surface 
     211            ELSE  
     212               CALL wheneq( jpi*jpj, tmask(:,:,1), 1, 1., ndextrd1, ndimtrd1 )    ! surface 
     213            ENDIF                                 
     214 
     215            ! no more pass here 
     216            ionce = 0 
     217 
     218         ENDIF 
     219          
     220         IF( idebug /= 0 ) THEN 
     221            ! CALL prihre (zvlmsk,jpi,jpj,1,jpi,2,1,jpj,2,3,numout) 
     222            WRITE(numout,*) ' debuging trd_mld_zint: I.1 done '   
     223            CALL FLUSH(numout) 
     224         ENDIF 
     225 
     226 
     227         ! I.2 probability density function of presence in mixed-layer 
     228         ! -------------------------------- 
     229         ! (i.e. weight of each grid point in vertical integration : wkx(ji,jj,jk) 
     230 
     231 
     232         ! initialize wkx with vertical scale factor in mixed-layer 
     233 
     234         wkx(:,:,:) = 0.e0 
     235         DO jk = 1, jpktrd 
     236            DO jj = 1,jpj 
     237               DO ji = 1,jpi 
     238                  IF( jk - nmld(ji,jj) < 0. )   wkx(ji,jj,jk) = fse3t(ji,jj,jk) * tmask(ji,jj,jk) 
     239               END DO 
    249240            END DO 
    250241         END DO 
    251       ENDIF 
    252        
     242          
     243         ! compute mixed-layer depth : rmld 
     244          
     245         rmld(:,:) = 0. 
     246         DO jk = 1, jpktrd 
     247            rmld(:,:) = rmld(:,:) + wkx(:,:,jk) 
     248         END DO 
     249          
     250         ! compute PDF 
     251 
     252         DO jk = 1, jpktrd 
     253            wkx(:,:,jk) = wkx(:,:,jk) / MAX( 1., rmld(:,:) ) 
     254         END DO 
     255 
     256         IF( idebug /= 0 ) THEN 
     257            WRITE(numout,*) ' debuging trd_mld_zint: I.2 done '   
     258            CALL FLUSH(numout) 
     259         ENDIF 
     260 
     261         ! Set counter icount to 0 to avoid this part at each time step 
     262         icount = 0 
     263 
     264      ENDIF 
     265 
     266 
     267      !  ==================================================== 
     268      !   II. vertical integration of trends in mixed-layer 
     269      !  ==================================================== 
     270 
     271      ! II.1 vertical integration of 3D and 2D trends 
     272      ! --------------------------------------------- 
     273 
     274      SELECT CASE (ctype) 
     275 
     276      CASE ('3D')       ! 3D treatment 
     277 
     278         ! trends terms in the mixed-layer 
     279         DO jk = 1, jpktrd 
     280            ! Temperature 
     281            tmltrd(:,:,ktrd) = tmltrd(:,:,ktrd) + pttrdmld(:,:,jk) * wkx(:,:,jk)    
     282 
     283            ! Salinity 
     284            smltrd(:,:,ktrd) = smltrd(:,:,ktrd) + pstrdmld(:,:,jk) * wkx(:,:,jk)    
     285         ENDDO 
     286 
     287      CASE ('2D')       ! 2D treatment 
     288 
     289         SELECT CASE (ktrd)  
     290 
     291         CASE (jpmldldf) 
     292 
     293# if defined key_trabbl_dif 
     294               ! trends terms from Beckman over-flow parameterization 
     295               DO jj = 1,jpj 
     296                  DO ji = 1,jpi 
     297                     ikb = MAX( mbathy(ji,jj)-1, 1 ) 
     298                     ! beckmann component -> horiz. part of lateral diffusion 
     299                     tmltrd(ji,jj,ktrd) = tmltrd(ji,jj,ktrd) + pttrdmld(ji,jj,1) * wkx(ji,jj,ikb) 
     300                     smltrd(ji,jj,ktrd) = smltrd(ji,jj,ktrd) + pstrdmld(ji,jj,1) * wkx(ji,jj,ikb) 
     301                  END DO 
     302               END DO 
     303# endif 
     304 
     305         CASE DEFAULT 
     306 
     307            ! trends terms at upper boundary of mixed-layer 
     308 
     309            ! forcing term (non penetrative) 
     310            ! Temperature 
     311            tmltrd(:,:,ktrd) = tmltrd(:,:,ktrd) + pttrdmld(:,:,1) * wkx(:,:,1)    
     312 
     313            ! forcing term 
     314            ! Salinity 
     315            smltrd(:,:,ktrd) = smltrd(:,:,ktrd) + pstrdmld(:,:,1) * wkx(:,:,1)    
     316 
     317         END SELECT 
     318 
     319      END SELECT 
     320 
    253321      IF( idebug /= 0 ) THEN 
    254          ! CALL prihre (zvlmsk,jpi,jpj,1,jpi,2,1,jpj,2,3,numout) 
    255          WRITE(numout,*) ' debuging trd_mld: I.1 done '   
     322         IF(lwp) WRITE(numout,*) ' debuging trd_mld_zint: II.1 done'   
    256323         CALL FLUSH(numout) 
    257324      ENDIF 
    258325 
    259  
    260       ! I.2 probability density function of presence in mixed-layer 
    261       ! -------------------------------- 
    262       ! (i.e. weight of each grid point in vertical integration : zwkx(ji,jj,jk) 
    263  
    264  
    265       ! initialize zwkx with vertical scale factor in mixed-layer 
    266  
    267       zwkx(:,:,:) = 0.e0 
    268       DO jk = 1, jpktrd 
    269          DO jj = 1,jpj 
    270             DO ji = 1,jpi 
    271                IF( jk - nmld(ji,jj) < 0. )   zwkx(ji,jj,jk) = fse3t(ji,jj,jk) * tmask(ji,jj,jk) 
    272        END DO 
    273     END DO 
    274       END DO 
    275        
    276       ! compute mixed-layer depth : rmld 
    277        
    278       rmld(:,:) = 0. 
    279       DO jk = 1, jpktrd 
    280          rmld(:,:) = rmld(:,:) + zwkx(:,:,jk) 
    281       END DO 
    282        
    283       ! compute PDF 
    284  
    285       DO jk = 1, jpktrd 
    286          zwkx(:,:,jk) = zwkx(:,:,jk) / MAX( 1., rmld(:,:) ) 
    287       END DO 
    288  
    289       IF( idebug /= 0 ) THEN 
    290          WRITE(numout,*) ' debuging trd_mld: I.2 done '   
    291          CALL FLUSH(numout) 
    292       ENDIF 
    293  
    294  
    295       ! I.3 vertically integrated T and S 
    296       ! --------------------------------- 
    297  
    298       tml(:,:) = 0. 
    299       sml(:,:) = 0. 
    300  
    301       DO jk = 1, jpktrd - 1 
    302          tml(:,:) = tml(:,:) + zwkx(:,:,jk) * tn(:,:,jk) 
    303          sml(:,:) = sml(:,:) + zwkx(:,:,jk) * sn(:,:,jk)  
    304       END DO 
    305  
    306       IF(idebug /= 0) THEN 
    307          WRITE(numout,*) ' debuging trd_mld: I.3 done'   
    308          CALL FLUSH(numout) 
    309       ENDIF 
    310  
    311  
    312       !  =================================== 
    313       !   II. netCDF output initialization 
    314       !  =================================== 
    315  
    316 #if defined key_dimgout  
    317  
    318 #else 
    319 #include "trdmld_ncinit.h90" 
     326   END SUBROUTINE trd_mld_zint 
     327 
     328 
     329 
     330   SUBROUTINE trd_mld( kt ) 
     331      !!---------------------------------------------------------------------- 
     332      !!                  ***  ROUTINE trd_mld  *** 
     333      !!  
     334      !! ** Purpose :  computation of cumulated trends over analysis period 
     335      !!               and make outputs (NetCDF or DIMG format) 
     336      !! 
     337      !! ** Method/usage : 
     338      !! 
     339      !! History : 
     340      !!   9.0  !  04-08  (C. Talandier) New trends organization 
     341      !!---------------------------------------------------------------------- 
     342      !! * Arguments 
     343      INTEGER, INTENT( in ) ::   kt   ! ocean time-step index 
     344 
     345      !! * Local declarations 
     346      INTEGER :: ji, jj, jk, jl, ik, it 
     347 
     348      REAL(wp) :: zmean, zavt 
     349 
     350      REAL(wp) ,DIMENSION(jpi,jpj) ::   & 
     351         ztmltot, ztmlres,              & 
     352         zsmltot, zsmlres,              &  
     353         z2d 
     354 
     355#if defined key_dimgout 
     356      INTEGER ::  iyear,imon,iday 
     357      CHARACTER(LEN=80) :: cltext, clmode 
    320358#endif 
    321  
    322       IF( idebug /= 0 ) THEN 
    323          WRITE(numout,*) ' debuging trd_mld: II. done'   
    324          CALL FLUSH(numout) 
    325       ENDIF 
    326  
    327       !  ==================================================== 
    328       !   III. vertical integration of trends in mixed-layer 
    329       !  ==================================================== 
    330  
    331  
    332       ! III.0 initializations 
    333       ! --------------------- 
    334  
    335       tmltrd(:,:,:) = 0.e0 
    336       smltrd(:,:,:) = 0.e0 
    337  
    338       IF( idebug /= 0 ) THEN 
    339          WRITE(numout,*) ' debuging trd_mld: III.0 done'   
    340          CALL FLUSH(numout) 
    341       ENDIF 
    342  
    343  
    344       ! III.1 vertical integration of 3D trends 
    345       ! --------------------------------------- 
    346        
    347       DO jk = 1,jpktrd 
    348  
    349          ! Temperature 
    350          tmltrd(:,:,1) = tmltrd(:,:,1) + ttrdh(:,:,jk,1) * zwkx(:,:,jk)   ! zonal advection 
    351          tmltrd(:,:,2) = tmltrd(:,:,2) + ttrdh(:,:,jk,2) * zwkx(:,:,jk)   ! meridional advection 
    352          tmltrd(:,:,3) = tmltrd(:,:,3) + ttrd (:,:,jk,2) * zwkx(:,:,jk)   ! vertical advection 
    353          tmltrd(:,:,4) = tmltrd(:,:,4) + ttrd (:,:,jk,3) * zwkx(:,:,jk)   ! lateral diffusion (hor. part) 
    354          tmltrd(:,:,5) = tmltrd(:,:,5) + ttrd (:,:,jk,7) * zwkx(:,:,jk)   ! forcing (penetrative) 
    355          IF( l_traldf_iso ) THEN 
    356             tmltrd(:,:,7) = tmltrd(:,:,7) + ttrd (:,:,jk,4) * zwkx(:,:,jk)   ! lateral diffusion (explicit  
    357             !                                                                ! vert. part (isopycnal diff.) 
    358          ENDIF 
    359 !#if defined key_traldf_eiv 
    360        ! tmltrd(:,:,8 ) = tmltrdg(:,:,8) + ttrdh(:,:,jk,3) * zwkx(:,:,jk)   ! eddy induced zonal advection 
    361        ! tmltrd(:,:,9 ) = tmltrdg(:,:,9) + ttrdh(:,:,jk,4) * zwkx(:,:,jk)   ! eddy induced merid. advection 
    362        ! tmltrd(:,:,10) = tmltrdg(:,:,10) + ttrd(:,:,jk,6) * zwkx(:,:,jk)  ! eddy induced vert. advection 
    363 !#endif 
    364  
    365          ! Salinity 
    366          smltrd(:,:,1) = smltrd(:,:,1) + strdh(:,:,jk,1) * zwkx(:,:,jk)   ! zonal advection 
    367          smltrd(:,:,2) = smltrd(:,:,2) + strdh(:,:,jk,2) * zwkx(:,:,jk)   ! meridional advection 
    368          smltrd(:,:,3) = smltrd(:,:,3) + strd (:,:,jk,2) * zwkx(:,:,jk)   ! vertical advection 
    369          smltrd(:,:,4) = smltrd(:,:,4) + strd (:,:,jk,3) * zwkx(:,:,jk)   ! lateral diffusion (hor. part) 
    370          IF( l_traldf_iso ) THEN 
    371             smltrd(:,:,7) = smltrd(:,:,7) + strd (:,:,jk,4) * zwkx(:,:,jk)   ! lateral diffusion (explicit  
    372             !                                                                ! vert. part (isopycnal diff.) 
    373          ENDIF 
    374 !#if defined key_traldf_eiv 
    375        ! smltrd(:,:,8) = smltrdg(:,:,8) + strdh(:,:,jk,3) * zwkx(:,:,jk)   ! eddy induced zonal advection 
    376        ! smltrd(:,:,9) = smltrdg(:,:,9) + strdh(:,:,jk,4) * zwkx(:,:,jk)   ! eddy induced merid. advection 
    377        ! smltrd(:,:,10) = smltrdg(:,:,10) + strd(:,:,jk,6) * zwkx(:,:,jk)   ! eddy induced vert. advection 
    378 !#endif 
    379  
    380       END DO 
    381  
    382  
    383       IF( idebug /= 0 ) THEN 
    384          IF(lwp) WRITE(numout,*) ' debuging trd_mld: III.1 done'   
    385          CALL FLUSH(numout) 
    386       ENDIF 
    387  
    388  
    389       ! III.2 trends terms at upper and lower boundaries of mixed-layer 
    390       ! --------------------------------------------------------------- 
     359      !!---------------------------------------------------------------------- 
     360 
     361      ! I. trends terms at lower boundary of mixed-layer 
     362      ! ------------------------------------------------ 
    391363 
    392364      DO jj = 1,jpj 
     
    396368             
    397369            ! Temperature 
    398              
    399             ! forcing (non penetrative) 
    400             tmltrd(ji,jj,5) = tmltrd(ji,jj,5) + flxtrd(ji,jj,1) * zwkx(ji,jj,1) 
    401370            ! entrainment due to vertical diffusion 
    402371            !       - due to vertical mixing scheme (TKE) 
    403372            zavt = avt(ji,jj,ik) 
    404             tmltrd(ji,jj,6) = - 1. * zavt / fse3w(ji,jj,ik) * tmask(ji,jj,ik)   & 
    405                                    * ( tn(ji,jj,ik-1) - tn(ji,jj,ik) )   & 
    406                                    / MAX( 1., rmld(ji,jj) ) * tmask(ji,jj,1) 
    407  
     373            tmltrd(ji,jj,jpmldevd) = - 1. * zavt / fse3w(ji,jj,ik) * tmask(ji,jj,ik)   & 
     374               &                   * ( tn(ji,jj,ik-1) - tn(ji,jj,ik) )   & 
     375               &                   / MAX( 1., rmld(ji,jj) ) * tmask(ji,jj,1) 
    408376            ! Salinity 
    409  
    410             ! forcing 
    411             smltrd(ji,jj,5) = flxtrd(ji,jj,2) * zwkx(ji,jj,1) 
    412377            ! entrainment due to vertical diffusion 
    413378            !       - due to vertical mixing scheme (TKE) 
    414379            zavt = fsavs(ji,jj,ik) 
    415             smltrd(ji,jj,6) = -1. * zavt / fse3w(ji,jj,ik) * tmask(ji,jj,ik)   & 
     380            smltrd(ji,jj,jpmldevd) = -1. * zavt / fse3w(ji,jj,ik) * tmask(ji,jj,ik)   & 
    416381               &                  * ( sn(ji,jj,ik-1) - sn(ji,jj,ik) )   & 
    417382               &                  / MAX( 1., rmld(ji,jj) ) * tmask(ji,jj,1) 
     
    420385 
    421386      IF( l_traldf_iso ) THEN 
    422 !!Clem On retire de la diffusion verticale TOTALE calculee par tmltrd(:,:,7) 
    423 !!Clem ds trazdf.isopycnal et implicit, la partie verticale due au Kz afin de ne garder 
    424 !!Clem effectivement que la diffusion verticale isopycnale (ie composante de la 
    425 !!Clem diff isopycnale sur la verticale) : 
    426             tmltrd(:,:,7) = tmltrd(:,:,7) - tmltrd(:,:,6)   ! - due to isopycnal mixing scheme (implicit part) 
    427             smltrd(:,:,7) = smltrd(:,:,7) - smltrd(:,:,6)   ! - due to isopycnal mixing scheme (implicit part) 
     387         ! We substract to the TOTAL vertical diffusion tmltrd(:,:,jpmldzdf)  
     388         ! computed in subroutines trazdf_iso.F90 or trazdf_imp.F90 
     389         ! the vertical part du to the Kz in order to keep only the vertical 
     390         ! isopycnal diffusion (i.e the isopycnal diffusion componant on the vertical): 
     391         tmltrd(:,:,jpmldzdf) = tmltrd(:,:,jpmldzdf) - tmltrd(:,:,jpmldevd)   ! - due to isopycnal mixing scheme (implicit part) 
     392         smltrd(:,:,jpmldzdf) = smltrd(:,:,jpmldzdf) - smltrd(:,:,jpmldevd)   ! - due to isopycnal mixing scheme (implicit part) 
    428393      ENDIF 
    429394 
     
    435400 
    436401      IF( idebug /= 0 ) THEN 
    437          WRITE(numout,*) ' debuging trd_mld: III.2 done'   
     402         WRITE(numout,*) ' debuging trd_mld: I. done'   
    438403         CALL FLUSH(numout) 
    439404      ENDIF 
    440405 
    441 #if defined key_trabbl_dif 
    442       ! III.3 trends terms from beckman over-flow parameterization 
    443       ! ---------------------------------------------------------- 
    444  
    445       DO jj = 1,jpj 
    446          DO ji = 1,jpi 
    447             ikb = MAX( mbathy(ji,jj)-1, 1 ) 
    448             ! beckmann component -> horiz. part of lateral diffusion 
    449             tmltrd(ji,jj,4) = tmltrd(ji,jj,4) + bbltrd(ji,jj,1) * zwkx(ji,jj,ikb) 
    450             smltrd(ji,jj,4) = smltrd(ji,jj,4) + bbltrd(ji,jj,2) * zwkx(ji,jj,ikb) 
    451          END DO 
     406      !  ================================= 
     407      !   II. Cumulated trends 
     408      !  ================================= 
     409 
     410      ! II.1 set before values of vertically average T and S  
     411      ! --------------------------------------------------- 
     412 
     413      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 
     424      DO jk = 1, jpktrd - 1 
     425         tml(:,:) = tml(:,:) + wkx(:,:,jk) * tn(:,:,jk) 
     426         sml(:,:) = sml(:,:) + wkx(:,:,jk) * sn(:,:,jk)  
    452427      END DO 
    453        
    454 #endif 
    455  
    456       IF( idebug /= 0 ) THEN 
    457          WRITE(numout,*) ' debuging trd_mld: III.3 done'   
     428 
     429      IF(idebug /= 0) THEN 
     430         WRITE(numout,*) ' debuging trd_mld: II.2 done'   
    458431         CALL FLUSH(numout) 
    459432      ENDIF 
    460433 
    461  
    462       !  ================================= 
    463       !   IV. Cumulated trends 
    464       !  ================================= 
    465  
    466  
    467  
    468       ! IV.1 set `before' mixed layer values for kt = nit000+1 
     434      ! II.3 set `before' mixed layer values for kt = nit000+1 
    469435      ! -------------------------------------------------------- 
    470436 
     
    477443 
    478444      IF( idebug /= 0 ) THEN 
    479          WRITE(numout,*) ' debuging trd_mld: IV.1 done'   
     445         WRITE(numout,*) ' debuging trd_mld: II.3 done'   
    480446         CALL FLUSH(numout) 
    481447      ENDIF 
    482448 
    483  
    484       ! IV.2 cumulated trends over analysis period (kt=2 to nwrite) 
    485       ! ---------------------- 
     449      ! II.4 cumulated trends over analysis period (kt=2 to nwrite) 
     450      ! ----------------------------------------------------------- 
    486451 
    487452      ! trends cumulated over nwrite-2 time steps 
     
    496461 
    497462      IF( idebug /= 0 ) THEN 
    498          WRITE(numout,*) ' debuging trd_mld: IV.2 done'   
     463         WRITE(numout,*) ' debuging trd_mld: II.4 done'   
    499464         CALL FLUSH(numout) 
    500465      ENDIF 
    501466 
    502  
    503467      !  ============================================= 
    504       !   V. Output in netCDF + residual computation 
     468      !   III. Output in netCDF + residual computation 
    505469      !  ============================================= 
    506470 
     
    512476      IF( MOD( kt - nit000+1, nwrite ) == 0 ) THEN 
    513477 
    514          ! V.1 compute total trend  
     478         ! III.1 compute total trend  
    515479         ! ------------------------ 
    516480 
     
    522486         IF(idebug /= 0) THEN 
    523487            WRITE(numout,*) ' zmean = ',zmean   
    524             WRITE(numout,*) ' debuging trd_mld: V.1 done'   
     488            WRITE(numout,*) ' debuging trd_mld: III.1 done'   
    525489            CALL FLUSH(numout) 
    526490         ENDIF 
    527491           
    528492 
    529          ! V.2 compute residual  
     493         ! III.2 compute residual  
    530494         ! --------------------- 
    531495 
     
    542506 
    543507         IF( idebug /= 0 ) THEN 
    544             WRITE(numout,*) ' debuging trd_mld: V.2 done'   
     508            WRITE(numout,*) ' debuging trd_mld: III.2 done'   
    545509            CALL FLUSH(numout) 
    546510         ENDIF 
    547511 
    548512 
    549          ! V.3 time evolution array swap 
     513         ! III.3 time evolution array swap 
    550514         ! ------------------------------ 
    551515 
     
    556520 
    557521         IF( idebug /= 0 ) THEN 
    558             WRITE(numout,*) ' debuging trd_mld: V.3 done'   
     522            WRITE(numout,*) ' debuging trd_mld: III.3 done'   
    559523            CALL FLUSH(numout) 
    560524         ENDIF 
    561525 
    562526 
    563          ! V.4 zero cumulative array 
     527         ! III.4 zero cumulative array 
    564528         ! --------------------------- 
    565529 
     
    570534 
    571535          IF(idebug /= 0) THEN 
    572               WRITE(numout,*) ' debuging trd_mld: IV.4 done'   
     536              WRITE(numout,*) ' debuging trd_mld: III.4 done'   
    573537              CALL FLUSH(numout) 
    574538          ENDIF 
     
    576540      ENDIF 
    577541 
    578       ! IV.5 write trends to output 
     542      ! III.5 write trends to output 
    579543      ! --------------------------- 
    580544 
     
    595559      IF( kt >=  nit000+1 ) THEN 
    596560 
    597 #include "trdmld_ncwrite.h90" 
     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( l_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( l_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) 
     612#endif 
    598613 
    599614         IF( idebug /= 0 ) THEN 
    600             WRITE(numout,*) ' debuging trd_mld: IV.5 done'   
     615            WRITE(numout,*) ' debuging trd_mld: III.5 done'   
    601616            CALL FLUSH(numout) 
    602617         ENDIF 
    603618 
    604       ENDIF 
     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 
    605629 
    606630      IF( kt == nitend )   CALL histclo( nidtrd ) 
     
    608632 
    609633   END SUBROUTINE trd_mld 
     634 
     635 
     636 
     637   SUBROUTINE trd_mld_init 
     638      !!---------------------------------------------------------------------- 
     639      !!                  ***  ROUTINE trd_mld_init  *** 
     640      !!  
     641      !! ** Purpose :   computation of vertically integrated T and S budgets 
     642      !!      from ocean surface down to control surface (NetCDF output) 
     643      !! 
     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 
     652      !!---------------------------------------------------------------------- 
     653      !! * Local declarations 
     654      INTEGER :: ilseq 
     655 
     656      REAL(wp) ::   zjulian, zsto, zout 
     657 
     658      CHARACTER (LEN=21) ::   & 
     659         clold ='OLD'        , & ! open specifier (direct access files) 
     660         clunf ='UNFORMATTED', & ! open specifier (direct access files) 
     661         clseq ='SEQUENTIAL'     ! open specifier (direct access files) 
     662      CHARACTER (LEN=40) ::   clhstnam 
     663      CHARACTER (LEN=40) ::   clop 
     664      CHARACTER (LEN=12) ::   clmxl 
     665 
     666      NAMELIST/namtrd/ ntrd, nctls 
     667      !!---------------------------------------------------------------------- 
     668 
     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 ) 
     682 
     683      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 
     694      nmoymltrd = 0 
     695      tmltrdm(:,:) = 0.e0 
     696      smltrdm(:,:) = 0.e0 
     697 
     698      !  read control surface from file ctlsurf_idx 
     699 
     700      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      !  =================================== 
     717 
     718#if defined key_dimgout  
     719 
     720#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  
     728         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      !----------------------------------------- 
     735      ! II.1 Define frequency of output and means 
     736      ! ----------------------------------------- 
     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' 
     748 
     749      ! II.2 Compute julian date from starting date of the run 
     750      ! ------------------------ 
     751 
     752      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 
     757 
     758 
     759      ! II.3 Define the T grid trend file (nidtrd) 
     760      ! --------------------------------- 
     761 
     762      CALL dia_nam( clhstnam, nwrite, 'trends' )                  ! filename 
     763      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) 
     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( l_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( l_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 
     843      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 
    610853 
    611854#else 
     
    615858   LOGICAL, PUBLIC, PARAMETER ::   lk_trdmld = .FALSE.   !: momentum trend flag 
    616859CONTAINS 
    617    SUBROUTINE trd_mld( kt )        ! Empty routine 
     860   SUBROUTINE trd_mld( kt )             ! Empty routine 
     861      INTEGER, INTENT( in) ::   kt 
    618862      WRITE(*,*) 'trd_mld: You should not have seen this print! error?', kt 
    619863   END SUBROUTINE trd_mld 
     864   SUBROUTINE trd_mld_zint( pttrdmld, pstrdmld, ktrd, ctype ) 
     865      REAL, DIMENSION(:,:,:), INTENT( in ) ::   & 
     866         pttrdmld, pstrdmld                   ! Temperature and Salinity trends 
     867      INTEGER, INTENT( in ) ::   ktrd         ! ocean trend index 
     868      CHARACTER(len=2), INTENT( in ) ::   &   
     869         ctype                                ! surface/bottom (2D arrays) or 
     870         !                                    ! interior (3D arrays) physics 
     871      WRITE(*,*) 'trd_mld_zint: You should not have seen this print! error?', pttrdmld(1,1,1) 
     872      WRITE(*,*) '  "      "  : You should not have seen this print! error?', pstrdmld(1,1,1) 
     873      WRITE(*,*) '  "      "  : You should not have seen this print! error?', ctype 
     874      WRITE(*,*) '  "      "  : You should not have seen this print! error?', ktrd 
     875   END SUBROUTINE trd_mld_zint 
     876   SUBROUTINE trd_mld_init              ! Empty routine 
     877      WRITE(*,*) 'trd_mld_init: You should not have seen this print! error?' 
     878   END SUBROUTINE trd_mld_init 
    620879#endif 
    621880 
Note: See TracChangeset for help on using the changeset viewer.