source: CONFIG/UNIFORM/v6/IPSLCM5A2/SOURCES/NEMO/PALEO/diafwb.F90 @ 5879

Last change on this file since 5879 was 5879, checked in by snguyen, 3 years ago

Modified Makefile to add configuration PALEOIPSLCM5A2-VLR while retaining IPSLCM5A2-VLR as default configuration for compilation. Moved NEMO SOURCES of IPSLCM5A2-VLR to SOURCES/NEMO/STANDARD and created SOURCES/NEMO/PALEO for PALEOIPSLCM5A2-VLR configuration. Created paleolmdz in Makefile to compile LMDZ sources in SOURCES/LMDZ/PALEO. Added experiments IPSLCM/paleo and LMDZOR/paleo. Added file_def_nemo-lim2_paleo.xml file_def_histmth_lmdz_paleo.xml file_def_nemo-opa_paleo.xml file_def_nemo-pisces_rivers_paleo.xml file_def_nemo-pisces_paleo.xml file_def_orchidee_paleo.xml namelist_ORCA2_cfg_paleo namelist_pisces_ORCA2_cfg_paleo to GENERAL/PARAM for paleo configurations. Set day_step=720 in GENERAL/PARAM/gcm.def_96x95 for paleo configurations. Modified GENERAL/DRIVER/opa9.driver to use namelist_ORCA2_cfg_paleo for paleo configurations.

