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

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

move daymod public variables in dom_oce, see ticket:590

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