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 NEMO/trunk/src/OCE/DIA – NEMO

source: NEMO/trunk/src/OCE/DIA/dia25h.F90 @ 12377

Last change on this file since 12377 was 12377, checked in by acc, 4 years ago

The big one. Merging all 2019 developments from the option 1 branch back onto the trunk.

This changeset reproduces 2019/dev_r11943_MERGE_2019 on the trunk using a 2-URL merge
onto a working copy of the trunk. I.e.:

svn merge --ignore-ancestry \

svn+ssh://acc@forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/NEMO/trunk \
svn+ssh://acc@forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/NEMO/branches/2019/dev_r11943_MERGE_2019 ./

The --ignore-ancestry flag avoids problems that may otherwise arise from the fact that
the merge history been trunk and branch may have been applied in a different order but
care has been taken before this step to ensure that all applicable fixes and updates
are present in the merge branch.

The trunk state just before this step has been branched to releases/release-4.0-HEAD
and that branch has been immediately tagged as releases/release-4.0.2. Any fixes
or additions in response to tickets on 4.0, 4.0.1 or 4.0.2 should be done on
releases/release-4.0-HEAD. From now on future 'point' releases (e.g. 4.0.2) will
remain unchanged with periodic releases as needs demand. Note release-4.0-HEAD is a
transitional naming convention. Future full releases, say 4.2, will have a release-4.2
branch which fulfills this role and the first point release (e.g. 4.2.0) will be made
immediately following the release branch creation.

2020 developments can be started from any trunk revision later than this one.

  • Property svn:keywords set to Id
