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 11949 for NEMO/branches/2019/dev_r11943_MERGE_2019/tests/CANAL/MY_SRC/diawri.F90 – NEMO

Ignore:
Timestamp:
2019-11-22T15:29:17+01:00 (4 years ago)
Author:
acc
Message:

Merge in changes from 2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps. This just creates a fresh copy of this branch to use as the merge base. See ticket #2341

Location:
NEMO/branches/2019/dev_r11943_MERGE_2019/tests
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/dev_r11943_MERGE_2019/tests

    • Property svn:mergeinfo deleted
  • NEMO/branches/2019/dev_r11943_MERGE_2019/tests/CANAL/MY_SRC/diawri.F90

    r11536 r11949  
    5757   USE lib_mpp         ! MPP library 
    5858   USE timing          ! preformance summary 
    59    USE diurnal_bulk    ! diurnal warm layer 
    60    USE cool_skin       ! Cool skin 
     59   USE diu_bulk        ! diurnal warm layer 
     60   USE diu_coolskin    ! Cool skin 
    6161 
    6262   IMPLICIT NONE 
     
    9797 
    9898    
    99    SUBROUTINE dia_wri( kt ) 
     99   SUBROUTINE dia_wri( kt, Kmm ) 
    100100      !!--------------------------------------------------------------------- 
    101101      !!                  ***  ROUTINE dia_wri  *** 
     
    107107      !!---------------------------------------------------------------------- 
    108108      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index 
     109      INTEGER, INTENT( in ) ::   Kmm     ! ocean time level index 
    109110      !! 
    110111      INTEGER ::   ji, jj, jk       ! dummy loop indices 
     
    115116      REAL(wp), DIMENSION(jpi,jpj)     ::   z2d   ! 2D workspace 
    116117      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   z3d   ! 3D workspace 
    117       REAL(wp), DIMENSION(jpi,jpj,jpk) ::   bu, bv   ! volume of u- and v-boxes 
    118       REAL(wp), DIMENSION(jpi,jpj,jpk) ::   r1_bt    ! inverse of t-box volume 
    119118      !!---------------------------------------------------------------------- 
    120119      !  
     
    123122      ! Output the initial state and forcings 
    124123      IF( ninist == 1 ) THEN                        
    125          CALL dia_wri_state( 'output.init' ) 
     124         CALL dia_wri_state( Kmm, 'output.init' ) 
    126125         ninist = 0 
    127126      ENDIF 
     
    132131      CALL iom_put("e3v_0", e3v_0(:,:,:) ) 
    133132      ! 
    134       CALL iom_put( "e3t" , e3t_n(:,:,:) ) 
    135       CALL iom_put( "e3u" , e3u_n(:,:,:) ) 
    136       CALL iom_put( "e3v" , e3v_n(:,:,:) ) 
    137       CALL iom_put( "e3w" , e3w_n(:,:,:) ) 
     133      CALL iom_put( "e3t" , e3t(:,:,:,Kmm) ) 
     134      CALL iom_put( "e3u" , e3u(:,:,:,Kmm) ) 
     135      CALL iom_put( "e3v" , e3v(:,:,:,Kmm) ) 
     136      CALL iom_put( "e3w" , e3w(:,:,:,Kmm) ) 
    138137      IF( iom_use("e3tdef") )   & 
    139          CALL iom_put( "e3tdef"  , ( ( e3t_n(:,:,:) - e3t_0(:,:,:) ) / e3t_0(:,:,:) * 100 * tmask(:,:,:) ) ** 2 ) 
     138         CALL iom_put( "e3tdef"  , ( ( e3t(:,:,:,Kmm) - e3t_0(:,:,:) ) / e3t_0(:,:,:) * 100 * tmask(:,:,:) ) ** 2 ) 
    140139 
    141140      IF( ll_wd ) THEN 
    142          CALL iom_put( "ssh" , (sshn+ssh_ref)*tmask(:,:,1) )   ! sea surface height (brought back to the reference used for wetting and drying) 
     141         CALL iom_put( "ssh" , (ssh(:,:,Kmm)+ssh_ref)*tmask(:,:,1) )   ! sea surface height (brought back to the reference used for wetting and drying) 
    143142      ELSE 
    144          CALL iom_put( "ssh" , sshn )              ! sea surface height 
     143         CALL iom_put( "ssh" , ssh(:,:,Kmm) )              ! sea surface height 
    145144      ENDIF 
    146145 
    147146      IF( iom_use("wetdep") )   &                  ! wet depth 
    148          CALL iom_put( "wetdep" , ht_0(:,:) + sshn(:,:) ) 
     147         CALL iom_put( "wetdep" , ht_0(:,:) + ssh(:,:,Kmm) ) 
    149148       
    150       CALL iom_put( "toce", tsn(:,:,:,jp_tem) )    ! 3D temperature 
    151       CALL iom_put(  "sst", tsn(:,:,1,jp_tem) )    ! surface temperature 
     149      CALL iom_put( "toce", ts(:,:,:,jp_tem,Kmm) )    ! 3D temperature 
     150      CALL iom_put(  "sst", ts(:,:,1,jp_tem,Kmm) )    ! surface temperature 
    152151      IF ( iom_use("sbt") ) THEN 
    153152         DO jj = 1, jpj 
    154153            DO ji = 1, jpi 
    155154               ikbot = mbkt(ji,jj) 
    156                z2d(ji,jj) = tsn(ji,jj,ikbot,jp_tem) 
     155               z2d(ji,jj) = ts(ji,jj,ikbot,jp_tem,Kmm) 
    157156            END DO 
    158157         END DO 
     
    160159      ENDIF 
    161160       
    162       CALL iom_put( "soce", tsn(:,:,:,jp_sal) )    ! 3D salinity 
    163       CALL iom_put(  "sss", tsn(:,:,1,jp_sal) )    ! surface salinity 
     161      CALL iom_put( "soce", ts(:,:,:,jp_sal,Kmm) )    ! 3D salinity 
     162      CALL iom_put(  "sss", ts(:,:,1,jp_sal,Kmm) )    ! surface salinity 
    164163      IF ( iom_use("sbs") ) THEN 
    165164         DO jj = 1, jpj 
    166165            DO ji = 1, jpi 
    167166               ikbot = mbkt(ji,jj) 
    168                z2d(ji,jj) = tsn(ji,jj,ikbot,jp_sal) 
     167               z2d(ji,jj) = ts(ji,jj,ikbot,jp_sal,Kmm) 
    169168            END DO 
    170169         END DO 
     
    177176         DO jj = 2, jpjm1 
    178177            DO ji = fs_2, fs_jpim1   ! vector opt. 
    179                zztmp2 = (  ( rCdU_bot(ji+1,jj)+rCdU_bot(ji  ,jj) ) * un(ji  ,jj,mbku(ji  ,jj))  )**2   & 
    180                   &   + (  ( rCdU_bot(ji  ,jj)+rCdU_bot(ji-1,jj) ) * un(ji-1,jj,mbku(ji-1,jj))  )**2   & 
    181                   &   + (  ( rCdU_bot(ji,jj+1)+rCdU_bot(ji,jj  ) ) * vn(ji,jj  ,mbkv(ji,jj  ))  )**2   & 
    182                   &   + (  ( rCdU_bot(ji,jj  )+rCdU_bot(ji,jj-1) ) * vn(ji,jj-1,mbkv(ji,jj-1))  )**2 
     178               zztmp2 = (  ( rCdU_bot(ji+1,jj)+rCdU_bot(ji  ,jj) ) * uu(ji  ,jj,mbku(ji  ,jj),Kmm)  )**2   & 
     179                  &   + (  ( rCdU_bot(ji  ,jj)+rCdU_bot(ji-1,jj) ) * uu(ji-1,jj,mbku(ji-1,jj),Kmm)  )**2   & 
     180                  &   + (  ( rCdU_bot(ji,jj+1)+rCdU_bot(ji,jj  ) ) * vv(ji,jj  ,mbkv(ji,jj  ),Kmm)  )**2   & 
     181                  &   + (  ( rCdU_bot(ji,jj  )+rCdU_bot(ji,jj-1) ) * vv(ji,jj-1,mbkv(ji,jj-1),Kmm)  )**2 
    183182               z2d(ji,jj) = zztmp * SQRT( zztmp2 ) * tmask(ji,jj,1)  
    184183               ! 
     
    189188      ENDIF 
    190189          
    191       CALL iom_put( "uoce", un(:,:,:) )            ! 3D i-current 
    192       CALL iom_put(  "ssu", un(:,:,1) )            ! surface i-current 
     190      CALL iom_put( "uoce", uu(:,:,:,Kmm) )            ! 3D i-current 
     191      CALL iom_put(  "ssu", uu(:,:,1,Kmm) )            ! surface i-current 
    193192      IF ( iom_use("sbu") ) THEN 
    194193         DO jj = 1, jpj 
    195194            DO ji = 1, jpi 
    196195               ikbot = mbku(ji,jj) 
    197                z2d(ji,jj) = un(ji,jj,ikbot) 
     196               z2d(ji,jj) = uu(ji,jj,ikbot,Kmm) 
    198197            END DO 
    199198         END DO 
     
    201200      ENDIF 
    202201       
    203       CALL iom_put( "voce", vn(:,:,:) )            ! 3D j-current 
    204       CALL iom_put(  "ssv", vn(:,:,1) )            ! surface j-current 
     202      CALL iom_put( "voce", vv(:,:,:,Kmm) )            ! 3D j-current 
     203      CALL iom_put(  "ssv", vv(:,:,1,Kmm) )            ! surface j-current 
    205204      IF ( iom_use("sbv") ) THEN 
    206205         DO jj = 1, jpj 
    207206            DO ji = 1, jpi 
    208207               ikbot = mbkv(ji,jj) 
    209                z2d(ji,jj) = vn(ji,jj,ikbot) 
     208               z2d(ji,jj) = vv(ji,jj,ikbot,Kmm) 
    210209            END DO 
    211210         END DO 
     
    213212      ENDIF 
    214213 
    215       CALL iom_put( "woce", wn )                   ! vertical velocity 
     214      CALL iom_put( "woce", ww )                   ! vertical velocity 
    216215      IF( iom_use('w_masstr') .OR. iom_use('w_masstr2') ) THEN   ! vertical mass transport & its square value 
    217216         ! Caution: in the VVL case, it only correponds to the baroclinic mass transport. 
    218217         z2d(:,:) = rau0 * e1e2t(:,:) 
    219218         DO jk = 1, jpk 
    220             z3d(:,:,jk) = wn(:,:,jk) * z2d(:,:) 
     219            z3d(:,:,jk) = ww(:,:,jk) * z2d(:,:) 
    221220         END DO 
    222221         CALL iom_put( "w_masstr" , z3d )   
     
    236235            DO jj = 2, jpjm1                                    ! sal gradient 
    237236               DO ji = fs_2, fs_jpim1   ! vector opt. 
    238                   zztmp  = tsn(ji,jj,jk,jp_sal) 
    239                   zztmpx = ( tsn(ji+1,jj,jk,jp_sal) - zztmp ) * r1_e1u(ji,jj) + ( zztmp - tsn(ji-1,jj  ,jk,jp_sal) ) * r1_e1u(ji-1,jj) 
    240                   zztmpy = ( tsn(ji,jj+1,jk,jp_sal) - zztmp ) * r1_e2v(ji,jj) + ( zztmp - tsn(ji  ,jj-1,jk,jp_sal) ) * r1_e2v(ji,jj-1) 
     237                  zztmp  = ts(ji,jj,jk,jp_sal,Kmm) 
     238                  zztmpx = ( ts(ji+1,jj,jk,jp_sal,Kmm) - zztmp ) * r1_e1u(ji,jj) + ( zztmp - ts(ji-1,jj  ,jk,jp_sal,Kmm) ) * r1_e1u(ji-1,jj) 
     239                  zztmpy = ( ts(ji,jj+1,jk,jp_sal,Kmm) - zztmp ) * r1_e2v(ji,jj) + ( zztmp - ts(ji  ,jj-1,jk,jp_sal,Kmm) ) * r1_e2v(ji,jj-1) 
    241240                  z3d(ji,jj,jk) = 0.25 * ( zztmpx * zztmpx + zztmpy * zztmpy )   & 
    242241                     &                 * umask(ji,jj,jk) * umask(ji-1,jj,jk) * vmask(ji,jj,jk) * umask(ji,jj-1,jk) 
     
    253252         DO jj = 2, jpjm1                                    ! sst gradient 
    254253            DO ji = fs_2, fs_jpim1   ! vector opt. 
    255                zztmp  = tsn(ji,jj,1,jp_tem) 
    256                zztmpx = ( tsn(ji+1,jj,1,jp_tem) - zztmp ) * r1_e1u(ji,jj) + ( zztmp - tsn(ji-1,jj  ,1,jp_tem) ) * r1_e1u(ji-1,jj) 
    257                zztmpy = ( tsn(ji,jj+1,1,jp_tem) - zztmp ) * r1_e2v(ji,jj) + ( zztmp - tsn(ji  ,jj-1,1,jp_tem) ) * r1_e2v(ji,jj-1) 
     254               zztmp  = ts(ji,jj,1,jp_tem,Kmm) 
     255               zztmpx = ( ts(ji+1,jj,1,jp_tem,Kmm) - zztmp ) * r1_e1u(ji,jj) + ( zztmp - ts(ji-1,jj  ,1,jp_tem,Kmm) ) * r1_e1u(ji-1,jj) 
     256               zztmpy = ( ts(ji,jj+1,1,jp_tem,Kmm) - zztmp ) * r1_e2v(ji,jj) + ( zztmp - ts(ji  ,jj-1,1,jp_tem,Kmm) ) * r1_e2v(ji,jj-1) 
    258257               z2d(ji,jj) = 0.25 * ( zztmpx * zztmpx + zztmpy * zztmpy )   & 
    259258                  &              * umask(ji,jj,1) * umask(ji-1,jj,1) * vmask(ji,jj,1) * umask(ji,jj-1,1) 
     
    272271            DO jj = 1, jpj 
    273272               DO ji = 1, jpi 
    274                   z2d(ji,jj) = z2d(ji,jj) + e3t_n(ji,jj,jk) * tsn(ji,jj,jk,jp_tem) * tmask(ji,jj,jk) 
     273                  z2d(ji,jj) = z2d(ji,jj) + e3t(ji,jj,jk,Kmm) * ts(ji,jj,jk,jp_tem,Kmm) * tmask(ji,jj,jk) 
    275274               END DO 
    276275            END DO 
     
    284283            DO jj = 1, jpj 
    285284               DO ji = 1, jpi 
    286                   z2d(ji,jj) = z2d(ji,jj) + e3t_n(ji,jj,jk) * tsn(ji,jj,jk,jp_sal) * tmask(ji,jj,jk) 
     285                  z2d(ji,jj) = z2d(ji,jj) + e3t(ji,jj,jk,Kmm) * ts(ji,jj,jk,jp_sal,Kmm) * tmask(ji,jj,jk) 
    287286               END DO 
    288287            END DO 
     
    296295            DO jj = 1, jpj 
    297296               DO ji = 1, jpi 
    298                   z2d(ji,jj) = z2d(ji,jj) + e3t_n(ji,jj,jk) * tsn(ji,jj,jk,jp_sal) * tsn(ji,jj,jk,jp_sal) * tmask(ji,jj,jk) 
     297                  z2d(ji,jj) = z2d(ji,jj) + e3t(ji,jj,jk,Kmm) * ts(ji,jj,jk,jp_sal,Kmm) * ts(ji,jj,jk,jp_sal,Kmm) * tmask(ji,jj,jk) 
    299298               END DO 
    300299            END DO 
     
    306305         z3d(:,:,jpk) = 0._wp  
    307306         DO jk = 1, jpkm1 
    308             DO jj = 2, jpj 
    309                DO ji = 2, jpi 
    310                   zztmpx = 0.5 * ( un(ji-1,jj  ,jk) + un(ji,jj,jk) ) 
    311                   zztmpy = 0.5 * ( vn(ji  ,jj-1,jk) + vn(ji,jj,jk) ) 
    312                   z3d(ji,jj,jk) = 0.5 * ( zztmpx*zztmpx + zztmpy*zztmpy ) 
     307            DO jj = 2, jpjm1 
     308               DO ji = fs_2, fs_jpim1   ! vector opt. 
     309                  zztmp  = 0.25_wp * r1_e1e2t(ji,jj) / e3t(ji,jj,jk,Kmm) 
     310                  z3d(ji,jj,jk) = zztmp * (  uu(ji-1,jj,jk,Kmm)**2 * e2u(ji-1,jj) * e3u(ji-1,jj,jk,Kmm)   & 
     311                     &                     + uu(ji  ,jj,jk,Kmm)**2 * e2u(ji  ,jj) * e3u(ji  ,jj,jk,Kmm)   & 
     312                     &                     + vv(ji,jj-1,jk,Kmm)**2 * e1v(ji,jj-1) * e3v(ji,jj-1,jk,Kmm)   & 
     313                     &                     + vv(ji,jj  ,jk,Kmm)**2 * e1v(ji,jj  ) * e3v(ji,jj  ,jk,Kmm)   ) 
    313314               END DO 
    314315            END DO 
     
    326327            DO jj = 2, jpj 
    327328               DO ji = 2, jpi 
    328                   z3d(ji,jj,jk) = 0.25_wp * ( un(ji  ,jj,jk) * un(ji  ,jj,jk) * e1e2u(ji  ,jj) * e3u_n(ji  ,jj,jk)  & 
    329                      &                      + un(ji-1,jj,jk) * un(ji-1,jj,jk) * e1e2u(ji-1,jj) * e3u_n(ji-1,jj,jk)  & 
    330                      &                      + vn(ji,jj  ,jk) * vn(ji,jj  ,jk) * e1e2v(ji,jj  ) * e3v_n(ji,jj  ,jk)  & 
    331                      &                      + vn(ji,jj-1,jk) * vn(ji,jj-1,jk) * e1e2v(ji,jj-1) * e3v_n(ji,jj-1,jk)  )  & 
    332                      &                    * r1_e1e2t(ji,jj) / e3t_n(ji,jj,jk) * tmask(ji,jj,jk) 
     329                  z3d(ji,jj,jk) = 0.25_wp * ( uu(ji  ,jj,jk,Kmm) * uu(ji  ,jj,jk,Kmm) * e1e2u(ji  ,jj) * e3u(ji  ,jj,jk,Kmm)  & 
     330                     &                      + uu(ji-1,jj,jk,Kmm) * uu(ji-1,jj,jk,Kmm) * e1e2u(ji-1,jj) * e3u(ji-1,jj,jk,Kmm)  & 
     331                     &                      + vv(ji,jj  ,jk,Kmm) * vv(ji,jj  ,jk,Kmm) * e1e2v(ji,jj  ) * e3v(ji,jj  ,jk,Kmm)  & 
     332                     &                      + vv(ji,jj-1,jk,Kmm) * vv(ji,jj-1,jk,Kmm) * e1e2v(ji,jj-1) * e3v(ji,jj-1,jk,Kmm)  )  & 
     333                     &                    * r1_e1e2t(ji,jj) / e3t(ji,jj,jk,Kmm) * tmask(ji,jj,jk) 
    333334               END DO 
    334335            END DO 
     
    342343            DO jj = 1, jpj 
    343344               DO ji = 1, jpi 
    344                   z2d(ji,jj) = z2d(ji,jj) + e3t_n(ji,jj,jk) * z3d(ji,jj,jk) * tmask(ji,jj,jk) 
     345                  z2d(ji,jj) = z2d(ji,jj) + e3t(ji,jj,jk,Kmm) * z3d(ji,jj,jk) * tmask(ji,jj,jk) 
    345346               END DO 
    346347            END DO 
     
    350351      ENDIF 
    351352      ! 
    352       CALL iom_put( "hdiv", hdivn )                  ! Horizontal divergence 
     353      CALL iom_put( "hdiv", hdiv )                  ! Horizontal divergence 
    353354 
    354355      IF ( iom_use("relvor") .OR. iom_use("absvor") .OR. iom_use("potvor") ) THEN 
     
    358359            DO jj = 1, jpjm1 
    359360               DO ji = 1, fs_jpim1   ! vector opt. 
    360                   z3d(ji,jj,jk) = (  e2v(ji+1,jj  ) * vn(ji+1,jj  ,jk) - e2v(ji,jj) * vn(ji,jj,jk)    & 
    361                      &              - e1u(ji  ,jj+1) * un(ji  ,jj+1,jk) + e1u(ji,jj) * un(ji,jj,jk)  ) * r1_e1e2f(ji,jj) 
     361                  z3d(ji,jj,jk) = (   e2v(ji+1,jj  ) * vv(ji+1,jj  ,jk,Kmm) - e2v(ji,jj) * vv(ji,jj,jk,Kmm)    & 
     362                     &              - e1u(ji  ,jj+1) * uu(ji  ,jj+1,jk,Kmm) + e1u(ji,jj) * uu(ji,jj,jk,Kmm)  ) * r1_e1e2f(ji,jj) 
    362363               END DO 
    363364            END DO 
     
    378379            DO jj = 1, jpjm1 
    379380               DO ji = 1, fs_jpim1   ! vector opt. 
    380                   ze3  = (  e3t_n(ji,jj+1,jk)*tmask(ji,jj+1,jk) + e3t_n(ji+1,jj+1,jk)*tmask(ji+1,jj+1,jk)   & 
    381                      &    + e3t_n(ji,jj  ,jk)*tmask(ji,jj  ,jk) + e3t_n(ji+1,jj  ,jk)*tmask(ji+1,jj  ,jk)  ) 
     381                  ze3  = (  e3t(ji,jj+1,jk,Kmm)*tmask(ji,jj+1,jk) + e3t(ji+1,jj+1,jk,Kmm)*tmask(ji+1,jj+1,jk)   & 
     382                     &    + e3t(ji,jj  ,jk,Kmm)*tmask(ji,jj  ,jk) + e3t(ji+1,jj  ,jk,Kmm)*tmask(ji+1,jj  ,jk)  ) 
    382383                  IF( ze3 /= 0._wp ) THEN   ;   ze3 = 4._wp / ze3 
    383384                  ELSE                      ;   ze3 = 0._wp 
     
    397398         z2d(:,:) = 0.e0 
    398399         DO jk = 1, jpkm1 
    399             z3d(:,:,jk) = rau0 * un(:,:,jk) * e2u(:,:) * e3u_n(:,:,jk) * umask(:,:,jk) 
     400            z3d(:,:,jk) = rau0 * uu(:,:,jk,Kmm) * e2u(:,:) * e3u(:,:,jk,Kmm) * umask(:,:,jk) 
    400401            z2d(:,:) = z2d(:,:) + z3d(:,:,jk) 
    401402         END DO 
     
    409410            DO jj = 2, jpjm1 
    410411               DO ji = fs_2, fs_jpim1   ! vector opt. 
    411                   z2d(ji,jj) = z2d(ji,jj) + z3d(ji,jj,jk) * ( tsn(ji,jj,jk,jp_tem) + tsn(ji+1,jj,jk,jp_tem) ) 
     412                  z2d(ji,jj) = z2d(ji,jj) + z3d(ji,jj,jk) * ( ts(ji,jj,jk,jp_tem,Kmm) + ts(ji+1,jj,jk,jp_tem,Kmm) ) 
    412413               END DO 
    413414            END DO 
     
    422423            DO jj = 2, jpjm1 
    423424               DO ji = fs_2, fs_jpim1   ! vector opt. 
    424                   z2d(ji,jj) = z2d(ji,jj) + z3d(ji,jj,jk) * ( tsn(ji,jj,jk,jp_sal) + tsn(ji+1,jj,jk,jp_sal) ) 
     425                  z2d(ji,jj) = z2d(ji,jj) + z3d(ji,jj,jk) * ( ts(ji,jj,jk,jp_sal,Kmm) + ts(ji+1,jj,jk,jp_sal,Kmm) ) 
    425426               END DO 
    426427            END DO 
     
    434435         z3d(:,:,jpk) = 0.e0 
    435436         DO jk = 1, jpkm1 
    436             z3d(:,:,jk) = rau0 * vn(:,:,jk) * e1v(:,:) * e3v_n(:,:,jk) * vmask(:,:,jk) 
     437            z3d(:,:,jk) = rau0 * vv(:,:,jk,Kmm) * e1v(:,:) * e3v(:,:,jk,Kmm) * vmask(:,:,jk) 
    437438         END DO 
    438439         CALL iom_put( "v_masstr", z3d )              ! mass transport in j-direction 
     
    444445            DO jj = 2, jpjm1 
    445446               DO ji = fs_2, fs_jpim1   ! vector opt. 
    446                   z2d(ji,jj) = z2d(ji,jj) + z3d(ji,jj,jk) * ( tsn(ji,jj,jk,jp_tem) + tsn(ji,jj+1,jk,jp_tem) ) 
     447                  z2d(ji,jj) = z2d(ji,jj) + z3d(ji,jj,jk) * ( ts(ji,jj,jk,jp_tem,Kmm) + ts(ji,jj+1,jk,jp_tem,Kmm) ) 
    447448               END DO 
    448449            END DO 
     
    457458            DO jj = 2, jpjm1 
    458459               DO ji = fs_2, fs_jpim1   ! vector opt. 
    459                   z2d(ji,jj) = z2d(ji,jj) + z3d(ji,jj,jk) * ( tsn(ji,jj,jk,jp_sal) + tsn(ji,jj+1,jk,jp_sal) ) 
     460                  z2d(ji,jj) = z2d(ji,jj) + z3d(ji,jj,jk) * ( ts(ji,jj,jk,jp_sal,Kmm) + ts(ji,jj+1,jk,jp_sal,Kmm) ) 
    460461               END DO 
    461462            END DO 
     
    470471            DO jj = 2, jpjm1 
    471472               DO ji = fs_2, fs_jpim1   ! vector opt. 
    472                   z2d(ji,jj) = z2d(ji,jj) + e3t_n(ji,jj,jk) *  tsn(ji,jj,jk,jp_tem) 
     473                  z2d(ji,jj) = z2d(ji,jj) + e3t(ji,jj,jk,Kmm) *  ts(ji,jj,jk,jp_tem,Kmm) 
    473474               END DO 
    474475            END DO 
     
    482483            DO jj = 2, jpjm1 
    483484               DO ji = fs_2, fs_jpim1   ! vector opt. 
    484                   z2d(ji,jj) = z2d(ji,jj) + e3t_n(ji,jj,jk) * tsn(ji,jj,jk,jp_sal) 
     485                  z2d(ji,jj) = z2d(ji,jj) + e3t(ji,jj,jk,Kmm) * ts(ji,jj,jk,jp_sal,Kmm) 
    485486               END DO 
    486487            END DO 
     
    493494      ! 
    494495 
    495       IF (ln_diatmb)   CALL dia_tmb                   ! tmb values  
     496      IF (ln_diatmb)   CALL dia_tmb( Kmm )            ! tmb values  
    496497           
    497       IF (ln_dia25h)   CALL dia_25h( kt )             ! 25h averaging 
     498      IF (ln_dia25h)   CALL dia_25h( kt, Kmm )        ! 25h averaging 
    498499 
    499500      IF( ln_timing )   CALL timing_stop('dia_wri') 
     
    521522 
    522523    
    523    SUBROUTINE dia_wri( kt ) 
     524   SUBROUTINE dia_wri( kt, Kmm ) 
    524525      !!--------------------------------------------------------------------- 
    525526      !!                  ***  ROUTINE dia_wri  *** 
     
    534535      !!---------------------------------------------------------------------- 
    535536      INTEGER, INTENT( in ) ::   kt   ! ocean time-step index 
     537      INTEGER, INTENT( in ) ::   Kmm  ! ocean time level index 
    536538      ! 
    537539      LOGICAL ::   ll_print = .FALSE.                        ! =T print and flush numout 
     
    549551      ! 
    550552      IF( ninist == 1 ) THEN     !==  Output the initial state and forcings  ==! 
    551          CALL dia_wri_state( 'output.init' ) 
     553         CALL dia_wri_state( Kmm, 'output.init' ) 
    552554         ninist = 0 
    553555      ENDIF 
     
    690692            &          jpi, jpj, nh_T, ipk, 1, ipk, nz_T, 32, clop, zsto, zout ) 
    691693         IF(  .NOT.ln_linssh  ) THEN 
    692             CALL histdef( nid_T, "vovvle3t", "Level thickness"                    , "m"      ,&  ! e3t_n 
     694            CALL histdef( nid_T, "vovvle3t", "Level thickness"                    , "m"      ,&  ! e3t(:,:,:,Kmm) 
    693695            &             jpi, jpj, nh_T, ipk, 1, ipk, nz_T, 32, clop, zsto, zout ) 
    694             CALL histdef( nid_T, "vovvldep", "T point depth"                      , "m"      ,&  ! e3t_n 
     696            CALL histdef( nid_T, "vovvldep", "T point depth"                      , "m"      ,&  ! e3t(:,:,:,Kmm) 
    695697            &             jpi, jpj, nh_T, ipk, 1, ipk, nz_T, 32, clop, zsto, zout ) 
    696             CALL histdef( nid_T, "vovvldef", "Squared level deformation"          , "%^2"    ,&  ! e3t_n 
     698            CALL histdef( nid_T, "vovvldef", "Squared level deformation"          , "%^2"    ,&  ! e3t(:,:,:,Kmm) 
    697699            &             jpi, jpj, nh_T, ipk, 1, ipk, nz_T, 32, clop, zsto, zout ) 
    698700         ENDIF 
     
    711713            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    712714         IF(  ln_linssh  ) THEN 
    713             CALL histdef( nid_T, "sosst_cd", "Concentration/Dilution term on temperature"     &  ! emp * tsn(:,:,1,jp_tem) 
     715            CALL histdef( nid_T, "sosst_cd", "Concentration/Dilution term on temperature"     &  ! emp * ts(:,:,1,jp_tem,Kmm) 
    714716            &                                                                  , "KgC/m2/s",  &  ! sosst_cd 
    715717            &             jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    716             CALL histdef( nid_T, "sosss_cd", "Concentration/Dilution term on salinity"        &  ! emp * tsn(:,:,1,jp_sal) 
     718            CALL histdef( nid_T, "sosss_cd", "Concentration/Dilution term on salinity"        &  ! emp * ts(:,:,1,jp_sal,Kmm) 
    717719            &                                                                  , "KgPSU/m2/s",&  ! sosss_cd 
    718720            &             jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
     
    790792 
    791793         !                                                                                      !!! nid_U : 3D 
    792          CALL histdef( nid_U, "vozocrtx", "Zonal Current"                      , "m/s"    ,   &  ! un 
     794         CALL histdef( nid_U, "vozocrtx", "Zonal Current"                      , "m/s"    ,   &  ! uu(:,:,:,Kmm) 
    793795            &          jpi, jpj, nh_U, ipk, 1, ipk, nz_U, 32, clop, zsto, zout ) 
    794796         IF( ln_wave .AND. ln_sdw) THEN 
     
    803805 
    804806         !                                                                                      !!! nid_V : 3D 
    805          CALL histdef( nid_V, "vomecrty", "Meridional Current"                 , "m/s"    ,   &  ! vn 
     807         CALL histdef( nid_V, "vomecrty", "Meridional Current"                 , "m/s"    ,   &  ! vv(:,:,:,Kmm) 
    806808            &          jpi, jpj, nh_V, ipk, 1, ipk, nz_V, 32, clop, zsto, zout ) 
    807809         IF( ln_wave .AND. ln_sdw) THEN 
     
    816818 
    817819         !                                                                                      !!! nid_W : 3D 
    818          CALL histdef( nid_W, "vovecrtz", "Vertical Velocity"                  , "m/s"    ,   &  ! wn 
     820         CALL histdef( nid_W, "vovecrtz", "Vertical Velocity"                  , "m/s"    ,   &  ! ww 
    819821            &          jpi, jpj, nh_W, ipk, 1, ipk, nz_W, 32, clop, zsto, zout ) 
    820822         CALL histdef( nid_W, "votkeavt", "Vertical Eddy Diffusivity"          , "m2/s"   ,   &  ! avt 
     
    854856 
    855857      IF( .NOT.ln_linssh ) THEN 
    856          CALL histwrite( nid_T, "votemper", it, tsn(:,:,:,jp_tem) * e3t_n(:,:,:) , ndim_T , ndex_T  )   ! heat content 
    857          CALL histwrite( nid_T, "vosaline", it, tsn(:,:,:,jp_sal) * e3t_n(:,:,:) , ndim_T , ndex_T  )   ! salt content 
    858          CALL histwrite( nid_T, "sosstsst", it, tsn(:,:,1,jp_tem) * e3t_n(:,:,1) , ndim_hT, ndex_hT )   ! sea surface heat content 
    859          CALL histwrite( nid_T, "sosaline", it, tsn(:,:,1,jp_sal) * e3t_n(:,:,1) , ndim_hT, ndex_hT )   ! sea surface salinity content 
     858         CALL histwrite( nid_T, "votemper", it, ts(:,:,:,jp_tem,Kmm) * e3t(:,:,:,Kmm) , ndim_T , ndex_T  )   ! heat content 
     859         CALL histwrite( nid_T, "vosaline", it, ts(:,:,:,jp_sal,Kmm) * e3t(:,:,:,Kmm) , ndim_T , ndex_T  )   ! salt content 
     860         CALL histwrite( nid_T, "sosstsst", it, ts(:,:,1,jp_tem,Kmm) * e3t(:,:,1,Kmm) , ndim_hT, ndex_hT )   ! sea surface heat content 
     861         CALL histwrite( nid_T, "sosaline", it, ts(:,:,1,jp_sal,Kmm) * e3t(:,:,1,Kmm) , ndim_hT, ndex_hT )   ! sea surface salinity content 
    860862      ELSE 
    861          CALL histwrite( nid_T, "votemper", it, tsn(:,:,:,jp_tem) , ndim_T , ndex_T  )   ! temperature 
    862          CALL histwrite( nid_T, "vosaline", it, tsn(:,:,:,jp_sal) , ndim_T , ndex_T  )   ! salinity 
    863          CALL histwrite( nid_T, "sosstsst", it, tsn(:,:,1,jp_tem) , ndim_hT, ndex_hT )   ! sea surface temperature 
    864          CALL histwrite( nid_T, "sosaline", it, tsn(:,:,1,jp_sal) , ndim_hT, ndex_hT )   ! sea surface salinity 
     863         CALL histwrite( nid_T, "votemper", it, ts(:,:,:,jp_tem,Kmm) , ndim_T , ndex_T  )   ! temperature 
     864         CALL histwrite( nid_T, "vosaline", it, ts(:,:,:,jp_sal,Kmm) , ndim_T , ndex_T  )   ! salinity 
     865         CALL histwrite( nid_T, "sosstsst", it, ts(:,:,1,jp_tem,Kmm) , ndim_hT, ndex_hT )   ! sea surface temperature 
     866         CALL histwrite( nid_T, "sosaline", it, ts(:,:,1,jp_sal,Kmm) , ndim_hT, ndex_hT )   ! sea surface salinity 
    865867      ENDIF 
    866868      IF( .NOT.ln_linssh ) THEN 
    867          zw3d(:,:,:) = ( ( e3t_n(:,:,:) - e3t_0(:,:,:) ) / e3t_0(:,:,:) * 100 * tmask(:,:,:) ) ** 2 
    868          CALL histwrite( nid_T, "vovvle3t", it, e3t_n (:,:,:) , ndim_T , ndex_T  )   ! level thickness 
    869          CALL histwrite( nid_T, "vovvldep", it, gdept_n(:,:,:) , ndim_T , ndex_T  )   ! t-point depth 
     869         zw3d(:,:,:) = ( ( e3t(:,:,:,Kmm) - e3t_0(:,:,:) ) / e3t_0(:,:,:) * 100 * tmask(:,:,:) ) ** 2 
     870         CALL histwrite( nid_T, "vovvle3t", it, e3t (:,:,:,Kmm) , ndim_T , ndex_T  )   ! level thickness 
     871         CALL histwrite( nid_T, "vovvldep", it, gdept(:,:,:,Kmm) , ndim_T , ndex_T  )   ! t-point depth 
    870872         CALL histwrite( nid_T, "vovvldef", it, zw3d             , ndim_T , ndex_T  )   ! level thickness deformation 
    871873      ENDIF 
    872       CALL histwrite( nid_T, "sossheig", it, sshn          , ndim_hT, ndex_hT )   ! sea surface height 
     874      CALL histwrite( nid_T, "sossheig", it, ssh(:,:,Kmm)          , ndim_hT, ndex_hT )   ! sea surface height 
    873875      CALL histwrite( nid_T, "sowaflup", it, ( emp-rnf )   , ndim_hT, ndex_hT )   ! upward water flux 
    874876      CALL histwrite( nid_T, "sorunoff", it, rnf           , ndim_hT, ndex_hT )   ! river runoffs 
     
    877879                                                                                  ! in linear free surface case) 
    878880      IF( ln_linssh ) THEN 
    879          zw2d(:,:) = emp (:,:) * tsn(:,:,1,jp_tem) 
     881         zw2d(:,:) = emp (:,:) * ts(:,:,1,jp_tem,Kmm) 
    880882         CALL histwrite( nid_T, "sosst_cd", it, zw2d, ndim_hT, ndex_hT )          ! c/d term on sst 
    881          zw2d(:,:) = emp (:,:) * tsn(:,:,1,jp_sal) 
     883         zw2d(:,:) = emp (:,:) * ts(:,:,1,jp_sal,Kmm) 
    882884         CALL histwrite( nid_T, "sosss_cd", it, zw2d, ndim_hT, ndex_hT )          ! c/d term on sss 
    883885      ENDIF 
     
    915917         CALL histwrite( nid_T, "sohefldp", it, qrp           , ndim_hT, ndex_hT )   ! heat flux damping 
    916918         CALL histwrite( nid_T, "sowafldp", it, erp           , ndim_hT, ndex_hT )   ! freshwater flux damping 
    917          zw2d(:,:) = erp(:,:) * tsn(:,:,1,jp_sal) * tmask(:,:,1) 
     919         zw2d(:,:) = erp(:,:) * ts(:,:,1,jp_sal,Kmm) * tmask(:,:,1) 
    918920         CALL histwrite( nid_T, "sosafldp", it, zw2d          , ndim_hT, ndex_hT )   ! salt flux damping 
    919921      ENDIF 
     
    928930#endif 
    929931 
    930       CALL histwrite( nid_U, "vozocrtx", it, un            , ndim_U , ndex_U )    ! i-current 
     932      CALL histwrite( nid_U, "vozocrtx", it, uu(:,:,:,Kmm)            , ndim_U , ndex_U )    ! i-current 
    931933      CALL histwrite( nid_U, "sozotaux", it, utau          , ndim_hU, ndex_hU )   ! i-wind stress 
    932934 
    933       CALL histwrite( nid_V, "vomecrty", it, vn            , ndim_V , ndex_V  )   ! j-current 
     935      CALL histwrite( nid_V, "vomecrty", it, vv(:,:,:,Kmm)            , ndim_V , ndex_V  )   ! j-current 
    934936      CALL histwrite( nid_V, "sometauy", it, vtau          , ndim_hV, ndex_hV )   ! j-wind stress 
    935937 
    936       CALL histwrite( nid_W, "vovecrtz", it, wn             , ndim_T, ndex_T )    ! vert. current 
     938      CALL histwrite( nid_W, "vovecrtz", it, ww             , ndim_T, ndex_T )    ! vert. current 
    937939      CALL histwrite( nid_W, "votkeavt", it, avt            , ndim_T, ndex_T )    ! T vert. eddy diff. coef. 
    938940      CALL histwrite( nid_W, "votkeavm", it, avm            , ndim_T, ndex_T )    ! T vert. eddy visc. coef. 
     
    961963#endif 
    962964 
    963    SUBROUTINE dia_wri_state( cdfile_name ) 
     965   SUBROUTINE dia_wri_state( Kmm, cdfile_name ) 
    964966      !!--------------------------------------------------------------------- 
    965967      !!                 ***  ROUTINE dia_wri_state  *** 
     
    974976      !!      File 'output.abort.nc' is created in case of abnormal job end 
    975977      !!---------------------------------------------------------------------- 
     978      INTEGER           , INTENT( in ) ::   Kmm              ! time level index 
    976979      CHARACTER (len=* ), INTENT( in ) ::   cdfile_name      ! name of the file created 
    977980      !! 
     
    990993#endif 
    991994 
    992       CALL iom_rstput( 0, 0, inum, 'votemper', tsn(:,:,:,jp_tem) )    ! now temperature 
    993       CALL iom_rstput( 0, 0, inum, 'vosaline', tsn(:,:,:,jp_sal) )    ! now salinity 
    994       CALL iom_rstput( 0, 0, inum, 'sossheig', sshn              )    ! sea surface height 
    995       CALL iom_rstput( 0, 0, inum, 'vozocrtx', un                )    ! now i-velocity 
    996       CALL iom_rstput( 0, 0, inum, 'vomecrty', vn                )    ! now j-velocity 
    997       CALL iom_rstput( 0, 0, inum, 'vovecrtz', wn                )    ! now k-velocity 
     995      CALL iom_rstput( 0, 0, inum, 'votemper', ts(:,:,:,jp_tem,Kmm) )    ! now temperature 
     996      CALL iom_rstput( 0, 0, inum, 'vosaline', ts(:,:,:,jp_sal,Kmm) )    ! now salinity 
     997      CALL iom_rstput( 0, 0, inum, 'sossheig', ssh(:,:,Kmm)              )    ! sea surface height 
     998      CALL iom_rstput( 0, 0, inum, 'vozocrtx', uu(:,:,:,Kmm)                )    ! now i-velocity 
     999      CALL iom_rstput( 0, 0, inum, 'vomecrty', vv(:,:,:,Kmm)                )    ! now j-velocity 
     1000      CALL iom_rstput( 0, 0, inum, 'vovecrtz', ww                )    ! now k-velocity 
    9981001      IF( ALLOCATED(ahtu) ) THEN 
    9991002         CALL iom_rstput( 0, 0, inum,  'ahtu', ahtu              )    ! aht at u-point 
     
    10111014      CALL iom_rstput( 0, 0, inum, 'sometauy', vtau              )    ! j-wind stress 
    10121015      IF(  .NOT.ln_linssh  ) THEN              
    1013          CALL iom_rstput( 0, 0, inum, 'vovvldep', gdept_n        )    !  T-cell depth  
    1014          CALL iom_rstput( 0, 0, inum, 'vovvle3t', e3t_n          )    !  T-cell thickness   
     1016         CALL iom_rstput( 0, 0, inum, 'vovvldep', gdept(:,:,:,Kmm)        )    !  T-cell depth  
     1017         CALL iom_rstput( 0, 0, inum, 'vovvle3t', e3t(:,:,:,Kmm)          )    !  T-cell thickness   
    10151018      END IF 
    10161019      IF( ln_wave .AND. ln_sdw ) THEN 
Note: See TracChangeset for help on using the changeset viewer.