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.
icewri.F90 in branches/2017/dev_CNRS_2017/NEMOGCM/NEMO/LIM_SRC_3 – NEMO

source: branches/2017/dev_CNRS_2017/NEMOGCM/NEMO/LIM_SRC_3/icewri.F90 @ 8884

Last change on this file since 8884 was 8884, checked in by clem, 6 years ago

dev_CNRS_2017: modify outputs for sea-ice

File size: 21.3 KB
Line 
1MODULE icewri
2   !!======================================================================
3   !!                     ***  MODULE  icewri  ***
4   !!   sea-ice : output ice variables
5   !!======================================================================
6#if defined key_lim3
7   !!----------------------------------------------------------------------
8   !!   'key_lim3'                                       ESIM sea-ice model
9   !!----------------------------------------------------------------------
10   !!   ice_wri       : write of the diagnostics variables in ouput file
11   !!   ice_wri_state : write for initial state or/and abandon
12   !!----------------------------------------------------------------------
13   USE dianam         ! build name of file (routine)
14   USE phycst         ! physical constant
15   USE dom_oce        ! domain: ocean
16   USE sbc_oce        ! surf. boundary cond.: ocean
17   USE sbc_ice        ! Surface boundary condition: ice fields
18   USE ice            ! sea-ice: variables
19   USE icevar         ! sea-ice: operations
20   !
21   USE ioipsl         !
22   USE in_out_manager ! I/O manager
23   USE iom            ! I/O manager library
24   USE lib_mpp        ! MPP library
25   USE lib_fortran    ! fortran utilities (glob_sum + no signed zero)
26   USE lbclnk         ! lateral boundary conditions (or mpp links)
27   USE timing         ! Timing
28
29   IMPLICIT NONE
30   PRIVATE
31
32   PUBLIC ice_wri        ! called by ice_stp
33   PUBLIC ice_wri_state  ! called by dia_wri_state
34
35   !!----------------------------------------------------------------------
36   !! NEMO/ICE 4.0 , NEMO Consortium (2017)
37   !! $Id: icewri.F90 8409 2017-08-07 15:29:21Z clem $
38   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
39   !!----------------------------------------------------------------------
40CONTAINS
41
42   SUBROUTINE ice_wri( kt )
43      !!-------------------------------------------------------------------
44      !!  This routine computes the average of some variables and write it
45      !!  on the ouput files.
46      !!-------------------------------------------------------------------
47      INTEGER, INTENT(in) ::   kt   ! time-step
48      !
49      INTEGER  ::   ji, jj, jk, jl  ! dummy loop indices
50      REAL(wp) ::   z2da, z2db, zrho1, zrho2
51      REAL(wp), DIMENSION(jpi,jpj)     ::   z2d !  2D workspace
52      REAL(wp), DIMENSION(jpi,jpj)     ::   zmsk00, zmsk05, zmsk15 ! O%, 5% and 15% concentration mask
53      REAL(wp), DIMENSION(jpi,jpj,jpl) ::   zmsk00l        ! cat masks
54      !
55      ! Global ice diagnostics (SIMIP)
56      REAL(wp) ::   zdiag_area_nh, zdiag_extt_nh, zdiag_volu_nh   ! area, extent, volume
57      REAL(wp) ::   zdiag_area_sh, zdiag_extt_sh, zdiag_volu_sh 
58      !!-------------------------------------------------------------------
59
60      IF( nn_timing == 1 )   CALL timing_start('icewri')
61
62      !----------------------------------------
63      ! Brine volume, switches, missing values
64      !----------------------------------------
65
66      CALL ice_var_bv      ! brine volume
67
68      ! tresholds for outputs
69      DO jj = 1, jpj
70         DO ji = 1, jpi
71            zmsk00(ji,jj) = MAX( 0._wp , SIGN( 1._wp , at_i(ji,jj) - epsi06  ) ) ! 1 if ice    , 0 if no ice
72            zmsk05(ji,jj) = MAX( 0._wp , SIGN( 1._wp , at_i(ji,jj) - 0.05_wp ) ) ! 1 if 5% ice , 0 if less
73            zmsk15(ji,jj) = MAX( 0._wp , SIGN( 1._wp , at_i(ji,jj) - 0.15_wp ) ) ! 1 if 15% ice, 0 if less
74         END DO
75      END DO
76      DO jl = 1, jpl
77         DO jj = 1, jpj
78            DO ji = 1, jpi
79               zmsk00l(ji,jj,jl)  = MAX( 0._wp , SIGN( 1._wp , a_i(ji,jj,jl) - epsi06 ) )
80            END DO
81         END DO
82      END DO
83
84      !-----------------
85      ! Standard outputs
86      !-----------------
87      zrho1 = ( rau0 - rhoic ) * r1_rau0; zrho2 = rhosn * r1_rau0
88      ! masks
89      IF( iom_use('icemask'  ) )   CALL iom_put( "icemask"  , zmsk00              )   ! ice mask 0%
90      IF( iom_use('icemask05') )   CALL iom_put( "icemask05", zmsk05              )   ! ice mask 5%
91      IF( iom_use('icemask15') )   CALL iom_put( "icemask15", zmsk15              )   ! ice mask 15%
92      !
93      ! general fields
94      IF( iom_use('icemass'  ) )   CALL iom_put( "icemass", rhoic * vt_i * zmsk00 )   ! Ice mass per cell area
95      IF( iom_use('snwmass'  ) )   CALL iom_put( "snwmass", rhosn * vt_s * zmsk00 )   ! Snow mass per cell area
96      IF( iom_use('icepres'  ) )   CALL iom_put( "icepres", zmsk00                )   ! Ice presence (1 or 0)
97      IF( iom_use('iceconc'  ) )   CALL iom_put( "iceconc", at_i  * zmsk00        )   ! ice concentration
98      IF( iom_use('icevolu'  ) )   CALL iom_put( "icevolu", vt_i  * zmsk00        )   ! ice volume = mean ice thickness over the cell
99      IF( iom_use('icethic'  ) )   CALL iom_put( "icethic", hm_i  * zmsk00        )   ! ice thickness
100      IF( iom_use('snwthic'  ) )   CALL iom_put( "snwthic", hm_s  * zmsk00        )   ! snw thickness
101      IF( iom_use('icebrv'   ) )   CALL iom_put( "icebrv" , bvm_i * zmsk00 * 100. )   ! brine volume
102      IF( iom_use('iceage'   ) )   CALL iom_put( "iceage" , om_i  * zmsk00 / rday )   ! ice age
103      IF( iom_use('icehnew'  ) )   CALL iom_put( "icehnew", ht_i_new              )   ! new ice thickness formed in the leads
104      IF( iom_use('snwvolu'  ) )   CALL iom_put( "snwvolu", vt_s  * zmsk00        )   ! snow volume
105      IF( iom_use('icefrb') ) THEN
106         z2d(:,:) = ( zrho1 * hm_i(:,:) - zrho2 * hm_s(:,:) )                                         
107         WHERE( z2d < 0._wp )   z2d = 0._wp
108                                   CALL iom_put( "icefrb" , z2d * zmsk00          )   ! Ice freeboard
109      ENDIF
110      !
111      ! melt ponds
112      IF( iom_use('iceapnd'  ) )   CALL iom_put( "iceapnd", at_ip  * zmsk00       )   ! melt pond total fraction
113      IF( iom_use('icevpnd'  ) )   CALL iom_put( "icevpnd", vt_ip  * zmsk00       )   ! melt pond total volume per unit area
114      !
115      ! salt
116      IF( iom_use('icesalt'  ) )   CALL iom_put( "icesalt", sm_i  * zmsk00        )   ! mean ice salinity
117      IF( iom_use('icesalm'  ) )   CALL iom_put( "icesalm", SUM( sv_i, DIM = 3 ) * rhoic * 1.0e-3 * zmsk00 )   ! Mass of salt in sea ice per cell area
118
119      ! heat
120      IF( iom_use('icetemp'  ) )   CALL iom_put( "icetemp", ( tm_i  - rt0 ) * zmsk00 )   ! ice mean temperature
121      IF( iom_use('icettop'  ) )   CALL iom_put( "icettop", ( tm_su - rt0 ) * zmsk00 )   ! temperature at the ice surface
122      IF( iom_use('icetbot'  ) )   CALL iom_put( "icetbot", ( t_bo  - rt0 ) * zmsk00 )   ! temperature at the ice bottom
123      IF( iom_use('icetsni'  ) )   CALL iom_put( "icetsni", ( tm_si - rt0 ) * zmsk00 )   ! temperature at the snow-ice interface
124      IF( iom_use('icehc'    ) )   CALL iom_put( "icehc"  ,  -et_i          * zmsk00 )   ! ice heat content
125      IF( iom_use('snwhc'    ) )   CALL iom_put( "snwhc"  ,  -et_s          * zmsk00 )   ! snow heat content
126
127      ! momentum
128      IF( iom_use('uice'     ) )   CALL iom_put( "uice"   , u_ice                 )   ! ice velocity u component
129      IF( iom_use('vice'     ) )   CALL iom_put( "vice"   , v_ice                 )   ! ice velocity v component
130      IF( iom_use('utau_ai'  ) )   CALL iom_put( "utau_ai", utau_ice * zmsk00     )   ! Wind stress term in force balance (x)
131      IF( iom_use('vtau_ai'  ) )   CALL iom_put( "vtau_ai", vtau_ice * zmsk00     )   ! Wind stress term in force balance (y)
132
133      IF( iom_use('icevel') ) THEN
134         DO jj = 2 , jpjm1
135            DO ji = 2 , jpim1
136               z2da  = ( u_ice(ji,jj) + u_ice(ji-1,jj) )
137               z2db  = ( v_ice(ji,jj) + v_ice(ji,jj-1) )
138               z2d(ji,jj) = 0.5_wp * SQRT( z2da * z2da + z2db * z2db )
139           END DO
140         END DO
141         CALL lbc_lnk( z2d, 'T', 1. )
142         IF( iom_use('icevel') )   CALL iom_put( "icevel" , z2d                   )   ! ice velocity module
143      ENDIF
144
145      ! --- category-dependent fields --- !
146      IF( iom_use('icemask_cat' ) )   CALL iom_put( "icemask_cat" , zmsk00l                                                    )   ! ice mask 0%
147      IF( iom_use('iceconc_cat' ) )   CALL iom_put( "iceconc_cat" , a_i * zmsk00l                                              )   ! area for categories
148      IF( iom_use('icethic_cat' ) )   CALL iom_put( "icethic_cat" , h_i * zmsk00l                                              )   ! thickness for categories
149      IF( iom_use('snwthic_cat' ) )   CALL iom_put( "snwthic_cat" , h_s * zmsk00l                                              )   ! snow depth for categories
150      IF( iom_use('icesalt_cat' ) )   CALL iom_put( "icesalt_cat" , s_i * zmsk00l                                              )   ! salinity for categories
151      IF( iom_use('iceage_cat'  ) )   CALL iom_put( "iceage_cat"  , o_i * zmsk00l / rday                                       )   ! ice age
152      IF( iom_use('icetemp_cat' ) )   CALL iom_put( "icetemp_cat" , ( SUM( t_i(:,:,:,:), dim=3 ) * r1_nlay_i - rt0 ) * zmsk00l )   ! ice temperature
153      IF( iom_use('snwtemp_cat' ) )   CALL iom_put( "snwtemp_cat" , ( SUM( t_s(:,:,:,:), dim=3 ) * r1_nlay_s - rt0 ) * zmsk00l )   ! snow temperature
154      IF( iom_use('icebrv_cat'  ) )   CALL iom_put( "icebrv_cat"  , bv_i * 100. * zmsk00l                                      )   ! brine volume
155      IF( iom_use('iceapnd_cat' ) )   CALL iom_put( "iceapnd_cat" , a_ip        * zmsk00l                                      )   ! melt pond frac for categories
156      IF( iom_use('icehpnd_cat' ) )   CALL iom_put( "icehpnd_cat" , h_ip        * zmsk00l                                      )   ! melt pond frac for categories
157      IF( iom_use('iceafpnd_cat') )   CALL iom_put( "iceafpnd_cat", a_ip_frac   * zmsk00l                                      )   ! melt pond frac for categories
158
159      !------------------
160      ! Add-ons for SIMIP
161      !------------------
162      ! trends
163      IF( iom_use('dmithd') )   CALL iom_put( "dmithd", - wfx_bog - wfx_bom - wfx_sum - wfx_sni - wfx_opw - wfx_lam - wfx_res ) ! Sea-ice mass change from thermodynamics
164      IF( iom_use('dmidyn') )   CALL iom_put( "dmidyn", - wfx_dyn + rhoic * diag_trp_vi     )   ! Sea-ice mass change from dynamics(kg/m2/s)
165      IF( iom_use('dmiopw') )   CALL iom_put( "dmiopw", - wfx_opw                           )   ! Sea-ice mass change through growth in open water
166      IF( iom_use('dmibog') )   CALL iom_put( "dmibog", - wfx_bog                           )   ! Sea-ice mass change through basal growth
167      IF( iom_use('dmisni') )   CALL iom_put( "dmisni", - wfx_sni                           )   ! Sea-ice mass change through snow-to-ice conversion
168      IF( iom_use('dmisum') )   CALL iom_put( "dmisum", - wfx_sum                           )   ! Sea-ice mass change through surface melting
169      IF( iom_use('dmibom') )   CALL iom_put( "dmibom", - wfx_bom                           )   ! Sea-ice mass change through bottom melting
170      IF( iom_use('dmtsub') )   CALL iom_put( "dmtsub", - wfx_sub                           )   ! Sea-ice mass change through evaporation and sublimation
171      IF( iom_use('dmssub') )   CALL iom_put( "dmssub", - wfx_snw_sub                       )   ! Snow mass change through sublimation
172      IF( iom_use('dmisub') )   CALL iom_put( "dmisub", - wfx_ice_sub                       )   ! Sea-ice mass change through sublimation
173      IF( iom_use('dmsspr') )   CALL iom_put( "dmsspr", - wfx_spr                           )   ! Snow mass change through snow fall
174      IF( iom_use('dmsssi') )   CALL iom_put( "dmsssi",   wfx_sni*rhosn*r1_rhoic            )   ! Snow mass change through snow-to-ice conversion
175      IF( iom_use('dmsmel') )   CALL iom_put( "dmsmel", - wfx_snw_sum                       )   ! Snow mass change through melt
176      IF( iom_use('dmsdyn') )   CALL iom_put( "dmsdyn", - wfx_snw_dyn + rhosn * diag_trp_vs )   ! Snow mass change through dynamics(kg/m2/s)
177
178      ! Global ice diagnostics
179      IF( iom_use('NH_icearea') .OR. iom_use('NH_icevolu') .OR. iom_use('NH_iceextt') )   THEN   ! NH diagnostics
180         !
181         WHERE( ff_t > 0._wp )   ;   zmsk00(:,:) = 1.0e-12
182         ELSEWHERE               ;   zmsk00(:,:) = 0.
183         END WHERE
184         zdiag_area_nh = glob_sum( at_i(:,:) * zmsk00(:,:) * e1e2t(:,:) )
185         zdiag_volu_nh = glob_sum( vt_i(:,:) * zmsk00(:,:) * e1e2t(:,:) )
186         !
187         WHERE( ff_t > 0._wp .AND. at_i > 0.15 )   ; zmsk00(:,:) = 1.0e-12
188         ELSEWHERE                                 ; zmsk00(:,:) = 0.
189         END WHERE
190         zdiag_extt_nh = glob_sum( zmsk00(:,:) * e1e2t(:,:) )
191         !
192         IF( iom_use('NH_icearea') )   CALL iom_put( "NH_icearea" ,  zdiag_area_nh )
193         IF( iom_use('NH_icevolu') )   CALL iom_put( "NH_icevolu" ,  zdiag_volu_nh )
194         IF( iom_use('NH_iceextt') )   CALL iom_put( "NH_iceextt" ,  zdiag_extt_nh )
195         !
196      ENDIF
197      !
198      IF( iom_use('SH_icearea') .OR. iom_use('SH_icevolu') .OR. iom_use('SH_iceextt') )   THEN   ! SH diagnostics
199         !
200         WHERE( ff_t < 0._wp ); zmsk00(:,:) = 1.0e-12; 
201         ELSEWHERE            ; zmsk00(:,:) = 0.
202         END WHERE
203         zdiag_area_sh = glob_sum( at_i(:,:) * zmsk00(:,:) * e1e2t(:,:) ) 
204         zdiag_volu_sh = glob_sum( vt_i(:,:) * zmsk00(:,:) * e1e2t(:,:) )
205         !
206         WHERE( ff_t < 0._wp .AND. at_i > 0.15 ); zmsk00(:,:) = 1.0e-12
207         ELSEWHERE                              ; zmsk00(:,:) = 0.
208         END WHERE
209         zdiag_extt_sh = glob_sum( zmsk00(:,:) * e1e2t(:,:) )
210         !
211         IF( iom_use('SH_icearea') ) CALL iom_put( "SH_icearea", zdiag_area_sh )
212         IF( iom_use('SH_icevolu') ) CALL iom_put( "SH_icevolu", zdiag_volu_sh )
213         IF( iom_use('SH_iceextt') ) CALL iom_put( "SH_iceextt", zdiag_extt_sh )
214         !
215      ENDIF 
216      !
217!!CR      !     !  Create an output files (output.lim.abort.nc) if S < 0 or u > 20 m/s
218!!CR      !     IF( kindic < 0 )   CALL ice_wri_state( 'output.abort' )
219!!CR      !     not yet implemented
220!!gm  idem for the ocean...  Ask Seb how to get read of ioipsl....
221      !
222      IF( nn_timing == 1 )  CALL timing_stop('icewri')
223      !
224   END SUBROUTINE ice_wri
225
226 
227   SUBROUTINE ice_wri_state( kt, kid, kh_i )
228      !!---------------------------------------------------------------------
229      !!                 ***  ROUTINE ice_wri_state  ***
230      !!       
231      !! ** Purpose :   create a NetCDF file named cdfile_name which contains
232      !!      the instantaneous ice state and forcing fields for ice model
233      !!        Used to find errors in the initial state or save the last
234      !!      ocean state in case of abnormal end of a simulation
235      !!
236      !! History :   4.0  !  2013-06  (C. Rousset)
237      !!----------------------------------------------------------------------
238      INTEGER, INTENT( in ) ::   kt               ! ocean time-step index
239      INTEGER, INTENT( in ) ::   kid , kh_i
240      INTEGER               ::   nz_i, jl
241      REAL(wp), DIMENSION(jpl) ::   jcat
242      !!----------------------------------------------------------------------
243      !
244      DO jl = 1, jpl
245         jcat(jl) = REAL(jl)
246      END DO
247     
248      CALL histvert( kid, "ncatice", "Ice Categories","", jpl, jcat, nz_i, "up")
249
250      CALL histdef( kid, "sithic", "Ice thickness"           , "m"      ,   &
251      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
252      CALL histdef( kid, "siconc", "Ice concentration"       , "%"      ,   &
253      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
254      CALL histdef( kid, "sitemp", "Ice temperature"         , "C"      ,   &
255      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
256      CALL histdef( kid, "sivelu", "i-Ice speed "            , "m/s"    ,   &
257      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
258      CALL histdef( kid, "sivelv", "j-Ice speed "            , "m/s"    ,   &
259      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
260      CALL histdef( kid, "sistru", "i-Wind stress over ice " , "Pa"     ,   &
261      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
262      CALL histdef( kid, "sistrv", "j-Wind stress over ice " , "Pa"     ,   &
263      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
264      CALL histdef( kid, "sisflx", "Solar flux over ocean"     , "w/m2" ,   &
265      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
266      CALL histdef( kid, "sinflx", "Non-solar flux over ocean" , "w/m2" ,   &
267      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
268      CALL histdef( kid, "isnowpre", "Snow precipitation"      , "kg/m2/s",   &
269      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
270      CALL histdef( kid, "sisali", "Ice salinity"            , "PSU"    ,   &
271      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
272      CALL histdef( kid, "sivolu", "Ice volume"              , "m"      ,   &
273      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
274      CALL histdef( kid, "sidive", "Ice divergence"          , "10-8s-1",   &
275      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
276      CALL histdef( kid, "si_amp", "Melt pond fraction"      , "%"      ,   &
277      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
278      CALL histdef( kid, "si_vmp", "Melt pond volume"        ,  "m"     ,   &
279      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
280      CALL histdef( kid, "vfxbog", "Ice bottom production"   , "m/s"    ,   &
281      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
282      CALL histdef( kid, "vfxdyn", "Ice dynamic production"  , "m/s"    ,   &
283      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
284      CALL histdef( kid, "vfxopw", "Ice open water prod"     , "m/s"    ,   &
285      &       jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
286      CALL histdef( kid, "vfxsni", "Snow ice production "    , "m/s"    ,   &
287      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
288      CALL histdef( kid, "vfxres", "Ice prod from corrections" , "m/s"  ,   &
289      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
290      CALL histdef( kid, "vfxbom", "Ice bottom melt"         , "m/s"    ,   &
291      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
292      CALL histdef( kid, "vfxsum", "Ice surface melt"        , "m/s"    ,   &
293      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
294      CALL histdef( kid, "vfxpnd", "Ice melt ponds flux"     , "m/s"    ,   &
295      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
296
297      CALL histdef( kid, "sithicat", "Ice thickness"         , "m"      ,   &
298      &      jpi, jpj, kh_i, jpl, 1, jpl, nz_i, 32, "inst(x)", rdt, rdt )
299      CALL histdef( kid, "siconcat", "Ice concentration"     , "%"      ,   &
300      &      jpi, jpj, kh_i, jpl, 1, jpl, nz_i, 32, "inst(x)", rdt, rdt )
301      CALL histdef( kid, "sisalcat", "Ice salinity"           , ""      ,   &
302      &      jpi, jpj, kh_i, jpl, 1, jpl, nz_i, 32, "inst(x)", rdt, rdt )
303      CALL histdef( kid, "snthicat", "Snw thickness"         , "m"      ,   &
304      &      jpi, jpj, kh_i, jpl, 1, jpl, nz_i, 32, "inst(x)", rdt, rdt )
305
306      CALL histend( kid, snc4set )   ! end of the file definition
307
308      CALL histwrite( kid, "sithic", kt, hm_i           , jpi*jpj, (/1/) )   
309      CALL histwrite( kid, "siconc", kt, at_i           , jpi*jpj, (/1/) )
310      CALL histwrite( kid, "sitemp", kt, tm_i - rt0     , jpi*jpj, (/1/) )
311      CALL histwrite( kid, "sivelu", kt, u_ice          , jpi*jpj, (/1/) )
312      CALL histwrite( kid, "sivelv", kt, v_ice          , jpi*jpj, (/1/) )
313      CALL histwrite( kid, "sistru", kt, utau_ice       , jpi*jpj, (/1/) )
314      CALL histwrite( kid, "sistrv", kt, vtau_ice       , jpi*jpj, (/1/) )
315      CALL histwrite( kid, "sisflx", kt, qsr , jpi*jpj, (/1/) )
316      CALL histwrite( kid, "sinflx", kt, qns , jpi*jpj, (/1/) )
317      CALL histwrite( kid, "isnowpre", kt, sprecip        , jpi*jpj, (/1/) )
318      CALL histwrite( kid, "sisali", kt, sm_i           , jpi*jpj, (/1/) )
319      CALL histwrite( kid, "sivolu", kt, vt_i           , jpi*jpj, (/1/) )
320      CALL histwrite( kid, "sidive", kt, divu_i*1.0e8   , jpi*jpj, (/1/) )
321
322      CALL histwrite( kid, "si_amp", kt, at_ip         , jpi*jpj, (/1/) )
323      CALL histwrite( kid, "si_vmp", kt, vt_ip         , jpi*jpj, (/1/) )
324
325      CALL histwrite( kid, "vfxbog", kt, wfx_bog        , jpi*jpj, (/1/) )
326      CALL histwrite( kid, "vfxdyn", kt, wfx_dyn        , jpi*jpj, (/1/) )
327      CALL histwrite( kid, "vfxopw", kt, wfx_opw        , jpi*jpj, (/1/) )
328      CALL histwrite( kid, "vfxsni", kt, wfx_sni        , jpi*jpj, (/1/) )
329      CALL histwrite( kid, "vfxres", kt, wfx_res        , jpi*jpj, (/1/) )
330      CALL histwrite( kid, "vfxbom", kt, wfx_bom        , jpi*jpj, (/1/) )
331      CALL histwrite( kid, "vfxsum", kt, wfx_sum        , jpi*jpj, (/1/) )
332      CALL histwrite( kid, "vfxpnd", kt, wfx_pnd        , jpi*jpj, (/1/) )
333
334      CALL histwrite( kid, "sithicat", kt, h_i         , jpi*jpj*jpl, (/1/) )   
335      CALL histwrite( kid, "siconcat", kt, a_i         , jpi*jpj*jpl, (/1/) )   
336      CALL histwrite( kid, "sisalcat", kt, s_i         , jpi*jpj*jpl, (/1/) )   
337      CALL histwrite( kid, "snthicat", kt, h_s         , jpi*jpj*jpl, (/1/) )   
338
339      !! The file is closed in dia_wri_state (ocean routine)
340      !! CALL histclo( kid )
341      !
342    END SUBROUTINE ice_wri_state
343
344#else
345   !!----------------------------------------------------------------------
346   !!   Default option :         Empty module         NO ESIM sea-ice model
347   !!----------------------------------------------------------------------
348#endif
349
350   !!======================================================================
351END MODULE icewri
Note: See TracBrowser for help on using the repository browser.