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/NEMO/OPA_SRC/DIA – NEMO

source: trunk/NEMO/OPA_SRC/DIA/diawri.F90 @ 708

Last change on this file since 708 was 708, checked in by smasson, 17 years ago

continue changeset:704, see ticket:5

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 35.8 KB
Line 
1MODULE diawri
2   !!======================================================================
3   !!                     ***  MODULE  diawri  ***
4   !! Ocean diagnostics :  write ocean output files
5   !!=====================================================================
6
7   !!----------------------------------------------------------------------
8   !! * Modules used
9   USE oce             ! ocean dynamics and tracers
10   USE dom_oce         ! ocean space and time domain
11   USE zdf_oce         ! ocean vertical physics
12   USE ldftra_oce      ! ocean active tracers: lateral physics
13   USE ldfdyn_oce      ! ocean dynamics: lateral physics
14   USE sol_oce         ! solver variables
15   USE ice_oce         ! ice variables
16   USE sbc_oce         ! surface boundary condition: ocean
17   USE phycst          ! physical constants
18   USE ocfzpt          ! ocean freezing point
19   USE zdfmxl          ! mixed layer
20   USE daymod          ! calendar
21   USE dianam          ! build name of file (routine)
22   USE zdfddm          ! vertical  physics: double diffusion
23   USE diahth          ! thermocline diagnostics
24   USE diaspr          ! surface pressure diagnostics (rigid lid case)
25   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
26   USE in_out_manager  ! I/O manager
27   USE diadimg         ! dimg direct access file format output
28   USE ioipsl
29
30   IMPLICIT NONE
31   PRIVATE
32
33   !! * Accessibility
34   PUBLIC dia_wri                 ! routines called by step.F90
35   PUBLIC dia_wri_state
36
37   !! * Module variables
38   INTEGER ::   &
39      nid_T, nz_T, nh_T, ndim_T, ndim_hT,      &   ! grid_T file
40      nid_U, nz_U, nh_U, ndim_U, ndim_hU,      &   ! grid_U file
41      nid_V, nz_V, nh_V, ndim_V, ndim_hV,      &   ! grid_V file
42      nid_W, nz_W, nh_W,                       &   ! grid_W file
43      ndex(1)                                      ! ???
44   INTEGER, DIMENSION(jpi*jpj) ::   &
45      ndex_hT, ndex_hU, ndex_hV
46   INTEGER, DIMENSION(jpi*jpj*jpk) ::   &
47      ndex_T, ndex_U, ndex_V
48
49   !! * Substitutions
50#  include "zdfddm_substitute.h90"
51   !!----------------------------------------------------------------------
52   !!   OPA 9.0 , LOCEAN-IPSL (2005)
53   !! $Id$
54   !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
55   !!----------------------------------------------------------------------
56
57CONTAINS
58
59#if defined key_dimgout
60   !!----------------------------------------------------------------------
61   !!   dia_wri       : create the dimg direct access output file (mpp)
62   !!----------------------------------------------------------------------
63#   include "diawri_dimg.h90"
64
65#else
66   !!----------------------------------------------------------------------
67   !!   Default option                                   NetCDF output file
68   !!----------------------------------------------------------------------
69   !!   dia_wri       : create the standart NetCDF output files
70   !!   dia_wri_state : create an output NetCDF file for a single
71   !!                   instantaeous ocean state and forcing fields
72   !!----------------------------------------------------------------------
73
74   SUBROUTINE dia_wri( kt, kindic )
75      !!---------------------------------------------------------------------
76      !!                  ***  ROUTINE dia_wri  ***
77      !!                   
78      !! ** Purpose :   Standard output of opa: dynamics and tracer fields
79      !!      NETCDF format is used by default
80      !!
81      !! ** Method  :   At the beginning of the first time step (nit000),
82      !!      define all the NETCDF files and fields
83      !!      At each time step call histdef to compute the mean if ncessary
84      !!      Each nwrite time step, output the instantaneous or mean fields
85      !!      IF kindic <0, output of fields before the model interruption.
86      !!      IF kindic =0, time step loop
87      !!      IF kindic >0, output of fields before the time step loop
88      !!
89      !! History :
90      !!        !  91-03  (M.-A. Foujols)  Original code
91      !!        !  91-11  (G. Madec)
92      !!        !  92-06  (M. Imbard)  correction restart file
93      !!        !  92-07  (M. Imbard)  split into diawri and rstwri
94      !!        !  93-03  (M. Imbard)  suppress writibm
95      !!        !  98-01  (C. Levy)  NETCDF format using ioipsl INTERFACE
96      !!        !  99-02  (E. Guilyardi)  name of netCDF files + variables
97      !!   8.5  !  02-09  (G. Madec)  F90: Free form and module
98      !!   9.0  !  05-11  (V. Garnier) Surface pressure gradient organization
99      !!----------------------------------------------------------------------
100      !! * Arguments
101      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index
102      INTEGER, INTENT( in ) ::   kindic  !
103
104      !! * Local declarations
105      LOGICAL ::   ll_print = .FALSE.    ! =T print and flush numout
106      CHARACTER (len=40) ::           &
107         clhstnam, clop, clmx            ! temporary names
108      INTEGER ::   inum = 11             ! temporary logical unit
109      INTEGER ::   &
110         iimi, iima, ipk, it,         &  ! temporary integers
111         ijmi, ijma                      !    "          "
112      REAL(wp) ::   &
113         zsto, zout, zmax,            &  ! temporary scalars
114         zjulian, zdt                    !    "         "
115      REAL(wp), DIMENSION(jpi,jpj) :: &
116         zw2d                            ! temporary workspace
117      CHARACTER (len=80) :: clname
118      !!----------------------------------------------------------------------
119
120      ! 0. Initialisation
121      ! -----------------
122
123      ! local variable for debugging
124      ll_print = .FALSE.
125      ll_print = ll_print .AND. lwp
126
127      ! Define frequency of output and means
128      zdt = rdt
129      IF( nacc == 1 ) zdt = rdtmin
130#if defined key_diainstant
131      zsto = nwrite * zdt
132      clop = "inst(x)"           ! no use of the mask value (require less cpu time)
133      !!! clop="inst(only(x))"   ! put 1.e+20 on land (very expensive!!)
134#else
135      zsto=zdt
136      clop="ave(x)"              ! no use of the mask value (require less cpu time)
137      !!! clop="ave(only(x))"    ! put 1.e+20 on land (very expensive!!)
138#endif
139      zout = nwrite * zdt
140      zmax = ( nitend - nit000 + 1 ) * zdt
141
142      ! Define indices of the horizontal output zoom and vertical limit storage
143      iimi = 1      ;      iima = jpi
144      ijmi = 1      ;      ijma = jpj
145      ipk = jpk
146
147      ! define time axis
148      it = kt - nit000 + 1
149
150
151      ! 1. Define NETCDF files and fields at beginning of first time step
152      ! -----------------------------------------------------------------
153
154      IF(ll_print) WRITE(numout,*) 'dia_wri kt = ', kt, ' kindic ', kindic
155
156      IF( kt == nit000 ) THEN
157
158         ! Define the NETCDF files (one per grid)
159
160         ! Compute julian date from starting date of the run
161         CALL ymds2ju( nyear, nmonth, nday, 0.e0, zjulian )
162         IF(lwp)WRITE(numout,*)
163         IF(lwp)WRITE(numout,*) 'Date 0 used :', nit000, ' YEAR ', nyear,   &
164            &                    ' MONTH ', nmonth, ' DAY ', nday, 'Julian day : ', zjulian
165         IF(lwp)WRITE(numout,*) ' indexes of zoom = ', iimi, iima, ijmi, ijma,   &
166                                 ' limit storage in depth = ', ipk
167
168         ! WRITE root name in date.file for use by postpro
169         CALL dia_nam( clhstnam, nwrite,' ' )
170         clname = 'date.file'
171         CALL ctlopn( inum, clname,  'UNKNOWN', 'FORMATTED', 'SEQUENTIAL', 1, numout, lwp, 1 )
172         WRITE(inum,*) clhstnam
173         CLOSE(inum)
174
175         ! Define the T grid FILE ( nid_T )
176
177         CALL dia_nam( clhstnam, nwrite, 'grid_T' )
178         IF(lwp) WRITE(numout,*) " Name of NETCDF file ", clhstnam    ! filename
179         CALL histbeg( clhstnam, jpi, glamt, jpj, gphit,           &  ! Horizontal grid: glamt and gphit
180            &          iimi, iima-iimi+1, ijmi, ijma-ijmi+1,       &
181            &          0, zjulian, zdt, nh_T, nid_T, domain_id=nidom )
182         CALL histvert( nid_T, "deptht", "Vertical T levels",      &  ! Vertical grid: gdept
183            &           "m", ipk, gdept_0, nz_T )
184         !                                                            ! Index of ocean points
185         CALL wheneq( jpi*jpj*ipk, tmask, 1, 1., ndex_T , ndim_T  )      ! volume
186         CALL wheneq( jpi*jpj    , tmask, 1, 1., ndex_hT, ndim_hT )      ! surface
187
188         ! Define the U grid FILE ( nid_U )
189
190         CALL dia_nam( clhstnam, nwrite, 'grid_U' )
191         IF(lwp) WRITE(numout,*) " Name of NETCDF file ", clhstnam    ! filename
192         CALL histbeg( clhstnam, jpi, glamu, jpj, gphiu,           &  ! Horizontal grid: glamu and gphiu
193            &          iimi, iima-iimi+1, ijmi, ijma-ijmi+1,       &
194            &          0, zjulian, zdt, nh_U, nid_U, domain_id=nidom )
195         CALL histvert( nid_U, "depthu", "Vertical U levels",      &  ! Vertical grid: gdept
196            &           "m", ipk, gdept_0, nz_U )
197         !                                                            ! Index of ocean points
198         CALL wheneq( jpi*jpj*ipk, umask, 1, 1., ndex_U , ndim_U  )      ! volume
199         CALL wheneq( jpi*jpj    , umask, 1, 1., ndex_hU, ndim_hU )      ! surface
200
201         ! Define the V grid FILE ( nid_V )
202
203         CALL dia_nam( clhstnam, nwrite, 'grid_V' )                   ! filename
204         IF(lwp) WRITE(numout,*) " Name of NETCDF file ", clhstnam
205         CALL histbeg( clhstnam, jpi, glamv, jpj, gphiv,           &  ! Horizontal grid: glamv and gphiv
206            &          iimi, iima-iimi+1, ijmi, ijma-ijmi+1,       &
207            &          0, zjulian, zdt, nh_V, nid_V, domain_id=nidom )
208         CALL histvert( nid_V, "depthv", "Vertical V levels",      &  ! Vertical grid : gdept
209            &          "m", ipk, gdept_0, nz_V )
210         !                                                            ! Index of ocean points
211         CALL wheneq( jpi*jpj*ipk, vmask, 1, 1., ndex_V , ndim_V  )      ! volume
212         CALL wheneq( jpi*jpj    , vmask, 1, 1., ndex_hV, ndim_hV )      ! surface
213
214         ! Define the W grid FILE ( nid_W )
215
216         CALL dia_nam( clhstnam, nwrite, 'grid_W' )                   ! filename
217         IF(lwp) WRITE(numout,*) " Name of NETCDF file ", clhstnam
218         CALL histbeg( clhstnam, jpi, glamt, jpj, gphit,           &  ! Horizontal grid: glamt and gphit
219            &          iimi, iima-iimi+1, ijmi, ijma-ijmi+1,       &
220            &          0, zjulian, zdt, nh_W, nid_W, domain_id=nidom )
221         CALL histvert( nid_W, "depthw", "Vertical W levels",      &  ! Vertical grid: gdepw
222            &          "m", ipk, gdepw_0, nz_W )
223
224
225         ! Declare all the output fields as NETCDF variables
226
227         !                                                                                      !!! nid_T : 3D
228         CALL histdef( nid_T, "votemper", "Temperature"                        , "C"      ,   &  ! tn
229            &          jpi, jpj, nh_T, ipk, 1, ipk, nz_T, 32, clop, zsto, zout )
230         CALL histdef( nid_T, "vosaline", "Salinity"                           , "PSU"    ,   &  ! sn
231            &          jpi, jpj, nh_T, ipk, 1, ipk, nz_T, 32, clop, zsto, zout )
232         !                                                                                      !!! nid_T : 2D
233         CALL histdef( nid_T, "sosstsst", "Sea Surface temperature"            , "C"      ,   &  ! sst
234            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
235         CALL histdef( nid_T, "sosaline", "Sea Surface Salinity"               , "PSU"    ,   &  ! sss
236            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
237#if defined key_dynspg_rl
238         CALL histdef( nid_T, "sobarstf","Barotropic StreamFunction"           , "m3/s2"  ,   &  ! bsf
239            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
240#else
241         CALL histdef( nid_T, "sossheig", "Sea Surface Height"                 , "m"      ,   &  ! ssh
242            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
243#endif
244#if ! defined key_dynspg_rl && defined key_ice_lim
245         ! sowaflup = sowaflep + sorunoff + sowafldp + a term associated to
246         !    internal damping to Levitus that can be diagnosed from others
247         ! sowaflcd = sowaflep + sorunoff + sowafldp + iowaflup
248         CALL histdef( nid_T, "iowaflup", "Ice=>ocean net freshwater"          , "kg/m2/s",   &  ! fsalt
249            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
250         CALL histdef( nid_T, "sowaflep", "atmos=>ocean net freshwater"        , "kg/m2/s",   &  ! fmass
251            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
252#endif
253         CALL histdef( nid_T, "sowaflup", "Net Upward Water Flux"              , "Kg/m2/s",   &  ! emp
254            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
255         CALL histdef( nid_T, "sorunoff", "Runoffs"                            , "Kg/m2/s",   &  ! runoffs
256            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
257         CALL histdef( nid_T, "sowaflcd", "concentration/dilution water flux"  , "kg/m2/s",   &  ! emps
258            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
259         CALL histdef( nid_T, "sosalflx", "Surface Salt Flux"                  , "Kg/m2/s",   &  ! emps * sn
260            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
261         CALL histdef( nid_T, "sohefldo", "Net Downward Heat Flux"             , "W/m2"   ,   &  ! qt
262            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
263         CALL histdef( nid_T, "soshfldo", "Shortwave Radiation"                , "W/m2"   ,   &  ! qsr
264            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
265         CALL histdef( nid_T, "somxl010", "Mixed Layer Depth 0.01"             , "m"      ,   &  ! hmlp
266            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
267         CALL histdef( nid_T, "somixhgt", "Turbocline Depth"                   , "m"      ,   &  ! hmld
268            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
269         CALL histdef( nid_T, "soicecov", "Ice Cover"                          , "[0,1]"  ,   &  ! freeze
270            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
271#if ! defined key_coupled
272         CALL histdef( nid_T, "sohefldp", "Surface Heat Flux: Damping"         , "W/m2"   ,   &  ! qrp
273            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
274         CALL histdef( nid_T, "sowafldp", "Surface Water Flux: Damping"        , "Kg/m2/s",   &  ! erp
275            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
276         CALL histdef( nid_T, "sosafldp", "Surface salt flux: damping"         , "Kg/m2/s",   &  ! erp * sn
277            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
278#endif
279
280#if defined key_flx_core
281         CALL histdef( nid_T, "solhflup", "Latent Heat Flux Upward"         , "W/m2"   ,   &  ! qla
282            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
283         CALL histdef( nid_T, "solwfldo", "Longwave Radiation downward"     , "W/m2"   ,   &  ! qlw
284            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
285         CALL histdef( nid_T, "sosbhfup", "Sensible Heat Flux upward"       , "W/m2"   ,   &  ! qsb
286            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
287#endif
288
289
290#if ( defined key_coupled && ! defined key_ice_lim )
291         CALL histdef( nid_T, "sohefldp", "Surface Heat Flux: Damping"         , "W/m2"   ,   &  ! qrp
292            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
293         CALL histdef( nid_T, "sowafldp", "Surface Water Flux: Damping"        , "Kg/m2/s",   &  ! erp
294            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
295         CALL histdef( nid_T, "sosafldp", "Surface salt flux: Damping"         , "Kg/m2/s",   &  ! erp * sn
296            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
297#endif
298#if defined key_diaspr
299         CALL histdef( nid_T, "sosurfps", "Surface Pressure"                   , "cm"     ,   &  ! sp
300            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
301#endif
302         clmx ="l_max(only(x))"    ! max index on a period
303         CALL histdef( nid_T, "sobowlin", "Bowl Index"                         , "W-point",   &  ! bowl INDEX
304            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clmx, zsto, zout )
305#if defined key_diahth
306         CALL histdef( nid_T, "sothedep", "Thermocline Depth"                  , "m"      ,   & ! hth
307            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
308         CALL histdef( nid_T, "so20chgt", "Depth of 20C isotherm"              , "m"      ,   & ! hd20
309            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
310         CALL histdef( nid_T, "so28chgt", "Depth of 28C isotherm"              , "m"      ,   & ! hd28
311            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
312         CALL histdef( nid_T, "sohtc300", "Heat content 300 m"                 , "W"      ,   & ! htc3
313            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
314#endif
315
316#if defined key_ice_lim && defined key_coupled
317         CALL histdef( nid_T,"soicetem" , "Ice Surface Temperature"            , "K"      ,   &  ! tn_ice
318            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
319         CALL histdef( nid_T,"soicealb" , "Ice Albedo"                         , "[0,1]"  ,   &  ! alb_ice
320            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
321#endif
322
323         CALL histend( nid_T )
324
325         !                                                                                      !!! nid_U : 3D
326         CALL histdef( nid_U, "vozocrtx", "Zonal Current"                      , "m/s"    ,   &  ! un
327            &          jpi, jpj, nh_U, ipk, 1, ipk, nz_U, 32, clop, zsto, zout )
328#if defined key_diaeiv
329         CALL histdef( nid_U, "vozoeivu", "Zonal EIV Current"                  , "m/s"    ,   &  ! u_eiv
330            &          jpi, jpj, nh_U, ipk, 1, ipk, nz_U, 32, clop, zsto, zout )
331#endif
332         !                                                                                      !!! nid_U : 2D
333         CALL histdef( nid_U, "sozotaux", "Wind Stress along i-axis"           , "N/m2"   ,   &  ! taux
334            &          jpi, jpj, nh_U, 1  , 1, 1  , - 99, 32, clop, zsto, zout )
335#if defined key_dynspg_rl
336         CALL histdef( nid_U, "sozospgx", "Zonal Surface Pressure Gradient"    , "N/kg"   ,   &  ! spgu
337            &          jpi, jpj, nh_U, 1  , 1, 1  , - 99, 32, clop, zsto, zout )
338#endif
339
340         CALL histend( nid_U )
341
342         !                                                                                      !!! nid_V : 3D
343         CALL histdef( nid_V, "vomecrty", "Meridional Current"                 , "m/s"    ,   &  ! vn
344            &          jpi, jpj, nh_V, ipk, 1, ipk, nz_V, 32, clop, zsto, zout )
345#if defined key_diaeiv
346         CALL histdef( nid_V, "vomeeivv", "Meridional EIV Current"             , "m/s"    ,   &  ! v_eiv
347            &          jpi, jpj, nh_V, ipk, 1, ipk, nz_V, 32, clop, zsto, zout )
348#endif
349         !                                                                                      !!! nid_V : 2D
350         CALL histdef( nid_V, "sometauy", "Wind Stress along j-axis"           , "N/m2"   ,   &  ! tauy
351            &          jpi, jpj, nh_V, 1  , 1, 1  , - 99, 32, clop, zsto, zout )
352#if defined key_dynspg_rl
353         CALL histdef( nid_V, "somespgy", "Meridional Surface Pressure Grad."  , "N/kg"   ,   &  ! spgv
354            &          jpi, jpj, nh_V, 1  , 1, 1  , - 99, 32, clop, zsto, zout )
355#endif
356
357         CALL histend( nid_V )
358
359         !                                                                                      !!! nid_W : 3D
360         CALL histdef( nid_W, "vovecrtz", "Vertical Velocity"                  , "m/s"    ,   &  ! wn
361            &          jpi, jpj, nh_W, ipk, 1, ipk, nz_W, 32, clop, zsto, zout )
362#if defined key_diaeiv
363         CALL histdef( nid_W, "voveeivw", "Vertical EIV Velocity"              , "m/s"    ,   &  ! w_eiv
364            &          jpi, jpj, nh_W, ipk, 1, ipk, nz_W, 32, clop, zsto, zout )
365#endif
366         CALL histdef( nid_W, "votkeavt", "Vertical Eddy Diffusivity"          , "m2/s"   ,   &  ! avt
367            &          jpi, jpj, nh_W, ipk, 1, ipk, nz_W, 32, clop, zsto, zout )
368
369         CALL histdef( nid_W, "votkeevd", "Enhanced Vertical Diffusivity",       "m2/s"   ,   &  ! avt_evd
370            &          jpi, jpj, nh_W, ipk, 1, ipk, nz_W, 32, clop, zsto, zout )
371         !
372         CALL histdef( nid_W, "votkeavm", "Vertical Eddy Viscosity"             , "m2/s"  ,   &  ! avmu
373            &          jpi, jpj, nh_W, ipk, 1, ipk, nz_W, 32, clop, zsto, zout )
374
375         CALL histdef( nid_W, "votkeevm", "Enhanced Vertical Viscosity",         "m2/s"   ,   &  ! avmu_evd
376            &          jpi, jpj, nh_W, ipk, 1, ipk, nz_W, 32, clop, zsto, zout )
377
378         IF( lk_zdfddm ) THEN
379            CALL histdef( nid_W,"voddmavs","Salt Vertical Eddy Diffusivity"    , "m2/s"   ,   &  ! avs
380               &          jpi, jpj, nh_W, ipk, 1, ipk, nz_W, 32, clop, zsto, zout )
381         ENDIF
382         !                                                                                      !!! nid_W : 2D
383#if defined key_traldf_c2d
384         CALL histdef( nid_W, "soleahtw", "lateral eddy diffusivity"           , "m2/s"   ,   &  ! ahtw
385            &          jpi, jpj, nh_W, 1  , 1, 1  , - 99, 32, clop, zsto, zout )
386# if defined key_traldf_eiv 
387            CALL histdef( nid_W, "soleaeiw", "eddy induced vel. coeff. at w-point", "m2/s",   &  ! aeiw
388               &       jpi, jpj, nh_W, 1  , 1, 1  , - 99, 32, clop, zsto, zout )
389# endif
390#endif
391
392         CALL histend( nid_W )
393
394         IF(lwp) WRITE(numout,*)
395         IF(lwp) WRITE(numout,*) 'End of NetCDF Initialization'
396         IF(ll_print) CALL FLUSH(numout )
397
398      ENDIF
399
400      ! 2. Start writing data
401      ! ---------------------
402
403      ! ndex(1) est utilise ssi l'avant dernier argument est diffferent de
404      ! la taille du tableau en sortie. Dans ce cas , l'avant dernier argument
405      ! donne le nombre d'elements, et ndex la liste des indices a sortir
406
407      IF( lwp .AND. MOD( kt, nwrite ) == 0 ) THEN
408         WRITE(numout,*) 'dia_wri : write model outputs in NetCDF files at ', kt, 'time-step'
409         WRITE(numout,*) '~~~~~~ '
410      ENDIF
411
412      ! Write fields on T grid
413      CALL histwrite( nid_T, "votemper", it, tn            , ndim_T , ndex_T  )   ! temperature
414      CALL histwrite( nid_T, "vosaline", it, sn            , ndim_T , ndex_T  )   ! salinity
415      CALL histwrite( nid_T, "sosstsst", it, tn(:,:,1)     , ndim_hT, ndex_hT )   ! sea surface temperature
416      CALL histwrite( nid_T, "sosaline", it, sn(:,:,1)     , ndim_hT, ndex_hT )   ! sea surface salinity
417#if defined key_dynspg_rl
418      CALL histwrite( nid_T, "sobarstf", it, bsfn          , ndim_hT, ndex_hT )   ! barotropic streamfunction
419#else
420      CALL histwrite( nid_T, "sossheig", it, sshn          , ndim_hT, ndex_hT )   ! sea surface height
421#endif
422#if ! defined key_dynspg_rl && defined key_ice_lim
423      CALL histwrite( nid_T, "iowaflup", it, fsalt(:,:)    , ndim_hT, ndex_hT )   ! ice=>ocean water flux
424      CALL histwrite( nid_T, "sowaflep", it, fmass(:,:)    , ndim_hT, ndex_hT )   ! atmos=>ocean water flux
425#endif
426      CALL histwrite( nid_T, "sowaflup", it, emp           , ndim_hT, ndex_hT )   ! upward water flux
427      CALL histwrite( nid_T, "sorunoff", it, runoff        , ndim_hT, ndex_hT )   ! runoff
428      CALL histwrite( nid_T, "sowaflcd", it, emps          , ndim_hT, ndex_hT )   ! c/d water flux
429      zw2d(:,:) = emps(:,:) * sn(:,:,1) * tmask(:,:,1)
430      CALL histwrite( nid_T, "sosalflx", it, zw2d          , ndim_hT, ndex_hT )   ! c/d salt flux
431      CALL histwrite( nid_T, "sohefldo", it, qt            , ndim_hT, ndex_hT )   ! total heat flux
432      CALL histwrite( nid_T, "soshfldo", it, qsr           , ndim_hT, ndex_hT )   ! solar heat flux
433      CALL histwrite( nid_T, "somxl010", it, hmlp          , ndim_hT, ndex_hT )   ! mixed layer depth
434      CALL histwrite( nid_T, "somixhgt", it, hmld          , ndim_hT, ndex_hT )   ! turbocline depth
435      CALL histwrite( nid_T, "soicecov", it, freeze        , ndim_hT, ndex_hT )   ! ice cover
436#if ! defined key_coupled
437      CALL histwrite( nid_T, "sohefldp", it, qrp           , ndim_hT, ndex_hT )   ! heat flux damping
438      CALL histwrite( nid_T, "sowafldp", it, erp           , ndim_hT, ndex_hT )   ! freshwater flux damping
439      zw2d(:,:) = erp(:,:) * sn(:,:,1) * tmask(:,:,1)
440      CALL histwrite( nid_T, "sosafldp", it, zw2d          , ndim_hT, ndex_hT )   ! salt flux damping
441#endif
442#if defined key_flx_core
443      CALL histwrite( nid_T, "solhflup", it, qla           , ndim_hT, ndex_hT )   ! latent heat flux
444      CALL histwrite( nid_T, "solwfldo", it, qlw           , ndim_hT, ndex_hT )   ! longwave heat flux
445      CALL histwrite( nid_T, "sosbhfup", it, qsb           , ndim_hT, ndex_hT )   ! sensible heat flux
446#endif
447#if ( defined key_coupled && ! defined key_ice_lim )
448      CALL histwrite( nid_T, "sohefldp", it, qrp           , ndim_hT, ndex_hT )   ! heat flux damping
449      CALL histwrite( nid_T, "sowafldp", it, erp           , ndim_hT, ndex_hT )   ! freshwater flux damping
450         zw2d(:,:) = erp(:,:) * sn(:,:,1) * tmask(:,:,1)
451      CALL histwrite( nid_T, "sosafldp", it, zw2d          , ndim_hT, ndex_hT )   ! salt flux damping
452#endif
453#if defined key_diaspr
454      CALL histwrite( nid_T, "sosurfps", it, gps           , ndim_hT, ndex_hT )   ! surface pressure
455#endif
456         zw2d(:,:) = FLOAT( nmln(:,:) ) * tmask(:,:,1)
457      CALL histwrite( nid_T, "sobowlin", it, zw2d          , ndim_hT, ndex_hT )   ! ???
458
459#if defined key_diahth
460      CALL histwrite( nid_T, "sothedep", it, hth           , ndim_hT, ndex_hT )   ! depth of the thermocline
461      CALL histwrite( nid_T, "so20chgt", it, hd20          , ndim_hT, ndex_hT )   ! depth of the 20 isotherm
462      CALL histwrite( nid_T, "so28chgt", it, hd28          , ndim_hT, ndex_hT )   ! depth of the 28 isotherm
463      CALL histwrite( nid_T, "sohtc300", it, htc3          , ndim_hT, ndex_hT )   ! first 300m heaat content
464#endif
465#if defined key_ice_lim &&  defined key_coupled 
466      CALL histwrite( nid_T, "soicetem", it, tn_ice        , ndim_hT, ndex_hT )   ! surf. ice temperature
467      CALL histwrite( nid_T, "soicealb", it, alb_ice       , ndim_hT, ndex_hT )   ! ice albedo
468#endif
469         ! Write fields on U grid
470      CALL histwrite( nid_U, "vozocrtx", it, un            , ndim_U , ndex_U )    ! i-current
471#if defined key_diaeiv
472      CALL histwrite( nid_U, "vozoeivu", it, u_eiv         , ndim_U , ndex_U )    ! i-eiv current
473#endif
474      CALL histwrite( nid_U, "sozotaux", it, taux          , ndim_hU, ndex_hU )   ! i-wind stress
475#if defined key_dynspg_rl
476      CALL lbc_lnk( spgu, 'U', -1. )
477      CALL histwrite( nid_U, "sozospgx", it, spgu          , ndim_hU, ndex_hU )   ! i-surf. press. grad.
478#endif
479
480         ! Write fields on V grid
481      CALL histwrite( nid_V, "vomecrty", it, vn            , ndim_V , ndex_V  )   ! j-current
482#if defined key_diaeiv
483      CALL histwrite( nid_V, "vomeeivv", it, v_eiv         , ndim_V , ndex_V  )   ! j-eiv current
484#endif
485      CALL histwrite( nid_V, "sometauy", it, tauy          , ndim_hV, ndex_hV )   ! j-wind stress
486#if defined key_dynspg_rl
487      CALL lbc_lnk( spgv, 'V', -1. )
488      CALL histwrite( nid_V, "somespgy", it, spgv          , ndim_hV, ndex_hV )   ! j-surf. pressure grad.
489#endif
490
491         ! Write fields on W grid
492      CALL histwrite( nid_W, "vovecrtz", it, wn             , ndim_T, ndex_T )    ! vert. current
493#   if defined key_diaeiv
494      CALL histwrite( nid_W, "voveeivw", it, w_eiv          , ndim_T, ndex_T )    ! vert. eiv current
495#   endif
496      CALL histwrite( nid_W, "votkeavt", it, avt            , ndim_T, ndex_T )    ! T vert. eddy diff. coef.
497      CALL histwrite( nid_W, "votkeevd", it, avt_evd        , ndim_T, ndex_T )    ! T enhan. vert. eddy diff. coef.
498      CALL histwrite( nid_W, "votkeavm", it, avmu           , ndim_T, ndex_T )    ! T vert. eddy visc. coef.
499      CALL histwrite( nid_W, "votkeevm", it, avmu_evd       , ndim_T, ndex_T )    ! T enhan. vert. eddy visc. coef.
500      IF( lk_zdfddm ) THEN
501         CALL histwrite( nid_W, "voddmavs", it, fsavs(:,:,:), ndim_T, ndex_T )    ! S vert. eddy diff. coef.
502      ENDIF
503#if defined key_traldf_c2d
504      CALL histwrite( nid_W, "soleahtw", it, ahtw          , ndim_hT, ndex_hT )   ! lateral eddy diff. coef.
505# if defined key_traldf_eiv
506         CALL histwrite( nid_W, "soleaeiw", it, aeiw       , ndim_hT, ndex_hT )   ! EIV coefficient at w-point
507# endif
508#endif
509
510      ! 3. Synchronise and close all files
511      ! ---------------------------------------
512      IF( MOD( kt, nwrite ) == 0 .OR. kindic < 0 ) THEN
513         CALL histsync( nid_T )
514         CALL histsync( nid_U )
515         CALL histsync( nid_V )
516         CALL histsync( nid_W )
517      ENDIF
518
519      !  Create an output files (output.abort.nc) if S < 0 or u > 20 m/s
520      IF( kindic < 0 )   CALL dia_wri_state( 'output.abort' )
521
522      IF( kt == nitend .OR. kindic < 0 ) THEN
523         CALL histclo( nid_T )
524         CALL histclo( nid_U )
525         CALL histclo( nid_V )
526         CALL histclo( nid_W )
527      ENDIF
528
529   END SUBROUTINE dia_wri
530
531
532   SUBROUTINE dia_wri_state( cdfile_name )
533      !!---------------------------------------------------------------------
534      !!                 ***  ROUTINE dia_wri_state  ***
535      !!       
536      !! ** Purpose :   create a NetCDF file named cdfile_name which contains
537      !!      the instantaneous ocean state and forcing fields.
538      !!        Used to find errors in the initial state or save the last
539      !!      ocean state in case of abnormal end of a simulation
540      !!
541      !! ** Method  :   NetCDF files using ioipsl
542      !!      File 'output.init.nc'  is created if ninist = 1 (namelist)
543      !!      File 'output.abort.nc' is created in case of abnormal job end
544      !!
545      !! History :
546      !!   8.2  !  00-06  (M. Imbard)  Original code (diabort.F)
547      !!   8.5  !  02-06  (A.Bozec, E. Durand)  Original code (diainit.F)
548      !!   9.0  !  02-12  (G. Madec)  merge of diabort and diainit, F90
549      !!    "   !  05-11  (V. Garnier) Surface pressure gradient organization
550      !!----------------------------------------------------------------------
551      !! * Arguments
552      CHARACTER (len=* ), INTENT( in ) ::   &
553         cdfile_name      ! name of the file created
554
555      !! * Local declarations
556      CHARACTER (len=32) :: clname
557      CHARACTER (len=40) :: clop
558      INTEGER  ::   &
559         id_i , nz_i, nh_i       
560      INTEGER, DIMENSION(1) ::   &
561         idex             ! temprary workspace
562      REAL(wp) ::   &
563         zsto, zout, zmax,   &
564         zjulian, zdt
565      !!----------------------------------------------------------------------
566
567      ! 0. Initialisation
568      ! -----------------
569
570      ! Define name, frequency of output and means
571      clname = cdfile_name
572#if defined key_agrif
573      if ( .NOT. Agrif_Root() ) clname = TRIM(Agrif_CFixed())//'_'//TRIM(clname)
574#endif
575      zdt  = rdt
576      zsto = rdt
577      clop = "inst(x)"           ! no use of the mask value (require less cpu time)
578      zout = rdt
579      zmax = ( nitend - nit000 + 1 ) * zdt
580
581      IF(lwp) WRITE(numout,*)
582      IF(lwp) WRITE(numout,*) 'dia_wri_state : single instantaneous ocean state'
583      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~~   and forcing fields file created '
584      IF(lwp) WRITE(numout,*) '                and named :', clname, '.nc'
585
586
587      ! 1. Define NETCDF files and fields at beginning of first time step
588      ! -----------------------------------------------------------------
589
590      ! Compute julian date from starting date of the run
591      CALL ymds2ju( nyear, nmonth, nday, 0.e0, zjulian )         ! time axis
592      CALL histbeg( clname, jpi, glamt, jpj, gphit,   &
593          1, jpi, 1, jpj, 0, zjulian, zdt, nh_i, id_i, domain_id=nidom )          ! Horizontal grid : glamt and gphit
594      CALL histvert( id_i, "deptht", "Vertical T levels",   &    ! Vertical grid : gdept
595          "m", jpk, gdept_0, nz_i)
596
597      ! Declare all the output fields as NetCDF variables
598
599      CALL histdef( id_i, "vosaline", "Salinity"              , "PSU"    ,   &   ! salinity
600         &          jpi, jpj, nh_i, jpk, 1, jpk, nz_i, 32, clop, zsto, zout )
601      CALL histdef( id_i, "votemper", "Temperature"           , "C"      ,   &   ! temperature
602         &          jpi, jpj, nh_i, jpk, 1, jpk, nz_i, 32, clop, zsto, zout )
603#if defined key_dynspg_rl
604      CALL histdef( id_i, "sobarstf","Barotropic StreamFunction", "m3/s2"  ,   &  ! bsf
605         &          jpi, jpj, nh_i, 1  , 1, 1  , nz_i, 32, clop, zsto, zout )
606#else
607      CALL histdef( id_i, "sossheig", "Sea Surface Height"    , "m"      ,   &  ! ssh
608         &          jpi, jpj, nh_i, 1  , 1, 1  , nz_i, 32, clop, zsto, zout )
609#endif
610      CALL histdef( id_i, "vozocrtx", "Zonal Current"         , "m/s"    ,   &   ! zonal current
611         &          jpi, jpj, nh_i, jpk, 1, jpk, nz_i, 32, clop, zsto, zout )
612      CALL histdef( id_i, "vomecrty", "Meridional Current"    , "m/s"    ,   &   ! meridonal current
613         &          jpi, jpj, nh_i, jpk, 1, jpk, nz_i, 32, clop, zsto, zout ) 
614      CALL histdef( id_i, "vovecrtz", "Vertical Velocity"     , "m/s"    ,   &   ! vertical current
615         &          jpi, jpj, nh_i, jpk, 1, jpk, nz_i, 32, clop, zsto, zout ) 
616      CALL histdef( id_i, "sowaflup", "Net Upward Water Flux" , "Kg/m2/S",   &   ! net freshwater
617         &          jpi, jpj, nh_i, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
618      CALL histdef( id_i, "sohefldo", "Net Downward Heat Flux", "W/m2"   ,   &   ! net heat flux
619         &          jpi, jpj, nh_i, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
620      CALL histdef( id_i, "soshfldo", "Shortwave Radiation"   , "W/m2"   ,   &   ! solar flux
621         &          jpi, jpj, nh_i, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
622      CALL histdef( id_i, "soicecov", "Ice fraction"          , "[0,1]"  ,   &   ! freeze
623         &          jpi, jpj, nh_i, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
624      CALL histdef( id_i, "sozotaux", "Zonal Wind Stress"     , "N/m2"   ,   &   ! i-wind stress
625         &          jpi, jpj, nh_i, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
626      CALL histdef( id_i, "sometauy", "Meridional Wind Stress", "N/m2"   ,   &   ! j-wind stress
627         &          jpi, jpj, nh_i, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
628
629      CALL histend( id_i )
630
631      ! 2. Start writing data
632      ! ---------------------
633      ! idex(1) est utilise ssi l'avant dernier argument est diffferent de
634      ! la taille du tableau en sortie. Dans ce cas , l'avant dernier argument
635      ! donne le nombre d'elements, et idex la liste des indices a sortir
636      idex(1) = 1   ! init to avoid compil warning
637
638      ! Write all fields on T grid
639      CALL histwrite( id_i, "votemper", 1, tn    , jpi*jpj*jpk, idex )    ! now temperature
640      CALL histwrite( id_i, "vosaline", 1, sn    , jpi*jpj*jpk, idex )    ! now salinity
641#if defined key_dynspg_rl
642      CALL histwrite( id_i, "sobarstf", 1, bsfn  , jpi*jpj    , idex )    ! barotropic streamfunction
643#else
644      CALL histwrite( id_i, "sossheig", 1, sshn  , jpi*jpj    , idex )    ! sea surface height
645#endif
646      CALL histwrite( id_i, "vozocrtx", 1, un    , jpi*jpj*jpk, idex )    ! now i-velocity
647      CALL histwrite( id_i, "vomecrty", 1, vn    , jpi*jpj*jpk, idex )    ! now j-velocity
648      CALL histwrite( id_i, "vovecrtz", 1, wn    , jpi*jpj*jpk, idex )    ! now k-velocity
649      CALL histwrite( id_i, "sowaflup", 1, emp   , jpi*jpj    , idex )    ! freshwater budget
650      CALL histwrite( id_i, "sohefldo", 1, qt    , jpi*jpj    , idex )    ! total heat flux
651      CALL histwrite( id_i, "soshfldo", 1, qsr   , jpi*jpj    , idex )    ! total heat flux
652      CALL histwrite( id_i, "soicecov", 1, freeze, jpi*jpj    , idex )    ! ice cover
653      CALL histwrite( id_i, "sozotaux", 1, taux  , jpi*jpj    , idex )    ! i-wind stress
654      CALL histwrite( id_i, "sometauy", 1, tauy  , jpi*jpj    , idex )    ! j-wind stress
655
656      ! 3. Close the file
657      ! -----------------
658      CALL histclo( id_i )
659
660   END SUBROUTINE dia_wri_state
661
662#endif
663   !!======================================================================
664END MODULE diawri
Note: See TracBrowser for help on using the repository browser.