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.F90 in branches/2016/dev_v3_6_STABLE_r6506_AGRIF_LIM3/NEMOGCM/NEMO/SAS_SRC – NEMO

source: branches/2016/dev_v3_6_STABLE_r6506_AGRIF_LIM3/NEMOGCM/NEMO/SAS_SRC/diawri.F90 @ 8085

Last change on this file since 8085 was 7757, checked in by clem, 7 years ago

make LIM3 and AGRIF fully compatible

  • Property svn:keywords set to Id
File size: 22.3 KB
RevLine 
[3331]1MODULE diawri
2   !!======================================================================
3   !!                     ***  MODULE  diawri  ***
4   !! Ocean diagnostics :  write ocean output files
5   !!=====================================================================
6   !! History :  OPA  ! 1991-03  (M.-A. Foujols)  Original code
7   !!            4.0  ! 1991-11  (G. Madec)
8   !!                 ! 1992-06  (M. Imbard)  correction restart file
9   !!                 ! 1992-07  (M. Imbard)  split into diawri and rstwri
10   !!                 ! 1993-03  (M. Imbard)  suppress writibm
11   !!                 ! 1998-01  (C. Levy)  NETCDF format using ioipsl INTERFACE
12   !!                 ! 1999-02  (E. Guilyardi)  name of netCDF files + variables
13   !!            8.2  ! 2000-06  (M. Imbard)  Original code (diabort.F)
14   !!   NEMO     1.0  ! 2002-06  (A.Bozec, E. Durand)  Original code (diainit.F)
15   !!             -   ! 2002-09  (G. Madec)  F90: Free form and module
16   !!             -   ! 2002-12  (G. Madec)  merge of diabort and diainit, F90
17   !!                 ! 2005-11  (V. Garnier) Surface pressure gradient organization
18   !!            3.2  ! 2008-11  (B. Lemaire) creation from old diawri
19   !!----------------------------------------------------------------------
20
21   !!----------------------------------------------------------------------
22   !!   dia_wri       : create the standart output files
23   !!   dia_wri_state : create an output NetCDF file for a single instantaeous ocean state and forcing fields
24   !!----------------------------------------------------------------------
25   USE oce             ! ocean dynamics and tracers
26   USE dom_oce         ! ocean space and time domain
27   USE zdf_oce         ! ocean vertical physics
28   USE ldftra_oce      ! ocean active tracers: lateral physics
29   USE ldfdyn_oce      ! ocean dynamics: lateral physics
30   USE traldf_iso_grif, ONLY : psix_eiv, psiy_eiv
31   USE sol_oce         ! solver variables
32   USE sbc_oce         ! Surface boundary condition: ocean fields
33   USE sbc_ice         ! Surface boundary condition: ice fields
34   USE sbcssr          ! restoring term toward SST/SSS climatology
35   USE phycst          ! physical constants
36   USE zdfmxl          ! mixed layer
37   USE dianam          ! build name of file (routine)
38   USE zdfddm          ! vertical  physics: double diffusion
39   USE diahth          ! thermocline diagnostics
40   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
41   USE in_out_manager  ! I/O manager
42   USE diadimg         ! dimg direct access file format output
43   USE diaar5, ONLY :   lk_diaar5
44   USE iom
45   USE ioipsl
46#if defined key_lim2
47   USE limwri_2 
[7757]48#elif defined key_lim3
49   USE limwri
[3331]50#endif
51   USE lib_mpp         ! MPP library
52   USE timing          ! preformance summary
53   USE wrk_nemo        ! working array
54
55   IMPLICIT NONE
56   PRIVATE
57
58   PUBLIC   dia_wri                 ! routines called by step.F90
59   PUBLIC   dia_wri_state
60   PUBLIC   dia_wri_alloc           ! Called by nemogcm module
61
62   INTEGER ::   nid_T, nz_T, nh_T, ndim_T, ndim_hT   ! grid_T file
63   INTEGER ::   nid_U, nz_U, nh_U, ndim_U, ndim_hU   ! grid_U file
64   INTEGER ::   nid_V, nz_V, nh_V, ndim_V, ndim_hV   ! grid_V file
65   INTEGER ::   ndex(1)                              ! ???
66   INTEGER, SAVE, ALLOCATABLE, DIMENSION(:) :: ndex_hT, ndex_hU, ndex_hV
67
68   !! * Substitutions
69#  include "zdfddm_substitute.h90"
70#  include "domzgr_substitute.h90"
71#  include "vectopt_loop_substitute.h90"
72   !!----------------------------------------------------------------------
73   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
[5217]74   !! $Id$
[3331]75   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
76   !!----------------------------------------------------------------------
77CONTAINS
78
79   INTEGER FUNCTION dia_wri_alloc()
80      !!----------------------------------------------------------------------
81      INTEGER :: ierr
82      !!----------------------------------------------------------------------
83      !
84      ALLOCATE( ndex_hT(jpi*jpj), ndex_hU(jpi*jpj), ndex_hV(jpi*jpj), STAT=dia_wri_alloc )
85      IF( lk_mpp )   CALL mpp_sum( dia_wri_alloc )
86      !
87  END FUNCTION dia_wri_alloc
88
89#if defined key_dimgout
90   !!----------------------------------------------------------------------
91   !!   'key_dimgout'                                      DIMG output file
92   !!----------------------------------------------------------------------
93#   include "diawri_dimg.h90"
94
95#else
96   !!----------------------------------------------------------------------
97   !!   Default option                                   NetCDF output file
98   !!----------------------------------------------------------------------
99# if defined key_iomput
100   !!----------------------------------------------------------------------
101   !!   'key_iomput'                                        use IOM library
102   !!----------------------------------------------------------------------
103
104   SUBROUTINE dia_wri( kt )
105      !!---------------------------------------------------------------------
106      !!                  ***  ROUTINE dia_wri  ***
107      !!                   
108      !! ** Purpose :   Standard output of opa: dynamics and tracer fields
109      !!      NETCDF format is used by default
110      !!      Standalone surface scheme
111      !!
112      !! ** Method  :  use iom_put
113      !!----------------------------------------------------------------------
114      !!
115      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index
116      !!----------------------------------------------------------------------
117      !
[7757]118      ! Output the initial state and forcings
119      IF( ninist == 1 ) THEN
120         CALL dia_wri_state( 'output.init', kt )
121         ninist = 0
122      ENDIF
[3331]123      !
124   END SUBROUTINE dia_wri
125
126#else
127   !!----------------------------------------------------------------------
128   !!   Default option                                  use IOIPSL  library
129   !!----------------------------------------------------------------------
130
131   SUBROUTINE dia_wri( kt )
132      !!---------------------------------------------------------------------
133      !!                  ***  ROUTINE dia_wri  ***
134      !!                   
135      !! ** Purpose :   Standard output of opa: dynamics and tracer fields
136      !!      NETCDF format is used by default
137      !!
138      !! ** Method  :   At the beginning of the first time step (nit000),
139      !!      define all the NETCDF files and fields
140      !!      At each time step call histdef to compute the mean if ncessary
141      !!      Each nwrite time step, output the instantaneous or mean fields
142      !!----------------------------------------------------------------------
143      !!
144      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index
145      !!
146      LOGICAL ::   ll_print = .FALSE.                        ! =T print and flush numout
147      CHARACTER (len=40) ::   clhstnam, clop, clmx           ! local names
148      INTEGER  ::   inum = 11                                ! temporary logical unit
149      INTEGER  ::   ji, jj, jk                               ! dummy loop indices
150      INTEGER  ::   ierr                                     ! error code return from allocation
151      INTEGER  ::   iimi, iima, ipk, it, itmod, ijmi, ijma   ! local integers
152      REAL(wp) ::   zsto, zout, zmax, zjulian, zdt           ! local scalars
153      !!----------------------------------------------------------------------
154      !
155      IF( nn_timing == 1 )   CALL timing_start('dia_wri')
156      !
157      ! Output the initial state and forcings
158      IF( ninist == 1 ) THEN                       
159         CALL dia_wri_state( 'output.init', kt )
160         ninist = 0
161      ENDIF
162      !
163      ! 0. Initialisation
164      ! -----------------
165
166      ! local variable for debugging
167      ll_print = .FALSE.
168      ll_print = ll_print .AND. lwp
169
170      ! Define frequency of output and means
171      zdt = rdt
172      IF( ln_mskland )   THEN   ;   clop = "only(x)"   ! put 1.e+20 on land (very expensive!!)
173      ELSE                      ;   clop = "x"         ! no use of the mask value (require less cpu time)
174      ENDIF
175#if defined key_diainstant
176      zsto = nwrite * zdt
177      clop = "inst("//TRIM(clop)//")"
178#else
179      zsto=zdt
180      clop = "ave("//TRIM(clop)//")"
181#endif
182      zout = nwrite * zdt
183      zmax = ( nitend - nit000 + 1 ) * zdt
184
185      ! Define indices of the horizontal output zoom and vertical limit storage
186      iimi = 1      ;      iima = jpi
187      ijmi = 1      ;      ijma = jpj
188      ipk = jpk
189
190      ! define time axis
191      it = kt
192      itmod = kt - nit000 + 1
193
194
195      ! 1. Define NETCDF files and fields at beginning of first time step
196      ! -----------------------------------------------------------------
197
198      IF( kt == nit000 ) THEN
199
200         ! Define the NETCDF files (one per grid)
201
202         ! Compute julian date from starting date of the run
203         CALL ymds2ju( nyear, nmonth, nday, rdt, zjulian )
204         zjulian = zjulian - adatrj   !   set calendar origin to the beginning of the experiment
205         IF(lwp)WRITE(numout,*)
206         IF(lwp)WRITE(numout,*) 'Date 0 used :', nit000, ' YEAR ', nyear,   &
207            &                    ' MONTH ', nmonth, ' DAY ', nday, 'Julian day : ', zjulian
208         IF(lwp)WRITE(numout,*) ' indexes of zoom = ', iimi, iima, ijmi, ijma,   &
209                                 ' limit storage in depth = ', ipk
210
211         ! WRITE root name in date.file for use by postpro
212         IF(lwp) THEN
213            CALL dia_nam( clhstnam, nwrite,' ' )
214            CALL ctl_opn( inum, 'date.file', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea )
215            WRITE(inum,*) clhstnam
216            CLOSE(inum)
217         ENDIF
218
219         ! Define the T grid FILE ( nid_T )
220
221         CALL dia_nam( clhstnam, nwrite, 'grid_T' )
222         IF(lwp) WRITE(numout,*) " Name of NETCDF file ", clhstnam    ! filename
223         CALL histbeg( clhstnam, jpi, glamt, jpj, gphit,           &  ! Horizontal grid: glamt and gphit
224            &          iimi, iima-iimi+1, ijmi, ijma-ijmi+1,       &
225            &          nit000-1, zjulian, zdt, nh_T, nid_T, domain_id=nidom, snc4chunks=snc4set )
226         CALL histvert( nid_T, "deptht", "Vertical T levels",      &  ! Vertical grid: gdept
[4292]227            &           "m", ipk, gdept_1d, nz_T, "down" )
[3331]228         !                                                            ! Index of ocean points
229         CALL wheneq( jpi*jpj    , tmask, 1, 1., ndex_hT, ndim_hT )      ! surface
230
231         ! Define the U grid FILE ( nid_U )
232
233         CALL dia_nam( clhstnam, nwrite, 'grid_U' )
234         IF(lwp) WRITE(numout,*) " Name of NETCDF file ", clhstnam    ! filename
235         CALL histbeg( clhstnam, jpi, glamu, jpj, gphiu,           &  ! Horizontal grid: glamu and gphiu
236            &          iimi, iima-iimi+1, ijmi, ijma-ijmi+1,       &
237            &          nit000-1, zjulian, zdt, nh_U, nid_U, domain_id=nidom, snc4chunks=snc4set )
238         CALL histvert( nid_U, "depthu", "Vertical U levels",      &  ! Vertical grid: gdept
[4292]239            &           "m", ipk, gdept_1d, nz_U, "down" )
[3331]240         !                                                            ! Index of ocean points
241         CALL wheneq( jpi*jpj    , umask, 1, 1., ndex_hU, ndim_hU )      ! surface
242
243         ! Define the V grid FILE ( nid_V )
244
245         CALL dia_nam( clhstnam, nwrite, 'grid_V' )                   ! filename
246         IF(lwp) WRITE(numout,*) " Name of NETCDF file ", clhstnam
247         CALL histbeg( clhstnam, jpi, glamv, jpj, gphiv,           &  ! Horizontal grid: glamv and gphiv
248            &          iimi, iima-iimi+1, ijmi, ijma-ijmi+1,       &
249            &          nit000-1, zjulian, zdt, nh_V, nid_V, domain_id=nidom, snc4chunks=snc4set )
250         CALL histvert( nid_V, "depthv", "Vertical V levels",      &  ! Vertical grid : gdept
[4292]251            &          "m", ipk, gdept_1d, nz_V, "down" )
[3331]252         !                                                            ! Index of ocean points
253         CALL wheneq( jpi*jpj    , vmask, 1, 1., ndex_hV, ndim_hV )      ! surface
254
255         ! No W grid FILE
256
257         ! Declare all the output fields as NETCDF variables
258
259         !                                                                                      !!! nid_T : 3D
260         CALL histdef( nid_T, "sst_m", "Sea Surface temperature"            , "C"      ,   &  ! sst
261            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
262         CALL histdef( nid_T, "sss_m", "Sea Surface Salinity"               , "PSU"    ,   &  ! sss
263            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
264         CALL histdef( nid_T, "sowaflup", "Net Upward Water Flux"              , "Kg/m2/s",   &  ! (emp-rnf)
265            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
[4148]266         CALL histdef( nid_T, "sosfldow", "downward salt flux"                 , "PSU/m2/s",  &  ! (sfx)
267             &         jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
[3331]268         CALL histdef( nid_T, "sohefldo", "Net Downward Heat Flux"             , "W/m2"   ,   &  ! qns + qsr
269            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
270         CALL histdef( nid_T, "soshfldo", "Shortwave Radiation"                , "W/m2"   ,   &  ! qsr
271            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
272         CALL histdef( nid_T, "soicecov", "Ice fraction"                       , "[0,1]"  ,   &  ! fr_i
273            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
274         CALL histdef( nid_T, "sowindsp", "wind speed at 10m"                  , "m/s"    ,   &  ! wndm
275            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
276
277         CALL histend( nid_T, snc4chunks=snc4set )
278
279         !                                                                                      !!! nid_U : 3D
280         CALL histdef( nid_U, "ssu_m", "Velocity component in x-direction", "m/s"   ,         &  ! ssu
281            &          jpi, jpj, nh_U, 1  , 1, 1  , - 99, 32, clop, zsto, zout )
282         CALL histdef( nid_U, "sozotaux", "Wind Stress along i-axis"           , "N/m2"   ,   &  ! utau
283            &          jpi, jpj, nh_U, 1  , 1, 1  , - 99, 32, clop, zsto, zout )
284
285         CALL histend( nid_U, snc4chunks=snc4set )
286
287         !                                                                                      !!! nid_V : 3D
288         CALL histdef( nid_V, "ssv_m", "Velocity component in y-direction", "m/s",            &  ! ssv_m
289            &          jpi, jpj, nh_V, 1  , 1, 1  , - 99, 32, clop, zsto, zout )
290         CALL histdef( nid_V, "sometauy", "Wind Stress along j-axis"           , "N/m2"   ,   &  ! vtau
291            &          jpi, jpj, nh_V, 1  , 1, 1  , - 99, 32, clop, zsto, zout )
292
293         CALL histend( nid_V, snc4chunks=snc4set )
294
295         IF(lwp) WRITE(numout,*)
296         IF(lwp) WRITE(numout,*) 'End of NetCDF Initialization'
297         IF(ll_print) CALL FLUSH(numout )
298
299      ENDIF
300
301      ! 2. Start writing data
302      ! ---------------------
303
304      ! ndex(1) est utilise ssi l'avant dernier argument est diffferent de
305      ! la taille du tableau en sortie. Dans ce cas , l'avant dernier argument
306      ! donne le nombre d'elements, et ndex la liste des indices a sortir
307
308      IF( lwp .AND. MOD( itmod, nwrite ) == 0 ) THEN
309         WRITE(numout,*) 'dia_wri : write model outputs in NetCDF files at ', kt, 'time-step'
310         WRITE(numout,*) '~~~~~~ '
311      ENDIF
312
313      ! Write fields on T grid
314      CALL histwrite( nid_T, "sst_m", it, sst_m, ndim_hT, ndex_hT )   ! sea surface temperature
315      CALL histwrite( nid_T, "sss_m", it, sss_m, ndim_hT, ndex_hT )   ! sea surface salinity
[4148]316      CALL histwrite( nid_T, "sowaflup", it, (emp - rnf )  , ndim_hT, ndex_hT )   ! upward water flux
317      CALL histwrite( nid_T, "sosfldow", it, sfx           , ndim_hT, ndex_hT )   ! downward salt flux
318                                                                                  ! (includes virtual salt flux beneath ice
319                                                                                  ! in linear free surface case)
320
[3331]321      CALL histwrite( nid_T, "sohefldo", it, qns + qsr     , ndim_hT, ndex_hT )   ! total heat flux
322      CALL histwrite( nid_T, "soshfldo", it, qsr           , ndim_hT, ndex_hT )   ! solar heat flux
323      CALL histwrite( nid_T, "soicecov", it, fr_i          , ndim_hT, ndex_hT )   ! ice fraction   
324      CALL histwrite( nid_T, "sowindsp", it, wndm          , ndim_hT, ndex_hT )   ! wind speed   
325
326         ! Write fields on U grid
327      CALL histwrite( nid_U, "ssu_m"   , it, ssu_m         , ndim_hU, ndex_hU )   ! i-current speed
328      CALL histwrite( nid_U, "sozotaux", it, utau          , ndim_hU, ndex_hU )   ! i-wind stress
329
330         ! Write fields on V grid
331      CALL histwrite( nid_V, "ssv_m"   , it, ssv_m         , ndim_hV, ndex_hV )   ! j-current speed
332      CALL histwrite( nid_V, "sometauy", it, vtau          , ndim_hV, ndex_hV )   ! j-wind stress
333
334      ! 3. Close all files
335      ! ---------------------------------------
336      IF( kt == nitend ) THEN
337         CALL histclo( nid_T )
338         CALL histclo( nid_U )
339         CALL histclo( nid_V )
340      ENDIF
341      !
342      IF( nn_timing == 1 )   CALL timing_stop('dia_wri')
343      !
344   END SUBROUTINE dia_wri
345# endif
346
347#endif
348
349   SUBROUTINE dia_wri_state( cdfile_name, kt )
350      !!---------------------------------------------------------------------
351      !!                 ***  ROUTINE dia_wri_state  ***
352      !!       
353      !! ** Purpose :   create a NetCDF file named cdfile_name which contains
354      !!      the instantaneous ocean state and forcing fields.
355      !!        Used to find errors in the initial state or save the last
356      !!      ocean state in case of abnormal end of a simulation
357      !!
358      !! ** Method  :   NetCDF files using ioipsl
359      !!      File 'output.init.nc'  is created if ninist = 1 (namelist)
360      !!      File 'output.abort.nc' is created in case of abnormal job end
361      !!----------------------------------------------------------------------
362      CHARACTER (len=* ), INTENT( in ) ::   cdfile_name      ! name of the file created
363      INTEGER           , INTENT( in ) ::   kt               ! ocean time-step index
364      !!
365      CHARACTER (len=32) :: clname
366      CHARACTER (len=40) :: clop
367      INTEGER  ::   id_i , nz_i, nh_i       
368      INTEGER, DIMENSION(1) ::   idex             ! local workspace
369      REAL(wp) ::   zsto, zout, zmax, zjulian, zdt
370      !!----------------------------------------------------------------------
371      !
372      IF( nn_timing == 1 )   CALL timing_start('dia_wri_state')
373
374      ! 0. Initialisation
375      ! -----------------
376
377      ! Define name, frequency of output and means
378      clname = cdfile_name
379      IF( .NOT. Agrif_Root() ) clname = TRIM(Agrif_CFixed())//'_'//TRIM(clname)
380      zdt  = rdt
381      zsto = rdt
382      clop = "inst(x)"           ! no use of the mask value (require less cpu time)
383      zout = rdt
384      zmax = ( nitend - nit000 + 1 ) * zdt
385
386      IF(lwp) WRITE(numout,*)
387      IF(lwp) WRITE(numout,*) 'dia_wri_state : single instantaneous ocean state'
388      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~~   and forcing fields file created '
389      IF(lwp) WRITE(numout,*) '                and named :', clname, '.nc'
390
391
392      ! 1. Define NETCDF files and fields at beginning of first time step
393      ! -----------------------------------------------------------------
394
395      ! Compute julian date from starting date of the run
396      CALL ymds2ju( nyear, nmonth, nday, rdt, zjulian )         ! time axis
397      zjulian = zjulian - adatrj   !   set calendar origin to the beginning of the experiment
398      CALL histbeg( clname, jpi, glamt, jpj, gphit,   &
399          1, jpi, 1, jpj, nit000-1, zjulian, zdt, nh_i, id_i, domain_id=nidom, snc4chunks=snc4set ) ! Horizontal grid : glamt and gphit
400      CALL histvert( id_i, "deptht", "Vertical T levels",   &    ! Vertical grid : gdept
[4292]401          "m", jpk, gdept_1d, nz_i, "down")
[3331]402
403      ! Declare all the output fields as NetCDF variables
404
405      CALL histdef( id_i, "sowaflup", "Net Upward Water Flux" , "Kg/m2/S",   &   ! net freshwater
406         &          jpi, jpj, nh_i, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
407      CALL histdef( id_i, "sohefldo", "Net Downward Heat Flux", "W/m2"   ,   &   ! net heat flux
408         &          jpi, jpj, nh_i, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
409      CALL histdef( id_i, "soshfldo", "Shortwave Radiation"   , "W/m2"   ,   &   ! solar flux
410         &          jpi, jpj, nh_i, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
411      CALL histdef( id_i, "soicecov", "Ice fraction"          , "[0,1]"  ,   &   ! fr_i
412         &          jpi, jpj, nh_i, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
413      CALL histdef( id_i, "sozotaux", "Zonal Wind Stress"     , "N/m2"   ,   &   ! i-wind stress
414         &          jpi, jpj, nh_i, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
415      CALL histdef( id_i, "sometauy", "Meridional Wind Stress", "N/m2"   ,   &   ! j-wind stress
416         &          jpi, jpj, nh_i, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
417
418#if defined key_lim2
419      CALL lim_wri_state_2( kt, id_i, nh_i )
[7757]420#elif defined key_lim3
421      CALL lim_wri_state( kt, id_i, nh_i )
[3331]422#else
423      CALL histend( id_i, snc4chunks=snc4set )
424#endif
425
426      ! 2. Start writing data
427      ! ---------------------
428      ! idex(1) est utilise ssi l'avant dernier argument est diffferent de
429      ! la taille du tableau en sortie. Dans ce cas , l'avant dernier argument
430      ! donne le nombre d'elements, et idex la liste des indices a sortir
431      idex(1) = 1   ! init to avoid compil warning
432
433      ! Write all fields on T grid
434      CALL histwrite( id_i, "sowaflup", kt, emp              , jpi*jpj    , idex )    ! freshwater budget
435      CALL histwrite( id_i, "sohefldo", kt, qsr + qns        , jpi*jpj    , idex )    ! total heat flux
436      CALL histwrite( id_i, "soshfldo", kt, qsr              , jpi*jpj    , idex )    ! solar heat flux
437      CALL histwrite( id_i, "soicecov", kt, fr_i             , jpi*jpj    , idex )    ! ice fraction
438      CALL histwrite( id_i, "sozotaux", kt, utau             , jpi*jpj    , idex )    ! i-wind stress
439      CALL histwrite( id_i, "sometauy", kt, vtau             , jpi*jpj    , idex )    ! j-wind stress
440
441      ! 3. Close the file
442      ! -----------------
443      CALL histclo( id_i )
444#if ! defined key_iomput && ! defined key_dimgout
445      IF( ninist /= 1  ) THEN
446         CALL histclo( nid_T )
447         CALL histclo( nid_U )
448         CALL histclo( nid_V )
449      ENDIF
450#endif
451       
452      IF( nn_timing == 1 )   CALL timing_stop('dia_wri_state')
453      !
454
455   END SUBROUTINE dia_wri_state
456   !!======================================================================
457END MODULE diawri
Note: See TracBrowser for help on using the repository browser.