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

source: trunk/NEMOGCM/NEMO/SAS_SRC/diawri.F90 @ 7646

Last change on this file since 7646 was 7646, checked in by timgraham, 7 years ago

Merge of dev_merge_2016 into trunk. UPDATE TO ARCHFILES NEEDED for XIOS2.
LIM_SRC_s/limrhg.F90 to follow in next commit due to change of kind (I'm unable to do it in this commit).
Merged using the following steps:

1) svn merge --reintegrate svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/trunk .
2) Resolve minor conflicts in sette.sh and namelist_cfg for ORCA2LIM3 (due to a change in trunk after branch was created)
3) svn commit
4) svn switch svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/trunk
5) svn merge svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/branches/2016/dev_merge_2016 .
6) At this stage I checked out a clean copy of the branch to compare against what is about to be committed to the trunk.
6) svn commit #Commit code to the trunk

In this commit I have also reverted a change to Fcheck_archfile.sh which was causing problems on the Paris machine.

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