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

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

CT : UPDATE151 : New trends organization

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