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.
limwri.F90 in branches/UKMO/dev_1d_bugfixes_tocommit/NEMOGCM/NEMO/LIM_SRC_3 – NEMO

source: branches/UKMO/dev_1d_bugfixes_tocommit/NEMOGCM/NEMO/LIM_SRC_3/limwri.F90 @ 13354

Last change on this file since 13354 was 6498, checked in by timgraham, 8 years ago

Merge head of nemo_v3_6_STABLE into package branch

File size: 20.7 KB
Line 
1MODULE 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   !!----------------------------------------------------------------------
41CONTAINS
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, zt_i, zt_s
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, zt_i, zt_s )
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" ) )   CALL iom_put( "icecolf", hicol )  ! frazil ice collection thickness
160
161      CALL iom_put( "isst"        , sst_m               )        ! sea surface temperature
162      CALL iom_put( "isss"        , sss_m               )        ! sea surface salinity
163      CALL iom_put( "iceconc"     , at_i                )        ! ice concentration
164      CALL iom_put( "icevolu"     , vt_i                )        ! ice volume = mean ice thickness over the cell
165      CALL iom_put( "icehc"       , et_i                )        ! ice total heat content
166      CALL iom_put( "isnowhc"     , et_s                )        ! snow total heat content
167      CALL iom_put( "ibrinv"      , bv_i * 100._wp      )        ! brine volume
168      CALL iom_put( "utau_ice"    , utau_ice            )        ! wind stress over ice along i-axis at I-point
169      CALL iom_put( "vtau_ice"    , vtau_ice            )        ! wind stress over ice along j-axis at I-point
170      CALL iom_put( "snowpre"     , sprecip * 86400.    )        ! snow precipitation
171      CALL iom_put( "micesalt"    , smt_i               )        ! mean ice salinity
172
173      CALL iom_put( "icestr"      , strength * 0.001    )        ! ice strength
174      CALL iom_put( "idive"       , divu_i * 1.0e8      )        ! divergence
175      CALL iom_put( "ishear"      , shear_i * 1.0e8     )        ! shear
176      CALL iom_put( "snowvol"     , vt_s                )        ! snow volume
177     
178      CALL iom_put( "icetrp"      , diag_trp_vi * rday  )        ! ice volume transport
179      CALL iom_put( "snwtrp"      , diag_trp_vs * rday  )        ! snw volume transport
180      CALL iom_put( "saltrp"      , diag_trp_smv * rday * rhoic ) ! salt content transport
181      CALL iom_put( "deitrp"      , diag_trp_ei         )        ! advected ice enthalpy (W/m2)
182      CALL iom_put( "destrp"      , diag_trp_es         )        ! advected snw enthalpy (W/m2)
183
184      CALL iom_put( "sfxbog"      , sfx_bog * rday      )        ! salt flux from bottom growth
185      CALL iom_put( "sfxbom"      , sfx_bom * rday      )        ! salt flux from bottom melt
186      CALL iom_put( "sfxsum"      , sfx_sum * rday      )        ! salt flux from surface melt
187      CALL iom_put( "sfxsni"      , sfx_sni * rday      )        ! salt flux from snow ice formation
188      CALL iom_put( "sfxopw"      , sfx_opw * rday      )        ! salt flux from open water formation
189      CALL iom_put( "sfxdyn"      , sfx_dyn * rday      )        ! salt flux from ridging rafting
190      CALL iom_put( "sfxres"      , sfx_res * rday      )        ! salt flux from residual
191      CALL iom_put( "sfxbri"      , sfx_bri * rday      )        ! salt flux from brines
192      CALL iom_put( "sfxsub"      , sfx_sub * rday      )        ! salt flux from sublimation
193      CALL iom_put( "sfx"         , sfx     * rday      )        ! total salt flux
194
195      ztmp = rday / rhoic
196      CALL iom_put( "vfxres"     , wfx_res * ztmp       )        ! daily prod./melting due to limupdate
197      CALL iom_put( "vfxopw"     , wfx_opw * ztmp       )        ! daily lateral thermodynamic ice production
198      CALL iom_put( "vfxsni"     , wfx_sni * ztmp       )        ! daily snowice ice production
199      CALL iom_put( "vfxbog"     , wfx_bog * ztmp       )        ! daily bottom thermodynamic ice production
200      CALL iom_put( "vfxdyn"     , wfx_dyn * ztmp       )        ! daily dynamic ice production (rid/raft)
201      CALL iom_put( "vfxsum"     , wfx_sum * ztmp       )        ! surface melt
202      CALL iom_put( "vfxbom"     , wfx_bom * ztmp       )        ! bottom melt
203      CALL iom_put( "vfxice"     , wfx_ice * ztmp       )        ! total ice growth/melt
204      CALL iom_put( "vfxsnw"     , wfx_snw * ztmp       )        ! total snw growth/melt
205      CALL iom_put( "vfxsub"     , wfx_sub * ztmp       )        ! sublimation (snow)
206      CALL iom_put( "vfxspr"     , wfx_spr * ztmp       )        ! precip (snow)
207     
208      CALL iom_put( "afxtot"     , afx_tot * rday       )        ! concentration tendency (total)
209      CALL iom_put( "afxdyn"     , afx_dyn * rday       )        ! concentration tendency (dynamics)
210      CALL iom_put( "afxthd"     , afx_thd * rday       )        ! concentration tendency (thermo)
211
212      CALL iom_put ('hfxthd'     , hfx_thd(:,:)         )   
213      CALL iom_put ('hfxdyn'     , hfx_dyn(:,:)         )   
214      CALL iom_put ('hfxres'     , hfx_res(:,:)         )   
215      CALL iom_put ('hfxout'     , hfx_out(:,:)         )   
216      CALL iom_put ('hfxin'      , hfx_in(:,:)          )   
217      CALL iom_put ('hfxsnw'     , hfx_snw(:,:)         )   
218      CALL iom_put ('hfxsub'     , hfx_sub(:,:)         )   
219      CALL iom_put ('hfxerr'     , hfx_err(:,:)         )   
220      CALL iom_put ('hfxerr_rem' , hfx_err_rem(:,:)     )   
221     
222      CALL iom_put ('hfxsum'     , hfx_sum(:,:)         )   
223      CALL iom_put ('hfxbom'     , hfx_bom(:,:)         )   
224      CALL iom_put ('hfxbog'     , hfx_bog(:,:)         )   
225      CALL iom_put ('hfxdif'     , hfx_dif(:,:)         )   
226      CALL iom_put ('hfxopw'     , hfx_opw(:,:)         )   
227      CALL iom_put ('hfxtur'     , fhtur(:,:) * SUM(a_i_b(:,:,:), dim=3) ) ! turbulent heat flux at ice base
228      CALL iom_put ('hfxdhc'     , diag_heat(:,:)       )   ! Heat content variation in snow and ice
229      CALL iom_put ('hfxspr'     , hfx_spr(:,:)         )   ! Heat content of snow precip
230
231
232      IF ( iom_use( "vfxthin" ) ) THEN   ! ice production for open water + thin ice (<20cm) => comparable to observations 
233         DO jj = 1, jpj 
234            DO ji = 1, jpi
235               z2d(ji,jj)  = vt_i(ji,jj) / MAX( at_i(ji,jj), epsi06 ) * zswi(ji,jj) ! mean ice thickness
236            END DO
237         END DO
238         WHERE( z2d(:,:) < 0.2 .AND. z2d(:,:) > 0. ) ; z2da = wfx_bog
239         ELSEWHERE                                   ; z2da = 0._wp
240         END WHERE
241         CALL iom_put( "vfxthin", ( wfx_opw + z2da ) * ztmp )
242      ENDIF
243     
244      !--------------------------------
245      ! Output values for each category
246      !--------------------------------
247      CALL iom_put( "iceconc_cat"      , a_i         )        ! area for categories
248      CALL iom_put( "icethic_cat"      , ht_i        )        ! thickness for categories
249      CALL iom_put( "snowthic_cat"     , ht_s        )        ! snow depth for categories
250      CALL iom_put( "salinity_cat"     , sm_i        )        ! salinity for categories
251
252      ! ice temperature
253      IF ( iom_use( "icetemp_cat" ) ) THEN
254         zt_i(:,:,:) = SUM( t_i(:,:,:,:), dim=3 ) * r1_nlay_i
255         CALL iom_put( "icetemp_cat"   , zt_i - rt0  )
256      ENDIF
257     
258      ! snow temperature
259      IF ( iom_use( "snwtemp_cat" ) ) THEN
260         zt_s(:,:,:) = SUM( t_s(:,:,:,:), dim=3 ) * r1_nlay_s
261         CALL iom_put( "snwtemp_cat"   , zt_s - rt0  )
262      ENDIF
263
264      ! Compute ice age
265      IF ( iom_use( "iceage_cat" ) ) THEN
266         DO jl = 1, jpl 
267            DO jj = 1, jpj
268               DO ji = 1, jpi
269                  rswitch = MAX( 0._wp , SIGN( 1._wp , at_i(ji,jj) - 0.1 ) )
270                  rswitch = rswitch * MAX( 0._wp , SIGN( 1._wp , a_i(ji,jj,jl) - 0.1 ) )
271                  zoi(ji,jj,jl) = oa_i(ji,jj,jl)  / MAX( a_i(ji,jj,jl) , 0.1 ) * rswitch
272               END DO
273            END DO
274         END DO
275         CALL iom_put( "iceage_cat"   , zoi * z1_365 )        ! ice age for categories
276      ENDIF
277
278      ! Compute brine volume
279      IF ( iom_use( "brinevol_cat" ) ) THEN
280         zei(:,:,:) = 0._wp
281         DO jl = 1, jpl 
282            DO jk = 1, nlay_i
283               DO jj = 1, jpj
284                  DO ji = 1, jpi
285                     rswitch = MAX( 0._wp , SIGN( 1._wp , a_i(ji,jj,jl) - epsi06 ) )
286                     zei(ji,jj,jl) = zei(ji,jj,jl) + 100.0 *  &
287                        ( - tmut * s_i(ji,jj,jk,jl) / MIN( ( t_i(ji,jj,jk,jl) - rt0 ), - epsi06 ) ) * &
288                        rswitch * r1_nlay_i
289                  END DO
290               END DO
291            END DO
292         END DO
293         CALL iom_put( "brinevol_cat"     , zei      )        ! brine volume for categories
294      ENDIF
295
296      !     !  Create an output files (output.lim.abort.nc) if S < 0 or u > 20 m/s
297      !     IF( kindic < 0 )   CALL lim_wri_state( 'output.abort' )
298      !     not yet implemented
299     
300      CALL wrk_dealloc( jpi, jpj, jpl, zoi, zei, zt_i, zt_s )
301      CALL wrk_dealloc( jpi, jpj     , z2d, zswi, z2da, z2db )
302
303      IF( nn_timing == 1 )  CALL timing_stop('limwri')
304     
305   END SUBROUTINE lim_wri
306#endif
307
308 
309   SUBROUTINE lim_wri_state( kt, kid, kh_i )
310      !!---------------------------------------------------------------------
311      !!                 ***  ROUTINE lim_wri_state  ***
312      !!       
313      !! ** Purpose :   create a NetCDF file named cdfile_name which contains
314      !!      the instantaneous ice state and forcing fields for ice model
315      !!        Used to find errors in the initial state or save the last
316      !!      ocean state in case of abnormal end of a simulation
317      !!
318      !! History :
319      !!   4.0  !  2013-06  (C. Rousset)
320      !!----------------------------------------------------------------------
321      INTEGER, INTENT( in ) ::   kt               ! ocean time-step index)
322      INTEGER, INTENT( in ) ::   kid , kh_i       
323      !!----------------------------------------------------------------------
324
325      CALL histdef( kid, "iicethic", "Ice thickness"           , "m"      ,   &
326      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
327      CALL histdef( kid, "iiceconc", "Ice concentration"       , "%"      ,   &
328      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
329      CALL histdef( kid, "iicetemp", "Ice temperature"         , "C"      ,   &
330      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
331      CALL histdef( kid, "iicevelu", "i-Ice speed (I-point)"   , "m/s"    ,   &
332      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
333      CALL histdef( kid, "iicevelv", "j-Ice speed (I-point)"   , "m/s"    ,   &
334      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
335      CALL histdef( kid, "iicestru", "i-Wind stress over ice (I-pt)", "Pa",   &
336      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
337      CALL histdef( kid, "iicestrv", "j-Wind stress over ice (I-pt)", "Pa",   &
338      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
339      CALL histdef( kid, "iicesflx", "Solar flux over ocean"     , "w/m2" ,   &
340      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
341      CALL histdef( kid, "iicenflx", "Non-solar flux over ocean" , "w/m2" ,   &
342      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
343      CALL histdef( kid, "isnowpre", "Snow precipitation"      , "kg/m2/s",   &
344      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
345      CALL histdef( kid, "iicesali", "Ice salinity"            , "PSU"    ,   &
346      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
347      CALL histdef( kid, "iicevolu", "Ice volume"              , "m"      ,   &
348      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
349      CALL histdef( kid, "iicedive", "Ice divergence"          , "10-8s-1",   &
350      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
351      CALL histdef( kid, "iicebopr", "Ice bottom production"   , "m/s"    ,   &
352      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
353      CALL histdef( kid, "iicedypr", "Ice dynamic production"  , "m/s"    ,   &
354      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
355      CALL histdef( kid, "iicelapr", "Ice open water prod"     , "m/s"    ,   &
356      &       jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
357      CALL histdef( kid, "iicesipr", "Snow ice production "    , "m/s"    ,   &
358      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
359      CALL histdef( kid, "iicerepr", "Ice prod from limupdate" , "m/s"    ,   &
360      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
361      CALL histdef( kid, "iicebome", "Ice bottom melt"         , "m/s"    ,   &
362      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
363      CALL histdef( kid, "iicesume", "Ice surface melt"        , "m/s"    ,   &
364      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
365      CALL histdef( kid, "iisfxdyn", "Salt flux from dynmics"  , ""       ,   &
366      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
367      CALL histdef( kid, "iisfxres", "Salt flux from limupdate", ""       ,   &
368      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
369
370      CALL histend( kid, snc4set )   ! end of the file definition
371
372      CALL histwrite( kid, "iicethic", kt, icethi        , jpi*jpj, (/1/) )   
373      CALL histwrite( kid, "iiceconc", kt, at_i          , jpi*jpj, (/1/) )
374      CALL histwrite( kid, "iicetemp", kt, tm_i - rt0    , jpi*jpj, (/1/) )
375      CALL histwrite( kid, "iicevelu", kt, u_ice          , jpi*jpj, (/1/) )
376      CALL histwrite( kid, "iicevelv", kt, v_ice          , jpi*jpj, (/1/) )
377      CALL histwrite( kid, "iicestru", kt, utau_ice       , jpi*jpj, (/1/) )
378      CALL histwrite( kid, "iicestrv", kt, vtau_ice       , jpi*jpj, (/1/) )
379      CALL histwrite( kid, "iicesflx", kt, qsr , jpi*jpj, (/1/) )
380      CALL histwrite( kid, "iicenflx", kt, qns , jpi*jpj, (/1/) )
381      CALL histwrite( kid, "isnowpre", kt, sprecip        , jpi*jpj, (/1/) )
382      CALL histwrite( kid, "iicesali", kt, smt_i          , jpi*jpj, (/1/) )
383      CALL histwrite( kid, "iicevolu", kt, vt_i           , jpi*jpj, (/1/) )
384      CALL histwrite( kid, "iicedive", kt, divu_i*1.0e8   , jpi*jpj, (/1/) )
385
386      CALL histwrite( kid, "iicebopr", kt, wfx_bog        , jpi*jpj, (/1/) )
387      CALL histwrite( kid, "iicedypr", kt, wfx_dyn        , jpi*jpj, (/1/) )
388      CALL histwrite( kid, "iicelapr", kt, wfx_opw        , jpi*jpj, (/1/) )
389      CALL histwrite( kid, "iicesipr", kt, wfx_sni        , jpi*jpj, (/1/) )
390      CALL histwrite( kid, "iicerepr", kt, wfx_res        , jpi*jpj, (/1/) )
391      CALL histwrite( kid, "iicebome", kt, wfx_bom        , jpi*jpj, (/1/) )
392      CALL histwrite( kid, "iicesume", kt, wfx_sum        , jpi*jpj, (/1/) )
393      CALL histwrite( kid, "iisfxdyn", kt, sfx_dyn        , jpi*jpj, (/1/) )
394      CALL histwrite( kid, "iisfxres", kt, sfx_res        , jpi*jpj, (/1/) )
395
396      ! Close the file
397      ! -----------------
398      !CALL histclo( kid )
399
400    END SUBROUTINE lim_wri_state
401
402#else
403   !!----------------------------------------------------------------------
404   !!   Default option :         Empty module          NO LIM sea-ice model
405   !!----------------------------------------------------------------------
406CONTAINS
407   SUBROUTINE lim_wri          ! Empty routine
408   END SUBROUTINE lim_wri
409#endif
410
411   !!======================================================================
412END MODULE limwri
Note: See TracBrowser for help on using the repository browser.