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 9019 for branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/DIA/dia25h.F90 – NEMO

Ignore:
Timestamp:
2017-12-13T15:58:53+01:00 (6 years ago)
Author:
timgraham
Message:

Merge of dev_CNRS_2017 into branch

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/DIA/dia25h.F90

    r8329 r9019  
    88   USE oce             ! ocean dynamics and tracers variables 
    99   USE dom_oce         ! ocean space and time domain 
     10   USE zdf_oce         ! ocean vertical physics     
     11   USE zdfgls   , ONLY : hmxl_n 
     12   ! 
    1013   USE in_out_manager  ! I/O units 
    1114   USE iom             ! I/0 library 
    12    USE wrk_nemo        ! working arrays 
    13 #if defined key_zdftke  
    14    USE zdf_oce, ONLY: en 
    15 #endif 
    16    USE zdf_oce, ONLY: avt, avm 
    17 #if defined key_zdfgls 
    18    USE zdf_oce, ONLY: en 
    19    USE zdfgls, ONLY: mxln 
    20 #endif 
    2115 
    2216   IMPLICIT NONE 
    2317   PRIVATE 
    2418 
    25    LOGICAL , PUBLIC ::   ln_dia25h     !:  25h mean output 
    2619   PUBLIC   dia_25h_init               ! routine called by nemogcm.F90 
    2720   PUBLIC   dia_25h                    ! routine called by diawri.F90 
    2821 
    29   !! * variables for calculating 25-hourly means 
    30    REAL(wp),SAVE, ALLOCATABLE,   DIMENSION(:,:,:) ::   tn_25h  , sn_25h 
    31    REAL(wp),SAVE, ALLOCATABLE,   DIMENSION(:,:)   ::   sshn_25h  
    32    REAL(wp),SAVE, ALLOCATABLE,   DIMENSION(:,:,:) ::   un_25h  , vn_25h  , wn_25h 
    33    REAL(wp),SAVE, ALLOCATABLE,   DIMENSION(:,:,:) ::   avt_25h , avm_25h 
    34 #if defined key_zdfgls || key_zdftke 
    35    REAL(wp),SAVE, ALLOCATABLE,   DIMENSION(:,:,:) ::   en_25h 
    36 #endif 
    37 #if defined key_zdfgls  
    38    REAL(wp),SAVE, ALLOCATABLE,   DIMENSION(:,:,:) ::   rmxln_25h 
    39 #endif 
    40    INTEGER, SAVE :: cnt_25h     ! Counter for 25 hour means 
    41  
    42  
     22   LOGICAL, PUBLIC ::   ln_dia25h      !:  25h mean output 
     23 
     24   ! variables for calculating 25-hourly means 
     25   INTEGER , SAVE ::   cnt_25h           ! Counter for 25 hour means 
     26   REAL(wp), SAVE ::   r1_25 = 0.04_wp   ! =1/25  
     27   REAL(wp), SAVE, ALLOCATABLE, DIMENSION(:,:,:) ::   tn_25h  , sn_25h 
     28   REAL(wp), SAVE, ALLOCATABLE, DIMENSION(:,:)   ::   sshn_25h  
     29   REAL(wp), SAVE, ALLOCATABLE, DIMENSION(:,:,:) ::   un_25h  , vn_25h  , wn_25h 
     30   REAL(wp), SAVE, ALLOCATABLE, DIMENSION(:,:,:) ::   avt_25h , avm_25h 
     31   REAL(wp), SAVE, ALLOCATABLE, DIMENSION(:,:,:) ::   en_25h  , rmxln_25h 
    4332 
    4433   !!---------------------------------------------------------------------- 
     
    5645      !!         
    5746      !! ** Method : Read namelist 
    58       !!   History 
    59       !!   3.6  !  08-14  (E. O'Dea) Routine to initialize dia_25h 
    6047      !!--------------------------------------------------------------------------- 
    61       !! 
    6248      INTEGER ::   ios                 ! Local integer output status for namelist read 
    6349      INTEGER ::   ierror              ! Local integer for memory allocation 
     
    7965         WRITE(numout,*) 'dia_25h_init : Output 25 hour mean diagnostics' 
    8066         WRITE(numout,*) '~~~~~~~~~~~~' 
    81          WRITE(numout,*) 'Namelist nam_dia25h : set 25h outputs ' 
    82          WRITE(numout,*) 'Switch for 25h diagnostics (T) or not (F)  ln_dia25h  = ', ln_dia25h 
     67         WRITE(numout,*) '   Namelist nam_dia25h : set 25h outputs ' 
     68         WRITE(numout,*) '      Switch for 25h diagnostics (T) or not (F)  ln_dia25h  = ', ln_dia25h 
    8369      ENDIF 
    8470      IF( .NOT. ln_dia25h )   RETURN 
     
    8672      ! 1 - Allocate memory ! 
    8773      ! ------------------- ! 
    88       ALLOCATE( tn_25h(jpi,jpj,jpk), STAT=ierror ) 
     74      !                                ! ocean arrays 
     75      ALLOCATE( tn_25h (jpi,jpj,jpk), sn_25h (jpi,jpj,jpk), sshn_25h(jpi,jpj)  ,     & 
     76         &      un_25h (jpi,jpj,jpk), vn_25h (jpi,jpj,jpk), wn_25h(jpi,jpj,jpk),     & 
     77         &      avt_25h(jpi,jpj,jpk), avm_25h(jpi,jpj,jpk),                      STAT=ierror ) 
    8978      IF( ierror > 0 ) THEN 
    90          CALL ctl_stop( 'dia_25h: unable to allocate tn_25h' )   ;   RETURN 
    91       ENDIF 
    92       ALLOCATE( sn_25h(jpi,jpj,jpk), STAT=ierror ) 
    93       IF( ierror > 0 ) THEN 
    94          CALL ctl_stop( 'dia_25h: unable to allocate sn_25h' )   ;   RETURN 
    95       ENDIF 
    96       ALLOCATE( un_25h(jpi,jpj,jpk), STAT=ierror ) 
    97       IF( ierror > 0 ) THEN 
    98          CALL ctl_stop( 'dia_25h: unable to allocate un_25h' )   ;   RETURN 
    99       ENDIF 
    100       ALLOCATE( vn_25h(jpi,jpj,jpk), STAT=ierror ) 
    101       IF( ierror > 0 ) THEN 
    102          CALL ctl_stop( 'dia_25h: unable to allocate vn_25h' )   ;   RETURN 
    103       ENDIF 
    104       ALLOCATE( wn_25h(jpi,jpj,jpk), STAT=ierror ) 
    105       IF( ierror > 0 ) THEN 
    106          CALL ctl_stop( 'dia_25h: unable to allocate wn_25h' )   ;   RETURN 
    107       ENDIF 
    108       ALLOCATE( avt_25h(jpi,jpj,jpk), STAT=ierror ) 
    109       IF( ierror > 0 ) THEN 
    110          CALL ctl_stop( 'dia_25h: unable to allocate avt_25h' )   ;   RETURN 
    111       ENDIF 
    112       ALLOCATE( avm_25h(jpi,jpj,jpk), STAT=ierror ) 
    113       IF( ierror > 0 ) THEN 
    114          CALL ctl_stop( 'dia_25h: unable to allocate avm_25h' )   ;   RETURN 
    115       ENDIF 
    116 # if defined key_zdfgls || defined key_zdftke 
    117       ALLOCATE( en_25h(jpi,jpj,jpk), STAT=ierror ) 
    118       IF( ierror > 0 ) THEN 
    119          CALL ctl_stop( 'dia_25h: unable to allocate en_25h' )   ;   RETURN 
    120       ENDIF 
    121 #endif 
    122 # if defined key_zdfgls  
    123       ALLOCATE( rmxln_25h(jpi,jpj,jpk), STAT=ierror ) 
    124       IF( ierror > 0 ) THEN 
    125          CALL ctl_stop( 'dia_25h: unable to allocate rmxln_25h' )   ;   RETURN 
    126       ENDIF 
    127 #endif 
    128       ALLOCATE( sshn_25h(jpi,jpj), STAT=ierror ) 
    129       IF( ierror > 0 ) THEN 
    130          CALL ctl_stop( 'dia_25h: unable to allocate sshn_25h' )   ;   RETURN 
     79         CALL ctl_stop( 'dia_25h: unable to allocate ocean arrays' )   ;   RETURN 
     80      ENDIF 
     81      IF( ln_zdftke ) THEN             ! TKE physics 
     82         ALLOCATE( en_25h(jpi,jpj,jpk), STAT=ierror ) 
     83         IF( ierror > 0 ) THEN 
     84            CALL ctl_stop( 'dia_25h: unable to allocate en_25h' )   ;   RETURN 
     85         ENDIF 
     86      ENDIF 
     87      IF( ln_zdfgls ) THEN             ! GLS physics 
     88         ALLOCATE( en_25h(jpi,jpj,jpk), rmxln_25h(jpi,jpj,jpk), STAT=ierror ) 
     89         IF( ierror > 0 ) THEN 
     90            CALL ctl_stop( 'dia_25h: unable to allocate en_25h and rmxln_25h' )   ;   RETURN 
     91         ENDIF 
    13192      ENDIF 
    13293      ! ------------------------- ! 
     
    13495      ! ------------------------- ! 
    13596      cnt_25h = 1  ! sets the first value of sum at timestep 1 (note - should strictly be at timestep zero so before values used where possible)  
    136       tn_25h(:,:,:) = tsb(:,:,:,jp_tem) 
    137       sn_25h(:,:,:) = tsb(:,:,:,jp_sal) 
    138       sshn_25h(:,:) = sshb(:,:) 
    139       un_25h(:,:,:) = ub(:,:,:) 
    140       vn_25h(:,:,:) = vb(:,:,:) 
    141       wn_25h(:,:,:) = wn(:,:,:) 
    142       avt_25h(:,:,:) = avt(:,:,:) 
    143       avm_25h(:,:,:) = avm(:,:,:) 
    144 # if defined key_zdfgls || defined key_zdftke 
     97      tn_25h  (:,:,:) = tsb (:,:,:,jp_tem) 
     98      sn_25h  (:,:,:) = tsb (:,:,:,jp_sal) 
     99      sshn_25h(:,:)   = sshb(:,:) 
     100      un_25h  (:,:,:) = ub  (:,:,:) 
     101      vn_25h  (:,:,:) = vb  (:,:,:) 
     102      wn_25h  (:,:,:) = wn  (:,:,:) 
     103      avt_25h (:,:,:) = avt (:,:,:) 
     104      avm_25h (:,:,:) = avm (:,:,:) 
     105      IF( ln_zdftke ) THEN 
    145106         en_25h(:,:,:) = en(:,:,:) 
    146 #endif 
    147 # if defined key_zdfgls 
    148          rmxln_25h(:,:,:) = mxln(:,:,:) 
    149 #endif 
    150 #if defined key_lim3 || defined key_lim2 
    151          CALL ctl_stop('STOP', 'dia_25h not setup yet to do tidemean ice') 
     107      ENDIF 
     108      IF( ln_zdfgls ) THEN 
     109         en_25h   (:,:,:) = en    (:,:,:) 
     110         rmxln_25h(:,:,:) = hmxl_n(:,:,:) 
     111      ENDIF 
     112#if defined key_lim3 
     113      CALL ctl_stop('STOP', 'dia_25h not setup yet to do tidemean ice') 
    152114#endif  
    153  
    154       ! -------------------------- ! 
    155       ! 3 - Return to dia_wri      ! 
    156       ! -------------------------- ! 
    157  
    158  
     115      ! 
    159116   END SUBROUTINE dia_25h_init 
    160117 
     
    164121      !!                 ***  ROUTINE dia_25h  *** 
    165122      !!          
    166       !! 
    167       !!-------------------------------------------------------------------- 
    168       !!                    
    169123      !! ** Purpose :   Write diagnostics with M2/S2 tide removed 
    170124      !! 
    171       !! ** Method  :    
    172       !!      25hr mean outputs for shelf seas 
     125      !! ** Method  :   25hr mean outputs for shelf seas 
     126      !!---------------------------------------------------------------------- 
     127      INTEGER, INTENT(in) ::   kt   ! ocean time-step index 
    173128      !! 
    174       !! History : 
    175       !!   ?.0  !  07-04  (A. Hines) New routine, developed from dia_wri_foam 
    176       !!   3.4  !  02-13  (J. Siddorn) Routine taken from old dia_wri_foam 
    177       !!   3.6  !  08-14  (E. O'Dea) adapted for VN3.6 
    178       !!---------------------------------------------------------------------- 
    179       !! * Modules used 
    180  
    181       IMPLICIT NONE 
    182  
    183       !! * Arguments 
    184       INTEGER, INTENT( in ) ::   kt      ! ocean time-step index 
    185  
    186  
    187       !! * Local declarations 
    188129      INTEGER ::   ji, jj, jk 
    189  
     130      INTEGER                          ::   iyear0, nimonth0,iday0            ! start year,imonth,day 
    190131      LOGICAL ::   ll_print = .FALSE.    ! =T print and flush numout 
    191       REAL(wp)                         ::   zsto, zout, zmax, zjulian, zmdi       ! temporary reals 
    192       INTEGER                          ::   i_steps                               ! no of timesteps per hour 
    193       REAL(wp), DIMENSION(jpi,jpj    ) ::   zw2d, un_dm, vn_dm                    ! temporary workspace 
    194       REAL(wp), DIMENSION(jpi,jpj,jpk) ::   zw3d                                  ! temporary workspace 
    195       REAL(wp), DIMENSION(jpi,jpj,3)   ::   zwtmb                                 ! temporary workspace 
    196       INTEGER                          ::   iyear0, nimonth0,iday0                ! start year,imonth,day 
    197  
     132      REAL(wp)                         ::   zsto, zout, zmax, zjulian, zmdi   ! local scalars 
     133      INTEGER                          ::   i_steps                           ! no of timesteps per hour 
     134      REAL(wp), DIMENSION(jpi,jpj    ) ::   zw2d, un_dm, vn_dm                ! workspace 
     135      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   zw3d                              ! workspace 
     136      REAL(wp), DIMENSION(jpi,jpj,3)   ::   zwtmb                             ! workspace 
    198137      !!---------------------------------------------------------------------- 
    199138 
     
    207146      ENDIF 
    208147 
    209 #if defined key_lim3 || defined key_lim2 
    210       CALL ctl_stop('STOP', 'dia_wri_tide not setup yet to do tidemean ice') 
    211 #endif 
    212  
    213148      ! local variable for debugging 
    214149      ll_print = ll_print .AND. lwp 
    215150 
    216       ! Sum of 25 hourly instantaneous values to give a 25h mean from 24hours 
    217       ! every day 
    218       IF( MOD( kt, i_steps ) == 0  .and. kt .ne. nn_it000 ) THEN 
     151      ! Sum of 25 hourly instantaneous values to give a 25h mean from 24hours every day 
     152      IF( MOD( kt, i_steps ) == 0  .AND. kt /= nn_it000 ) THEN 
    219153 
    220154         IF (lwp) THEN 
     
    223157         ENDIF 
    224158 
    225          tn_25h(:,:,:)        = tn_25h(:,:,:) + tsn(:,:,:,jp_tem) 
    226          sn_25h(:,:,:)        = sn_25h(:,:,:) + tsn(:,:,:,jp_sal) 
    227          sshn_25h(:,:)        = sshn_25h(:,:) + sshn (:,:) 
    228          un_25h(:,:,:)        = un_25h(:,:,:) + un(:,:,:) 
    229          vn_25h(:,:,:)        = vn_25h(:,:,:) + vn(:,:,:) 
    230          wn_25h(:,:,:)        = wn_25h(:,:,:) + wn(:,:,:) 
    231          avt_25h(:,:,:)       = avt_25h(:,:,:) + avt(:,:,:) 
    232          avm_25h(:,:,:)       = avm_25h(:,:,:) + avm(:,:,:) 
    233 # if defined key_zdfgls || defined key_zdftke 
    234          en_25h(:,:,:)        = en_25h(:,:,:) + en(:,:,:) 
    235 #endif 
    236 # if defined key_zdfgls 
    237          rmxln_25h(:,:,:)      = rmxln_25h(:,:,:) + mxln(:,:,:) 
    238 #endif 
     159         tn_25h  (:,:,:)     = tn_25h  (:,:,:) + tsn (:,:,:,jp_tem) 
     160         sn_25h  (:,:,:)     = sn_25h  (:,:,:) + tsn (:,:,:,jp_sal) 
     161         sshn_25h(:,:)       = sshn_25h(:,:)   + sshn(:,:) 
     162         un_25h  (:,:,:)     = un_25h  (:,:,:) + un  (:,:,:) 
     163         vn_25h  (:,:,:)     = vn_25h  (:,:,:) + vn  (:,:,:) 
     164         wn_25h  (:,:,:)     = wn_25h  (:,:,:) + wn  (:,:,:) 
     165         avt_25h (:,:,:)     = avt_25h (:,:,:) + avt (:,:,:) 
     166         avm_25h (:,:,:)     = avm_25h (:,:,:) + avm (:,:,:) 
     167         IF( ln_zdftke ) THEN 
     168            en_25h(:,:,:)    = en_25h  (:,:,:) + en(:,:,:) 
     169         ENDIF 
     170         IF( ln_zdfgls ) THEN 
     171            en_25h   (:,:,:) = en_25h   (:,:,:) + en    (:,:,:) 
     172            rmxln_25h(:,:,:) = rmxln_25h(:,:,:) + hmxl_n(:,:,:) 
     173         ENDIF 
    239174         cnt_25h = cnt_25h + 1 
    240  
     175         ! 
    241176         IF (lwp) THEN 
    242177            WRITE(numout,*) 'dia_tide : Summed the following number of hourly values so far',cnt_25h 
    243178         ENDIF 
    244  
     179         ! 
    245180      ENDIF ! MOD( kt, i_steps ) == 0 
    246181 
    247          ! Write data for 25 hour mean output streams 
    248       IF( cnt_25h .EQ. 25 .AND.  MOD( kt, i_steps*24) == 0 .AND. kt .NE. nn_it000 ) THEN 
    249  
    250             IF(lwp) THEN 
    251                WRITE(numout,*) 'dia_wri_tide : Writing 25 hour mean tide diagnostics at timestep', kt 
    252                WRITE(numout,*) '~~~~~~~~~~~~ ' 
    253             ENDIF 
    254  
    255             tn_25h(:,:,:)        = tn_25h(:,:,:) / 25.0_wp 
    256             sn_25h(:,:,:)        = sn_25h(:,:,:) / 25.0_wp 
    257             sshn_25h(:,:)        = sshn_25h(:,:) / 25.0_wp 
    258             un_25h(:,:,:)        = un_25h(:,:,:) / 25.0_wp 
    259             vn_25h(:,:,:)        = vn_25h(:,:,:) / 25.0_wp 
    260             wn_25h(:,:,:)        = wn_25h(:,:,:) / 25.0_wp 
    261             avt_25h(:,:,:)       = avt_25h(:,:,:) / 25.0_wp 
    262             avm_25h(:,:,:)       = avm_25h(:,:,:) / 25.0_wp 
    263 # if defined key_zdfgls || defined key_zdftke 
    264             en_25h(:,:,:)        = en_25h(:,:,:) / 25.0_wp 
    265 #endif 
    266 # if defined key_zdfgls 
    267             rmxln_25h(:,:,:)       = rmxln_25h(:,:,:) / 25.0_wp 
    268 #endif 
    269  
    270             IF (lwp)  WRITE(numout,*) 'dia_wri_tide : Mean calculated by dividing 25 hour sums and writing output' 
    271             zmdi=1.e+20 !missing data indicator for masking 
    272             ! write tracers (instantaneous) 
    273             zw3d(:,:,:) = tn_25h(:,:,:)*tmask(:,:,:) + zmdi*(1.0-tmask(:,:,:)) 
    274             CALL iom_put("temper25h", zw3d)   ! potential temperature 
    275             zw3d(:,:,:) = sn_25h(:,:,:)*tmask(:,:,:) + zmdi*(1.0-tmask(:,:,:)) 
    276             CALL iom_put( "salin25h", zw3d  )   ! salinity 
    277             zw2d(:,:) = sshn_25h(:,:)*tmask(:,:,1) + zmdi*(1.0-tmask(:,:,1)) 
    278             CALL iom_put( "ssh25h", zw2d )   ! sea surface  
    279  
    280  
    281             ! Write velocities (instantaneous) 
    282             zw3d(:,:,:) = un_25h(:,:,:)*umask(:,:,:) + zmdi*(1.0-umask(:,:,:)) 
    283             CALL iom_put("vozocrtx25h", zw3d)    ! i-current 
    284             zw3d(:,:,:) = vn_25h(:,:,:)*vmask(:,:,:) + zmdi*(1.0-vmask(:,:,:)) 
    285             CALL iom_put("vomecrty25h", zw3d  )   ! j-current 
    286  
    287             zw3d(:,:,:) = wn_25h(:,:,:)*tmask(:,:,:) + zmdi*(1.0-tmask(:,:,:)) 
    288             CALL iom_put("vomecrtz25h", zw3d )   ! k-current 
    289             zw3d(:,:,:) = avt_25h(:,:,:)*tmask(:,:,:) + zmdi*(1.0-tmask(:,:,:)) 
    290             CALL iom_put("avt25h", zw3d )   ! diffusivity 
    291             zw3d(:,:,:) = avm_25h(:,:,:)*tmask(:,:,:) + zmdi*(1.0-tmask(:,:,:)) 
    292             CALL iom_put("avm25h", zw3d)   ! viscosity 
    293 #if defined key_zdftke || defined key_zdfgls  
    294             zw3d(:,:,:) = en_25h(:,:,:)*tmask(:,:,:) + zmdi*(1.0-tmask(:,:,:)) 
     182      ! Write data for 25 hour mean output streams 
     183      IF( cnt_25h == 25 .AND.  MOD( kt, i_steps*24) == 0 .AND. kt /= nn_it000 ) THEN 
     184         ! 
     185         IF(lwp) THEN 
     186            WRITE(numout,*) 'dia_wri_tide : Writing 25 hour mean tide diagnostics at timestep', kt 
     187            WRITE(numout,*) '~~~~~~~~~~~~ ' 
     188         ENDIF 
     189         ! 
     190         tn_25h  (:,:,:) = tn_25h  (:,:,:) * r1_25 
     191         sn_25h  (:,:,:) = sn_25h  (:,:,:) * r1_25 
     192         sshn_25h(:,:)   = sshn_25h(:,:)   * r1_25 
     193         un_25h  (:,:,:) = un_25h  (:,:,:) * r1_25 
     194         vn_25h  (:,:,:) = vn_25h  (:,:,:) * r1_25 
     195         wn_25h  (:,:,:) = wn_25h  (:,:,:) * r1_25 
     196         avt_25h (:,:,:) = avt_25h (:,:,:) * r1_25 
     197         avm_25h (:,:,:) = avm_25h (:,:,:) * r1_25 
     198         IF( ln_zdftke ) THEN 
     199            en_25h(:,:,:) = en_25h(:,:,:) * r1_25 
     200         ENDIF 
     201         IF( ln_zdfgls ) THEN 
     202            en_25h   (:,:,:) = en_25h   (:,:,:) * r1_25 
     203            rmxln_25h(:,:,:) = rmxln_25h(:,:,:) * r1_25 
     204         ENDIF 
     205         ! 
     206         IF(lwp)  WRITE(numout,*) 'dia_wri_tide : Mean calculated by dividing 25 hour sums and writing output' 
     207         zmdi=1.e+20 !missing data indicator for masking 
     208         ! write tracers (instantaneous) 
     209         zw3d(:,:,:) = tn_25h(:,:,:)*tmask(:,:,:) + zmdi*(1.0-tmask(:,:,:)) 
     210         CALL iom_put("temper25h", zw3d)   ! potential temperature 
     211         zw3d(:,:,:) = sn_25h(:,:,:)*tmask(:,:,:) + zmdi*(1.0-tmask(:,:,:)) 
     212         CALL iom_put( "salin25h", zw3d  )   ! salinity 
     213         zw2d(:,:) = sshn_25h(:,:)*tmask(:,:,1) + zmdi*(1.0-tmask(:,:,1)) 
     214         CALL iom_put( "ssh25h", zw2d )   ! sea surface  
     215         ! Write velocities (instantaneous) 
     216         zw3d(:,:,:) = un_25h(:,:,:)*umask(:,:,:) + zmdi*(1.0-umask(:,:,:)) 
     217         CALL iom_put("vozocrtx25h", zw3d)    ! i-current 
     218         zw3d(:,:,:) = vn_25h(:,:,:)*vmask(:,:,:) + zmdi*(1.0-vmask(:,:,:)) 
     219         CALL iom_put("vomecrty25h", zw3d  )   ! j-current 
     220         zw3d(:,:,:) = wn_25h(:,:,:)*wmask(:,:,:) + zmdi*(1.0-tmask(:,:,:)) 
     221         CALL iom_put("vomecrtz25h", zw3d )   ! k-current 
     222         ! Write vertical physics 
     223         zw3d(:,:,:) = avt_25h(:,:,:)*wmask(:,:,:) + zmdi*(1.0-tmask(:,:,:)) 
     224         CALL iom_put("avt25h", zw3d )   ! diffusivity 
     225         zw3d(:,:,:) = avm_25h(:,:,:)*wmask(:,:,:) + zmdi*(1.0-tmask(:,:,:)) 
     226         CALL iom_put("avm25h", zw3d)   ! viscosity 
     227         IF( ln_zdftke ) THEN 
     228            zw3d(:,:,:) = en_25h(:,:,:)*wmask(:,:,:) + zmdi*(1.0-tmask(:,:,:)) 
    295229            CALL iom_put("tke25h", zw3d)   ! tke 
    296 #endif 
    297 #if defined key_zdfgls  
    298             zw3d(:,:,:) = rmxln_25h(:,:,:)*tmask(:,:,:) + zmdi*(1.0-tmask(:,:,:)) 
     230         ENDIF 
     231         IF( ln_zdfgls ) THEN 
     232            zw3d(:,:,:) = en_25h(:,:,:)*wmask(:,:,:) + zmdi*(1.0-tmask(:,:,:)) 
     233            CALL iom_put("tke25h", zw3d)   ! tke 
     234            zw3d(:,:,:) = rmxln_25h(:,:,:)*wmask(:,:,:) + zmdi*(1.0-tmask(:,:,:)) 
    299235            CALL iom_put( "mxln25h",zw3d) 
    300 #endif 
    301  
    302             ! After the write reset the values to cnt=1 and sum values equal current value  
    303             tn_25h(:,:,:) = tsn(:,:,:,jp_tem) 
    304             sn_25h(:,:,:) = tsn(:,:,:,jp_sal) 
    305             sshn_25h(:,:) = sshn (:,:) 
    306             un_25h(:,:,:) = un(:,:,:) 
    307             vn_25h(:,:,:) = vn(:,:,:) 
    308             wn_25h(:,:,:) = wn(:,:,:) 
    309             avt_25h(:,:,:) = avt(:,:,:) 
    310             avm_25h(:,:,:) = avm(:,:,:) 
    311 # if defined key_zdfgls || defined key_zdftke 
     236         ENDIF 
     237         ! 
     238         ! After the write reset the values to cnt=1 and sum values equal current value  
     239         tn_25h  (:,:,:) = tsn (:,:,:,jp_tem) 
     240         sn_25h  (:,:,:) = tsn (:,:,:,jp_sal) 
     241         sshn_25h(:,:)   = sshn(:,:) 
     242         un_25h  (:,:,:) = un  (:,:,:) 
     243         vn_25h  (:,:,:) = vn  (:,:,:) 
     244         wn_25h  (:,:,:) = wn  (:,:,:) 
     245         avt_25h (:,:,:) = avt (:,:,:) 
     246         avm_25h (:,:,:) = avm (:,:,:) 
     247         IF( ln_zdftke ) THEN 
    312248            en_25h(:,:,:) = en(:,:,:) 
    313 #endif 
    314 # if defined key_zdfgls 
    315             rmxln_25h(:,:,:) = mxln(:,:,:) 
    316 #endif 
    317             cnt_25h = 1 
    318             IF (lwp)  WRITE(numout,*) 'dia_wri_tide :   & 
    319         &    After 25hr mean write, reset sum to current value and cnt_25h to one for overlapping average',cnt_25h 
    320  
     249         ENDIF 
     250         IF( ln_zdfgls ) THEN 
     251            en_25h   (:,:,:) = en    (:,:,:) 
     252            rmxln_25h(:,:,:) = hmxl_n(:,:,:) 
     253         ENDIF 
     254         cnt_25h = 1 
     255         IF(lwp)  WRITE(numout,*) 'dia_wri_tide :   & 
     256            &    After 25hr mean write, reset sum to current value and cnt_25h to one for overlapping average', cnt_25h 
    321257      ENDIF !  cnt_25h .EQ. 25 .AND.  MOD( kt, i_steps * 24) == 0 .AND. kt .NE. nn_it000 
    322  
    323  
     258      ! 
    324259   END SUBROUTINE dia_25h  
    325260 
Note: See TracChangeset for help on using the changeset viewer.