File size: 21.1 KB
Line 
1MODULE diafwb
2   !!======================================================================
3   !!                       ***  MODULE  diafwb  ***
4   !! Ocean diagnostics: freshwater budget
5   !!======================================================================
6   !! History :  8.2  !  01-02  (E. Durand)  Original code
7   !!            8.5  !  02-06  (G. Madec)  F90: Free form and module
8   !!            9.0  !  05-11  (V. Garnier) Surface pressure gradient organization
9   !!----------------------------------------------------------------------
10   !!----------------------------------------------------------------------
11   !!   Only for ORCA2 ORCA1 and ORCA025
12   !!----------------------------------------------------------------------
13   !!----------------------------------------------------------------------
14   !!   dia_fwb     : freshwater budget for global ocean configurations
15   !!----------------------------------------------------------------------
16   USE oce             ! ocean dynamics and tracers
17   USE dom_oce         ! ocean space and time domain
18   USE phycst          ! physical constants
19   USE sbc_oce         ! ???
20   USE zdf_oce         ! ocean vertical physics
21   USE in_out_manager  ! I/O manager
22   USE lib_mpp         ! distributed memory computing library
23   USE timing          ! preformance summary
24
25   IMPLICIT NONE
26   PRIVATE
27
28   PUBLIC dia_fwb    ! routine called by step.F90
29
30   REAL(wp)               ::   a_fwf ,          &
31      &                        a_sshb, a_sshn, a_salb, a_saln
32   REAL(wp), DIMENSION(4) ::   a_flxi, a_flxo, a_temi, a_temo, a_sali, a_salo
33
34   !! * Substitutions
35#  include "domzgr_substitute.h90"
36#  include "vectopt_loop_substitute.h90"
37   !!----------------------------------------------------------------------
38   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
39   !! $Id: diafwb.F90 5506 2015-06-29 15:19:38Z clevy $
40   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
41   !!----------------------------------------------------------------------
42
43CONTAINS
44
45   SUBROUTINE dia_fwb( kt )
46      !!---------------------------------------------------------------------
47      !!                  ***  ROUTINE dia_fwb  ***
48      !!     
49      !! ** Purpose :
50      !!----------------------------------------------------------------------
51      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index
52      !!
53      INTEGER  :: inum             ! temporary logical unit
54      INTEGER  :: ji, jj, jk, jt   ! dummy loop indices
55      INTEGER  :: ii0, ii1, ij0, ij1
56      INTEGER  :: isrow         ! index for ORCA1 starting row
57      REAL(wp) :: zarea, zvol, zwei
58      REAL(wp) :: ztemi(4), ztemo(4), zsali(4), zsalo(4), zflxi(4), zflxo(4)
59      REAL(wp) :: zt, zs, zu 
60      REAL(wp) :: zsm0, zfwfnew
61      ! Add PALEORCA2 configuration -- JBL 08.02.2017
62      IF( ( cp_cfg == "orca" .OR. cp_cfg == "paleorca" ) .AND. jp_cfg == 1 .OR. jp_cfg == 2 .OR. jp_cfg == 4 ) THEN
63      !!----------------------------------------------------------------------
64      IF( nn_timing == 1 )   CALL timing_start('dia_fwb')
65
66      ! Mean global salinity
67      ! CORRECTED FOR PALEORCA2 -- JBL 08.02.2017
68      ! zsm0 = 34.72654
69      zsm0 = 34.7
70
71      ! To compute fwf mean value mean fwf
72
73      IF( kt == nit000 ) THEN
74
75         a_fwf    = 0.e0
76         a_sshb   = 0.e0 ! valeur de ssh au debut de la simulation
77         a_salb   = 0.e0 ! valeur de sal au debut de la simulation
78         ! sshb used because diafwb called after tranxt (i.e. after the swap)
79         a_sshb = SUM( e1t(:,:) * e2t(:,:) * sshb(:,:) * tmask_i(:,:) )
80         IF( lk_mpp )   CALL mpp_sum( a_sshb )      ! sum over the global domain
81
82         DO jk = 1, jpkm1
83            DO jj = 2, jpjm1
84               DO ji = fs_2, fs_jpim1   ! vector opt.
85                  zwei  = e1t(ji,jj) * e2t(ji,jj) * fse3t(ji,jj,jk) * tmask(ji,jj,jk) * tmask_i(ji,jj)
86                  a_salb = a_salb + ( tsb(ji,jj,jk,jp_sal) - zsm0 ) * zwei
87               END DO
88            END DO
89         END DO
90         IF( lk_mpp )   CALL mpp_sum( a_salb )      ! sum over the global domain
91      ENDIF
92     
93      a_fwf    = SUM( e1t(:,:) * e2t(:,:) * ( emp(:,:)-rnf(:,:) ) * tmask_i(:,:) ) 
94      IF( lk_mpp )   CALL mpp_sum( a_fwf    )       ! sum over the global domain
95
96      IF( kt == nitend ) THEN
97         a_sshn = 0.e0
98         a_saln = 0.e0
99         zarea = 0.e0
100         zvol  = 0.e0
101         zfwfnew = 0.e0
102         ! Mean sea level at nitend
103         a_sshn = SUM( e1t(:,:) * e2t(:,:) * sshn(:,:) * tmask_i(:,:) )
104         IF( lk_mpp )   CALL mpp_sum( a_sshn )      ! sum over the global domain
105         zarea  = SUM( e1t(:,:) * e2t(:,:) *             tmask_i(:,:) )
106         IF( lk_mpp )   CALL mpp_sum( zarea  )      ! sum over the global domain
107         
108         DO jk = 1, jpkm1   
109            DO jj = 2, jpjm1
110               DO ji = fs_2, fs_jpim1   ! vector opt.
111                  zwei  = e1t(ji,jj) * e2t(ji,jj) * fse3t(ji,jj,jk) * tmask(ji,jj,jk) * tmask_i(ji,jj)
112                  a_saln = a_saln + ( tsn(ji,jj,jk,jp_sal) - zsm0 ) * zwei
113                  zvol  = zvol  + zwei
114               END DO
115            END DO
116         END DO
117         IF( lk_mpp )   CALL mpp_sum( a_saln )      ! sum over the global domain
118         IF( lk_mpp )   CALL mpp_sum( zvol )      ! sum over the global domain
119         
120         ! Conversion in m3
121         a_fwf    = a_fwf * rdttra(1) * 1.e-3 
122         
123         ! fwf correction to bring back the mean ssh to zero
124         zfwfnew = a_sshn / ( ( nitend - nit000 + 1 ) * rdt ) * 1.e3 / zarea
125
126      ENDIF
127
128
129      ! Calcul des termes de transport
130      ! ------------------------------
131     
132      ! 1 --> Gibraltar
133      ! 2 --> Cadiz
134      ! 3 --> Red Sea
135      ! 4 --> Baltic Sea
136
137      IF( kt == nit000 ) THEN
138         a_flxi(:) = 0.e0
139         a_flxo(:) = 0.e0
140         a_temi(:) = 0.e0
141         a_temo(:) = 0.e0
142         a_sali(:) = 0.e0
143         a_salo(:) = 0.e0
144      ENDIF
145
146      zflxi(:) = 0.e0
147      zflxo(:) = 0.e0
148      ztemi(:) = 0.e0
149      ztemo(:) = 0.e0
150      zsali(:) = 0.e0
151      zsalo(:) = 0.e0
152
153      ! Mean flow at Gibraltar
154
155      IF( cp_cfg == "orca" ) THEN 
156               
157         SELECT CASE ( jp_cfg )
158         !                                           ! =======================
159         CASE ( 4 )                                  !  ORCA_R4 configuration
160            !                                        ! =======================
161            ii0 = 70   ;   ii1 = 70
162            ij0 = 52   ;   ij1 = 52
163            !                                        ! =======================
164         CASE ( 2 )                                  !  ORCA_R2 configuration
165            !                                        ! =======================
166            ii0 = 140   ;   ii1 = 140
167            ij0 = 102   ;   ij1 = 102
168            !                                        ! =======================
169         CASE ( 1 )                                  !  ORCA_R1 configurations
170            !                                        ! =======================
171            ! This dirty section will be suppressed by simplification process:
172            ! all this will come back in input files
173            ! Currently these hard-wired indices relate to configuration with
174            ! extend grid (jpjglo=332)
175            isrow = 332 - jpjglo
176            !
177            ii0 = 283           ;   ii1 = 283
178            ij0 = 241 - isrow   ;   ij1 = 241 - isrow
179            !                                        ! =======================
180         CASE DEFAULT                                !    ORCA R05 or R025
181            !                                        ! =======================
182            CALL ctl_stop( ' dia_fwb Not yet implemented in ORCA_R05 or R025' )
183            !
184         END SELECT
185         !
186         DO ji = mi0(ii0), MIN(mi1(ii1),jpim1)
187            DO jj = mj0(ij0), mj1(ij1)
188               DO jk = 1, jpk 
189                  zt = 0.5 * ( tsn(ji,jj,jk,jp_tem) + tsn(ji+1,jj,jk,jp_tem) )
190                  zs = 0.5 * ( tsn(ji,jj,jk,jp_sal) + tsn(ji+1,jj,jk,jp_sal) )
191                  zu = un(ji,jj,jk) * fse3t(ji,jj,jk) * e2u(ji,jj) * tmask_i(ji,jj)
192
193                  IF( un(ji,jj,jk) > 0.e0 ) THEN
194                     zflxi(1) = zflxi(1) +    zu
195                     ztemi(1) = ztemi(1) + zt*zu
196                     zsali(1) = zsali(1) + zs*zu
197                  ELSE
198                     zflxo(1) = zflxo(1) +    zu
199                     ztemo(1) = ztemo(1) + zt*zu
200                     zsalo(1) = zsalo(1) + zs*zu
201                  ENDIF
202               END DO
203            END DO
204         END DO
205      ENDIF
206     
207      ! Mean flow at Cadiz
208      IF( cp_cfg == "orca" ) THEN
209               
210         SELECT CASE ( jp_cfg )
211         !                                           ! =======================
212         CASE ( 4 )                                  !  ORCA_R4 configuration
213            !                                        ! =======================
214            ii0 = 69   ;   ii1 = 69
215            ij0 = 52   ;   ij1 = 52
216            !                                        ! =======================
217         CASE ( 2 )                                  !  ORCA_R2 configuration
218            !                                        ! =======================
219            ii0 = 137   ;   ii1 = 137
220            ij0 = 101   ;   ij1 = 102
221            !                                        ! =======================
222         CASE ( 1 )                                  !  ORCA_R1 configurations
223            !                                        ! =======================
224            ! This dirty section will be suppressed by simplification process:
225            ! all this will come back in input files
226            ! Currently these hard-wired indices relate to configuration with
227            ! extend grid (jpjglo=332)
228            isrow = 332 - jpjglo
229            ii0 = 282           ;   ii1 = 282
230            ij0 = 240 - isrow   ;   ij1 = 240 - isrow
231            !                                        ! =======================
232         CASE DEFAULT                                !    ORCA R05 or R025
233            !                                        ! =======================
234            CALL ctl_stop( ' dia_fwb Not yet implemented in ORCA_R05 or R025' )
235            !
236         END SELECT
237         !
238         DO ji = mi0(ii0), MIN(mi1(ii1),jpim1)
239            DO jj = mj0(ij0), mj1(ij1)
240               DO jk = 1, jpk 
241                  zt = 0.5 * ( tsn(ji,jj,jk,jp_tem) + tsn(ji+1,jj,jk,jp_tem) )
242                  zs = 0.5 * ( tsn(ji,jj,jk,jp_sal) + tsn(ji+1,jj,jk,jp_sal) )
243                  zu = un(ji,jj,jk) * fse3t(ji,jj,jk) * e2u(ji,jj) * tmask_i(ji,jj)
244                 
245                  IF( un(ji,jj,jk) > 0.e0 ) THEN
246                     zflxi(2) = zflxi(2) +    zu
247                     ztemi(2) = ztemi(2) + zt*zu
248                     zsali(2) = zsali(2) + zs*zu
249                  ELSE
250                     zflxo(2) = zflxo(2) +    zu
251                     ztemo(2) = ztemo(2) + zt*zu
252                     zsalo(2) = zsalo(2) + zs*zu
253                  ENDIF
254               END DO
255            END DO
256         END DO
257      ENDIF
258
259      ! Mean flow at Red Sea entrance
260      IF( cp_cfg == "orca" ) THEN
261               
262         SELECT CASE ( jp_cfg )
263         !                                           ! =======================
264         CASE ( 4 )                                  !  ORCA_R4 configuration
265            !                                        ! =======================
266            ii0 = 83   ;   ii1 = 83
267            ij0 = 45   ;   ij1 = 45
268            !                                        ! =======================
269         CASE ( 2 )                                  !  ORCA_R2 configuration
270            !                                        ! =======================
271            ii0 = 160   ;   ii1 = 160
272            ij0 = 88    ;   ij1 = 88 
273            !                                        ! =======================
274         CASE ( 1 )                                  !  ORCA_R1 configurations
275            !                                        ! =======================
276            ! This dirty section will be suppressed by simplification process:
277            ! all this will come back in input files
278            ! Currently these hard-wired indices relate to configuration with
279            ! extend grid (jpjglo=332)
280            isrow = 332 - jpjglo
281            ii0 = 331           ;   ii1 = 331
282            ij0 = 215 - isrow   ;   ij1 = 215 - isrow
283            !                                        ! =======================
284         CASE DEFAULT                                !    ORCA R05 or R025
285            !                                        ! =======================
286            CALL ctl_stop( ' dia_fwb Not yet implemented in ORCA_R05 or R025' )
287            !
288         END SELECT
289         !
290         DO ji = mi0(ii0), MIN(mi1(ii1),jpim1)
291            DO jj = mj0(ij0), mj1(ij1)
292               DO jk = 1, jpk 
293                  zt = 0.5 * ( tsn(ji,jj,jk,jp_tem) + tsn(ji+1,jj,jk,jp_tem) )
294                  zs = 0.5 * ( tsn(ji,jj,jk,jp_sal) + tsn(ji+1,jj,jk,jp_sal) )
295                  zu = un(ji,jj,jk) * fse3t(ji,jj,jk) * e2u(ji,jj) * tmask_i(ji,jj)
296                 
297                  IF( un(ji,jj,jk) > 0.e0 ) THEN
298                     zflxi(3) = zflxi(3) +    zu
299                     ztemi(3) = ztemi(3) + zt*zu
300                     zsali(3) = zsali(3) + zs*zu
301                  ELSE
302                     zflxo(3) = zflxo(3) +    zu
303                     ztemo(3) = ztemo(3) + zt*zu
304                     zsalo(3) = zsalo(3) + zs*zu
305                  ENDIF
306               END DO
307            END DO
308         END DO
309      ENDIF
310
311      ! Mean flow at Baltic Sea entrance
312      IF( cp_cfg == "orca" ) THEN
313               
314         SELECT CASE ( jp_cfg )
315         !                                           ! =======================
316         CASE ( 4 )                                  !  ORCA_R4 configuration
317            !                                        ! =======================
318            ii0 = 1     ;   ii1 = 1 
319            ij0 = 1     ;   ij1 = 1 
320            !                                        ! =======================
321         CASE ( 2 )                                  !  ORCA_R2 configuration
322            !                                        ! =======================
323            ii0 = 146   ;   ii1 = 146 
324            ij0 = 116   ;   ij1 = 116
325            !                                        ! =======================
326         CASE ( 1 )                                  !  ORCA_R1 configurations
327            !                                        ! =======================
328            ! This dirty section will be suppressed by simplification process:
329            ! all this will come back in input files
330            ! Currently these hard-wired indices relate to configuration with
331            ! extend grid (jpjglo=332)
332            isrow = 332 - jpjglo
333            ii0 = 297           ;   ii1 = 297
334            ij0 = 269 - isrow   ;   ij1 = 269 - isrow
335            !                                        ! =======================
336         CASE DEFAULT                                !    ORCA R05 or R025
337            !                                        ! =======================
338            CALL ctl_stop( ' dia_fwb Not yet implemented in ORCA_R05 or R025' )
339            !
340         END SELECT
341         !
342         DO ji = mi0(ii0), MIN(mi1(ii1),jpim1)
343            DO jj = mj0(ij0), mj1(ij1)
344               DO jk = 1, jpk
345                  zt = 0.5 * ( tsn(ji,jj,jk,jp_tem) + tsn(ji+1,jj,jk,jp_tem) )
346                  zs = 0.5 * ( tsn(ji,jj,jk,jp_sal) + tsn(ji+1,jj,jk,jp_sal) )
347                  zu = un(ji,jj,jk) * fse3t(ji,jj,jk) * e2u(ji,jj) * tmask_i(ji,jj)
348                 
349                  IF( un(ji,jj,jk) > 0.e0 ) THEN
350                     zflxi(4) = zflxi(4) +    zu
351                     ztemi(4) = ztemi(4) + zt*zu
352                     zsali(4) = zsali(4) + zs*zu
353                  ELSE
354                     zflxo(4) = zflxo(4) +    zu
355                     ztemo(4) = ztemo(4) + zt*zu
356                     zsalo(4) = zsalo(4) + zs*zu
357                  ENDIF
358               END DO
359            END DO
360         END DO
361      ENDIF
362
363      ! Sum at each time-step
364      DO jt = 1, 4 
365         !
366         IF( zflxi(jt) /= 0.e0 ) THEN
367            a_flxi(jt) = a_flxi(jt) + zflxi(jt)
368            a_temi(jt) = a_temi(jt) + ztemi(jt)/zflxi(jt)
369            a_sali(jt) = a_sali(jt) + zsali(jt)/zflxi(jt)
370         ENDIF
371         !
372         IF( zflxo(jt) /= 0.e0 ) THEN
373            a_flxo(jt) = a_flxo(jt) + zflxo(jt)
374            a_temo(jt) = a_temo(jt) + ztemo(jt)/zflxo(jt)
375            a_salo(jt) = a_salo(jt) + zsalo(jt)/zflxo(jt)
376         ENDIF
377         !
378      END DO
379
380      IF( kt == nitend ) THEN
381         DO jt = 1, 4 
382            a_flxi(jt) = a_flxi(jt) / ( FLOAT( nitend - nit000 + 1 ) * 1.e6 )
383            a_temi(jt) = a_temi(jt) /   FLOAT( nitend - nit000 + 1 )
384            a_sali(jt) = a_sali(jt) /   FLOAT( nitend - nit000 + 1 )
385            a_flxo(jt) = a_flxo(jt) / ( FLOAT( nitend - nit000 + 1 ) * 1.e6 )
386            a_temo(jt) = a_temo(jt) /   FLOAT( nitend - nit000 + 1 )
387            a_salo(jt) = a_salo(jt) /   FLOAT( nitend - nit000 + 1 )
388         END DO
389         IF( lk_mpp ) THEN
390            CALL mpp_sum( a_flxi, 4 )      ! sum over the global domain
391            CALL mpp_sum( a_temi, 4 )      ! sum over the global domain
392            CALL mpp_sum( a_sali, 4 )      ! sum over the global domain
393
394            CALL mpp_sum( a_flxo, 4 )      ! sum over the global domain
395            CALL mpp_sum( a_temo, 4 )      ! sum over the global domain
396            CALL mpp_sum( a_salo, 4 )      ! sum over the global domain
397         ENDIF
398      ENDIF
399
400
401      ! Ecriture des diagnostiques
402      ! --------------------------
403
404      ! Add PALEORCA2 configuration -- JBL 08.02.2017
405      !IF ( kt == nitend .AND. cp_cfg == "orca" .AND. lwp ) THEN
406      IF ( kt == nitend .AND. ( cp_cfg == "orca" .OR. cp_cfg == "paleorca" ) .AND. lwp ) THEN
407
408         CALL ctl_opn( inum, 'STRAIT.dat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea )
409         WRITE(inum,*)
410         WRITE(inum,*)    'Net freshwater budget '
411         WRITE(inum,9010) '  fwf    = ',a_fwf,   ' m3 =', a_fwf   /(FLOAT(nitend-nit000+1)*rdttra(1)) * 1.e-6,' Sv'
412         WRITE(inum,*)
413         WRITE(inum,9010) '  zarea =',zarea
414         WRITE(inum,9010) '  zvol  =',zvol
415         WRITE(inum,*)
416         WRITE(inum,*)    'Mean sea level : '
417         WRITE(inum,9010) '  at nit000 = ',a_sshb        ,' m3 '
418         WRITE(inum,9010) '  at nitend = ',a_sshn        ,' m3 '
419         WRITE(inum,9010) '  diff      = ',(a_sshn-a_sshb),' m3 =', (a_sshn-a_sshb)/(FLOAT(nitend-nit000+1)*rdt) * 1.e-6,' Sv'
420         WRITE(inum,9020) '  mean sea level elevation    =', a_sshn/zarea,' m'
421         WRITE(inum,*)
422         WRITE(inum,*)    'Anomaly of salinity content : '
423         WRITE(inum,9010) '  at nit000 = ',a_salb        ,' psu.m3 '
424         WRITE(inum,9010) '  at nitend = ',a_saln        ,' psu.m3 '
425         WRITE(inum,9010) '  diff      = ',(a_saln-a_salb),' psu.m3'
426         WRITE(inum,*)
427         WRITE(inum,*)    'Mean salinity : '
428         WRITE(inum,9020) '  at nit000 =',a_salb/zvol+zsm0   ,' psu '
429         WRITE(inum,9020) '  at nitend =',a_saln/zvol+zsm0   ,' psu '
430         WRITE(inum,9020) '  diff      =',(a_saln-a_salb)/zvol,' psu'
431         WRITE(inum,9020) '  S-SLevitus=',a_saln/zvol,' psu'
432         WRITE(inum,*)
433         WRITE(inum,*)    'Gibraltar : '
434         WRITE(inum,9030) '  Flux entrant (Sv) :', a_flxi(1)
435         WRITE(inum,9030) '  Flux sortant (Sv) :', a_flxo(1)
436         WRITE(inum,9030) '  T entrant (deg)   :', a_temi(1)
437         WRITE(inum,9030) '  T sortant (deg)   :', a_temo(1)
438         WRITE(inum,9030) '  S entrant (psu)   :', a_sali(1)
439         WRITE(inum,9030) '  S sortant (psu)   :', a_salo(1)
440         WRITE(inum,*)
441         WRITE(inum,*)    'Cadiz : '
442         WRITE(inum,9030) '  Flux entrant (Sv) :', a_flxi(2)
443         WRITE(inum,9030) '  Flux sortant (Sv) :', a_flxo(2)
444         WRITE(inum,9030) '  T entrant (deg)   :', a_temi(2)
445         WRITE(inum,9030) '  T sortant (deg)   :', a_temo(2)
446         WRITE(inum,9030) '  S entrant (psu)   :', a_sali(2)
447         WRITE(inum,9030) '  S sortant (psu)   :', a_salo(2)
448         WRITE(inum,*)
449         WRITE(inum,*)    'Bab el Mandeb : '
450         WRITE(inum,9030) '  Flux entrant (Sv) :', a_flxi(3)
451         WRITE(inum,9030) '  Flux sortant (Sv) :', a_flxo(3)
452         WRITE(inum,9030) '  T entrant (deg)   :', a_temi(3)
453         WRITE(inum,9030) '  T sortant (deg)   :', a_temo(3)
454         WRITE(inum,9030) '  S entrant (psu)   :', a_sali(3)
455         WRITE(inum,9030) '  S sortant (psu)   :', a_salo(3)
456         WRITE(inum,*)
457         WRITE(inum,*)    'Baltic : '
458         WRITE(inum,9030) '  Flux entrant (Sv) :', a_flxi(4)
459         WRITE(inum,9030) '  Flux sortant (Sv) :', a_flxo(4)
460         WRITE(inum,9030) '  T entrant (deg)   :', a_temi(4)
461         WRITE(inum,9030) '  T sortant (deg)   :', a_temo(4)
462         WRITE(inum,9030) '  S entrant (psu)   :', a_sali(4)
463         WRITE(inum,9030) '  S sortant (psu)   :', a_salo(4)
464         CLOSE(inum)
465      ENDIF
466
467      IF( nn_timing == 1 )   CALL timing_start('dia_fwb')
468
469 9005 FORMAT(1X,A,ES24.16)
470 9010 FORMAT(1X,A,ES12.5,A,F10.5,A)
471 9020 FORMAT(1X,A,F10.5,A)
472 9030 FORMAT(1X,A,F9.4,A)
473 
474      ENDIF
475
476   END SUBROUTINE dia_fwb
477
478   !!======================================================================
479END MODULE diafwb
Note: See TracBrowser for help on using the repository browser.