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/2016/dev_r6519_HPC_4/NEMOGCM/NEMO/OPA_SRC/DIA – NEMO

source: branches/2016/dev_r6519_HPC_4/NEMOGCM/NEMO/OPA_SRC/DIA/dia25h.F90 @ 7037

Last change on this file since 7037 was 7037, checked in by mocavero, 8 years ago

ORCA2_LIM_PISCES hybrid version update

File size: 14.1 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 in_out_manager  ! I/O units
11   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
21
22   IMPLICIT NONE
23   PRIVATE
24
25   LOGICAL , PUBLIC ::   ln_dia25h     !:  25h mean output
26   PUBLIC   dia_25h_init               ! routine called by nemogcm.F90
27   PUBLIC   dia_25h                    ! routine called by diawri.F90
28
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
43
44   !!----------------------------------------------------------------------
45   !! NEMO/OPA 3.6 , NEMO Consortium (2014)
46   !! $Id:$
47   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
48   !!----------------------------------------------------------------------
49CONTAINS
50
51   SUBROUTINE dia_25h_init 
52      !!---------------------------------------------------------------------------
53      !!                  ***  ROUTINE dia_25h_init  ***
54      !!     
55      !! ** Purpose: Initialization of 25h mean namelist
56      !!       
57      !! ** Method : Read namelist
58      !!   History
59      !!   3.6  !  08-14  (E. O'Dea) Routine to initialize dia_25h
60      !!---------------------------------------------------------------------------
61      !!
62      INTEGER ::   ios                 ! Local integer output status for namelist read
63      INTEGER ::   ierror              ! Local integer for memory allocation
64      !
65      NAMELIST/nam_dia25h/ ln_dia25h
66      !!----------------------------------------------------------------------
67      !
68      REWIND ( numnam_ref )              ! Read Namelist nam_dia25h in reference namelist : 25hour mean diagnostics
69      READ   ( numnam_ref, nam_dia25h, IOSTAT=ios, ERR= 901 )
70901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nam_dia25h in reference namelist', lwp )
71
72      REWIND( numnam_cfg )              ! Namelist nam_dia25h in configuration namelist  25hour diagnostics
73      READ  ( numnam_cfg, nam_dia25h, IOSTAT = ios, ERR = 902 )
74902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nam_dia25h in configuration namelist', lwp )
75      IF(lwm) WRITE ( numond, nam_dia25h )
76
77      IF(lwp) THEN                   ! Control print
78         WRITE(numout,*)
79         WRITE(numout,*) 'dia_25h_init : Output 25 hour mean diagnostics'
80         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
83      ENDIF
84      IF( .NOT. ln_dia25h )   RETURN
85      ! ------------------- !
86      ! 1 - Allocate memory !
87      ! ------------------- !
88      ALLOCATE( tn_25h(jpi,jpj,jpk), STAT=ierror )
89      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
131      ENDIF
132      ! ------------------------- !
133      ! 2 - Assign Initial Values !
134      ! ------------------------- !
135      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!$OMP PARALLEL WORKSHARE
137      tn_25h(:,:,:) = tsb(:,:,:,jp_tem)
138      sn_25h(:,:,:) = tsb(:,:,:,jp_sal)
139      sshn_25h(:,:) = sshb(:,:)
140      un_25h(:,:,:) = ub(:,:,:)
141      vn_25h(:,:,:) = vb(:,:,:)
142      wn_25h(:,:,:) = wn(:,:,:)
143      avt_25h(:,:,:) = avt(:,:,:)
144      avm_25h(:,:,:) = avm(:,:,:)
145# if defined key_zdfgls || defined key_zdftke
146         en_25h(:,:,:) = en(:,:,:)
147#endif
148# if defined key_zdfgls
149         rmxln_25h(:,:,:) = mxln(:,:,:)
150#endif
151!$OMP END PARALLEL WORKSHARE
152#if defined key_lim3 || defined key_lim2
153         CALL ctl_stop('STOP', 'dia_25h not setup yet to do tidemean ice')
154#endif 
155
156      ! -------------------------- !
157      ! 3 - Return to dia_wri      !
158      ! -------------------------- !
159
160
161   END SUBROUTINE dia_25h_init
162
163
164   SUBROUTINE dia_25h( kt ) 
165      !!----------------------------------------------------------------------
166      !!                 ***  ROUTINE dia_25h  ***
167      !!         
168      !!
169      !!--------------------------------------------------------------------
170      !!                   
171      !! ** Purpose :   Write diagnostics with M2/S2 tide removed
172      !!
173      !! ** Method  :   
174      !!      25hr mean outputs for shelf seas
175      !!
176      !! History :
177      !!   ?.0  !  07-04  (A. Hines) New routine, developed from dia_wri_foam
178      !!   3.4  !  02-13  (J. Siddorn) Routine taken from old dia_wri_foam
179      !!   3.6  !  08-14  (E. O'Dea) adapted for VN3.6
180      !!----------------------------------------------------------------------
181      !! * Modules used
182
183      IMPLICIT NONE
184
185      !! * Arguments
186      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index
187
188
189      !! * Local declarations
190      INTEGER ::   ji, jj, jk
191
192      LOGICAL ::   ll_print = .FALSE.    ! =T print and flush numout
193      REAL(wp)                         ::   zsto, zout, zmax, zjulian, zmdi       ! temporary reals
194      INTEGER                          ::   i_steps                               ! no of timesteps per hour
195      REAL(wp), DIMENSION(jpi,jpj    ) ::   zw2d, un_dm, vn_dm                    ! temporary workspace
196      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   zw3d                                  ! temporary workspace
197      REAL(wp), DIMENSION(jpi,jpj,3)   ::   zwtmb                                 ! temporary workspace
198      INTEGER                          ::   iyear0, nimonth0,iday0                ! start year,imonth,day
199
200      !!----------------------------------------------------------------------
201
202      ! 0. Initialisation
203      ! -----------------
204      ! Define frequency of summing to create 25 h mean
205      IF( MOD( 3600,INT(rdt) ) == 0 ) THEN
206         i_steps = 3600/INT(rdt)
207      ELSE
208         CALL ctl_stop('STOP', 'dia_wri_tide: timestep must give MOD(3600,rdt) = 0 otherwise no hourly values are possible')
209      ENDIF
210
211#if defined key_lim3 || defined key_lim2
212      CALL ctl_stop('STOP', 'dia_wri_tide not setup yet to do tidemean ice')
213#endif
214
215      ! local variable for debugging
216      ll_print = ll_print .AND. lwp
217
218      ! Sum of 25 hourly instantaneous values to give a 25h mean from 24hours
219      ! every day
220      IF( MOD( kt, i_steps ) == 0  .and. kt .ne. nn_it000 ) THEN
221
222         IF (lwp) THEN
223              WRITE(numout,*) 'dia_wri_tide : Summing instantaneous hourly diagnostics at timestep ',kt
224              WRITE(numout,*) '~~~~~~~~~~~~ '
225         ENDIF
226
227!$OMP PARALLEL WORKSHARE
228         tn_25h(:,:,:)        = tn_25h(:,:,:) + tsn(:,:,:,jp_tem)
229         sn_25h(:,:,:)        = sn_25h(:,:,:) + tsn(:,:,:,jp_sal)
230         sshn_25h(:,:)        = sshn_25h(:,:) + sshn (:,:)
231         un_25h(:,:,:)        = un_25h(:,:,:) + un(:,:,:)
232         vn_25h(:,:,:)        = vn_25h(:,:,:) + vn(:,:,:)
233         wn_25h(:,:,:)        = wn_25h(:,:,:) + wn(:,:,:)
234         avt_25h(:,:,:)       = avt_25h(:,:,:) + avt(:,:,:)
235         avm_25h(:,:,:)       = avm_25h(:,:,:) + avm(:,:,:)
236# if defined key_zdfgls || defined key_zdftke
237         en_25h(:,:,:)        = en_25h(:,:,:) + en(:,:,:)
238#endif
239# if defined key_zdfgls
240         rmxln_25h(:,:,:)      = rmxln_25h(:,:,:) + mxln(:,:,:)
241#endif
242!$OMP END PARALLEL WORKSHARE
243         cnt_25h = cnt_25h + 1
244
245         IF (lwp) THEN
246            WRITE(numout,*) 'dia_tide : Summed the following number of hourly values so far',cnt_25h
247         ENDIF
248
249      ENDIF ! MOD( kt, i_steps ) == 0
250
251         ! Write data for 25 hour mean output streams
252      IF( cnt_25h .EQ. 25 .AND.  MOD( kt, i_steps*24) == 0 .AND. kt .NE. nn_it000 ) THEN
253
254            IF(lwp) THEN
255               WRITE(numout,*) 'dia_wri_tide : Writing 25 hour mean tide diagnostics at timestep', kt
256               WRITE(numout,*) '~~~~~~~~~~~~ '
257            ENDIF
258
259!$OMP PARALLEL WORKSHARE
260            tn_25h(:,:,:)        = tn_25h(:,:,:) / 25.0_wp
261            sn_25h(:,:,:)        = sn_25h(:,:,:) / 25.0_wp
262            sshn_25h(:,:)        = sshn_25h(:,:) / 25.0_wp
263            un_25h(:,:,:)        = un_25h(:,:,:) / 25.0_wp
264            vn_25h(:,:,:)        = vn_25h(:,:,:) / 25.0_wp
265            wn_25h(:,:,:)        = wn_25h(:,:,:) / 25.0_wp
266            avt_25h(:,:,:)       = avt_25h(:,:,:) / 25.0_wp
267            avm_25h(:,:,:)       = avm_25h(:,:,:) / 25.0_wp
268# if defined key_zdfgls || defined key_zdftke
269            en_25h(:,:,:)        = en_25h(:,:,:) / 25.0_wp
270#endif
271# if defined key_zdfgls
272            rmxln_25h(:,:,:)       = rmxln_25h(:,:,:) / 25.0_wp
273#endif
274!$OMP END PARALLEL WORKSHARE
275
276            IF (lwp)  WRITE(numout,*) 'dia_wri_tide : Mean calculated by dividing 25 hour sums and writing output'
277            zmdi=1.e+20 !missing data indicator for masking
278            ! write tracers (instantaneous)
279!$OMP PARALLEL WORKSHARE
280            zw3d(:,:,:) = tn_25h(:,:,:)*tmask(:,:,:) + zmdi*(1.0-tmask(:,:,:))
281!$OMP END PARALLEL WORKSHARE
282            CALL iom_put("temper25h", zw3d)   ! potential temperature
283!$OMP PARALLEL WORKSHARE
284            zw3d(:,:,:) = sn_25h(:,:,:)*tmask(:,:,:) + zmdi*(1.0-tmask(:,:,:))
285!$OMP END PARALLEL WORKSHARE
286            CALL iom_put( "salin25h", zw3d  )   ! salinity
287!$OMP PARALLEL WORKSHARE
288            zw2d(:,:) = sshn_25h(:,:)*tmask(:,:,1) + zmdi*(1.0-tmask(:,:,1))
289!$OMP END PARALLEL WORKSHARE
290            CALL iom_put( "ssh25h", zw2d )   ! sea surface
291
292
293            ! Write velocities (instantaneous)
294!$OMP PARALLEL WORKSHARE
295            zw3d(:,:,:) = un_25h(:,:,:)*umask(:,:,:) + zmdi*(1.0-umask(:,:,:))
296!$OMP END PARALLEL WORKSHARE
297            CALL iom_put("vozocrtx25h", zw3d)    ! i-current
298!$OMP PARALLEL WORKSHARE
299            zw3d(:,:,:) = vn_25h(:,:,:)*vmask(:,:,:) + zmdi*(1.0-vmask(:,:,:))
300!$OMP END PARALLEL WORKSHARE
301            CALL iom_put("vomecrty25h", zw3d  )   ! j-current
302
303!$OMP PARALLEL WORKSHARE
304            zw3d(:,:,:) = wn_25h(:,:,:)*tmask(:,:,:) + zmdi*(1.0-tmask(:,:,:))
305!$OMP END PARALLEL WORKSHARE
306            CALL iom_put("vomecrtz25h", zw3d )   ! k-current
307!$OMP PARALLEL WORKSHARE
308            zw3d(:,:,:) = avt_25h(:,:,:)*tmask(:,:,:) + zmdi*(1.0-tmask(:,:,:))
309!$OMP END PARALLEL WORKSHARE
310            CALL iom_put("avt25h", zw3d )   ! diffusivity
311!$OMP PARALLEL WORKSHARE
312            zw3d(:,:,:) = avm_25h(:,:,:)*tmask(:,:,:) + zmdi*(1.0-tmask(:,:,:))
313!$OMP END PARALLEL WORKSHARE
314            CALL iom_put("avm25h", zw3d)   ! viscosity
315#if defined key_zdftke || defined key_zdfgls 
316!$OMP PARALLEL WORKSHARE
317            zw3d(:,:,:) = en_25h(:,:,:)*tmask(:,:,:) + zmdi*(1.0-tmask(:,:,:))
318!$OMP END PARALLEL WORKSHARE
319            CALL iom_put("tke25h", zw3d)   ! tke
320#endif
321#if defined key_zdfgls 
322!$OMP PARALLEL WORKSHARE
323            zw3d(:,:,:) = rmxln_25h(:,:,:)*tmask(:,:,:) + zmdi*(1.0-tmask(:,:,:))
324!$OMP END PARALLEL WORKSHARE
325            CALL iom_put( "mxln25h",zw3d)
326#endif
327
328            ! After the write reset the values to cnt=1 and sum values equal current value
329!$OMP PARALLEL WORKSHARE
330            tn_25h(:,:,:) = tsn(:,:,:,jp_tem)
331            sn_25h(:,:,:) = tsn(:,:,:,jp_sal)
332            sshn_25h(:,:) = sshn (:,:)
333            un_25h(:,:,:) = un(:,:,:)
334            vn_25h(:,:,:) = vn(:,:,:)
335            wn_25h(:,:,:) = wn(:,:,:)
336            avt_25h(:,:,:) = avt(:,:,:)
337            avm_25h(:,:,:) = avm(:,:,:)
338# if defined key_zdfgls || defined key_zdftke
339            en_25h(:,:,:) = en(:,:,:)
340#endif
341# if defined key_zdfgls
342            rmxln_25h(:,:,:) = mxln(:,:,:)
343#endif
344!$OMP END PARALLEL WORKSHARE
345            cnt_25h = 1
346            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
347
348      ENDIF !  cnt_25h .EQ. 25 .AND.  MOD( kt, i_steps * 24) == 0 .AND. kt .NE. nn_it000
349
350
351   END SUBROUTINE dia_25h 
352
353   !!======================================================================
354END MODULE dia25h
Note: See TracBrowser for help on using the repository browser.