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 @ 1037

Last change on this file since 1037 was 1037, checked in by ctlod, 16 years ago

trunk: replace freeze(:,:) variable with fr_i(:,:), use the tfreez function defined in eosbn2.F90 and remove the useless ocfzpt.F90 module, see ticket: #177

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