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/2012/dev_NOC_2012_rev3555/NEMOGCM/NEMO/SAS_SRC – NEMO

source: branches/2012/dev_NOC_2012_rev3555/NEMOGCM/NEMO/SAS_SRC/diawri.F90 @ 3634

Last change on this file since 3634 was 3331, checked in by sga, 12 years ago

NEMO 2012 development branch dev_r3322_NOCS09_SAS
Code changes made for compilation and running of StandAlone? Surface scheme (tinkering still required)

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