File size: 12.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 zdf_oce         ! ocean vertical physics   
11   USE zdfgls   , ONLY : hmxl_n
12   !
13   USE in_out_manager  ! I/O units
14   USE iom             ! I/0 library
15   USE wet_dry
16
17   IMPLICIT NONE
18   PRIVATE
19
20   PUBLIC   dia_25h_init               ! routine called by nemogcm.F90
21   PUBLIC   dia_25h                    ! routine called by diawri.F90
22
23   LOGICAL, PUBLIC ::   ln_dia25h      !:  25h mean output
24
25   ! variables for calculating 25-hourly means
26   INTEGER , SAVE ::   cnt_25h           ! Counter for 25 hour means
27   REAL(wp), SAVE ::   r1_25 = 0.04_wp   ! =1/25
28   REAL(wp), SAVE, ALLOCATABLE, DIMENSION(:,:,:) ::   tn_25h  , sn_25h
29   REAL(wp), SAVE, ALLOCATABLE, DIMENSION(:,:)   ::   sshn_25h 
30   REAL(wp), SAVE, ALLOCATABLE, DIMENSION(:,:,:) ::   un_25h  , vn_25h  , wn_25h
31   REAL(wp), SAVE, ALLOCATABLE, DIMENSION(:,:,:) ::   avt_25h , avm_25h
32   REAL(wp), SAVE, ALLOCATABLE, DIMENSION(:,:,:) ::   en_25h  , rmxln_25h
33
34   !!----------------------------------------------------------------------
35   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
36   !! $Id$
37   !! Software governed by the CeCILL license (see ./LICENSE)
38   !!----------------------------------------------------------------------
39CONTAINS
40
41   SUBROUTINE dia_25h_init( Kbb )
42      !!---------------------------------------------------------------------------
43      !!                  ***  ROUTINE dia_25h_init  ***
44      !!     
45      !! ** Purpose: Initialization of 25h mean namelist
46      !!       
47      !! ** Method : Read namelist
48      !!---------------------------------------------------------------------------
49      INTEGER, INTENT(in) :: Kbb       ! Time level index
50      !
51      INTEGER ::   ios                 ! Local integer output status for namelist read
52      INTEGER ::   ierror              ! Local integer for memory allocation
53      !
54      NAMELIST/nam_dia25h/ ln_dia25h
55      !!----------------------------------------------------------------------
56      !
57      READ   ( numnam_ref, nam_dia25h, IOSTAT=ios, ERR= 901 )
58901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'nam_dia25h in reference namelist' )
59      READ  ( numnam_cfg, nam_dia25h, IOSTAT = ios, ERR = 902 )
60902   IF( ios >  0 )   CALL ctl_nam ( ios , 'nam_dia25h in configuration namelist' )
61      IF(lwm) WRITE ( numond, nam_dia25h )
62
63      IF(lwp) THEN                   ! Control print
64         WRITE(numout,*)
65         WRITE(numout,*) 'dia_25h_init : Output 25 hour mean diagnostics'
66         WRITE(numout,*) '~~~~~~~~~~~~'
67         WRITE(numout,*) '   Namelist nam_dia25h : set 25h outputs '
68         WRITE(numout,*) '      Switch for 25h diagnostics (T) or not (F)  ln_dia25h  = ', ln_dia25h
69      ENDIF
70      IF( .NOT. ln_dia25h )   RETURN
71      ! ------------------- !
72      ! 1 - Allocate memory !
73      ! ------------------- !
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 )
78      IF( ierror > 0 ) THEN
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
92      ENDIF
93      ! ------------------------- !
94      ! 2 - Assign Initial Values !
95      ! ------------------------- !
96      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)
97      tn_25h  (:,:,:) = ts (:,:,:,jp_tem,Kbb)
98      sn_25h  (:,:,:) = ts (:,:,:,jp_sal,Kbb)
99      sshn_25h(:,:)   = ssh(:,:,Kbb)
100      un_25h  (:,:,:) = uu  (:,:,:,Kbb)
101      vn_25h  (:,:,:) = vv  (:,:,:,Kbb)
102      avt_25h (:,:,:) = avt (:,:,:)
103      avm_25h (:,:,:) = avm (:,:,:)
104      IF( ln_zdftke ) THEN
105         en_25h(:,:,:) = en(:,:,:)
106      ENDIF
107      IF( ln_zdfgls ) THEN
108         en_25h   (:,:,:) = en    (:,:,:)
109         rmxln_25h(:,:,:) = hmxl_n(:,:,:)
110      ENDIF
111#if defined key_si3
112      CALL ctl_stop('STOP', 'dia_25h not setup yet to do tidemean ice')
113#endif 
114      !
115   END SUBROUTINE dia_25h_init
116
117
118   SUBROUTINE dia_25h( kt, Kmm ) 
119      !!----------------------------------------------------------------------
120      !!                 ***  ROUTINE dia_25h  ***
121      !!         
122      !! ** Purpose :   Write diagnostics with M2/S2 tide removed
123      !!
124      !! ** Method  :   25hr mean outputs for shelf seas
125      !!----------------------------------------------------------------------
126      INTEGER, INTENT(in) ::   kt   ! ocean time-step index
127      INTEGER, INTENT(in) ::   Kmm  ! ocean time level index
128      !!
129      INTEGER ::   ji, jj, jk
130      INTEGER                          ::   iyear0, nimonth0,iday0            ! start year,imonth,day
131      LOGICAL ::   ll_print = .FALSE.    ! =T print and flush numout
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
137      !!----------------------------------------------------------------------
138
139      ! 0. Initialisation
140      ! -----------------
141      ! Define frequency of summing to create 25 h mean
142      IF( MOD( 3600,NINT(rdt) ) == 0 ) THEN
143         i_steps = 3600/NINT(rdt)
144      ELSE
145         CALL ctl_stop('STOP', 'dia_wri_tide: timestep must give MOD(3600,rdt) = 0 otherwise no hourly values are possible')
146      ENDIF
147
148      ! local variable for debugging
149      ll_print = ll_print .AND. lwp
150
151      ! wn_25h could not be initialised in dia_25h_init, so we do it here instead
152      IF( kt == nn_it000 ) THEN
153         wn_25h(:,:,:) = ww(:,:,:)
154      ENDIF
155
156      ! Sum of 25 hourly instantaneous values to give a 25h mean from 24hours every day
157      IF( MOD( kt, i_steps ) == 0  .AND. kt /= nn_it000 ) THEN
158
159         IF (lwp) THEN
160              WRITE(numout,*) 'dia_wri_tide : Summing instantaneous hourly diagnostics at timestep ',kt
161              WRITE(numout,*) '~~~~~~~~~~~~ '
162         ENDIF
163
164         tn_25h  (:,:,:)     = tn_25h  (:,:,:) + ts (:,:,:,jp_tem,Kmm)
165         sn_25h  (:,:,:)     = sn_25h  (:,:,:) + ts (:,:,:,jp_sal,Kmm)
166         sshn_25h(:,:)       = sshn_25h(:,:)   + ssh(:,:,Kmm)
167         un_25h  (:,:,:)     = un_25h  (:,:,:) + uu  (:,:,:,Kmm)
168         vn_25h  (:,:,:)     = vn_25h  (:,:,:) + vv  (:,:,:,Kmm)
169         wn_25h  (:,:,:)     = wn_25h  (:,:,:) + ww  (:,:,:)
170         avt_25h (:,:,:)     = avt_25h (:,:,:) + avt (:,:,:)
171         avm_25h (:,:,:)     = avm_25h (:,:,:) + avm (:,:,:)
172         IF( ln_zdftke ) THEN
173            en_25h(:,:,:)    = en_25h  (:,:,:) + en(:,:,:)
174         ENDIF
175         IF( ln_zdfgls ) THEN
176            en_25h   (:,:,:) = en_25h   (:,:,:) + en    (:,:,:)
177            rmxln_25h(:,:,:) = rmxln_25h(:,:,:) + hmxl_n(:,:,:)
178         ENDIF
179         cnt_25h = cnt_25h + 1
180         !
181         IF (lwp) THEN
182            WRITE(numout,*) 'dia_tide : Summed the following number of hourly values so far',cnt_25h
183         ENDIF
184         !
185      ENDIF ! MOD( kt, i_steps ) == 0
186
187      ! Write data for 25 hour mean output streams
188      IF( cnt_25h == 25 .AND.  MOD( kt, i_steps*24) == 0 .AND. kt /= nn_it000 ) THEN
189         !
190         IF(lwp) THEN
191            WRITE(numout,*) 'dia_wri_tide : Writing 25 hour mean tide diagnostics at timestep', kt
192            WRITE(numout,*) '~~~~~~~~~~~~ '
193         ENDIF
194         !
195         tn_25h  (:,:,:) = tn_25h  (:,:,:) * r1_25
196         sn_25h  (:,:,:) = sn_25h  (:,:,:) * r1_25
197         sshn_25h(:,:)   = sshn_25h(:,:)   * r1_25
198         un_25h  (:,:,:) = un_25h  (:,:,:) * r1_25
199         vn_25h  (:,:,:) = vn_25h  (:,:,:) * r1_25
200         wn_25h  (:,:,:) = wn_25h  (:,:,:) * r1_25
201         avt_25h (:,:,:) = avt_25h (:,:,:) * r1_25
202         avm_25h (:,:,:) = avm_25h (:,:,:) * r1_25
203         IF( ln_zdftke ) THEN
204            en_25h(:,:,:) = en_25h(:,:,:) * r1_25
205         ENDIF
206         IF( ln_zdfgls ) THEN
207            en_25h   (:,:,:) = en_25h   (:,:,:) * r1_25
208            rmxln_25h(:,:,:) = rmxln_25h(:,:,:) * r1_25
209         ENDIF
210         !
211         IF(lwp)  WRITE(numout,*) 'dia_wri_tide : Mean calculated by dividing 25 hour sums and writing output'
212         zmdi=1.e+20 !missing data indicator for masking
213         ! write tracers (instantaneous)
214         zw3d(:,:,:) = tn_25h(:,:,:)*tmask(:,:,:) + zmdi*(1.0-tmask(:,:,:))
215         CALL iom_put("temper25h", zw3d)   ! potential temperature
216         zw3d(:,:,:) = sn_25h(:,:,:)*tmask(:,:,:) + zmdi*(1.0-tmask(:,:,:))
217         CALL iom_put( "salin25h", zw3d  )   ! salinity
218         zw2d(:,:) = sshn_25h(:,:)*tmask(:,:,1) + zmdi*(1.0-tmask(:,:,1))
219         IF( ll_wd ) THEN
220            CALL iom_put( "ssh25h", zw2d+ssh_ref )   ! sea surface
221         ELSE
222            CALL iom_put( "ssh25h", zw2d )   ! sea surface
223         ENDIF
224         ! Write velocities (instantaneous)
225         zw3d(:,:,:) = un_25h(:,:,:)*umask(:,:,:) + zmdi*(1.0-umask(:,:,:))
226         CALL iom_put("vozocrtx25h", zw3d)    ! i-current
227         zw3d(:,:,:) = vn_25h(:,:,:)*vmask(:,:,:) + zmdi*(1.0-vmask(:,:,:))
228         CALL iom_put("vomecrty25h", zw3d  )   ! j-current
229         zw3d(:,:,:) = wn_25h(:,:,:)*wmask(:,:,:) + zmdi*(1.0-tmask(:,:,:))
230         CALL iom_put("vovecrtz25h", zw3d )   ! k-current
231         ! Write vertical physics
232         zw3d(:,:,:) = avt_25h(:,:,:)*wmask(:,:,:) + zmdi*(1.0-tmask(:,:,:))
233         CALL iom_put("avt25h", zw3d )   ! diffusivity
234         zw3d(:,:,:) = avm_25h(:,:,:)*wmask(:,:,:) + zmdi*(1.0-tmask(:,:,:))
235         CALL iom_put("avm25h", zw3d)   ! viscosity
236         IF( ln_zdftke ) THEN
237            zw3d(:,:,:) = en_25h(:,:,:)*wmask(:,:,:) + zmdi*(1.0-tmask(:,:,:))
238            CALL iom_put("tke25h", zw3d)   ! tke
239         ENDIF
240         IF( ln_zdfgls ) THEN
241            zw3d(:,:,:) = en_25h(:,:,:)*wmask(:,:,:) + zmdi*(1.0-tmask(:,:,:))
242            CALL iom_put("tke25h", zw3d)   ! tke
243            zw3d(:,:,:) = rmxln_25h(:,:,:)*wmask(:,:,:) + zmdi*(1.0-tmask(:,:,:))
244            CALL iom_put( "mxln25h",zw3d)
245         ENDIF
246         !
247         ! After the write reset the values to cnt=1 and sum values equal current value
248         tn_25h  (:,:,:) = ts (:,:,:,jp_tem,Kmm)
249         sn_25h  (:,:,:) = ts (:,:,:,jp_sal,Kmm)
250         sshn_25h(:,:)   = ssh(:,:,Kmm)
251         un_25h  (:,:,:) = uu  (:,:,:,Kmm)
252         vn_25h  (:,:,:) = vv  (:,:,:,Kmm)
253         wn_25h  (:,:,:) = ww  (:,:,:)
254         avt_25h (:,:,:) = avt (:,:,:)
255         avm_25h (:,:,:) = avm (:,:,:)
256         IF( ln_zdftke ) THEN
257            en_25h(:,:,:) = en(:,:,:)
258         ENDIF
259         IF( ln_zdfgls ) THEN
260            en_25h   (:,:,:) = en    (:,:,:)
261            rmxln_25h(:,:,:) = hmxl_n(:,:,:)
262         ENDIF
263         cnt_25h = 1
264         IF(lwp)  WRITE(numout,*) 'dia_wri_tide :   &
265            &    After 25hr mean write, reset sum to current value and cnt_25h to one for overlapping average', cnt_25h
266      ENDIF !  cnt_25h .EQ. 25 .AND.  MOD( kt, i_steps * 24) == 0 .AND. kt .NE. nn_it000
267      !
268   END SUBROUTINE dia_25h 
269
270   !!======================================================================
271END MODULE dia25h
Note: See TracBrowser for help on using the repository browser.