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

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

Last change on this file since 8085 was 7158, checked in by clem, 8 years ago

debug branch

  • Property svn:keywords set to Id
File size: 22.1 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( ln_mskland )   THEN   ;   clop = "only(x)"   ! put 1.e+20 on land (very expensive!!)
167      ELSE                      ;   clop = "x"         ! no use of the mask value (require less cpu time)
168      ENDIF
169#if defined key_diainstant
170      zsto = nwrite * zdt
171      clop = "inst("//TRIM(clop)//")"
172#else
173      zsto=zdt
174      clop = "ave("//TRIM(clop)//")"
175#endif
176      zout = nwrite * zdt
177      zmax = ( nitend - nit000 + 1 ) * zdt
178
179      ! Define indices of the horizontal output zoom and vertical limit storage
180      iimi = 1      ;      iima = jpi
181      ijmi = 1      ;      ijma = jpj
182      ipk = jpk
183
184      ! define time axis
185      it = kt
186      itmod = kt - nit000 + 1
187
188
189      ! 1. Define NETCDF files and fields at beginning of first time step
190      ! -----------------------------------------------------------------
191
192      IF( kt == nit000 ) THEN
193
194         ! Define the NETCDF files (one per grid)
195
196         ! Compute julian date from starting date of the run
197         CALL ymds2ju( nyear, nmonth, nday, rdt, zjulian )
198         zjulian = zjulian - adatrj   !   set calendar origin to the beginning of the experiment
199         IF(lwp)WRITE(numout,*)
200         IF(lwp)WRITE(numout,*) 'Date 0 used :', nit000, ' YEAR ', nyear,   &
201            &                    ' MONTH ', nmonth, ' DAY ', nday, 'Julian day : ', zjulian
202         IF(lwp)WRITE(numout,*) ' indexes of zoom = ', iimi, iima, ijmi, ijma,   &
203                                 ' limit storage in depth = ', ipk
204
205         ! WRITE root name in date.file for use by postpro
206         IF(lwp) THEN
207            CALL dia_nam( clhstnam, nwrite,' ' )
208            CALL ctl_opn( inum, 'date.file', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea )
209            WRITE(inum,*) clhstnam
210            CLOSE(inum)
211         ENDIF
212
213         ! Define the T grid FILE ( nid_T )
214
215         CALL dia_nam( clhstnam, nwrite, 'grid_T' )
216         IF(lwp) WRITE(numout,*) " Name of NETCDF file ", clhstnam    ! filename
217         CALL histbeg( clhstnam, jpi, glamt, jpj, gphit,           &  ! Horizontal grid: glamt and gphit
218            &          iimi, iima-iimi+1, ijmi, ijma-ijmi+1,       &
219            &          nit000-1, zjulian, zdt, nh_T, nid_T, domain_id=nidom, snc4chunks=snc4set )
220         CALL histvert( nid_T, "deptht", "Vertical T levels",      &  ! Vertical grid: gdept
221            &           "m", ipk, gdept_1d, nz_T, "down" )
222         !                                                            ! Index of ocean points
223         CALL wheneq( jpi*jpj    , tmask, 1, 1., ndex_hT, ndim_hT )      ! surface
224
225         ! Define the U grid FILE ( nid_U )
226
227         CALL dia_nam( clhstnam, nwrite, 'grid_U' )
228         IF(lwp) WRITE(numout,*) " Name of NETCDF file ", clhstnam    ! filename
229         CALL histbeg( clhstnam, jpi, glamu, jpj, gphiu,           &  ! Horizontal grid: glamu and gphiu
230            &          iimi, iima-iimi+1, ijmi, ijma-ijmi+1,       &
231            &          nit000-1, zjulian, zdt, nh_U, nid_U, domain_id=nidom, snc4chunks=snc4set )
232         CALL histvert( nid_U, "depthu", "Vertical U levels",      &  ! Vertical grid: gdept
233            &           "m", ipk, gdept_1d, nz_U, "down" )
234         !                                                            ! Index of ocean points
235         CALL wheneq( jpi*jpj    , umask, 1, 1., ndex_hU, ndim_hU )      ! surface
236
237         ! Define the V grid FILE ( nid_V )
238
239         CALL dia_nam( clhstnam, nwrite, 'grid_V' )                   ! filename
240         IF(lwp) WRITE(numout,*) " Name of NETCDF file ", clhstnam
241         CALL histbeg( clhstnam, jpi, glamv, jpj, gphiv,           &  ! Horizontal grid: glamv and gphiv
242            &          iimi, iima-iimi+1, ijmi, ijma-ijmi+1,       &
243            &          nit000-1, zjulian, zdt, nh_V, nid_V, domain_id=nidom, snc4chunks=snc4set )
244         CALL histvert( nid_V, "depthv", "Vertical V levels",      &  ! Vertical grid : gdept
245            &          "m", ipk, gdept_1d, nz_V, "down" )
246         !                                                            ! Index of ocean points
247         CALL wheneq( jpi*jpj    , vmask, 1, 1., ndex_hV, ndim_hV )      ! surface
248
249         ! No W grid FILE
250
251         ! Declare all the output fields as NETCDF variables
252
253         !                                                                                      !!! nid_T : 3D
254         CALL histdef( nid_T, "sst_m", "Sea Surface temperature"            , "C"      ,   &  ! sst
255            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
256         CALL histdef( nid_T, "sss_m", "Sea Surface Salinity"               , "PSU"    ,   &  ! sss
257            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
258         CALL histdef( nid_T, "sowaflup", "Net Upward Water Flux"              , "Kg/m2/s",   &  ! (emp-rnf)
259            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
260         CALL histdef( nid_T, "sosfldow", "downward salt flux"                 , "PSU/m2/s",  &  ! (sfx)
261             &         jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
262         CALL histdef( nid_T, "sohefldo", "Net Downward Heat Flux"             , "W/m2"   ,   &  ! qns + qsr
263            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
264         CALL histdef( nid_T, "soshfldo", "Shortwave Radiation"                , "W/m2"   ,   &  ! qsr
265            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
266         CALL histdef( nid_T, "soicecov", "Ice fraction"                       , "[0,1]"  ,   &  ! fr_i
267            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
268         CALL histdef( nid_T, "sowindsp", "wind speed at 10m"                  , "m/s"    ,   &  ! wndm
269            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
270
271         CALL histend( nid_T, snc4chunks=snc4set )
272
273         !                                                                                      !!! nid_U : 3D
274         CALL histdef( nid_U, "ssu_m", "Velocity component in x-direction", "m/s"   ,         &  ! ssu
275            &          jpi, jpj, nh_U, 1  , 1, 1  , - 99, 32, clop, zsto, zout )
276         CALL histdef( nid_U, "sozotaux", "Wind Stress along i-axis"           , "N/m2"   ,   &  ! utau
277            &          jpi, jpj, nh_U, 1  , 1, 1  , - 99, 32, clop, zsto, zout )
278
279         CALL histend( nid_U, snc4chunks=snc4set )
280
281         !                                                                                      !!! nid_V : 3D
282         CALL histdef( nid_V, "ssv_m", "Velocity component in y-direction", "m/s",            &  ! ssv_m
283            &          jpi, jpj, nh_V, 1  , 1, 1  , - 99, 32, clop, zsto, zout )
284         CALL histdef( nid_V, "sometauy", "Wind Stress along j-axis"           , "N/m2"   ,   &  ! vtau
285            &          jpi, jpj, nh_V, 1  , 1, 1  , - 99, 32, clop, zsto, zout )
286
287         CALL histend( nid_V, snc4chunks=snc4set )
288
289         IF(lwp) WRITE(numout,*)
290         IF(lwp) WRITE(numout,*) 'End of NetCDF Initialization'
291         IF(ll_print) CALL FLUSH(numout )
292
293      ENDIF
294
295      ! 2. Start writing data
296      ! ---------------------
297
298      ! ndex(1) est utilise ssi l'avant dernier argument est diffferent de
299      ! la taille du tableau en sortie. Dans ce cas , l'avant dernier argument
300      ! donne le nombre d'elements, et ndex la liste des indices a sortir
301
302      IF( lwp .AND. MOD( itmod, nwrite ) == 0 ) THEN
303         WRITE(numout,*) 'dia_wri : write model outputs in NetCDF files at ', kt, 'time-step'
304         WRITE(numout,*) '~~~~~~ '
305      ENDIF
306
307      ! Write fields on T grid
308      CALL histwrite( nid_T, "sst_m", it, sst_m, ndim_hT, ndex_hT )   ! sea surface temperature
309      CALL histwrite( nid_T, "sss_m", it, sss_m, ndim_hT, ndex_hT )   ! sea surface salinity
310      CALL histwrite( nid_T, "sowaflup", it, (emp - rnf )  , ndim_hT, ndex_hT )   ! upward water flux
311      CALL histwrite( nid_T, "sosfldow", it, sfx           , ndim_hT, ndex_hT )   ! downward salt flux
312                                                                                  ! (includes virtual salt flux beneath ice
313                                                                                  ! in linear free surface case)
314
315      CALL histwrite( nid_T, "sohefldo", it, qns + qsr     , ndim_hT, ndex_hT )   ! total heat flux
316      CALL histwrite( nid_T, "soshfldo", it, qsr           , ndim_hT, ndex_hT )   ! solar heat flux
317      CALL histwrite( nid_T, "soicecov", it, fr_i          , ndim_hT, ndex_hT )   ! ice fraction   
318      CALL histwrite( nid_T, "sowindsp", it, wndm          , ndim_hT, ndex_hT )   ! wind speed   
319
320         ! Write fields on U grid
321      CALL histwrite( nid_U, "ssu_m"   , it, ssu_m         , ndim_hU, ndex_hU )   ! i-current speed
322      CALL histwrite( nid_U, "sozotaux", it, utau          , ndim_hU, ndex_hU )   ! i-wind stress
323
324         ! Write fields on V grid
325      CALL histwrite( nid_V, "ssv_m"   , it, ssv_m         , ndim_hV, ndex_hV )   ! j-current speed
326      CALL histwrite( nid_V, "sometauy", it, vtau          , ndim_hV, ndex_hV )   ! j-wind stress
327
328      ! 3. Close all files
329      ! ---------------------------------------
330      IF( kt == nitend ) THEN
331         CALL histclo( nid_T )
332         CALL histclo( nid_U )
333         CALL histclo( nid_V )
334      ENDIF
335      !
336      IF( nn_timing == 1 )   CALL timing_stop('dia_wri')
337      !
338   END SUBROUTINE dia_wri
339# endif
340
341#endif
342
343   SUBROUTINE dia_wri_state( cdfile_name, kt )
344      !!---------------------------------------------------------------------
345      !!                 ***  ROUTINE dia_wri_state  ***
346      !!       
347      !! ** Purpose :   create a NetCDF file named cdfile_name which contains
348      !!      the instantaneous ocean state and forcing fields.
349      !!        Used to find errors in the initial state or save the last
350      !!      ocean state in case of abnormal end of a simulation
351      !!
352      !! ** Method  :   NetCDF files using ioipsl
353      !!      File 'output.init.nc'  is created if ninist = 1 (namelist)
354      !!      File 'output.abort.nc' is created in case of abnormal job end
355      !!----------------------------------------------------------------------
356      CHARACTER (len=* ), INTENT( in ) ::   cdfile_name      ! name of the file created
357      INTEGER           , INTENT( in ) ::   kt               ! ocean time-step index
358      !!
359      CHARACTER (len=32) :: clname
360      CHARACTER (len=40) :: clop
361      INTEGER  ::   id_i , nz_i, nh_i       
362      INTEGER, DIMENSION(1) ::   idex             ! local workspace
363      REAL(wp) ::   zsto, zout, zmax, zjulian, zdt
364      !!----------------------------------------------------------------------
365      !
366      IF( nn_timing == 1 )   CALL timing_start('dia_wri_state')
367
368      ! 0. Initialisation
369      ! -----------------
370
371      ! Define name, frequency of output and means
372      clname = cdfile_name
373      IF( .NOT. Agrif_Root() ) clname = TRIM(Agrif_CFixed())//'_'//TRIM(clname)
374      zdt  = rdt
375      zsto = rdt
376      clop = "inst(x)"           ! no use of the mask value (require less cpu time)
377      zout = rdt
378      zmax = ( nitend - nit000 + 1 ) * zdt
379
380      IF(lwp) WRITE(numout,*)
381      IF(lwp) WRITE(numout,*) 'dia_wri_state : single instantaneous ocean state'
382      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~~   and forcing fields file created '
383      IF(lwp) WRITE(numout,*) '                and named :', clname, '.nc'
384
385
386      ! 1. Define NETCDF files and fields at beginning of first time step
387      ! -----------------------------------------------------------------
388
389      ! Compute julian date from starting date of the run
390      CALL ymds2ju( nyear, nmonth, nday, rdt, zjulian )         ! time axis
391      zjulian = zjulian - adatrj   !   set calendar origin to the beginning of the experiment
392      CALL histbeg( clname, jpi, glamt, jpj, gphit,   &
393          1, jpi, 1, jpj, nit000-1, zjulian, zdt, nh_i, id_i, domain_id=nidom, snc4chunks=snc4set ) ! Horizontal grid : glamt and gphit
394      CALL histvert( id_i, "deptht", "Vertical T levels",   &    ! Vertical grid : gdept
395          "m", jpk, gdept_1d, nz_i, "down")
396
397      ! Declare all the output fields as NetCDF variables
398
399      CALL histdef( id_i, "sowaflup", "Net Upward Water Flux" , "Kg/m2/S",   &   ! net freshwater
400         &          jpi, jpj, nh_i, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
401      CALL histdef( id_i, "sohefldo", "Net Downward Heat Flux", "W/m2"   ,   &   ! net heat flux
402         &          jpi, jpj, nh_i, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
403      CALL histdef( id_i, "soshfldo", "Shortwave Radiation"   , "W/m2"   ,   &   ! solar flux
404         &          jpi, jpj, nh_i, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
405      CALL histdef( id_i, "soicecov", "Ice fraction"          , "[0,1]"  ,   &   ! fr_i
406         &          jpi, jpj, nh_i, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
407      CALL histdef( id_i, "sozotaux", "Zonal Wind Stress"     , "N/m2"   ,   &   ! i-wind stress
408         &          jpi, jpj, nh_i, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
409      CALL histdef( id_i, "sometauy", "Meridional Wind Stress", "N/m2"   ,   &   ! j-wind stress
410         &          jpi, jpj, nh_i, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
411
412#if defined key_lim2
413      CALL lim_wri_state_2( kt, id_i, nh_i )
414#else
415      CALL histend( id_i, snc4chunks=snc4set )
416#endif
417
418      ! 2. Start writing data
419      ! ---------------------
420      ! idex(1) est utilise ssi l'avant dernier argument est diffferent de
421      ! la taille du tableau en sortie. Dans ce cas , l'avant dernier argument
422      ! donne le nombre d'elements, et idex la liste des indices a sortir
423      idex(1) = 1   ! init to avoid compil warning
424
425      ! Write all fields on T grid
426      CALL histwrite( id_i, "sowaflup", kt, emp              , jpi*jpj    , idex )    ! freshwater budget
427      CALL histwrite( id_i, "sohefldo", kt, qsr + qns        , jpi*jpj    , idex )    ! total heat flux
428      CALL histwrite( id_i, "soshfldo", kt, qsr              , jpi*jpj    , idex )    ! solar heat flux
429      CALL histwrite( id_i, "soicecov", kt, fr_i             , jpi*jpj    , idex )    ! ice fraction
430      CALL histwrite( id_i, "sozotaux", kt, utau             , jpi*jpj    , idex )    ! i-wind stress
431      CALL histwrite( id_i, "sometauy", kt, vtau             , jpi*jpj    , idex )    ! j-wind stress
432
433      ! 3. Close the file
434      ! -----------------
435      CALL histclo( id_i )
436#if ! defined key_iomput && ! defined key_dimgout
437      IF( ninist /= 1  ) THEN
438         CALL histclo( nid_T )
439         CALL histclo( nid_U )
440         CALL histclo( nid_V )
441      ENDIF
442#endif
443       
444      IF( nn_timing == 1 )   CALL timing_stop('dia_wri_state')
445      !
446
447   END SUBROUTINE dia_wri_state
448   !!======================================================================
449END MODULE diawri
Note: See TracBrowser for help on using the repository browser.