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

Last change on this file since 247 was 247, checked in by opalod, 19 years ago

CL : Add CVS Header and CeCILL licence information

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 33.2 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          ! ocean freezing point
18   USE ocesbc          ! surface thermohaline fluxes
19   USE taumod          ! surface stress
20   USE flxrnf          ! ocean runoffs
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   USE diadimg         ! dimg direct access file format output
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   !! $Header$
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      !!----------------------------------------------------------------------
101      !! * Modules used
102      USE ioipsl
103
104      !! * Arguments
105      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index
106      INTEGER, INTENT( in ) ::   kindic  !
107
108      !! * Local declarations
109      LOGICAL ::   ll_print = .FALSE.    ! =T print and flush numout
110      CHARACTER (len=40) ::           &
111         clhstnam, clop, clmx            ! temporary names
112      INTEGER ::   inum = 11             ! temporary logical unit
113      INTEGER ::   &
114         iimi, iima, ipk, it,         &  ! temporary integers
115         ijmi, ijma                      !    "          "
116      REAL(wp) ::   &
117         zsto, zout, zmax,            &  ! temporary scalars
118         zjulian, zdt                    !    "         "
119      REAL(wp), DIMENSION(jpi,jpj) :: &
120         zw2d                            ! temporary workspace
121      !!----------------------------------------------------------------------
122     
123      ! 0. Initialisation
124      ! -----------------
125     
126      ! local variable for debugging
127      ll_print = .FALSE.
128      ll_print = ll_print .AND. lwp
129
130      ! Define frequency of output and means
131      zdt = rdt
132      IF( nacc == 1 ) zdt = rdtmin
133#if defined key_diainstant
134      zsto = nwrite * zdt
135      clop = "inst(x)"           ! no use of the mask value (require less cpu time)
136      !!! clop="inst(only(x))"   ! put 1.e+20 on land (very expensive!!)
137#else
138      zsto=zdt
139      clop="ave(x)"              ! no use of the mask value (require less cpu time)
140      !!! clop="ave(only(x))"    ! put 1.e+20 on land (very expensive!!)
141#endif
142      zout = nwrite * zdt
143      zmax = ( nitend - nit000 + 1 ) * zdt
144
145      ! Define indices of the horizontal output zoom and vertical limit storage
146      iimi = 1      ;      iima = jpi
147      ijmi = 1      ;      ijma = jpj
148      ipk = jpk
149
150      ! define time axis
151      it = kt - nit000 + 1
152
153
154      ! 1. Define NETCDF files and fields at beginning of first time step
155      ! -----------------------------------------------------------------
156
157      IF(ll_print) WRITE(numout,*) 'dia_wri kt = ', kt, ' kindic ', kindic
158
159      IF( kt == nit000 ) THEN
160
161         ! Define the NETCDF files (one per grid)
162         
163         ! Compute julian date from starting date of the run
164         CALL ymds2ju( nyear, nmonth, nday, 0.e0, zjulian )
165         IF(lwp)WRITE(numout,*)
166         IF(lwp)WRITE(numout,*) 'Date 0 used :', nit000, ' YEAR ', nyear,   &
167            &                    ' MONTH ', nmonth, ' DAY ', nday, 'Julian day : ', zjulian
168         IF(lwp)WRITE(numout,*) ' indexes of zoom = ', iimi, iima, ijmi, ijma,   &
169                                 ' limit storage in depth = ', ipk
170
171         ! WRITE root name in date.file for use by postpro
172         CALL dia_nam( clhstnam, nwrite,' ' )
173         CALL ctlopn( inum, 'date.file', '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 )
184         CALL histvert( nid_T, "deptht", "Vertical T levels",      &  ! Vertical grid: gdept
185            &           "m", ipk, gdept, 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 )
197         CALL histvert( nid_U, "depthu", "Vertical U levels",      &  ! Vertical grid: gdept
198            &           "m", ipk, gdept, 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 )
210         CALL histvert( nid_V, "depthv", "Vertical V levels",      &  ! Vertical grid : gdept
211            &          "m", ipk, gdept, 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 )
223         CALL histvert( nid_W, "depthw", "Vertical W levels",      &  ! Vertical grid: gdepw
224            &          "m", ipk, gdepw, 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_fsc
240         CALL histdef( nid_T, "sossheig", "Sea Surface Height"                 , "m"      ,   &  ! ssh
241            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
242#else
243         CALL histdef( nid_T, "sobarstf","Barotropic StreamFunction"           , "m3/s2"  ,   &  ! bsf
244            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
245#endif
246#if defined key_dynspg_fsc && 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"   ,   &  ! qt
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#if ( defined key_coupled && ! defined key_ice_lim )
283         CALL histdef( nid_T, "sohefldp", "Surface Heat Flux: Damping"         , "W/m2"   ,   &  ! qrp
284            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
285         CALL histdef( nid_T, "sowafldp", "Surface Water Flux: Damping"        , "Kg/m2/s",   &  ! erp
286            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
287         CALL histdef( nid_T, "sosafldp", "Surface salt flux: Damping"         , "Kg/m2/s",   &  ! erp * sn
288            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
289#endif
290#if defined key_diaspr
291         CALL histdef( nid_T, "sosurfps", "Surface Pressure"                   , "cm"     ,   &  ! sp
292            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
293#endif
294         clmx ="l_max(only(x))"    ! max index on a period
295         CALL histdef( nid_T, "sobowlin", "Bowl Index"                         , "W-point",   &  ! bowl INDEX
296            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clmx, zsto, zout )
297#if defined key_diahth
298         CALL histdef( nid_T, "sothedep", "Thermocline Depth"                  , "m"      ,   & ! hth
299            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
300         CALL histdef( nid_T, "so20chgt", "Depth of 20C isotherm"              , "m"      ,   & ! hd20
301            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
302         CALL histdef( nid_T, "so28chgt", "Depth of 28C isotherm"              , "m"      ,   & ! hd28
303            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
304         CALL histdef( nid_T, "sohtc300", "Heat content 300 m"                 , "W"      ,   & ! htc3
305            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
306#endif
307
308#if defined key_ice_lim && defined key_coupled
309         CALL histdef( nid_T,"soicetem" , "Ice Surface Temperature"            , "K"      ,   &  ! tn_ice
310            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
311         CALL histdef( nid_T,"soicealb" , "Ice Albedo"                         , "[0,1]"  ,   &  ! alb_ice
312            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
313#endif
314
315         CALL histend( nid_T )
316
317         !                                                                                      !!! nid_U : 3D
318         CALL histdef( nid_U, "vozocrtx", "Zonal Current"                      , "m/s"    ,   &  ! un
319            &          jpi, jpj, nh_U, ipk, 1, ipk, nz_U, 32, clop, zsto, zout )
320#if defined key_diaeiv
321         CALL histdef( nid_U, "vozoeivu", "Zonal EIV Current"                  , "m/s"    ,   &  ! u_eiv
322            &          jpi, jpj, nh_U, ipk, 1, ipk, nz_U, 32, clop, zsto, zout )
323#endif
324         !                                                                                      !!! nid_U : 2D
325         CALL histdef( nid_U, "sozotaux", "Wind Stress along i-axis"           , "N/m2"   ,   &  ! taux
326            &          jpi, jpj, nh_U, 1  , 1, 1  , - 99, 32, clop, zsto, zout )
327#if ! defined key_dynspg_fsc
328         CALL histdef( nid_U, "sozospgx", "Zonal Surface Pressure Gradient"    , "N/kg"   ,   &  ! spgu
329            &          jpi, jpj, nh_U, 1  , 1, 1  , - 99, 32, clop, zsto, zout )
330#endif
331
332         CALL histend( nid_U )
333
334         !                                                                                      !!! nid_V : 3D
335         CALL histdef( nid_V, "vomecrty", "Meridional Current"                 , "m/s"    ,   &  ! vn
336            &          jpi, jpj, nh_V, ipk, 1, ipk, nz_V, 32, clop, zsto, zout )
337#if defined key_diaeiv
338         CALL histdef( nid_V, "vomeeivv", "Meridional EIV Current"             , "m/s"    ,   &  ! v_eiv
339            &          jpi, jpj, nh_V, ipk, 1, ipk, nz_V, 32, clop, zsto, zout )
340#endif
341         !                                                                                      !!! nid_V : 2D
342         CALL histdef( nid_V, "sometauy", "Wind Stress along j-axis"           , "N/m2"   ,   &  ! tauy
343            &          jpi, jpj, nh_V, 1  , 1, 1  , - 99, 32, clop, zsto, zout )
344#if ! defined key_dynspg_fsc
345         CALL histdef( nid_V, "somespgy", "Meridional Surface Pressure Grad."  , "N/kg"   ,   &  ! spgv
346            &          jpi, jpj, nh_V, 1  , 1, 1  , - 99, 32, clop, zsto, zout )
347#endif
348
349         CALL histend( nid_V )
350
351         !                                                                                      !!! nid_W : 3D
352         CALL histdef( nid_W, "vovecrtz", "Vertical Velocity"                  , "m/s"    ,   &  ! wn
353            &          jpi, jpj, nh_W, ipk, 1, ipk, nz_W, 32, clop, zsto, zout )
354#if defined key_diaeiv
355         CALL histdef( nid_W, "voveeivw", "Vertical EIV Velocity"              , "m/s"    ,   &  ! w_eiv
356            &          jpi, jpj, nh_W, ipk, 1, ipk, nz_W, 32, clop, zsto, zout )
357#endif
358         CALL histdef( nid_W, "votkeavt", "Vertical Eddy Diffusivity"          , "m2/s"   ,   &  ! avt
359            &          jpi, jpj, nh_W, ipk, 1, ipk, nz_W, 32, clop, zsto, zout )
360         IF( lk_zdfddm ) THEN
361            CALL histdef( nid_W,"voddmavs","Salt Vertical Eddy Diffusivity"    , "m2/s"   ,   &  ! avs
362               &          jpi, jpj, nh_W, ipk, 1, ipk, nz_W, 32, clop, zsto, zout )
363         ENDIF
364         !                                                                                      !!! nid_W : 2D
365#if defined key_traldf_c2d
366         CALL histdef( nid_W, "soleahtw", "lateral eddy diffusivity"           , "m2/s"   ,   &  ! ahtw
367            &          jpi, jpj, nh_W, 1  , 1, 1  , - 99, 32, clop, zsto, zout )
368# if defined key_traldf_eiv 
369            CALL histdef( nid_W, "soleaeiw", "eddy induced vel. coeff. at w-point", "m2/s",   &  ! aeiw
370               &       jpi, jpj, nh_W, 1  , 1, 1  , - 99, 32, clop, zsto, zout )
371# endif
372#endif
373
374         CALL histend( nid_W )
375
376         IF(lwp) WRITE(numout,*)
377         IF(lwp) WRITE(numout,*) 'End of NetCDF Initialization'
378         IF(ll_print) CALL FLUSH(numout )
379
380      ENDIF
381
382      ! 2. Start writing data
383      ! ---------------------
384
385      ! ndex(1) est utilise ssi l'avant dernier argument est diffferent de
386      ! la taille du tableau en sortie. Dans ce cas , l'avant dernier argument
387      ! donne le nombre d'elements, et ndex la liste des indices a sortir
388
389      IF( lwp .AND. MOD( kt, nwrite ) == 0 ) THEN
390         WRITE(numout,*) 'dia_wri : write model outputs in NetCDF files at ', kt, 'time-step'
391         WRITE(numout,*) '~~~~~~ '
392      ENDIF
393
394      ! Write fields on T grid
395      CALL histwrite( nid_T, "votemper", it, tn            , ndim_T , ndex_T  )   ! temperature
396      CALL histwrite( nid_T, "vosaline", it, sn            , ndim_T , ndex_T  )   ! salinity
397      CALL histwrite( nid_T, "sosstsst", it, tn(:,:,1)     , ndim_hT, ndex_hT )   ! sea surface temperature
398      CALL histwrite( nid_T, "sosaline", it, sn(:,:,1)     , ndim_hT, ndex_hT )   ! sea surface salinity
399#if defined key_dynspg_fsc
400      CALL histwrite( nid_T, "sossheig", it, sshn          , ndim_hT, ndex_hT )   ! sea surface height
401#else
402      CALL histwrite( nid_T, "sobarstf", it, bsfn          , ndim_hT, ndex_hT )   ! barotropic streamfunction
403#endif
404#if defined key_dynspg_fsc && defined key_ice_lim
405      CALL histwrite( nid_T, "iowaflup", it, fsalt(:,:)    , ndim_hT, ndex_hT )   ! ice=>ocean water flux
406      CALL histwrite( nid_T, "sowaflep", it, fmass(:,:)    , ndim_hT, ndex_hT )   ! atmos=>ocean water flux
407#endif
408      CALL histwrite( nid_T, "sowaflup", it, emp           , ndim_hT, ndex_hT )   ! upward water flux
409      CALL histwrite( nid_T, "sorunoff", it, runoff        , ndim_hT, ndex_hT )   ! runoff
410      CALL histwrite( nid_T, "sowaflcd", it, emps          , ndim_hT, ndex_hT )   ! c/d water flux
411      zw2d(:,:) = emps(:,:) * sn(:,:,1) * tmask(:,:,1)
412      CALL histwrite( nid_T, "sosalflx", it, zw2d          , ndim_hT, ndex_hT )   ! c/d salt flux
413      CALL histwrite( nid_T, "sohefldo", it, qt            , ndim_hT, ndex_hT )   ! total heat flux
414      CALL histwrite( nid_T, "soshfldo", it, qsr           , ndim_hT, ndex_hT )   ! solar heat flux
415      CALL histwrite( nid_T, "somxl010", it, hmlp          , ndim_hT, ndex_hT )   ! mixed layer depth
416      CALL histwrite( nid_T, "somixhgt", it, hmld          , ndim_hT, ndex_hT )   ! turbocline depth
417      CALL histwrite( nid_T, "soicecov", it, freeze        , ndim_hT, ndex_hT )   ! ice cover
418#if ! defined key_coupled
419      CALL histwrite( nid_T, "sohefldp", it, qrp           , ndim_hT, ndex_hT )   ! heat flux damping
420      CALL histwrite( nid_T, "sowafldp", it, erp           , ndim_hT, ndex_hT )   ! freshwater flux damping
421      zw2d(:,:) = erp(:,:) * sn(:,:,1) * tmask(:,:,1)
422      CALL histwrite( nid_T, "sosafldp", it, zw2d          , ndim_hT, ndex_hT )   ! salt flux damping
423#endif
424#if ( defined key_coupled && ! defined key_ice_lim )
425      CALL histwrite( nid_T, "sohefldp", it, qrp           , ndim_hT, ndex_hT )   ! heat flux damping
426      CALL histwrite( nid_T, "sowafldp", it, erp           , ndim_hT, ndex_hT )   ! freshwater flux damping
427         zw2d(:,:) = erp(:,:) * sn(:,:,1) * tmask(:,:,1)
428      CALL histwrite( nid_T, "sosafldp", it, zw2d          , ndim_hT, ndex_hT )   ! salt flux damping
429#endif
430#if defined key_diaspr
431      CALL histwrite( nid_T, "sosurfps", it, gps           , ndim_hT, ndex_hT )   ! surface pressure
432#endif
433         zw2d(:,:) = FLOAT( nmln(:,:) ) * tmask(:,:,1)
434      CALL histwrite( nid_T, "sobowlin", it, zw2d          , ndim_hT, ndex_hT )   ! ???
435
436#if defined key_diahth
437      CALL histwrite( nid_T, "sothedep", it, hth           , ndim_hT, ndex_hT )   ! depth of the thermocline
438      CALL histwrite( nid_T, "so20chgt", it, hd20          , ndim_hT, ndex_hT )   ! depth of the 20 isotherm
439      CALL histwrite( nid_T, "so28chgt", it, hd28          , ndim_hT, ndex_hT )   ! depth of the 28 isotherm
440      CALL histwrite( nid_T, "sohtc300", it, htc3          , ndim_hT, ndex_hT )   ! first 300m heaat content
441#endif
442#if defined key_ice_lim &&  defined key_coupled 
443      CALL histwrite( nid_T, "soicetem", it, tn_ice        , ndim_hT, ndex_hT )   ! surf. ice temperature
444      CALL histwrite( nid_T, "soicealb", it, alb_ice       , ndim_hT, ndex_hT )   ! ice albedo
445#endif
446         ! Write fields on U grid
447      CALL histwrite( nid_U, "vozocrtx", it, un            , ndim_U , ndex_U )    ! i-current
448#if defined key_diaeiv
449      CALL histwrite( nid_U, "vozoeivu", it, u_eiv         , ndim_U , ndex_U )    ! i-eiv current
450#endif
451      CALL histwrite( nid_U, "sozotaux", it, taux          , ndim_hU, ndex_hU )   ! i-wind stress
452#if ! defined key_dynspg_fsc
453      CALL lbc_lnk( spgu, 'U', -1. )
454      CALL histwrite( nid_U, "sozospgx", it, spgu          , ndim_hU, ndex_hU )   ! i-surf. press. grad.
455#endif
456
457         ! Write fields on V grid
458      CALL histwrite( nid_V, "vomecrty", it, vn            , ndim_V , ndex_V  )   ! j-current
459#if defined key_diaeiv
460      CALL histwrite( nid_V, "vomeeivv", it, v_eiv         , ndim_V , ndex_V  )   ! j-eiv current
461#endif
462      CALL histwrite( nid_V, "sometauy", it, tauy          , ndim_hV, ndex_hV )   ! j-wind stress
463#if ! defined key_dynspg_fsc
464      CALL lbc_lnk( spgv, 'V', -1. )
465      CALL histwrite( nid_V, "somespgy", it, spgv          , ndim_hV, ndex_hV )   ! j-surf. pressure grad.
466#endif
467
468         ! Write fields on W grid
469      CALL histwrite( nid_W, "vovecrtz", it, wn             , ndim_T, ndex_T )    ! vert. current
470#   if defined key_diaeiv
471      CALL histwrite( nid_W, "voveeivw", it, w_eiv          , ndim_T, ndex_T )    ! vert. eiv current
472#   endif
473      CALL histwrite( nid_W, "votkeavt", it, avt            , ndim_T, ndex_T )    ! T vert. eddy diff. coef.
474      IF( lk_zdfddm ) THEN
475         CALL histwrite( nid_W, "voddmavs", it, fsavs(:,:,:), ndim_T, ndex_T )    ! S vert. eddy diff. coef.
476      ENDIF
477#if defined key_traldf_c2d
478      CALL histwrite( nid_W, "soleahtw", it, ahtw          , ndim_hT, ndex_hT )   ! lateral eddy diff. coef.
479# if defined key_traldf_eiv
480         CALL histwrite( nid_W, "soleaeiw", it, aeiw       , ndim_hT, ndex_hT )   ! EIV coefficient at w-point
481# endif
482#endif
483
484      ! 3. Synchronise and close all files
485      ! ---------------------------------------
486      IF( MOD( kt, nwrite ) == 0 .OR. kindic < 0 ) THEN
487         CALL histsync( nid_T )
488         CALL histsync( nid_U )
489         CALL histsync( nid_V )
490         CALL histsync( nid_W )
491      ENDIF
492
493      !  Create an output files (output.abort.nc) if S < 0 or u > 20 m/s
494      IF( kindic < 0 )   CALL dia_wri_state( 'output.abort' )
495
496      IF( kt == nitend .OR. kindic < 0 ) THEN
497         CALL histclo( nid_T )
498         CALL histclo( nid_U )
499         CALL histclo( nid_V )
500         CALL histclo( nid_W )
501      ENDIF
502
503   END SUBROUTINE dia_wri
504
505
506   SUBROUTINE dia_wri_state( cdfile_name )
507      !!---------------------------------------------------------------------
508      !!                 ***  ROUTINE dia_wri_state  ***
509      !!       
510      !! ** Purpose :   create a NetCDF file named cdfile_name which contains
511      !!      the instantaneous ocean state and forcing fields.
512      !!        Used to find errors in the initial state or save the last
513      !!      ocean state in case of abnormal end of a simulation
514      !!
515      !! ** Method  :   NetCDF files using ioipsl
516      !!      File 'output.init.nc'  is created if ninist = 1 (namelist)
517      !!      File 'output.abort.nc' is created in case of abnormal job end
518      !!
519      !! History :
520      !!   8.2  !  00-06  (M. Imbard)  Original code (diabort.F)
521      !!   8.5  !  02-06  (A.Bozec, E. Durand)  Original code (diainit.F)
522      !!   9.0  !  02-12  (G. Madec)  merge of diabort and diainit, F90
523      !!----------------------------------------------------------------------
524      !! * Modules used
525      USE ioipsl
526
527      !! * Arguments
528      CHARACTER (len=* ), INTENT( in ) ::   &
529         cdfile_name      ! name of the file created
530
531      !! * Local declarations
532      CHARACTER (len=40) :: clop
533      INTEGER  ::   &
534         id_i , nz_i, nh_i       
535      INTEGER, DIMENSION(1) ::   &
536         idex             ! temprary workspace
537      REAL(wp) ::   &
538         zsto, zout, zmax,   &
539         zjulian, zdt
540      !!----------------------------------------------------------------------
541
542      IF(lwp) WRITE(numout,*)
543      IF(lwp) WRITE(numout,*) 'dia_wri_state : single instantaneous ocean state'
544      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~~   and forcing fields file created '
545      IF(lwp) WRITE(numout,*) '                and named :', cdfile_name, '.nc'
546     
547      ! 0. Initialisation
548      ! -----------------
549     
550      ! Define frequency of output and means
551      zdt  = rdt
552      zsto = rdt
553      clop = "inst(x)"           ! no use of the mask value (require less cpu time)
554      zout = rdt
555      zmax = ( nitend - nit000 + 1 ) * zdt
556
557      ! 1. Define NETCDF files and fields at beginning of first time step
558      ! -----------------------------------------------------------------
559
560      ! Compute julian date from starting date of the run
561      CALL ymds2ju( nyear, nmonth, nday, 0.e0, zjulian )         ! time axis
562      CALL histbeg( cdfile_name, jpi, glamt, jpj, gphit,   &
563          1, jpi, 1, jpj, 0, zjulian, zdt, nh_i, id_i )       ! Horizontal grid : glamt and gphit
564      CALL histvert( id_i, "deptht", "Vertical T levels",   &    ! Vertical grid : gdept
565          "m", jpk, gdept, nz_i)
566
567      ! Declare all the output fields as NetCDF variables
568
569      CALL histdef( id_i, "vosaline", "Salinity"              , "PSU"    ,   &   ! salinity
570         &          jpi, jpj, nh_i, jpk, 1, jpk, nz_i, 32, clop, zsto, zout )
571      CALL histdef( id_i, "votemper", "Temperature"           , "C"      ,   &   ! temperature
572         &          jpi, jpj, nh_i, jpk, 1, jpk, nz_i, 32, clop, zsto, zout )
573      CALL histdef( id_i, "vozocrtx", "Zonal Current"         , "m/s"    ,   &   ! zonal current
574         &          jpi, jpj, nh_i, jpk, 1, jpk, nz_i, 32, clop, zsto, zout )
575      CALL histdef( id_i, "vomecrty", "Meridional Current"    , "m/s"    ,   &   ! meridonal current
576         &          jpi, jpj, nh_i, jpk, 1, jpk, nz_i, 32, clop, zsto, zout ) 
577      CALL histdef( id_i, "vovecrtz", "Vertical Velocity"     , "m/s"    ,   &   ! vertical current
578         &          jpi, jpj, nh_i, jpk, 1, jpk, nz_i, 32, clop, zsto, zout ) 
579      CALL histdef( id_i, "sowaflup", "Net Upward Water Flux" , "Kg/m2/S",   &   ! net freshwater
580         &          jpi, jpj, nh_i, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
581      CALL histdef( id_i, "sohefldo", "Net Downward Heat Flux", "W/m2"   ,   &   ! net heat flux
582         &          jpi, jpj, nh_i, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
583      CALL histdef( id_i, "soshfldo", "Shortwave Radiation"   , "W/m2"   ,   &   ! solar flux
584         &          jpi, jpj, nh_i, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
585      CALL histdef( id_i, "soicecov", "Ice fraction"          , "[0,1]"  ,   &   ! freeze
586         &          jpi, jpj, nh_i, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
587      CALL histdef( id_i, "sozotaux", "Zonal Wind Stress"     , "N/m2"   ,   &   ! i-wind stress
588         &          jpi, jpj, nh_i, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
589      CALL histdef( id_i, "sometauy", "Meridional Wind Stress", "N/m2"   ,   &   ! j-wind stress
590         &          jpi, jpj, nh_i, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
591
592      CALL histend( id_i )
593
594      ! 2. Start writing data
595      ! ---------------------
596      ! idex(1) est utilise ssi l'avant dernier argument est diffferent de
597      ! la taille du tableau en sortie. Dans ce cas , l'avant dernier argument
598      ! donne le nombre d'elements, et idex la liste des indices a sortir
599      idex(1) = 1   ! init to avoid compil warning
600     
601      ! Write all fields on T grid
602      CALL histwrite( id_i, "votemper", 1, tn    , jpi*jpj*jpk, idex )    ! now temperature
603      CALL histwrite( id_i, "vosaline", 1, sn    , jpi*jpj*jpk, idex )    ! now salinity
604      CALL histwrite( id_i, "vozocrtx", 1, un    , jpi*jpj*jpk, idex )    ! now i-velocity
605      CALL histwrite( id_i, "vomecrty", 1, vn    , jpi*jpj*jpk, idex )    ! now j-velocity
606      CALL histwrite( id_i, "vovecrtz", 1, wn    , jpi*jpj*jpk, idex )    ! now k-velocity
607      CALL histwrite( id_i, "sowaflup", 1, emp   , jpi*jpj    , idex )    ! freshwater budget
608      CALL histwrite( id_i, "sohefldo", 1, qt    , jpi*jpj    , idex )    ! total heat flux
609      CALL histwrite( id_i, "soshfldo", 1, qsr   , jpi*jpj    , idex )    ! total heat flux
610      CALL histwrite( id_i, "soicecov", 1, freeze, jpi*jpj    , idex )    ! ice cover
611      CALL histwrite( id_i, "sozotaux", 1, taux  , jpi*jpj    , idex )    ! i-wind stress
612      CALL histwrite( id_i, "sometauy", 1, tauy  , jpi*jpj    , idex )    ! j-wind stress
613
614      ! 3. Close the file
615      ! -----------------
616      CALL histclo( id_i )
617
618   END SUBROUTINE dia_wri_state
619 
620#endif
621   !!======================================================================
622END MODULE diawri
Note: See TracBrowser for help on using the repository browser.