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.
diawri1d.F90 in tags/nemo_v1_01/NEMO/C1D_SRC – NEMO

source: tags/nemo_v1_01/NEMO/C1D_SRC/diawri1d.F90 @ 4294

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

nemo_v1_update_001 : Add the 1D configuration possibility

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 23.7 KB
Line 
1MODULE diawri1d
2   !!======================================================================
3   !!                     ***  MODULE  diawri1d  ***
4   !! Ocean diagnostics :  write ocean output files
5   !!=====================================================================
6#if defined key_cfg_1d
7   !!----------------------------------------------------------------------
8   !!   'key_cfg_1d'               1D Configuration
9   !!---------------------------------------------------------------------- 
10   !!----------------------------------------------------------------------
11   !! * Modules used
12   USE oce             ! ocean dynamics and tracers
13   USE dom_oce         ! ocean space and time domain
14   USE zdf_oce         ! ocean vertical physics
15   USE zdftke          ! TKE vertical mixing
16   USE sol_oce         ! solver variables
17   USE ice_oce         ! ice variables
18   USE phycst          ! physical constants
19   USE ocfzpt          ! ???
20   USE ocesbc          ! surface thermohaline fluxes
21   USE taumod          ! surface stress
22   USE flxrnf          ! ???
23   USE zdfmxl          ! mixed layer
24   USE daymod          ! calendar
25   USE dianam          ! build name of file (routine)
26   USE diawri
27   USE zdfddm          ! vertical  physics: double diffusion
28   USE diahth          ! thermocline diagnostics
29   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
30   USE in_out_manager  ! I/O manager
31
32   IMPLICIT NONE
33   PRIVATE
34
35   !! * Accessibility
36   PUBLIC dia_wri_1d                 ! routines called by step.F90
37   !! * Module variables
38   INTEGER ::   &
39      nid_T, nz_T, nh_T, ndim_T, ndim_hT,      &   ! grid_T file
40      ndex(1)                                      ! ???
41   INTEGER, DIMENSION(jpi*jpj) ::   &
42      ndex_hT
43   INTEGER, DIMENSION(jpi*jpj*jpk) ::   &
44      ndex_T
45
46   !! * Substitutions
47#  include "zdfddm_substitute.h90"
48   !!----------------------------------------------------------------------
49   !!   OPA 9.0 , LODYC-IPSL  (2003)
50   !!----------------------------------------------------------------------
51
52CONTAINS
53   !!----------------------------------------------------------------------
54   !!   Default option                                   NetCDF output file
55   !!----------------------------------------------------------------------
56   !!   dia_wri_1d       : create the standart NetCDF output files
57   !!   dia_wri_state_1d : create an output NetCDF file for a single
58   !!                      instantaeous ocean state and forcing fields
59   !!----------------------------------------------------------------------
60
61   SUBROUTINE dia_wri_1d( kt, kindic )
62      !!---------------------------------------------------------------------
63      !!                  ***  ROUTINE dia_wri_1d  ***
64      !!                   
65      !! ** Purpose :   Standard output of opa: dynamics and tracer fields
66      !!      NETCDF format is used by default
67      !!
68      !! ** Method  :   At the beginning of the first time step (nit000),
69      !!      define all the NETCDF files and fields
70      !!      At each time step call histdef to compute the mean if ncessary
71      !!      Each nwrite time step, output the instantaneous or mean fields
72      !!      IF kindic <0, output of fields before the model interruption.
73      !!      IF kindic =0, time step loop
74      !!      IF kindic >0, output of fields before the time step loop
75      !!
76      !! History :
77      !!        !  91-03  (M.-A. Foujols)  Original code
78      !!        !  91-11  (G. Madec)
79      !!        !  92-06  (M. Imbard)  correction restart file
80      !!        !  92-07  (M. Imbard)  split into diawri and rstwri
81      !!        !  93-03  (M. Imbard)  suppress writibm
82      !!        !  98-01  (C. Levy)  NETCDF format using ioipsl INTERFACE
83      !!        !  99-02  (E. Guilyardi)  name of netCDF files + variables
84      !!   8.5  !  02-09  (G. Madec)  F90: Free form and module
85      !!   9.0  !  04-10  (C. Ethe)   1D Configuration
86      !!----------------------------------------------------------------------
87      !! * Modules used
88      USE ioipsl
89
90      !! * Arguments
91      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index
92      INTEGER, INTENT( in ) ::   kindic  !
93
94      !! * Local declarations
95      LOGICAL ::   ll_print = .FALSE.    ! =T print and flush numout
96      CHARACTER (len=40) ::           &
97         clhstnam, clop, clmx            ! temporary names
98      INTEGER ::   inum = 11             ! temporary logical unit
99      INTEGER ::   &
100         ji, jj, ik                      ! dummy loop indices
101      INTEGER ::   &
102         iimi, iima, ipk, it,         &  ! temporary integers
103         ijmi, ijma                      !    "          "
104      REAL(wp) ::   &
105         zsto, zout, zmax,            &  ! temporary scalars
106         zjulian, zdt                    !    "         "
107      REAL(wp), DIMENSION(jpi,jpj) :: &
108         zw2d                            ! temporary workspace
109      !!----------------------------------------------------------------------
110     
111      ! 0. Initialisation
112      ! -----------------
113     
114      ! local variable for debugging
115      ll_print = .FALSE.
116      ll_print = ll_print .AND. lwp
117
118      ! Define frequency of output and means
119      zdt = rdt
120      IF( nacc == 1 ) zdt = rdtmin
121#if defined key_diainstant
122      zsto = nwrite * zdt
123      clop = "inst(x)"           ! no use of the mask value (require less cpu time)
124      !!! clop="inst(only(x))"   ! put 1.e+20 on land (very expensive!!)
125#else
126      zsto=zdt
127      clop="ave(x)"              ! no use of the mask value (require less cpu time)
128      !!! clop="ave(only(x))"    ! put 1.e+20 on land (very expensive!!)
129#endif
130      zout = nwrite * zdt
131      zmax = ( nitend - nit000 + 1 ) * zdt
132
133      ! Define indices of the horizontal output zoom and vertical limit storage
134      iimi = 1      ;      iima = jpi
135      ijmi = 1      ;      ijma = jpj
136      ipk = jpk
137
138      ! define time axis
139      it = kt - nit000 + 1
140
141
142      ! 1. Define NETCDF files and fields at beginning of first time step
143      ! -----------------------------------------------------------------
144
145      IF(ll_print) WRITE(numout,*) 'dia_wri_1d kt = ', kt, ' kindic ', kindic
146
147      IF( kt == nit000 ) THEN
148
149         ! Define the NETCDF files (one per grid)
150         
151         ! Compute julian date from starting date of the run
152         CALL ymds2ju( nyear, nmonth, nday, 0.e0, zjulian )
153         IF(lwp)WRITE(numout,*)
154         IF(lwp)WRITE(numout,*) 'Date 0 used :', nit000, ' YEAR ', nyear,   &
155            &                    ' MONTH ', nmonth, ' DAY ', nday, 'Julian day : ', zjulian
156         IF(lwp)WRITE(numout,*) ' indexes of zoom = ', iimi, iima, ijmi, ijma,   &
157                                 ' limit storage in depth = ', ipk
158
159         ! WRITE root name in date.file for use by postpro
160         CALL dia_nam( clhstnam, nwrite,' ' )
161         CALL ctlopn( inum, 'date.file', 'UNKNOWN', 'FORMATTED', 'SEQUENTIAL', 1, numout, lwp, 1 )
162         WRITE(inum,*) clhstnam
163         CLOSE(inum)
164         
165         ! Define the T grid FILE ( nid_T )
166         
167         CALL dia_nam( clhstnam, nwrite, 'grid_T' )
168         IF(lwp) WRITE(numout,*) " Name of NETCDF file ", clhstnam    ! filename
169         CALL histbeg( clhstnam, jpi, glamt, jpj, gphit,           &  ! Horizontal grid: glamt and gphit
170            &          iimi, iima-iimi+1, ijmi, ijma-ijmi+1,       &
171            &          0, zjulian, zdt, nh_T, nid_T )
172         CALL histvert( nid_T, "deptht", "Vertical T levels",      &  ! Vertical grid: gdept
173            &           "m", ipk, gdept, nz_T )
174         !                                                            ! Index of ocean points
175         CALL wheneq( jpi*jpj*ipk, tmask, 1, 1., ndex_T , ndim_T  )      ! volume
176         CALL wheneq( jpi*jpj    , tmask, 1, 1., ndex_hT, ndim_hT )      ! surface
177
178
179         ! Declare all the output fields as NETCDF variables
180
181         !                                                                                      !!! nid_T : 3D
182         CALL histdef( nid_T, "votemper", "Temperature"                        , "C"      ,   &  ! tn
183            &          jpi, jpj, nh_T, ipk, 1, ipk, nz_T, 32, clop, zsto, zout )
184         CALL histdef( nid_T, "vosaline", "Salinity"                           , "PSU"    ,   &  ! sn
185            &          jpi, jpj, nh_T, ipk, 1, ipk, nz_T, 32, clop, zsto, zout )
186         !                                                                                      !!! nid_T : 2D
187         CALL histdef( nid_T, "sosstsst", "Sea Surface temperature"            , "C"      ,   &  ! sst
188            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
189         CALL histdef( nid_T, "sosaline", "Sea Surface Salinity"               , "PSU"    ,   &  ! sss
190            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
191
192#if defined key_dynspg_fsc && defined key_ice_lim
193         ! sowaflup = sowaflep + sorunoff + sowafldp + a term associated to
194         !    internal damping to Levitus that can be diagnosed from others
195         ! sowaflcd = sowaflep + sorunoff + sowafldp + iowaflup
196         CALL histdef( nid_T, "iowaflup", "Ice=>ocean net freshwater"          , "kg/m2/s",   &  ! fsalt
197            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
198         CALL histdef( nid_T, "sowaflep", "atmos=>ocean net freshwater"        , "kg/m2/s",   &  ! fmass
199            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
200#endif
201         CALL histdef( nid_T, "sowaflup", "Net Upward Water Flux"              , "Kg/m2/s",   &  ! emp
202            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
203         CALL histdef( nid_T, "sorunoff", "Runoffs"                            , "Kg/m2/s",   &  ! runoffs
204            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
205         CALL histdef( nid_T, "sowaflcd", "concentration/dilution water flux"  , "kg/m2/s",   &  ! emps
206            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
207         CALL histdef( nid_T, "sosalflx", "Surface Salt Flux"                  , "Kg/m2/s",   &  ! emps * sn
208            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
209         CALL histdef( nid_T, "sohefldo", "Net Downward Heat Flux"             , "W/m2"   ,   &  ! qt
210            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
211         CALL histdef( nid_T, "soshfldo", "Shortwave Radiation"                , "W/m2"   ,   &  ! qsr
212            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
213         CALL histdef( nid_T, "somxl010", "Mixed Layer Depth 0.01"             , "m"      ,   &  ! hmlp
214            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
215         CALL histdef( nid_T, "somxlavt", "AVT : bottom of the mixed layer    ", "m"      ,   &  ! avt_mxl
216            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
217         CALL histdef( nid_T, "somixhgt", "Turbocline Depth"                   , "m"      ,   &  ! hmld
218            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
219         CALL histdef( nid_T, "soicecov", "Ice Cover"                          , "[0,1]"  ,   &  ! freeze
220            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
221#if ! defined key_coupled
222         CALL histdef( nid_T, "sohefldp", "Surface Heat Flux: Damping"         , "W/m2"   ,   &  ! qrp
223            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
224         CALL histdef( nid_T, "sowafldp", "Surface Water Flux: Damping"        , "Kg/m2/s",   &  ! erp
225            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
226         CALL histdef( nid_T, "sosafldp", "Surface salt flux: damping"         , "Kg/m2/s",   &  ! erp * sn
227            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
228#endif
229
230#if ( defined key_coupled && ! defined key_ice_lim )
231         CALL histdef( nid_T, "sohefldp", "Surface Heat Flux: Damping"         , "W/m2"   ,   &  ! qrp
232            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
233         CALL histdef( nid_T, "sowafldp", "Surface Water Flux: Damping"        , "Kg/m2/s",   &  ! erp
234            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
235         CALL histdef( nid_T, "sosafldp", "Surface salt flux: Damping"         , "Kg/m2/s",   &  ! erp * sn
236            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
237#endif
238         clmx ="l_max(only(x))"    ! max index on a period
239         CALL histdef( nid_T, "sobowlin", "Bowl Index"                         , "W-point",   &  ! bowl INDEX
240            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clmx, zsto, zout )
241#if defined key_diahth
242         CALL histdef( nid_T, "sothedep", "Thermocline Depth"                  , "m"      ,   & ! hth
243            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
244         CALL histdef( nid_T, "so20chgt", "Depth of 20C isotherm"              , "m"      ,   & ! hd20
245            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
246         CALL histdef( nid_T, "so28chgt", "Depth of 28C isotherm"              , "m"      ,   & ! hd28
247            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
248         CALL histdef( nid_T, "sohtc300", "Heat content 300 m"                 , "W"      ,   & ! htc3
249            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
250#endif
251
252#if defined key_ice_lim && defined key_coupled
253         CALL histdef( nid_T,"soicetem" , "Ice Surface Temperature"            , "K"      ,   &  ! tn_ice
254            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
255         CALL histdef( nid_T,"soicealb" , "Ice Albedo"                         , "[0,1]"  ,   &  ! alb_ice
256            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout )
257#endif 
258
259         !                                                                                      !!! nid_U : 3D
260         CALL histdef( nid_T, "vozocrtx", "Zonal Current"                      , "m/s"    ,   &  ! un
261            &          jpi, jpj, nh_T, ipk, 1, ipk, nz_T, 32, clop, zsto, zout )
262#if defined key_diaeiv
263         CALL histdef( nid_T, "vozoeivu", "Zonal EIV Current"                  , "m/s"    ,   &  ! u_eiv
264            &          jpi, jpj, nh_T, ipk, 1, ipk, nz_T, 32, clop, zsto, zout )
265#endif
266         !                                                                                      !!! nid_U : 2D
267         CALL histdef( nid_T, "sozotaux", "Wind Stress along i-axis"           , "N/m2"   ,   &  ! taux
268            &          jpi, jpj, nh_T, 1  , 1, 1  , - 99, 32, clop, zsto, zout )
269
270         !                                                                                      !!! nid_V : 3D
271         CALL histdef( nid_T, "vomecrty", "Meridional Current"                 , "m/s"    ,   &  ! vn
272            &          jpi, jpj, nh_T, ipk, 1, ipk, nz_T, 32, clop, zsto, zout )
273#if defined key_diaeiv
274         CALL histdef( nid_T, "vomeeivv", "Meridional EIV Current"             , "m/s"    ,   &  ! v_eiv
275            &          jpi, jpj, nh_T, ipk, 1, ipk, nz_T, 32, clop, zsto, zout )
276#endif
277         !                                                                                      !!! nid_V : 2D
278         CALL histdef( nid_T, "sometauy", "Wind Stress along j-axis"           , "N/m2"   ,   &  ! tauy
279            &          jpi, jpj, nh_T, 1  , 1, 1  , - 99, 32, clop, zsto, zout )
280#if defined key_zdftke
281         !                                                                                      !!! nid_W : 3D
282         CALL histdef( nid_T, "votlsdis", " Dissipation Turbulent Lenght Scale", "m"      ,   &  ! e_dis
283            &          jpi, jpj, nh_T, ipk, 1, ipk, nz_T, 32, clop, zsto, zout )
284         !
285         CALL histdef( nid_T, "votlsmix", " Mixing Turbulent Lenght Scale"     , "m"      ,   &  ! e_mix
286            &          jpi, jpj, nh_T, ipk, 1, ipk, nz_T, 32, clop, zsto, zout )
287         !
288         CALL histdef( nid_T, "votlspdl", " Prandl Number",                      "-"       ,   &  ! e_pdl
289            &          jpi, jpj, nh_T, ipk, 1, ipk, nz_T, 32, clop, zsto, zout )
290         !
291         CALL histdef( nid_T, "votlsric", " Local Richardson Number",            "-"       ,   &  ! e_ric
292            &          jpi, jpj, nh_T, ipk, 1, ipk, nz_T, 32, clop, zsto, zout )
293         !
294         CALL histdef( nid_T, "votkeend", "TKE: Turbulent kinetic energy"       , "m2/s"   ,   &  ! TKE
295            &          jpi, jpj, nh_T, ipk, 1, ipk, nz_T, 32, clop, zsto, zout )
296#endif
297         !
298         CALL histdef( nid_T, "voeosbn2", "Brunt-Vaisala Frequency"             , "m2/s2"  ,   &  ! rn2
299            &          jpi, jpj, nh_T, ipk, 1, ipk, nz_T, 32, clop, zsto, zout )
300
301         CALL histdef( nid_T, "votkeavt", "Vertical Eddy Diffusivity"          , "m2/s"   ,   &  ! avt
302            &          jpi, jpj, nh_T, ipk, 1, ipk, nz_T, 32, clop, zsto, zout )
303
304
305         CALL histdef( nid_T, "votkeavm", "Vertical Eddy Viscosity",             "m2/s"   ,   &  ! avmu
306            &          jpi, jpj, nh_T, ipk, 1, ipk, nz_T, 32, clop, zsto, zout )
307         !
308
309         IF( lk_zdfddm ) THEN
310            CALL histdef( nid_T,"voddmavs","Salt Vertical Eddy Diffusivity"    , "m2/s"   ,   &  ! avs
311               &          jpi, jpj, nh_T, ipk, 1, ipk, nz_T, 32, clop, zsto, zout )
312         ENDIF
313
314         CALL histend( nid_T )
315
316         IF(lwp) WRITE(numout,*)
317         IF(lwp) WRITE(numout,*) 'End of NetCDF Initialization'
318         IF(ll_print) CALL FLUSH(numout )
319
320      ENDIF
321
322      ! 2. Start writing data
323      ! ---------------------
324
325      ! ndex(1) est utilise ssi l'avant dernier argument est diffferent de
326      ! la taille du tableau en sortie. Dans ce cas , l'avant dernier argument
327      ! donne le nombre d'elements, et ndex la liste des indices a sortir
328
329      IF( lwp .AND. MOD( kt, nwrite ) == 0 ) THEN
330         WRITE(numout,*) 'dia_wri : write model outputs in NetCDF files at ', kt, 'time-step'
331         WRITE(numout,*) '~~~~~~ '
332      ENDIF
333
334      ! Write fields on T grid
335      CALL histwrite( nid_T, "votemper", it, tn            , ndim_T , ndex_T  )   ! temperature
336      CALL histwrite( nid_T, "vosaline", it, sn            , ndim_T , ndex_T  )   ! salinity
337      CALL histwrite( nid_T, "sosstsst", it, tn(:,:,1)     , ndim_hT, ndex_hT )   ! sea surface temperature
338      CALL histwrite( nid_T, "sosaline", it, sn(:,:,1)     , ndim_hT, ndex_hT )   ! sea surface salinity
339#if defined key_dynspg_fsc && defined key_ice_lim
340      CALL histwrite( nid_T, "iowaflup", it, fsalt(:,:)    , ndim_hT, ndex_hT )   ! ice=>ocean water flux
341      CALL histwrite( nid_T, "sowaflep", it, fmass(:,:)    , ndim_hT, ndex_hT )   ! atmos=>ocean water flux
342#endif
343      CALL histwrite( nid_T, "sowaflup", it, emp           , ndim_hT, ndex_hT )   ! upward water flux
344      CALL histwrite( nid_T, "sorunoff", it, runoff        , ndim_hT, ndex_hT )   ! runoff
345      CALL histwrite( nid_T, "sowaflcd", it, emps          , ndim_hT, ndex_hT )   ! c/d water flux
346      zw2d(:,:) = emps(:,:) * sn(:,:,1) * tmask(:,:,1)
347      CALL histwrite( nid_T, "sosalflx", it, zw2d          , ndim_hT, ndex_hT )   ! c/d salt flux
348      CALL histwrite( nid_T, "sohefldo", it, qt            , ndim_hT, ndex_hT )   ! total heat flux
349      CALL histwrite( nid_T, "soshfldo", it, qsr           , ndim_hT, ndex_hT )   ! solar heat flux
350      CALL histwrite( nid_T, "somxl010", it, hmlp          , ndim_hT, ndex_hT )   ! mixed layer depth
351      ! store the vertical eddy diffusivity coef. at the bottom of the mixed layer
352      DO jj = 1, jpj
353         DO ji = 1, jpi
354            ik = nmln(ji,jj)
355            zw2d(ji,jj) = avt(ji,jj,ik) * tmask(ji,jj,1)
356         END DO
357      END DO
358      CALL histwrite( nid_T, "somxlavt", it, zw2d          , ndim_hT, ndex_hT )   ! Kz at bottom of mixed layer
359      CALL histwrite( nid_T, "somixhgt", it, hmld          , ndim_hT, ndex_hT )   ! turbocline depth
360      CALL histwrite( nid_T, "soicecov", it, freeze        , ndim_hT, ndex_hT )   ! ice cover
361#if ! defined key_coupled
362      CALL histwrite( nid_T, "sohefldp", it, qrp           , ndim_hT, ndex_hT )   ! heat flux damping
363      CALL histwrite( nid_T, "sowafldp", it, erp           , ndim_hT, ndex_hT )   ! freshwater flux damping
364      zw2d(:,:) = erp(:,:) * sn(:,:,1) * tmask(:,:,1)
365      CALL histwrite( nid_T, "sosafldp", it, zw2d          , ndim_hT, ndex_hT )   ! salt flux damping
366#endif
367#if ( defined key_coupled && ! defined key_ice_lim )
368      CALL histwrite( nid_T, "sohefldp", it, qrp           , ndim_hT, ndex_hT )   ! heat flux damping
369      CALL histwrite( nid_T, "sowafldp", it, erp           , ndim_hT, ndex_hT )   ! freshwater flux damping
370         zw2d(:,:) = erp(:,:) * sn(:,:,1) * tmask(:,:,1)
371      CALL histwrite( nid_T, "sosafldp", it, zw2d          , ndim_hT, ndex_hT )   ! salt flux damping
372#endif
373         zw2d(:,:) = FLOAT( nmln(:,:) ) * tmask(:,:,1)
374      CALL histwrite( nid_T, "sobowlin", it, zw2d          , ndim_hT, ndex_hT )   ! ???
375
376#if defined key_diahth
377      CALL histwrite( nid_T, "sothedep", it, hth           , ndim_hT, ndex_hT )   ! depth of the thermocline
378      CALL histwrite( nid_T, "so20chgt", it, hd20          , ndim_hT, ndex_hT )   ! depth of the 20 isotherm
379      CALL histwrite( nid_T, "so28chgt", it, hd28          , ndim_hT, ndex_hT )   ! depth of the 28 isotherm
380      CALL histwrite( nid_T, "sohtc300", it, htc3          , ndim_hT, ndex_hT )   ! first 300m heaat content
381#endif
382#if defined key_ice_lim &&  defined key_coupled 
383      CALL histwrite( nid_T, "soicetem", it, tn_ice        , ndim_hT, ndex_hT )   ! surf. ice temperature
384      CALL histwrite( nid_T, "soicealb", it, alb_ice       , ndim_hT, ndex_hT )   ! ice albedo
385#endif
386
387      CALL histwrite( nid_T, "vozocrtx", it, un            , ndim_T , ndex_T )    ! i-current
388      CALL histwrite( nid_T, "sozotaux", it, taux          , ndim_hT, ndex_hT )   ! i-wind stress
389      CALL histwrite( nid_T, "vomecrty", it, vn            , ndim_T , ndex_T  )   ! j-current
390      CALL histwrite( nid_T, "sometauy", it, tauy          , ndim_hT, ndex_hT )   ! j-wind stress
391#if defined key_zdftke
392      CALL histwrite( nid_T, "votlsdis", it, e_dis         , ndim_T , ndex_T )    ! Diss. Turb. lenght scale
393      CALL histwrite( nid_T, "votlsmix", it, e_mix         , ndim_T , ndex_T )    ! Mixing Turb. lenght scale
394      CALL histwrite( nid_T, "votlspdl", it, e_pdl         , ndim_T , ndex_T )    ! Prandl number
395      CALL histwrite( nid_T, "votlsric", it, e_ric         , ndim_T , ndex_T )    ! local Richardson number
396      CALL histwrite( nid_T, "votkeend", it, en            , ndim_T , ndex_T )    ! TKE
397#endif
398      CALL histwrite( nid_T, "voeosbn2", it, rn2           , ndim_T , ndex_T )    ! Brunt-Vaisala Frequency
399      CALL histwrite( nid_T, "votkeavt", it, avt           , ndim_T , ndex_T )    ! T vert. eddy diff. coef.
400      CALL histwrite( nid_T, "votkeavm", it, avmu          , ndim_T , ndex_T )    ! T vert. eddy visc. coef.
401      IF( lk_zdfddm ) THEN
402         CALL histwrite( nid_T, "voddmavs", it, fsavs(:,:,:), ndim_T, ndex_T )    ! S vert. eddy diff. coef.
403      ENDIF
404
405      ! 3. Synchronise and close all files
406      ! ---------------------------------------
407      IF( MOD( kt, nwrite ) == 0 .OR. kindic < 0 ) THEN
408         CALL histsync( nid_T )
409      ENDIF
410
411      !  Create an output files (output.abort.nc) if S < 0 or u > 20 m/s
412      IF( kindic < 0 )   CALL dia_wri_state( 'output.abort' )
413
414      IF( kt == nitend .OR. kindic < 0 ) THEN
415         CALL histclo( nid_T )
416      ENDIF
417
418   END SUBROUTINE dia_wri_1d
419#else
420   !!----------------------------------------------------------------------
421   !!   Default key                                     NO 1D Config
422   !!----------------------------------------------------------------------
423CONTAINS
424   SUBROUTINE dia_wri_1d ( kt, kindic )
425      WRITE(*,*) 'dia_wri_1d: You should not have seen this print! error?', kt, kindic
426   END SUBROUTINE dia_wri_1d
427#endif
428
429   !!======================================================================
430END MODULE diawri1d
Note: See TracBrowser for help on using the repository browser.