1 | MODULE limwri |
---|
2 | !!====================================================================== |
---|
3 | !! *** MODULE limwri *** |
---|
4 | !! Ice diagnostics : write ice output files |
---|
5 | !!====================================================================== |
---|
6 | #if defined key_lim3 |
---|
7 | !!---------------------------------------------------------------------- |
---|
8 | !! 'key_lim3' LIM3 sea-ice model |
---|
9 | !!---------------------------------------------------------------------- |
---|
10 | !! lim_wri : write of the diagnostics variables in ouput file |
---|
11 | !! lim_wri_state : write for initial state or/and abandon |
---|
12 | !!---------------------------------------------------------------------- |
---|
13 | USE ioipsl |
---|
14 | USE dianam ! build name of file (routine) |
---|
15 | USE phycst |
---|
16 | USE dom_oce |
---|
17 | USE sbc_oce ! Surface boundary condition: ocean fields |
---|
18 | USE sbc_ice ! Surface boundary condition: ice fields |
---|
19 | USE dom_ice |
---|
20 | USE ice |
---|
21 | USE limvar |
---|
22 | USE in_out_manager |
---|
23 | USE lbclnk |
---|
24 | USE lib_mpp ! MPP library |
---|
25 | USE wrk_nemo ! work arrays |
---|
26 | USE iom |
---|
27 | USE timing ! Timing |
---|
28 | USE lib_fortran ! Fortran utilities |
---|
29 | |
---|
30 | IMPLICIT NONE |
---|
31 | PRIVATE |
---|
32 | |
---|
33 | PUBLIC lim_wri ! routine called by lim_step.F90 |
---|
34 | PUBLIC lim_wri_state ! called by dia_wri_state |
---|
35 | |
---|
36 | !!---------------------------------------------------------------------- |
---|
37 | !! NEMO/LIM3 4.0 , UCL - NEMO Consortium (2011) |
---|
38 | !! $Id$ |
---|
39 | !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) |
---|
40 | !!---------------------------------------------------------------------- |
---|
41 | CONTAINS |
---|
42 | |
---|
43 | #if defined key_dimgout |
---|
44 | # include "limwri_dimg.h90" |
---|
45 | #else |
---|
46 | |
---|
47 | SUBROUTINE lim_wri( kindic ) |
---|
48 | !!------------------------------------------------------------------- |
---|
49 | !! This routine computes the average of some variables and write it |
---|
50 | !! on the ouput files. |
---|
51 | !! ATTENTION cette routine n'est valable que si le pas de temps est |
---|
52 | !! egale a une fraction entiere de 1 jours. |
---|
53 | !! Diff 1-D 3-D : suppress common also included in etat |
---|
54 | !! suppress cmoymo 11-18 |
---|
55 | !! modif : 03/06/98 |
---|
56 | !!------------------------------------------------------------------- |
---|
57 | INTEGER, INTENT(in) :: kindic ! if kindic < 0 there has been an error somewhere |
---|
58 | ! |
---|
59 | INTEGER :: ji, jj, jk, jl ! dummy loop indices |
---|
60 | REAL(wp) :: z1_365 |
---|
61 | REAL(wp) :: ztmp |
---|
62 | REAL(wp), POINTER, DIMENSION(:,:,:) :: zoi, zei |
---|
63 | REAL(wp), POINTER, DIMENSION(:,:) :: z2d, z2da, z2db, zswi ! 2D workspace |
---|
64 | !!------------------------------------------------------------------- |
---|
65 | |
---|
66 | IF( nn_timing == 1 ) CALL timing_start('limwri') |
---|
67 | |
---|
68 | CALL wrk_alloc( jpi, jpj, jpl, zoi, zei ) |
---|
69 | CALL wrk_alloc( jpi, jpj , z2d, z2da, z2db, zswi ) |
---|
70 | |
---|
71 | !----------------------------- |
---|
72 | ! Mean category values |
---|
73 | !----------------------------- |
---|
74 | z1_365 = 1._wp / 365._wp |
---|
75 | |
---|
76 | CALL lim_var_icetm ! mean sea ice temperature |
---|
77 | |
---|
78 | CALL lim_var_bv ! brine volume |
---|
79 | |
---|
80 | DO jj = 1, jpj ! presence indicator of ice |
---|
81 | DO ji = 1, jpi |
---|
82 | zswi(ji,jj) = MAX( 0._wp , SIGN( 1._wp , at_i(ji,jj) - epsi06 ) ) |
---|
83 | END DO |
---|
84 | END DO |
---|
85 | ! |
---|
86 | ! |
---|
87 | ! |
---|
88 | IF ( iom_use( "icethic_cea" ) ) THEN ! mean ice thickness |
---|
89 | DO jj = 1, jpj |
---|
90 | DO ji = 1, jpi |
---|
91 | z2d(ji,jj) = vt_i(ji,jj) / MAX( at_i(ji,jj), epsi06 ) * zswi(ji,jj) |
---|
92 | END DO |
---|
93 | END DO |
---|
94 | CALL iom_put( "icethic_cea" , z2d ) |
---|
95 | ENDIF |
---|
96 | |
---|
97 | IF ( iom_use( "snowthic_cea" ) ) THEN ! snow thickness = mean snow thickness over the cell |
---|
98 | DO jj = 1, jpj |
---|
99 | DO ji = 1, jpi |
---|
100 | z2d(ji,jj) = vt_s(ji,jj) / MAX( at_i(ji,jj), epsi06 ) * zswi(ji,jj) |
---|
101 | END DO |
---|
102 | END DO |
---|
103 | CALL iom_put( "snowthic_cea" , z2d ) |
---|
104 | ENDIF |
---|
105 | ! |
---|
106 | IF ( iom_use( "uice_ipa" ) .OR. iom_use( "vice_ipa" ) .OR. iom_use( "icevel" ) ) THEN |
---|
107 | DO jj = 2 , jpjm1 |
---|
108 | DO ji = 2 , jpim1 |
---|
109 | z2da(ji,jj) = ( u_ice(ji,jj) * umask(ji,jj,1) + u_ice(ji-1,jj) * umask(ji-1,jj,1) ) * 0.5_wp |
---|
110 | z2db(ji,jj) = ( v_ice(ji,jj) * vmask(ji,jj,1) + v_ice(ji,jj-1) * vmask(ji,jj-1,1) ) * 0.5_wp |
---|
111 | END DO |
---|
112 | END DO |
---|
113 | CALL lbc_lnk( z2da, 'T', -1. ) |
---|
114 | CALL lbc_lnk( z2db, 'T', -1. ) |
---|
115 | CALL iom_put( "uice_ipa" , z2da ) ! ice velocity u component |
---|
116 | CALL iom_put( "vice_ipa" , z2db ) ! ice velocity v component |
---|
117 | DO jj = 1, jpj |
---|
118 | DO ji = 1, jpi |
---|
119 | z2d(ji,jj) = SQRT( z2da(ji,jj) * z2da(ji,jj) + z2db(ji,jj) * z2db(ji,jj) ) |
---|
120 | END DO |
---|
121 | END DO |
---|
122 | CALL iom_put( "icevel" , z2d ) ! ice velocity module |
---|
123 | ENDIF |
---|
124 | ! |
---|
125 | IF ( iom_use( "miceage" ) ) THEN |
---|
126 | z2d(:,:) = 0.e0 |
---|
127 | DO jl = 1, jpl |
---|
128 | DO jj = 1, jpj |
---|
129 | DO ji = 1, jpi |
---|
130 | rswitch = MAX( 0._wp , SIGN( 1._wp , at_i(ji,jj) - 0.1 ) ) |
---|
131 | z2d(ji,jj) = z2d(ji,jj) + rswitch * oa_i(ji,jj,jl) / MAX( at_i(ji,jj), 0.1 ) |
---|
132 | END DO |
---|
133 | END DO |
---|
134 | END DO |
---|
135 | CALL iom_put( "miceage" , z2d * z1_365 ) ! mean ice age |
---|
136 | ENDIF |
---|
137 | |
---|
138 | IF ( iom_use( "micet" ) ) THEN |
---|
139 | DO jj = 1, jpj |
---|
140 | DO ji = 1, jpi |
---|
141 | z2d(ji,jj) = ( tm_i(ji,jj) - rt0 ) * zswi(ji,jj) |
---|
142 | END DO |
---|
143 | END DO |
---|
144 | CALL iom_put( "micet" , z2d ) ! mean ice temperature |
---|
145 | ENDIF |
---|
146 | ! |
---|
147 | IF ( iom_use( "icest" ) ) THEN |
---|
148 | z2d(:,:) = 0.e0 |
---|
149 | DO jl = 1, jpl |
---|
150 | DO jj = 1, jpj |
---|
151 | DO ji = 1, jpi |
---|
152 | z2d(ji,jj) = z2d(ji,jj) + zswi(ji,jj) * ( t_su(ji,jj,jl) - rt0 ) * a_i(ji,jj,jl) / MAX( at_i(ji,jj) , epsi06 ) |
---|
153 | END DO |
---|
154 | END DO |
---|
155 | END DO |
---|
156 | CALL iom_put( "icest" , z2d ) ! ice surface temperature |
---|
157 | ENDIF |
---|
158 | |
---|
159 | IF ( iom_use( "icecolf" ) ) THEN |
---|
160 | DO jj = 1, jpj |
---|
161 | DO ji = 1, jpi |
---|
162 | rswitch = MAX( 0._wp , SIGN( 1._wp , at_i(ji,jj) ) ) |
---|
163 | z2d(ji,jj) = hicol(ji,jj) * rswitch |
---|
164 | END DO |
---|
165 | END DO |
---|
166 | CALL iom_put( "icecolf" , z2d ) ! frazil ice collection thickness |
---|
167 | ENDIF |
---|
168 | |
---|
169 | CALL iom_put( "isst" , sst_m ) ! sea surface temperature |
---|
170 | CALL iom_put( "isss" , sss_m ) ! sea surface salinity |
---|
171 | CALL iom_put( "iceconc" , at_i ) ! ice concentration |
---|
172 | CALL iom_put( "icevolu" , vt_i ) ! ice volume = mean ice thickness over the cell |
---|
173 | CALL iom_put( "icehc" , et_i ) ! ice total heat content |
---|
174 | CALL iom_put( "isnowhc" , et_s ) ! snow total heat content |
---|
175 | CALL iom_put( "ibrinv" , bv_i * 100._wp ) ! brine volume |
---|
176 | CALL iom_put( "utau_ice" , utau_ice ) ! wind stress over ice along i-axis at I-point |
---|
177 | CALL iom_put( "vtau_ice" , vtau_ice ) ! wind stress over ice along j-axis at I-point |
---|
178 | CALL iom_put( "snowpre" , sprecip * 86400. ) ! snow precipitation |
---|
179 | CALL iom_put( "micesalt" , smt_i ) ! mean ice salinity |
---|
180 | |
---|
181 | CALL iom_put( "icestr" , strength * 0.001 ) ! ice strength |
---|
182 | CALL iom_put( "idive" , divu_i * 1.0e8 ) ! divergence |
---|
183 | CALL iom_put( "ishear" , shear_i * 1.0e8 ) ! shear |
---|
184 | CALL iom_put( "snowvol" , vt_s ) ! snow volume |
---|
185 | |
---|
186 | CALL iom_put( "icetrp" , diag_trp_vi * rday ) ! ice volume transport |
---|
187 | CALL iom_put( "snwtrp" , diag_trp_vs * rday ) ! snw volume transport |
---|
188 | CALL iom_put( "saltrp" , diag_trp_smv * rday * rhoic ) ! salt content transport |
---|
189 | CALL iom_put( "deitrp" , diag_trp_ei ) ! advected ice enthalpy (W/m2) |
---|
190 | CALL iom_put( "destrp" , diag_trp_es ) ! advected snw enthalpy (W/m2) |
---|
191 | |
---|
192 | CALL iom_put( "sfxbog" , sfx_bog * rday ) ! salt flux from brines |
---|
193 | CALL iom_put( "sfxbom" , sfx_bom * rday ) ! salt flux from brines |
---|
194 | CALL iom_put( "sfxsum" , sfx_sum * rday ) ! salt flux from brines |
---|
195 | CALL iom_put( "sfxsni" , sfx_sni * rday ) ! salt flux from brines |
---|
196 | CALL iom_put( "sfxopw" , sfx_opw * rday ) ! salt flux from brines |
---|
197 | CALL iom_put( "sfxdyn" , sfx_dyn * rday ) ! salt flux from ridging rafting |
---|
198 | CALL iom_put( "sfxres" , sfx_res * rday ) ! salt flux from limupdate (resultant) |
---|
199 | CALL iom_put( "sfxbri" , sfx_bri * rday ) ! salt flux from brines |
---|
200 | CALL iom_put( "sfx" , sfx * rday ) ! total salt flux |
---|
201 | |
---|
202 | ztmp = rday / rhoic |
---|
203 | CALL iom_put( "vfxres" , wfx_res * ztmp ) ! daily prod./melting due to limupdate |
---|
204 | CALL iom_put( "vfxopw" , wfx_opw * ztmp ) ! daily lateral thermodynamic ice production |
---|
205 | CALL iom_put( "vfxsni" , wfx_sni * ztmp ) ! daily snowice ice production |
---|
206 | CALL iom_put( "vfxbog" , wfx_bog * ztmp ) ! daily bottom thermodynamic ice production |
---|
207 | CALL iom_put( "vfxdyn" , wfx_dyn * ztmp ) ! daily dynamic ice production (rid/raft) |
---|
208 | CALL iom_put( "vfxsum" , wfx_sum * ztmp ) ! surface melt |
---|
209 | CALL iom_put( "vfxbom" , wfx_bom * ztmp ) ! bottom melt |
---|
210 | CALL iom_put( "vfxice" , wfx_ice * ztmp ) ! total ice growth/melt |
---|
211 | CALL iom_put( "vfxsnw" , wfx_snw * ztmp ) ! total snw growth/melt |
---|
212 | CALL iom_put( "vfxsub" , wfx_sub * ztmp ) ! sublimation (snow) |
---|
213 | CALL iom_put( "vfxspr" , wfx_spr * ztmp ) ! precip (snow) |
---|
214 | |
---|
215 | CALL iom_put( "afxtot" , afx_tot * rday ) ! concentration tendency (total) |
---|
216 | CALL iom_put( "afxdyn" , afx_dyn * rday ) ! concentration tendency (dynamics) |
---|
217 | CALL iom_put( "afxthd" , afx_thd * rday ) ! concentration tendency (thermo) |
---|
218 | |
---|
219 | CALL iom_put ('hfxthd' , hfx_thd(:,:) ) ! |
---|
220 | CALL iom_put ('hfxdyn' , hfx_dyn(:,:) ) ! |
---|
221 | CALL iom_put ('hfxres' , hfx_res(:,:) ) ! |
---|
222 | CALL iom_put ('hfxout' , hfx_out(:,:) ) ! |
---|
223 | CALL iom_put ('hfxin' , hfx_in(:,:) ) ! |
---|
224 | CALL iom_put ('hfxsnw' , hfx_snw(:,:) ) ! |
---|
225 | CALL iom_put ('hfxsub' , hfx_sub(:,:) ) ! |
---|
226 | CALL iom_put ('hfxerr' , hfx_err(:,:) ) ! |
---|
227 | CALL iom_put ('hfxerr_rem' , hfx_err_rem(:,:) ) ! |
---|
228 | |
---|
229 | CALL iom_put ('hfxsum' , hfx_sum(:,:) ) ! |
---|
230 | CALL iom_put ('hfxbom' , hfx_bom(:,:) ) ! |
---|
231 | CALL iom_put ('hfxbog' , hfx_bog(:,:) ) ! |
---|
232 | CALL iom_put ('hfxdif' , hfx_dif(:,:) ) ! |
---|
233 | CALL iom_put ('hfxopw' , hfx_opw(:,:) ) ! |
---|
234 | CALL iom_put ('hfxtur' , fhtur(:,:) * SUM(a_i_b(:,:,:), dim=3) ) ! turbulent heat flux at ice base |
---|
235 | CALL iom_put ('hfxdhc' , diag_heat(:,:) ) ! Heat content variation in snow and ice |
---|
236 | CALL iom_put ('hfxspr' , hfx_spr(:,:) ) ! Heat content of snow precip |
---|
237 | |
---|
238 | !-------------------------------- |
---|
239 | ! Output values for each category |
---|
240 | !-------------------------------- |
---|
241 | CALL iom_put( "iceconc_cat" , a_i ) ! area for categories |
---|
242 | CALL iom_put( "icethic_cat" , ht_i ) ! thickness for categories |
---|
243 | CALL iom_put( "snowthic_cat" , ht_s ) ! snow depth for categories |
---|
244 | CALL iom_put( "salinity_cat" , sm_i ) ! salinity for categories |
---|
245 | |
---|
246 | ! Compute ice age |
---|
247 | IF ( iom_use( "iceage_cat" ) ) THEN |
---|
248 | DO jl = 1, jpl |
---|
249 | DO jj = 1, jpj |
---|
250 | DO ji = 1, jpi |
---|
251 | rswitch = MAX( 0._wp , SIGN( 1._wp , at_i(ji,jj) - 0.1 ) ) |
---|
252 | rswitch = rswitch * MAX( 0._wp , SIGN( 1._wp , a_i(ji,jj,jl) - 0.1 ) ) |
---|
253 | zoi(ji,jj,jl) = oa_i(ji,jj,jl) / MAX( a_i(ji,jj,jl) , 0.1 ) * rswitch |
---|
254 | END DO |
---|
255 | END DO |
---|
256 | END DO |
---|
257 | CALL iom_put( "iceage_cat" , zoi * z1_365 ) ! ice age for categories |
---|
258 | ENDIF |
---|
259 | |
---|
260 | ! Compute brine volume |
---|
261 | IF ( iom_use( "brinevol_cat" ) ) THEN |
---|
262 | zei(:,:,:) = 0._wp |
---|
263 | DO jl = 1, jpl |
---|
264 | DO jk = 1, nlay_i |
---|
265 | DO jj = 1, jpj |
---|
266 | DO ji = 1, jpi |
---|
267 | rswitch = MAX( 0._wp , SIGN( 1._wp , a_i(ji,jj,jl) - epsi06 ) ) |
---|
268 | zei(ji,jj,jl) = zei(ji,jj,jl) + 100.0 * & |
---|
269 | ( - tmut * s_i(ji,jj,jk,jl) / MIN( ( t_i(ji,jj,jk,jl) - rt0 ), - epsi06 ) ) * & |
---|
270 | rswitch * r1_nlay_i |
---|
271 | END DO |
---|
272 | END DO |
---|
273 | END DO |
---|
274 | END DO |
---|
275 | CALL iom_put( "brinevol_cat" , zei ) ! brine volume for categories |
---|
276 | ENDIF |
---|
277 | |
---|
278 | ! ! Create an output files (output.lim.abort.nc) if S < 0 or u > 20 m/s |
---|
279 | ! IF( kindic < 0 ) CALL lim_wri_state( 'output.abort' ) |
---|
280 | ! not yet implemented |
---|
281 | |
---|
282 | CALL wrk_dealloc( jpi, jpj, jpl, zoi, zei ) |
---|
283 | CALL wrk_dealloc( jpi, jpj , z2d, zswi, z2da, z2db ) |
---|
284 | |
---|
285 | IF( nn_timing == 1 ) CALL timing_stop('limwri') |
---|
286 | |
---|
287 | END SUBROUTINE lim_wri |
---|
288 | #endif |
---|
289 | |
---|
290 | |
---|
291 | SUBROUTINE lim_wri_state( kt, kid, kh_i ) |
---|
292 | !!--------------------------------------------------------------------- |
---|
293 | !! *** ROUTINE lim_wri_state *** |
---|
294 | !! |
---|
295 | !! ** Purpose : create a NetCDF file named cdfile_name which contains |
---|
296 | !! the instantaneous ice state and forcing fields for ice model |
---|
297 | !! Used to find errors in the initial state or save the last |
---|
298 | !! ocean state in case of abnormal end of a simulation |
---|
299 | !! |
---|
300 | !! History : |
---|
301 | !! 4.1 ! 2013-06 (C. Rousset) |
---|
302 | !!---------------------------------------------------------------------- |
---|
303 | INTEGER, INTENT( in ) :: kt ! ocean time-step index) |
---|
304 | INTEGER, INTENT( in ) :: kid , kh_i |
---|
305 | !!---------------------------------------------------------------------- |
---|
306 | |
---|
307 | CALL histdef( kid, "iicethic", "Ice thickness" , "m" , & |
---|
308 | & jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) |
---|
309 | CALL histdef( kid, "iiceconc", "Ice concentration" , "%" , & |
---|
310 | & jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) |
---|
311 | CALL histdef( kid, "iicetemp", "Ice temperature" , "C" , & |
---|
312 | & jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) |
---|
313 | CALL histdef( kid, "iicevelu", "i-Ice speed (I-point)" , "m/s" , & |
---|
314 | & jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) |
---|
315 | CALL histdef( kid, "iicevelv", "j-Ice speed (I-point)" , "m/s" , & |
---|
316 | & jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) |
---|
317 | CALL histdef( kid, "iicestru", "i-Wind stress over ice (I-pt)", "Pa", & |
---|
318 | & jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) |
---|
319 | CALL histdef( kid, "iicestrv", "j-Wind stress over ice (I-pt)", "Pa", & |
---|
320 | & jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) |
---|
321 | CALL histdef( kid, "iicesflx", "Solar flux over ocean" , "w/m2" , & |
---|
322 | & jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) |
---|
323 | CALL histdef( kid, "iicenflx", "Non-solar flux over ocean" , "w/m2" , & |
---|
324 | & jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) |
---|
325 | CALL histdef( kid, "isnowpre", "Snow precipitation" , "kg/m2/s", & |
---|
326 | & jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) |
---|
327 | CALL histdef( kid, "iicesali", "Ice salinity" , "PSU" , & |
---|
328 | & jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) |
---|
329 | CALL histdef( kid, "iicevolu", "Ice volume" , "m" , & |
---|
330 | & jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) |
---|
331 | CALL histdef( kid, "iicedive", "Ice divergence" , "10-8s-1", & |
---|
332 | & jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) |
---|
333 | CALL histdef( kid, "iicebopr", "Ice bottom production" , "m/s" , & |
---|
334 | & jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) |
---|
335 | CALL histdef( kid, "iicedypr", "Ice dynamic production" , "m/s" , & |
---|
336 | & jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) |
---|
337 | CALL histdef( kid, "iicelapr", "Ice open water prod" , "m/s" , & |
---|
338 | & jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) |
---|
339 | CALL histdef( kid, "iicesipr", "Snow ice production " , "m/s" , & |
---|
340 | & jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) |
---|
341 | CALL histdef( kid, "iicerepr", "Ice prod from limupdate" , "m/s" , & |
---|
342 | & jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) |
---|
343 | CALL histdef( kid, "iicebome", "Ice bottom melt" , "m/s" , & |
---|
344 | & jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) |
---|
345 | CALL histdef( kid, "iicesume", "Ice surface melt" , "m/s" , & |
---|
346 | & jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) |
---|
347 | CALL histdef( kid, "iisfxdyn", "Salt flux from dynmics" , "" , & |
---|
348 | & jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) |
---|
349 | CALL histdef( kid, "iisfxres", "Salt flux from limupdate", "" , & |
---|
350 | & jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) |
---|
351 | |
---|
352 | CALL histend( kid, snc4set ) ! end of the file definition |
---|
353 | |
---|
354 | CALL histwrite( kid, "iicethic", kt, icethi , jpi*jpj, (/1/) ) |
---|
355 | CALL histwrite( kid, "iiceconc", kt, at_i , jpi*jpj, (/1/) ) |
---|
356 | CALL histwrite( kid, "iicetemp", kt, tm_i - rt0 , jpi*jpj, (/1/) ) |
---|
357 | CALL histwrite( kid, "iicevelu", kt, u_ice , jpi*jpj, (/1/) ) |
---|
358 | CALL histwrite( kid, "iicevelv", kt, v_ice , jpi*jpj, (/1/) ) |
---|
359 | CALL histwrite( kid, "iicestru", kt, utau_ice , jpi*jpj, (/1/) ) |
---|
360 | CALL histwrite( kid, "iicestrv", kt, vtau_ice , jpi*jpj, (/1/) ) |
---|
361 | CALL histwrite( kid, "iicesflx", kt, qsr , jpi*jpj, (/1/) ) |
---|
362 | CALL histwrite( kid, "iicenflx", kt, qns , jpi*jpj, (/1/) ) |
---|
363 | CALL histwrite( kid, "isnowpre", kt, sprecip , jpi*jpj, (/1/) ) |
---|
364 | CALL histwrite( kid, "iicesali", kt, smt_i , jpi*jpj, (/1/) ) |
---|
365 | CALL histwrite( kid, "iicevolu", kt, vt_i , jpi*jpj, (/1/) ) |
---|
366 | CALL histwrite( kid, "iicedive", kt, divu_i*1.0e8 , jpi*jpj, (/1/) ) |
---|
367 | |
---|
368 | CALL histwrite( kid, "iicebopr", kt, wfx_bog , jpi*jpj, (/1/) ) |
---|
369 | CALL histwrite( kid, "iicedypr", kt, wfx_dyn , jpi*jpj, (/1/) ) |
---|
370 | CALL histwrite( kid, "iicelapr", kt, wfx_opw , jpi*jpj, (/1/) ) |
---|
371 | CALL histwrite( kid, "iicesipr", kt, wfx_sni , jpi*jpj, (/1/) ) |
---|
372 | CALL histwrite( kid, "iicerepr", kt, wfx_res , jpi*jpj, (/1/) ) |
---|
373 | CALL histwrite( kid, "iicebome", kt, wfx_bom , jpi*jpj, (/1/) ) |
---|
374 | CALL histwrite( kid, "iicesume", kt, wfx_sum , jpi*jpj, (/1/) ) |
---|
375 | CALL histwrite( kid, "iisfxdyn", kt, sfx_dyn , jpi*jpj, (/1/) ) |
---|
376 | CALL histwrite( kid, "iisfxres", kt, sfx_res , jpi*jpj, (/1/) ) |
---|
377 | |
---|
378 | ! Close the file |
---|
379 | ! ----------------- |
---|
380 | !CALL histclo( kid ) |
---|
381 | |
---|
382 | END SUBROUTINE lim_wri_state |
---|
383 | |
---|
384 | #else |
---|
385 | !!---------------------------------------------------------------------- |
---|
386 | !! Default option : Empty module NO LIM sea-ice model |
---|
387 | !!---------------------------------------------------------------------- |
---|
388 | CONTAINS |
---|
389 | SUBROUTINE lim_wri ! Empty routine |
---|
390 | END SUBROUTINE lim_wri |
---|
391 | #endif |
---|
392 | |
---|
393 | !!====================================================================== |
---|
394 | END MODULE limwri |
---|