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.
diawri_dimg.h90 in branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/DIA – NEMO

source: branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/DIA/diawri_dimg.h90 @ 2329

Last change on this file since 2329 was 2329, checked in by gm, 14 years ago

v3.3beta: Suppress old keys (key_diaspr, key_flx..., key_vectopt_memory) & phasing of zdfgls interface

  • Property svn:keywords set to Id
File size: 13.0 KB
Line 
1  !!----------------------------------------------------------------------
2  !!                        ***  diawri_dimg.h90  ***
3  !!----------------------------------------------------------------------
4  !! NEMO/OPA 3.3 , NEMO Consortium (2010)
5  !! $Id $
6  !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
7  !!----------------------------------------------------------------------
8
9  SUBROUTINE dia_wri( kt )
10    !!----------------------------------------------------------------------
11    !!           *** routine dia_wri ***
12    !!
13    !! ** Purpose : output dynamics and tracer fields on direct access file
14    !!              suitable for MPP computing
15    !!
16    !! ** define key : 'key_dimgout'
17    !!
18    !! **  Method : Default is to cumulate the values over the interval between
19    !!      2 output, and each nwrite time-steps  the mean value is  computed
20    !!      and written to the direct access file.
21    !!     If 'key_diainstant' is defined, no mean values are computed and the
22    !!     instantaneous fields are dump.
23    !!       Each processor creates its own file with its local data
24    !!     Merging all the files is performed off line by a dedicated program
25    !!
26    !! ** Arguments :
27    !!     kt      : time-step number
28    !!     kindinc :  error condition indicator : >=0 :  OK, < 0 : error.
29    !!
30    !! ** Naming convention for files
31    !!
32    !! {cexper}_{var}_y----m--d--.dimg
33    !!   cexper is the name of the experience, given in the namelist
34    !!   var can be either U, V, T, S, KZ, SSH, ...
35    !!   var can also be 2D, which means that each level of the file is a 2D field as described below
36    !!    y----m--d--  is the date at the time of the dump
37    !!    For mpp output, each processor dumps its own memory, on appropriate record range
38    !!    (direct access : for level jk of a klev field on proc narea irec = 1+ klev*(narea -1) + jk )
39    !!    To be tested with a lot of procs !!!!
40    !!
41    !!  level 1:  utau(:,:) * umask(:,:,1) zonal stress in N.m-2
42    !!  level 2:  vtau(:,:) * vmask(:,:,1) meridional stress in N. m-2
43    !!  level 3:  qsr + qns                total heat flux (W/m2)
44    !!  level 4:  ( emp (:,:)-rnf(:,:) )   E-P flux (mm/day)
45    !!  level 5:  tb  (:,:,1)-sst          model SST -forcing sst (degree C) ! deprecated
46    !!  level 6:  bsfb(:,:)         streamfunction (m**3/s)
47    !!  level 7:  qsr (:,:)         solar flux (W/m2)
48    !!  level 8:  qrp (:,:)                relax component of T flux.
49    !!  level 9:  erp (:,:)                relax component of S flux
50    !!  level 10: hmld(:,:)                turbocline depth
51    !!  level 11: hmlp(:,:)                mixed layer depth
52    !!  level 12: fr_i(:,:)                ice fraction (between 0 and 1)
53    !!  level 13: sst(:,:)                 the observed SST we relax to. ! deprecated
54    !!  level 14: qct(:,:)                 equivalent flux due to treshold SST
55    !!  level 15: fbt(:,:)                 feedback term .
56    !!  level 16: ( emps(:,:) - rnf(:,:) ) concentration/dilution water flux
57    !!  level 17: fsalt(:,:)               Ice=>ocean net freshwater
58    !!  level 18: gps(:,:)                 the surface pressure (m).
59    !!  level 19: spgu(:,:)                the surface pressure gradient in X direction.
60    !!  level 20: spgv(:,:)                the surface pressure gradient in Y direction.
61    !!
62    !! History:  OPA  ! 1997-02 ( Clipper Group ) dimg files
63    !!            -   ! 2003-12 ( J.M. Molines) f90, mpp output for OPA9.0
64    !!   NEMO    1.0  ! 2005-05  (S. Theetten) add emps fsalt move gps spgu spgv 2 lines below
65    !!            -   ! 2005-11  (V. Garnier) Surface pressure gradient organization
66    !!----------------------------------------------------------------------
67    USE lib_mpp
68    !!
69    INTEGER ,INTENT(in) :: kt
70    !!
71    INTEGER :: inbsel, jk
72    INTEGER :: iyear,imon,iday
73    INTEGER, SAVE :: nmoyct
74
75#if defined key_diainstant
76    LOGICAL, PARAMETER :: ll_dia_inst=.TRUE.  !: for instantaneous output
77#else
78    LOGICAL, PARAMETER :: ll_dia_inst=.FALSE. !: for average output
79#endif
80
81    REAL(wp), SAVE, DIMENSION (jpi,jpj,jpk) ::  um , vm   ! used to compute mean u, v fields
82    REAL(wp), SAVE, DIMENSION (jpi,jpj,jpk) ::  wm        ! used to compute mean w fields
83    REAL(wp), SAVE, DIMENSION (jpi,jpj,jpk) ::  avtm      ! used to compute mean kz fields
84    REAL(wp), SAVE, DIMENSION (jpi,jpj,jpk) ::  tm , sm   ! used to compute mean t, s fields
85    REAL(wp), SAVE, DIMENSION (jpi,jpj,jpk) ::  fsel      ! used to compute mean 2d fields
86    REAL(wp) :: zdtj
87    !
88    CHARACTER(LEN=80) :: clname
89    CHARACTER(LEN=80) :: cltext
90    CHARACTER(LEN=80) :: clmode
91    CHARACTER(LEN= 4) :: clver
92    !!----------------------------------------------------------------------
93    !
94    !  Initialization
95    !  ---------------
96    !
97    inbsel = 17
98
99    IF( inbsel >  jpk ) THEN
100       IF(lwp) WRITE(numout,*)  ' STOP inbsel =',inbsel,' is larger than jpk=',jpk
101       STOP
102    ENDIF
103
104    iyear = ndastp/10000
105    imon = (ndastp-iyear*10000)/100
106    iday = ndastp - imon*100 - iyear*10000
107
108    !     
109    !! dimg format V1.0 should start with the 4 char. string '@!01'
110    !!
111    clver='@!01'
112    !
113    IF( .NOT. ll_dia_inst ) THEN
114       !
115       !! * Mean output section
116       !! ----------------------
117       !
118       IF( kt == nit000 .AND. lwp ) WRITE(numout,*) &
119            'THE OUTPUT FILES CONTAINS THE AVERAGE OF EACH FIELD'
120       !
121       IF( kt == nit000  ) THEN
122          ! reset arrays for average computation
123          nmoyct = 0
124          !
125          um(:,:,:) = 0._wp
126          vm(:,:,:) = 0._wp
127          wm(:,:,:) = 0._wp
128          avtm(:,:,:) = 0._wp
129          tm(:,:,:) = 0._wp
130          sm(:,:,:) = 0._wp
131          fsel(:,:,:) = 0._wp
132          !
133       ENDIF
134
135       !  cumulate values
136       !  ---------------
137
138       nmoyct = nmoyct+1
139       !
140       um(:,:,:)=um(:,:,:) + un (:,:,:)
141       vm(:,:,:)=vm(:,:,:) + vn (:,:,:)
142       wm(:,:,:)=wm(:,:,:) + wn (:,:,:)
143       avtm(:,:,:)=avtm(:,:,:) + avt (:,:,:)
144       tm(:,:,:)=tm(:,:,:) + tn (:,:,:)
145       sm(:,:,:)=sm(:,:,:) + sn (:,:,:)
146       !
147       fsel(:,:,1 ) = fsel(:,:,1 ) + utau(:,:) * umask(:,:,1)
148       fsel(:,:,2 ) = fsel(:,:,2 ) + vtau(:,:) * vmask(:,:,1)
149       fsel(:,:,3 ) = fsel(:,:,3 ) + qsr (:,:) + qns  (:,:)
150       fsel(:,:,4 ) = fsel(:,:,4 ) + ( emp(:,:)-rnf(:,:) )
151       !        fsel(:,:,5 ) = fsel(:,:,5 ) + tb  (:,:,1)  !RB not used
152       fsel(:,:,6 ) = fsel(:,:,6 ) + sshn(:,:)
153       fsel(:,:,7 ) = fsel(:,:,7 ) + qsr(:,:)
154       fsel(:,:,8 ) = fsel(:,:,8 ) + qrp (:,:)
155       fsel(:,:,9 ) = fsel(:,:,9 ) + erp (:,:)
156       fsel(:,:,10) = fsel(:,:,10) + hmld(:,:)
157       fsel(:,:,11) = fsel(:,:,11) + hmlp(:,:)
158       fsel(:,:,12) = fsel(:,:,12) + fr_i(:,:)
159       !        fsel(:,:,13) = fsel(:,:,13)   !RB not used
160       !        fsel(:,:,14) = fsel(:,:,14) + qct(:,:)
161       !        fsel(:,:,15) = fsel(:,:,15) + fbt(:,:)
162       fsel(:,:,16) = fsel(:,:,16) + ( emps(:,:)-rnf(:,:) )
163       !
164       ! Output of dynamics and tracer fields and selected fields
165       ! --------------------------------------------------------
166       !
167       !
168       zdtj=rdt/86400.   ! time step in days
169       WRITE(clmode,'(f5.1,a)' ) nwrite*zdtj,' days average'
170
171       !       iwrite=NINT(adatrj/rwrite)
172       !      IF (abs(adatrj-iwrite*rwrite) < zdtj/2.      &
173
174       IF(  ( MOD (kt-nit000+1,nwrite) ==  0 )          &
175            &   .OR. ( kt == 1 .AND. ninist ==1 )  ) THEN
176          ! it is time to make a dump on file
177          ! compute average
178          um(:,:,:) = um(:,:,:) / nmoyct
179          vm(:,:,:) = vm(:,:,:) / nmoyct
180          wm(:,:,:) = wm(:,:,:) / nmoyct
181          avtm(:,:,:) = avtm(:,:,:) / nmoyct
182          tm(:,:,:) = tm(:,:,:) / nmoyct
183          sm(:,:,:) = sm(:,:,:) / nmoyct
184          !
185          fsel(:,:,:) = fsel(:,:,:) / nmoyct
186          !
187          ! note : the surface pressure is not averaged, but rather
188          ! computed from the averaged gradients.
189          !
190          ! mask mean field with tmask except utau vtau (1,2)
191          DO jk=3,inbsel
192            fsel(:,:,jk)=fsel(:,:,jk)*tmask(:,:,1)
193          END DO
194       ENDIF
195       !
196    ELSE   ! ll_dia_inst true
197       !
198       !! * Instantaneous output section
199       !! ------------------------------
200       !
201       IF( kt == nit000 .AND. lwp ) WRITE(numout,*) &
202            'THE OUTPUT FILES CONTAINS INSTANTANEOUS VALUES OF EACH FIELD'
203       !
204       zdtj=rdt/86400.   ! time step in days
205       !  iwrite=NINT(adatrj/rwrite)
206       clmode='instantaneous'
207       !     IF (abs(adatrj-iwrite*rwrite) < zdtj/2.  &
208       IF (  ( MOD (kt-nit000+1,nwrite) ==  0 )          &
209            &   .OR. ( kt == 1 .AND. ninist == 1 )  ) THEN
210          !
211          ! transfer wp arrays to sp arrays for dimg files
212          fsel(:,:,:) = 0._wp
213          !
214          fsel(:,:,1 ) = utau(:,:) * umask(:,:,1)
215          fsel(:,:,2 ) = vtau(:,:) * vmask(:,:,1)
216          fsel(:,:,3 ) = (qsr (:,:) + qns (:,:)) * tmask(:,:,1)
217          fsel(:,:,4 ) = ( emp(:,:)-rnf(:,:) ) * tmask(:,:,1)
218          !         fsel(:,:,5 ) = (tb  (:,:,1) - sf_sst(1)%fnow(:,:) ) *tmask(:,:,1) !RB not used
219
220          fsel(:,:,6 ) = sshn(:,:)
221          fsel(:,:,7 ) = qsr (:,:) * tmask(:,:,1)
222          fsel(:,:,8 ) = qrp (:,:) * tmask(:,:,1)
223          fsel(:,:,9 ) = erp (:,:) * tmask(:,:,1)
224          fsel(:,:,10) = hmld(:,:) * tmask(:,:,1)
225          fsel(:,:,11) = hmlp(:,:) * tmask(:,:,1)
226          fsel(:,:,12) = fr_i(:,:) * tmask(:,:,1)
227          !         fsel(:,:,13) = sf_sst(1)%fnow(:,:) !RB not used
228          !         fsel(:,:,14) =  qct(:,:)
229          !         fsel(:,:,15) =  fbt(:,:)
230          fsel(:,:,16) = ( emps(:,:)-rnf(:,:) ) * tmask(:,:,1)
231          !
232          !         qct(:,:) = 0._wp
233       ENDIF
234    ENDIF
235    !
236    ! Opening of the datrj.out file with the absolute time in day of each dump
237    ! this file gives a record of the dump date for post processing ( ASCII file )
238    !
239    IF(  ( MOD (kt-nit000+1,nwrite) ==  0 )          &
240         &   .OR. ( kt == 1 .AND. ninist == 1 )  ) THEN
241
242       IF( lwp) WRITE(numout,*)'Days since the begining of the run :',adatrj
243
244       !! * U section
245
246       WRITE(clname,9000) TRIM(cexper),'U',iyear,imon,iday
247       cltext=TRIM(cexper)//' U(m/s) '//TRIM(clmode)
248       !
249       IF( ll_dia_inst) THEN
250          CALL dia_wri_dimg(clname, cltext, un, jpk, 'T')
251
252       ELSE
253          CALL dia_wri_dimg(clname, cltext, um, jpk, 'T')
254       ENDIF
255
256       !! * V section
257
258       WRITE(clname,9000) TRIM(cexper),'V',iyear,imon,iday
259       cltext=TRIM(cexper)//' V(m/s) '//TRIM(clmode)
260       !
261       IF( ll_dia_inst) THEN
262          CALL dia_wri_dimg(clname, cltext, vn, jpk, 'T')
263       ELSE
264          CALL dia_wri_dimg(clname, cltext, vm, jpk, 'T')
265       ENDIF
266       !
267
268       !! * KZ section
269
270       WRITE(clname,9000) TRIM(cexper),'KZ',iyear,imon,iday
271       cltext=TRIM(cexper)//' KZ(m2/s) '//TRIM(clmode)
272
273       IF( ll_dia_inst) THEN
274          CALL dia_wri_dimg(clname, cltext, avt, jpk, 'W')
275       ELSE
276          CALL dia_wri_dimg(clname, cltext, avtm, jpk, 'W')
277       ENDIF
278       !
279
280       !! * W section
281
282       WRITE(clname,9000) TRIM(cexper),'W',iyear,imon,iday
283       cltext=TRIM(cexper)//' W(m/s) '//TRIM(clmode)
284
285       IF( ll_dia_inst) THEN
286          CALL dia_wri_dimg(clname, cltext, wn, jpk, 'W')
287       ELSE
288          CALL dia_wri_dimg(clname, cltext, wm, jpk, 'W')
289       ENDIF
290
291       !! * T section
292
293       WRITE(clname,9000) TRIM(cexper),'T',iyear,imon,iday
294       cltext=TRIM(cexper)//' T (DegC) '//TRIM(clmode)
295
296       IF( ll_dia_inst) THEN
297          CALL dia_wri_dimg(clname, cltext, tn, jpk, 'T')
298       ELSE
299          CALL dia_wri_dimg(clname, cltext, tm, jpk, 'T')
300       ENDIF
301       !
302
303       !! * S section
304
305       WRITE(clname,9000) TRIM(cexper),'S',iyear,imon,iday
306       cltext=TRIM(cexper)//' S (PSU) '//TRIM(clmode)
307
308       IF( ll_dia_inst) THEN
309          CALL dia_wri_dimg(clname, cltext, sn, jpk, 'T')
310       ELSE
311          CALL dia_wri_dimg(clname, cltext, sm, jpk, 'T')
312       ENDIF
313       !
314
315       !! * 2D section
316
317       WRITE(clname,9000) TRIM(cexper),'2D',iyear,imon,iday
318       cltext='2D fields '//TRIM(clmode)
319
320       IF( ll_dia_inst) THEN
321          CALL dia_wri_dimg(clname, cltext, fsel, inbsel, '2')
322       ELSE
323          CALL dia_wri_dimg(clname, cltext, fsel, inbsel, '2')
324       ENDIF
325
326       IF( lk_mpp )   CALL mppsync   ! synchronization in mpp
327
328       !! * Log message in numout
329
330       IF( lwp)WRITE(numout,*) ' '
331       IF( lwp)WRITE(numout,*) ' **** WRITE in dimg file ',kt
332
333       IF( lwp .AND.        ll_dia_inst) WRITE(numout,*) '    instantaneous fields'
334       IF( lwp .AND. .NOT.  ll_dia_inst) WRITE(numout,*) '    average fields with ',nmoyct,'pdt'
335       !
336       !
337       !! * Reset cumulating arrays  and counter to 0 after writing
338       !
339       IF( .NOT. ll_dia_inst ) THEN
340          nmoyct = 0
341          !
342          um(:,:,:) = 0._wp
343          vm(:,:,:) = 0._wp
344          wm(:,:,:) = 0._wp
345          tm(:,:,:) = 0._wp
346          sm(:,:,:) = 0._wp
347          fsel(:,:,:) = 0._wp
348          avtm(:,:,:) = 0._wp
349       ENDIF
350    ENDIF
351    !
3529000 FORMAT(a,"_",a,"_y",i4.4,"m",i2.2,"d",i2.2,".dimgproc")
353    !
354  END SUBROUTINE dia_wri
Note: See TracBrowser for help on using the repository browser.