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

source: branches/dev_001_SBC/NEMO/OPA_SRC/DIA/diawri.F90 @ 748

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

remove the output of qla, qsb and qlw for CORE forcing, see ticket:#28

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