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

Last change on this file since 1310 was 1310, checked in by smasson, 15 years ago

set origin of outputs calendar, continue changeset:1309, see ticket:335

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