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

source: tags/nemo_dev_x8/NEMO/OPA_SRC/DIA/diawri.F90 @ 2023

Last change on this file since 2023 was 146, checked in by opalod, 20 years ago

CL + CT: BUGFIX091: Add missing "USE flx_oce" module

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