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.
dia25h.F90 in branches/UKMO/AMM15_v3_6_STABLE_package_collate_utils366_fabmv1_v2/NEMOGCM/NEMO/OPA_SRC/DIA – NEMO

source: branches/UKMO/AMM15_v3_6_STABLE_package_collate_utils366_fabmv1_v2/NEMOGCM/NEMO/OPA_SRC/DIA/dia25h.F90 @ 13489

Last change on this file since 13489 was 13489, checked in by dford, 4 years ago

Merge in previous branch.

File size: 21.5 KB
Line 
1MODULE dia25h 
2   !!======================================================================
3   !!                       ***  MODULE  diaharm  ***
4   !! Harmonic analysis of tidal constituents
5   !!======================================================================
6   !! History :  3.6  !  2014  (E O'Dea)  Original code
7   !!----------------------------------------------------------------------
8   USE oce             ! ocean dynamics and tracers variables
9   USE dom_oce         ! ocean space and time domain
10   USE diainsitutem, ONLY: rinsitu_t, theta2t
11   USE in_out_manager  ! I/O units
12   USE iom             ! I/0 library
13   USE wrk_nemo        ! working arrays
14#if defined key_zdftke 
15   USE zdftke, ONLY: en
16#endif
17   USE zdf_oce, ONLY: avt, avm
18#if defined key_zdfgls
19   USE zdfgls, ONLY: mxln
20   USE zdf_oce, ONLY: en
21#endif
22   USE diatmb
23#if defined key_fabm
24   USE trc, ONLY: trn
25   USE par_fabm
26   USE st2d_fabm, ONLY: fabm_st2dn
27#endif
28
29   IMPLICIT NONE
30   PRIVATE
31
32   LOGICAL , PUBLIC ::   ln_dia25h     !:  25h mean output
33   PUBLIC   dia_25h_init               ! routine called by nemogcm.F90
34   PUBLIC   dia_25h                    ! routine called by diawri.F90
35
36  !! * variables for calculating 25-hourly means
37   REAL(wp),SAVE, ALLOCATABLE,   DIMENSION(:,:,:) ::   tn_25h  , sn_25h, rinsitu_t_25h 
38   REAL(wp),SAVE, ALLOCATABLE,   DIMENSION(:,:)   ::   sshn_25h, insitu_bot_25h, temp_bot_25h 
39   REAL(wp),SAVE, ALLOCATABLE,   DIMENSION(:,:,:) ::   un_25h  , vn_25h  , wn_25h
40   REAL(wp),SAVE, ALLOCATABLE,   DIMENSION(:,:,:) ::   avt_25h , avm_25h
41#if defined key_zdfgls || key_zdftke
42   REAL(wp),SAVE, ALLOCATABLE,   DIMENSION(:,:,:) ::   en_25h
43#endif
44#if defined key_zdfgls 
45   REAL(wp),SAVE, ALLOCATABLE,   DIMENSION(:,:,:) ::   rmxln_25h
46#endif
47#if defined key_fabm
48   REAL(wp),SAVE, ALLOCATABLE,   DIMENSION(:,:,:,:) :: fabm_25h
49   REAL(wp),SAVE, ALLOCATABLE,   DIMENSION(:,:,:,:) :: fabm_3d_25h
50   REAL(wp),SAVE, ALLOCATABLE,   DIMENSION(:,:,:)   :: fabm_surface_25h
51   REAL(wp),SAVE, ALLOCATABLE,   DIMENSION(:,:,:)   :: fabm_bottom_25h
52   REAL(wp),SAVE, ALLOCATABLE,   DIMENSION(:,:,:)   :: fabm_2d_25h
53#endif
54   INTEGER, SAVE :: cnt_25h     ! Counter for 25 hour means
55
56
57
58   !!----------------------------------------------------------------------
59   !! NEMO/OPA 3.6 , NEMO Consortium (2014)
60   !! $Id$
61   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
62   !!----------------------------------------------------------------------
63CONTAINS
64
65   SUBROUTINE dia_25h_init 
66      !!---------------------------------------------------------------------------
67      !!                  ***  ROUTINE dia_25h_init  ***
68      !!     
69      !! ** Purpose: Initialization of 25h mean namelist
70      !!       
71      !! ** Method : Read namelist
72      !!   History
73      !!   3.6  !  08-14  (E. O'Dea) Routine to initialize dia_25h
74      !!---------------------------------------------------------------------------
75      !!
76      INTEGER ::   ios                 ! Local integer output status for namelist read
77      INTEGER ::   ierror              ! Local integer for memory allocation
78      INTEGER ::   jn                  ! Loop counter
79      REAL(wp), DIMENSION(jpi,jpj,3)   ::   zwtmb                                 ! temporary workspace
80      !
81      NAMELIST/nam_dia25h/ ln_dia25h
82      !!----------------------------------------------------------------------
83      !
84      REWIND ( numnam_ref )              ! Read Namelist nam_dia25h in reference namelist : 25hour mean diagnostics
85      READ   ( numnam_ref, nam_dia25h, IOSTAT=ios, ERR= 901 )
86901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nam_dia25h in reference namelist', lwp )
87
88      REWIND( numnam_cfg )              ! Namelist nam_dia25h in configuration namelist  25hour diagnostics
89      READ  ( numnam_cfg, nam_dia25h, IOSTAT = ios, ERR = 902 )
90902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nam_dia25h in configuration namelist', lwp )
91      IF(lwm) WRITE ( numond, nam_dia25h )
92
93      IF(lwp) THEN                   ! Control print
94         WRITE(numout,*)
95         WRITE(numout,*) 'dia_25h_init : Output 25 hour mean diagnostics'
96         WRITE(numout,*) '~~~~~~~~~~~~'
97         WRITE(numout,*) 'Namelist nam_dia25h : set 25h outputs '
98         WRITE(numout,*) 'Switch for 25h diagnostics (T) or not (F)  ln_dia25h  = ', ln_dia25h
99      ENDIF
100      IF( .NOT. ln_dia25h )   RETURN
101      ! ------------------- !
102      ! 1 - Allocate memory !
103      ! ------------------- !
104      ALLOCATE( tn_25h(jpi,jpj,jpk), STAT=ierror )
105      IF( ierror > 0 ) THEN
106         CALL ctl_stop( 'dia_25h: unable to allocate tn_25h' )   ;   RETURN
107      ENDIF
108      ALLOCATE( sn_25h(jpi,jpj,jpk), STAT=ierror )
109      IF( ierror > 0 ) THEN
110         CALL ctl_stop( 'dia_25h: unable to allocate sn_25h' )   ;   RETURN
111      ENDIF
112      ALLOCATE( rinsitu_t_25h(jpi,jpj,jpk), STAT=ierror )
113      IF( ierror > 0 ) THEN
114         CALL ctl_stop( 'dia_25h: unable to allocate rinsitu_t_25h' )   ;   RETURN
115      ENDIF
116      ALLOCATE( insitu_bot_25h(jpi,jpj), STAT=ierror )
117      IF( ierror > 0 ) THEN
118         CALL ctl_stop( 'dia_25h: unable to allocate insitu_bot_25h' )   ;   RETURN
119      ENDIF     
120      ALLOCATE( temp_bot_25h(jpi,jpj), STAT=ierror )
121      IF( ierror > 0 ) THEN
122         CALL ctl_stop( 'dia_25h: unable to allocate temp_bot_25h' )   ;   RETURN
123      ENDIF                           
124      ALLOCATE( un_25h(jpi,jpj,jpk), STAT=ierror )
125      IF( ierror > 0 ) THEN
126         CALL ctl_stop( 'dia_25h: unable to allocate un_25h' )   ;   RETURN
127      ENDIF
128      ALLOCATE( vn_25h(jpi,jpj,jpk), STAT=ierror )
129      IF( ierror > 0 ) THEN
130         CALL ctl_stop( 'dia_25h: unable to allocate vn_25h' )   ;   RETURN
131      ENDIF
132      ALLOCATE( wn_25h(jpi,jpj,jpk), STAT=ierror )
133      IF( ierror > 0 ) THEN
134         CALL ctl_stop( 'dia_25h: unable to allocate wn_25h' )   ;   RETURN
135      ENDIF
136      ALLOCATE( avt_25h(jpi,jpj,jpk), STAT=ierror )
137      IF( ierror > 0 ) THEN
138         CALL ctl_stop( 'dia_25h: unable to allocate avt_25h' )   ;   RETURN
139      ENDIF
140      ALLOCATE( avm_25h(jpi,jpj,jpk), STAT=ierror )
141      IF( ierror > 0 ) THEN
142         CALL ctl_stop( 'dia_25h: unable to allocate avm_25h' )   ;   RETURN
143      ENDIF
144# if defined key_zdfgls || defined key_zdftke
145      ALLOCATE( en_25h(jpi,jpj,jpk), STAT=ierror )
146      IF( ierror > 0 ) THEN
147         CALL ctl_stop( 'dia_25h: unable to allocate en_25h' )   ;   RETURN
148      ENDIF
149#endif
150# if defined key_zdfgls 
151      ALLOCATE( rmxln_25h(jpi,jpj,jpk), STAT=ierror )
152      IF( ierror > 0 ) THEN
153         CALL ctl_stop( 'dia_25h: unable to allocate rmxln_25h' )   ;   RETURN
154      ENDIF
155#endif
156      ALLOCATE( sshn_25h(jpi,jpj), STAT=ierror )
157      IF( ierror > 0 ) THEN
158         CALL ctl_stop( 'dia_25h: unable to allocate sshn_25h' )   ;   RETURN
159      ENDIF
160#if defined key_fabm
161      ALLOCATE( fabm_25h(jpi,jpj,jpk,jp_fabm), STAT=ierror )
162      IF( ierror > 0 ) THEN
163         CALL ctl_stop( 'dia_25h: unable to allocate fabm_25h' )   ;   RETURN
164      ENDIF
165      ALLOCATE( fabm_3d_25h(jpi,jpj,jpk,jp_fabm_3d), STAT=ierror )
166      IF( ierror > 0 ) THEN
167         CALL ctl_stop( 'dia_25h: unable to allocate fabm_3d_25h' )   ;   RETURN
168      ENDIF
169      ALLOCATE( fabm_surface_25h(jpi,jpj,jp_fabm_surface), STAT=ierror )
170      IF( ierror > 0 ) THEN
171         CALL ctl_stop( 'dia_25h: unable to allocate fabm_surface_25h' )   ;   RETURN
172      ENDIF
173      ALLOCATE( fabm_bottom_25h(jpi,jpj,jp_fabm_bottom), STAT=ierror )
174      IF( ierror > 0 ) THEN
175         CALL ctl_stop( 'dia_25h: unable to allocate fabm_bottom_25h' )   ;   RETURN
176      ENDIF
177      ALLOCATE( fabm_2d_25h(jpi,jpj,jp_fabm_2d), STAT=ierror )
178      IF( ierror > 0 ) THEN
179         CALL ctl_stop( 'dia_25h: unable to allocate fabm_2d_25h' )   ;   RETURN
180      ENDIF
181#endif 
182      ! ------------------------- !
183      ! 2 - Assign Initial Values !
184      ! ------------------------- !
185      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)
186      tn_25h(:,:,:) = tsb(:,:,:,jp_tem)
187      sn_25h(:,:,:) = tsb(:,:,:,jp_sal)
188      CALL theta2t
189      rinsitu_t_25h(:,:,:) = rinsitu_t(:,:,:)
190      CALL dia_calctmb( rinsitu_t(:,:,:),zwtmb )
191      insitu_bot_25h(:,:) = zwtmb(:,:,3)
192      CALL dia_calctmb( tn_25h(:,:,:),zwtmb )
193      temp_bot_25h(:,:) = zwtmb(:,:,3)
194      sshn_25h(:,:) = sshb(:,:)
195      un_25h(:,:,:) = ub(:,:,:)
196      vn_25h(:,:,:) = vb(:,:,:)
197      wn_25h(:,:,:) = wn(:,:,:)
198      avt_25h(:,:,:) = avt(:,:,:)
199      avm_25h(:,:,:) = avm(:,:,:)
200# if defined key_zdfgls || defined key_zdftke
201         en_25h(:,:,:) = en(:,:,:)
202#endif
203# if defined key_zdfgls
204         rmxln_25h(:,:,:) = mxln(:,:,:)
205#endif
206#if defined key_fabm
207      DO jn = 1, jp_fabm
208         fabm_25h(:,:,:,jn) = trn(:,:,:,jp_fabm_m1+jn)
209      END DO
210      DO jn = 1, jp_fabm_3d
211         IF (iom_use(TRIM(model%interior_diagnostic_variables(jn)%name)//'25h')) THEN
212            fabm_3d_25h(:,:,:,jn) = model%get_interior_diagnostic_data(jn)
213         ENDIF
214      END DO
215      DO jn = 1, jp_fabm_surface
216         fabm_surface_25h(:,:,jn) = fabm_st2dn(:,:,jn)
217      END DO
218      DO jn = 1, jp_fabm_bottom
219         fabm_bottom_25h(:,:,jn) = fabm_st2dn(:,:,jp_fabm_surface+jn)
220      END DO
221      DO jn = 1, jp_fabm_2d
222         IF (iom_use(TRIM(model%horizontal_diagnostic_variables(jn)%name)//'25h')) THEN
223            fabm_2d_25h(:,:,jn) = model%get_horizontal_diagnostic_data(jn)
224         ENDIF
225      END DO
226#endif
227#if defined key_lim3 || defined key_lim2
228         CALL ctl_stop('STOP', 'dia_25h not setup yet to do tidemean ice')
229#endif 
230
231      ! -------------------------- !
232      ! 3 - Return to dia_wri      !
233      ! -------------------------- !
234
235
236   END SUBROUTINE dia_25h_init
237
238
239   SUBROUTINE dia_25h( kt ) 
240      !!----------------------------------------------------------------------
241      !!                 ***  ROUTINE dia_25h  ***
242      !!         
243      !!
244      !!--------------------------------------------------------------------
245      !!                   
246      !! ** Purpose :   Write diagnostics with M2/S2 tide removed
247      !!
248      !! ** Method  :   
249      !!      25hr mean outputs for shelf seas
250      !!
251      !! History :
252      !!   ?.0  !  07-04  (A. Hines) New routine, developed from dia_wri_foam
253      !!   3.4  !  02-13  (J. Siddorn) Routine taken from old dia_wri_foam
254      !!   3.6  !  08-14  (E. O'Dea) adapted for VN3.6
255      !!----------------------------------------------------------------------
256      !! * Modules used
257
258      IMPLICIT NONE
259
260      !! * Arguments
261      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index
262
263
264      !! * Local declarations
265      INTEGER ::   ji, jj, jk, jn
266
267      LOGICAL ::   ll_print = .FALSE.    ! =T print and flush numout
268      REAL(wp)                         ::   zsto, zout, zmax, zjulian, zdt, zmdi  ! temporary reals
269      INTEGER                          ::   i_steps                               ! no of timesteps per hour
270      REAL(wp), DIMENSION(jpi,jpj    ) ::   zw2d, un_dm, vn_dm                    ! temporary workspace
271      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   zw3d                                  ! temporary workspace
272      REAL(wp), DIMENSION(jpi,jpj,3)   ::   zwtmb                                 ! temporary workspace
273      INTEGER                          ::   iyear0, nimonth0,iday0                ! start year,imonth,day
274
275      !!----------------------------------------------------------------------
276
277      ! 0. Initialisation
278      ! -----------------
279      ! Define frequency of summing to create 25 h mean
280      zdt = rdt
281      IF( nacc == 1 ) zdt = rdtmin
282
283      IF( MOD( 3600,INT(zdt) ) == 0 ) THEN
284         i_steps = 3600/INT(zdt)
285      ELSE
286         CALL ctl_stop('STOP', 'dia_wri_tide: timestep must give MOD(3600,rdt) = 0 otherwise no hourly values are possible')
287      ENDIF
288
289#if defined key_lim3 || defined key_lim2
290      CALL ctl_stop('STOP', 'dia_wri_tide not setup yet to do tidemean ice')
291#endif
292
293      ! local variable for debugging
294      ll_print = ll_print .AND. lwp
295
296      ! Sum of 25 hourly instantaneous values to give a 25h mean from 24hours
297      ! every day
298      IF( MOD( kt, i_steps ) == 0  .and. kt .ne. nn_it000 ) THEN
299
300         IF (lwp) THEN
301              WRITE(numout,*) 'dia_wri_tide : Summing instantaneous hourly diagnostics at timestep ',kt
302              WRITE(numout,*) '~~~~~~~~~~~~ '
303         ENDIF
304
305         tn_25h(:,:,:)        = tn_25h(:,:,:) + tsn(:,:,:,jp_tem)
306         sn_25h(:,:,:)        = sn_25h(:,:,:) + tsn(:,:,:,jp_sal)
307         CALL theta2t
308         rinsitu_t_25h(:,:,:)  = rinsitu_t_25h(:,:,:) + rinsitu_t(:,:,:)
309         CALL dia_calctmb( rinsitu_t(:,:,:),zwtmb )
310         insitu_bot_25h(:,:)  = insitu_bot_25h(:,:) + zwtmb(:,:,3)
311         zw3d(:,:,:)          = tsn(:,:,:,jp_tem)
312         CALL dia_calctmb( zw3d,zwtmb )
313         temp_bot_25h(:,:)    = temp_bot_25h(:,:) + zwtmb(:,:,3)
314         sshn_25h(:,:)        = sshn_25h(:,:) + sshn (:,:)
315         un_25h(:,:,:)        = un_25h(:,:,:) + un(:,:,:)
316         vn_25h(:,:,:)        = vn_25h(:,:,:) + vn(:,:,:)
317         wn_25h(:,:,:)        = wn_25h(:,:,:) + wn(:,:,:)
318         avt_25h(:,:,:)       = avt_25h(:,:,:) + avt(:,:,:)
319         avm_25h(:,:,:)       = avm_25h(:,:,:) + avm(:,:,:)
320# if defined key_zdfgls || defined key_zdftke
321         en_25h(:,:,:)        = en_25h(:,:,:) + en(:,:,:)
322#endif
323# if defined key_zdfgls
324         rmxln_25h(:,:,:)      = rmxln_25h(:,:,:) + mxln(:,:,:)
325#endif
326#if defined key_fabm
327      DO jn = 1, jp_fabm
328         fabm_25h(:,:,:,jn) = fabm_25h(:,:,:,jn) + trn(:,:,:,jp_fabm_m1+jn)
329      END DO
330      DO jn = 1, jp_fabm_3d
331         IF (iom_use(TRIM(model%interior_diagnostic_variables(jn)%name)//'25h')) THEN
332            fabm_3d_25h(:,:,:,jn) = fabm_3d_25h(:,:,:,jn) + model%get_interior_diagnostic_data(jn)
333         ENDIF
334      END DO
335      DO jn = 1, jp_fabm_surface
336         fabm_surface_25h(:,:,jn) = fabm_surface_25h(:,:,jn) + fabm_st2dn(:,:,jn)
337      END DO
338      DO jn = 1, jp_fabm_bottom
339         fabm_bottom_25h(:,:,jn) = fabm_bottom_25h(:,:,jn) + fabm_st2dn(:,:,jp_fabm_surface+jn)
340      END DO
341      DO jn = 1, jp_fabm_2d
342         IF (iom_use(TRIM(model%horizontal_diagnostic_variables(jn)%name)//'25h')) THEN
343            fabm_2d_25h(:,:,jn) = fabm_2d_25h(:,:,jn) + model%get_horizontal_diagnostic_data(jn)
344         ENDIF
345      END DO
346#endif
347         cnt_25h = cnt_25h + 1
348
349         IF (lwp) THEN
350            WRITE(numout,*) 'dia_tide : Summed the following number of hourly values so far',cnt_25h
351         ENDIF
352
353      ENDIF ! MOD( kt, i_steps ) == 0
354
355         ! Write data for 25 hour mean output streams
356      IF( cnt_25h .EQ. 25 .AND.  MOD( kt, i_steps*24) == 0 .AND. kt .NE. nn_it000 ) THEN
357
358            IF(lwp) THEN
359               WRITE(numout,*) 'dia_wri_tide : Writing 25 hour mean tide diagnostics at timestep', kt
360               WRITE(numout,*) '~~~~~~~~~~~~ '
361            ENDIF
362
363            tn_25h(:,:,:)        = tn_25h(:,:,:) / 25.0_wp
364            sn_25h(:,:,:)        = sn_25h(:,:,:) / 25.0_wp
365            rinsitu_t_25h(:,:,:)  = rinsitu_t_25h(:,:,:) / 25.0_wp
366            insitu_bot_25h(:,:)  = insitu_bot_25h(:,:) / 25.0_wp 
367            temp_bot_25h(:,:)    = temp_bot_25h(:,:) /25.0_wp
368            sshn_25h(:,:)        = sshn_25h(:,:) / 25.0_wp
369            un_25h(:,:,:)        = un_25h(:,:,:) / 25.0_wp
370            vn_25h(:,:,:)        = vn_25h(:,:,:) / 25.0_wp
371            wn_25h(:,:,:)        = wn_25h(:,:,:) / 25.0_wp
372            avt_25h(:,:,:)       = avt_25h(:,:,:) / 25.0_wp
373            avm_25h(:,:,:)       = avm_25h(:,:,:) / 25.0_wp
374# if defined key_zdfgls || defined key_zdftke
375            en_25h(:,:,:)        = en_25h(:,:,:) / 25.0_wp
376#endif
377# if defined key_zdfgls
378            rmxln_25h(:,:,:)       = rmxln_25h(:,:,:) / 25.0_wp
379#endif
380#if defined key_fabm
381            fabm_25h(:,:,:,:)       = fabm_25h(:,:,:,:)       / 25.0_wp
382            fabm_3d_25h(:,:,:,:)    = fabm_3d_25h(:,:,:,:)    / 25.0_wp
383            fabm_surface_25h(:,:,:) = fabm_surface_25h(:,:,:) / 25.0_wp
384            fabm_bottom_25h(:,:,:)  = fabm_bottom_25h(:,:,:)  / 25.0_wp
385            fabm_2d_25h(:,:,:)      = fabm_2d_25h(:,:,:)      / 25.0_wp
386#endif
387
388            IF (lwp)  WRITE(numout,*) 'dia_wri_tide : Mean calculated by dividing 25 hour sums and writing output'
389            zmdi=1.e+20 !missing data indicator for masking
390            ! write tracers (instantaneous)
391            zw3d(:,:,:) = tn_25h(:,:,:)*tmask(:,:,:) + zmdi*(1.0-tmask(:,:,:))
392            CALL iom_put("temper25h", zw3d)   ! potential temperature
393            CALL theta2t                                                                    ! calculate insitu temp
394            zw3d(:,:,:) = rinsitu_t_25h(:,:,:)*tmask(:,:,:) + zmdi*(1.0-tmask(:,:,:))
395            CALL iom_put("tempis25h", zw3d)   ! in-situ temperature
396            zw2d(:,:) = insitu_bot_25h(:,:)*tmask(:,:,1) + zmdi*(1.0-tmask(:,:,1))
397            CALL iom_put("tempisbot25h", zw2d) ! bottom in-situ temperature
398            zw2d(:,:) = temp_bot_25h(:,:)*tmask(:,:,1) + zmdi*(1.0-tmask(:,:,1))
399            CALL iom_put("temperbot25h",zw2d) ! bottom potential temperature
400            zw3d(:,:,:) = sn_25h(:,:,:)*tmask(:,:,:) + zmdi*(1.0-tmask(:,:,:))
401            CALL iom_put( "salin25h", zw3d  )   ! salinity
402            zw2d(:,:) = sshn_25h(:,:)*tmask(:,:,1) + zmdi*(1.0-tmask(:,:,1))
403            CALL iom_put( "ssh25h", zw2d )   ! sea surface
404
405#if defined key_fabm
406            ! Write ERSEM variables
407            DO jn = 1, jp_fabm
408               zw3d(:,:,:) = fabm_25h(:,:,:,jn)*tmask(:,:,:) + zmdi*(1.0-tmask(:,:,:))
409               CALL iom_put( TRIM(model%interior_state_variables(jn)%name)//"25h", zw3d  )
410            END DO
411            DO jn = 1, jp_fabm_3d
412               IF (iom_use(TRIM(model%interior_diagnostic_variables(jn)%name)//'25h')) THEN
413                  zw3d(:,:,:) = fabm_3d_25h(:,:,:,jn)*tmask(:,:,:) + zmdi*(1.0-tmask(:,:,:))
414                  CALL iom_put( TRIM(model%interior_diagnostic_variables(jn)%name)//"25h", zw3d  )
415               ENDIF
416            END DO
417            DO jn = 1, jp_fabm_surface
418               zw2d(:,:) = fabm_surface_25h(:,:,jn)*tmask(:,:,1) + zmdi*(1.0-tmask(:,:,1))
419               CALL iom_put( TRIM(model%surface_state_variables(jn)%name)//"25h", zw2d  )
420            END DO
421            DO jn = 1, jp_fabm_bottom
422               zw2d(:,:) = fabm_bottom_25h(:,:,jn)*tmask(:,:,1) + zmdi*(1.0-tmask(:,:,1))
423               CALL iom_put( TRIM(model%bottom_state_variables(jn)%name)//"25h", zw2d  )
424            END DO
425            DO jn = 1, jp_fabm_2d
426               IF (iom_use(TRIM(model%horizontal_diagnostic_variables(jn)%name)//'25h')) THEN
427                  zw2d(:,:) = fabm_2d_25h(:,:,jn)*tmask(:,:,1) + zmdi*(1.0-tmask(:,:,1))
428                  CALL iom_put( TRIM(model%horizontal_diagnostic_variables(jn)%name)//"25h", zw2d  )
429               ENDIF
430            END DO
431#endif
432
433            ! Write velocities (instantaneous)
434            zw3d(:,:,:) = un_25h(:,:,:)*umask(:,:,:) + zmdi*(1.0-umask(:,:,:))
435            CALL iom_put("vozocrtx25h", zw3d)    ! i-current
436            zw3d(:,:,:) = vn_25h(:,:,:)*vmask(:,:,:) + zmdi*(1.0-vmask(:,:,:))
437            CALL iom_put("vomecrty25h", zw3d  )   ! j-current
438
439            zw3d(:,:,:) = wn_25h(:,:,:)*tmask(:,:,:) + zmdi*(1.0-tmask(:,:,:))
440            CALL iom_put("vomecrtz25h", zw3d )   ! k-current
441            zw3d(:,:,:) = avt_25h(:,:,:)*tmask(:,:,:) + zmdi*(1.0-tmask(:,:,:))
442            CALL iom_put("avt25h", zw3d )   ! diffusivity
443            zw3d(:,:,:) = avm_25h(:,:,:)*tmask(:,:,:) + zmdi*(1.0-tmask(:,:,:))
444            CALL iom_put("avm25h", zw3d)   ! viscosity
445#if defined key_zdftke || defined key_zdfgls 
446!           zw3d(:,:,:) = en_25h(:,:,:)*tmask(:,:,:) + zmdi*(1.0-tmask(:,:,:))
447!           CALL iom_put("tke25h", zw3d)   ! tke
448#endif
449#if defined key_zdfgls 
450!           zw3d(:,:,:) = rmxln_25h(:,:,:)*tmask(:,:,:) + zmdi*(1.0-tmask(:,:,:))
451!           CALL iom_put( "mxln25h",zw3d)
452#endif
453
454            ! After the write reset the values to cnt=1 and sum values equal current value
455            tn_25h(:,:,:) = tsn(:,:,:,jp_tem)
456            sn_25h(:,:,:) = tsn(:,:,:,jp_sal)
457            CALL theta2t
458            rinsitu_t_25h(:,:,:) = rinsitu_t(:,:,:)
459            CALL dia_calctmb( rinsitu_t(:,:,:),zwtmb )
460            insitu_bot_25h(:,:) = zwtmb(:,:,3)
461            CALL dia_calctmb( tn_25h(:,:,:),zwtmb)
462            temp_bot_25h(:,:) = zwtmb(:,:,3)
463            sshn_25h(:,:) = sshn (:,:)
464            un_25h(:,:,:) = un(:,:,:)
465            vn_25h(:,:,:) = vn(:,:,:)
466            wn_25h(:,:,:) = wn(:,:,:)
467            avt_25h(:,:,:) = avt(:,:,:)
468            avm_25h(:,:,:) = avm(:,:,:)
469# if defined key_zdfgls || defined key_zdftke
470            en_25h(:,:,:) = en(:,:,:)
471#endif
472# if defined key_zdfgls
473            rmxln_25h(:,:,:) = mxln(:,:,:)
474#endif
475#if defined key_fabm
476      DO jn = 1, jp_fabm
477         fabm_25h(:,:,:,jn) = trn(:,:,:,jp_fabm_m1+jn)
478      END DO
479      DO jn = 1, jp_fabm_3d
480         IF (iom_use(TRIM(model%interior_diagnostic_variables(jn)%name)//'25h')) THEN
481            fabm_3d_25h(:,:,:,jn) = model%get_interior_diagnostic_data(jn)
482         ENDIF
483      END DO
484      DO jn = 1, jp_fabm_surface
485         fabm_surface_25h(:,:,jn) = fabm_st2dn(:,:,jn)
486      END DO
487      DO jn = 1, jp_fabm_bottom
488         fabm_bottom_25h(:,:,jn) = fabm_st2dn(:,:,jp_fabm_surface+jn)
489      END DO
490      DO jn = 1, jp_fabm_2d
491         IF (iom_use(TRIM(model%horizontal_diagnostic_variables(jn)%name)//'25h')) THEN
492            fabm_2d_25h(:,:,jn) = model%get_horizontal_diagnostic_data(jn)
493         ENDIF
494      END DO
495#endif
496            cnt_25h = 1
497            IF (lwp)  WRITE(numout,*) 'dia_wri_tide : After 25hr mean write, reset sum to current value and cnt_25h to one for overlapping average',cnt_25h
498
499      ENDIF !  cnt_25h .EQ. 25 .AND.  MOD( kt, i_steps * 24) == 0 .AND. kt .NE. nn_it000
500
501
502   END SUBROUTINE dia_25h 
503
504   !!======================================================================
505END MODULE dia25h
Note: See TracBrowser for help on using the repository browser.