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/2016/dev_r6859_LIM3_meltponds/NEMOGCM/NEMO/LIM_SRC_3 – NEMO

source: branches/2016/dev_r6859_LIM3_meltponds/NEMOGCM/NEMO/LIM_SRC_3/limwri.F90 @ 8142

Last change on this file since 8142 was 8142, checked in by vancop, 7 years ago

Melt pond interfaces practically operational

  • Property svn:keywords set to Id
File size: 22.9 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 ice
20   USE limvar
21   USE in_out_manager
22   USE lbclnk
23   USE lib_mpp         ! MPP library
24   USE wrk_nemo        ! work arrays
25   USE iom
26   USE timing          ! Timing
27   USE lib_fortran     ! Fortran utilities
28
29   IMPLICIT NONE
30   PRIVATE
31
32   PUBLIC lim_wri        ! routine called by lim_step.F90
33   PUBLIC lim_wri_state  ! called by dia_wri_state
34
35   !!----------------------------------------------------------------------
36   !! NEMO/LIM3 4.0 , UCL - NEMO Consortium (2011)
37   !! $Id$
38   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
39   !!----------------------------------------------------------------------
40CONTAINS
41
42   SUBROUTINE lim_wri( kindic )
43      !!-------------------------------------------------------------------
44      !!  This routine computes the average of some variables and write it
45      !!  on the ouput files.
46      !!  ATTENTION cette routine n'est valable que si le pas de temps est
47      !!  egale a une fraction entiere de 1 jours.
48      !!  Diff 1-D 3-D : suppress common also included in etat
49      !!                 suppress cmoymo 11-18
50      !!  modif : 03/06/98
51      !!-------------------------------------------------------------------
52      INTEGER, INTENT(in) ::   kindic   ! if kindic < 0 there has been an error somewhere
53      !
54      INTEGER  ::  ji, jj, jk, jl  ! dummy loop indices
55      REAL(wp) ::  z1_365
56      REAL(wp) ::  z2da, z2db, ztmp
57      REAL(wp), POINTER, DIMENSION(:,:,:) ::  zswi2
58      REAL(wp), POINTER, DIMENSION(:,:)   ::  z2d, zswi    ! 2D workspace
59      !!-------------------------------------------------------------------
60
61      IF( nn_timing == 1 )  CALL timing_start('limwri')
62
63      CALL wrk_alloc( jpi, jpj, jpl, zswi2 )
64      CALL wrk_alloc( jpi, jpj     , z2d, zswi )
65
66      !-----------------------------
67      ! Mean category values
68      !-----------------------------
69      z1_365 = 1._wp / 365._wp
70
71      ! brine volume
72      CALL lim_var_bv 
73
74      ! tresholds for outputs
75      DO jj = 1, jpj
76         DO ji = 1, jpi
77            zswi(ji,jj)  = MAX( 0._wp , SIGN( 1._wp , at_i(ji,jj) - epsi06 ) )
78         END DO
79      END DO
80      DO jl = 1, jpl
81         DO jj = 1, jpj
82            DO ji = 1, jpi
83               zswi2(ji,jj,jl)  = MAX( 0._wp , SIGN( 1._wp , a_i(ji,jj,jl) - epsi06 ) )
84            END DO
85         END DO
86      END DO
87      !
88      ! fluxes
89      ! pfrld is the lead fraction at the previous time step (actually between TRP and THD)
90      IF( iom_use('qsr_oce') )   CALL iom_put( "qsr_oce" , qsr_oce(:,:) * pfrld(:,:) )                                   !     solar flux at ocean surface
91      IF( iom_use('qns_oce') )   CALL iom_put( "qns_oce" , qns_oce(:,:) * pfrld(:,:) + qemp_oce(:,:) )                   ! non-solar flux at ocean surface
92      IF( iom_use('qsr_ice') )   CALL iom_put( "qsr_ice" , SUM( qsr_ice(:,:,:) * a_i_b(:,:,:), dim=3 ) )                 !     solar flux at ice surface
93      IF( iom_use('qns_ice') )   CALL iom_put( "qns_ice" , SUM( qns_ice(:,:,:) * a_i_b(:,:,:), dim=3 ) + qemp_ice(:,:) ) ! non-solar flux at ice surface
94      IF( iom_use('qtr_ice') )   CALL iom_put( "qtr_ice" , SUM( ftr_ice(:,:,:) * a_i_b(:,:,:), dim=3 ) )                 !     solar flux transmitted thru ice
95      IF( iom_use('qt_oce' ) )   CALL iom_put( "qt_oce"  , ( qsr_oce(:,:) + qns_oce(:,:) ) * pfrld(:,:) + qemp_oce(:,:) ) 
96      IF( iom_use('qt_ice' ) )   CALL iom_put( "qt_ice"  , SUM( ( qns_ice(:,:,:) + qsr_ice(:,:,:) )   &
97         &                                                      * a_i_b(:,:,:), dim=3 ) + qemp_ice(:,:) )
98      IF( iom_use('qemp_oce') )  CALL iom_put( "qemp_oce" , qemp_oce(:,:) ) 
99      IF( iom_use('qemp_ice') )  CALL iom_put( "qemp_ice" , qemp_ice(:,:) ) 
100      IF( iom_use('emp_oce' ) )  CALL iom_put( "emp_oce"  , emp_oce(:,:) )   ! emp over ocean (taking into account the snow blown away from the ice)
101      IF( iom_use('emp_ice' ) )  CALL iom_put( "emp_ice"  , emp_ice(:,:) )   ! emp over ice   (taking into account the snow blown away from the ice)
102
103      ! velocity
104      IF ( iom_use( "uice_ipa" ) .OR. iom_use( "vice_ipa" ) .OR. iom_use( "icevel" ) ) THEN
105         DO jj = 2 , jpjm1
106            DO ji = 2 , jpim1
107               z2da  = ( u_ice(ji,jj) * umask(ji,jj,1) + u_ice(ji-1,jj) * umask(ji-1,jj,1) ) * 0.5_wp
108               z2db  = ( v_ice(ji,jj) * vmask(ji,jj,1) + v_ice(ji,jj-1) * vmask(ji,jj-1,1) ) * 0.5_wp
109               z2d(ji,jj) = SQRT( z2da * z2da + z2db * z2db )
110           END DO
111         END DO
112         CALL lbc_lnk( z2d, 'T', 1. )
113         CALL iom_put( "uice_ipa"     , u_ice      )       ! ice velocity u component
114         CALL iom_put( "vice_ipa"     , v_ice      )       ! ice velocity v component
115         CALL iom_put( "icevel"       , z2d        )       ! ice velocity module
116      ENDIF
117
118      IF ( iom_use( "tau_icebfr" ) )    CALL iom_put( "tau_icebfr"  , tau_icebfr             )  ! ice friction with ocean bottom (landfast ice) 
119      !
120      IF ( iom_use( "miceage" ) )       CALL iom_put( "miceage"     , om_i * zswi * z1_365   )  ! mean ice age
121      IF ( iom_use( "icethic_cea" ) )   CALL iom_put( "icethic_cea" , htm_i * zswi           )  ! ice thickness mean
122      IF ( iom_use( "snowthic_cea" ) )  CALL iom_put( "snowthic_cea", htm_s * zswi           )  ! snow thickness mean
123      IF ( iom_use( "micet" ) )         CALL iom_put( "micet"       , ( tm_i  - rt0 ) * zswi )  ! ice mean    temperature
124      IF ( iom_use( "icest" ) )         CALL iom_put( "icest"       , ( tm_su - rt0 ) * zswi )  ! ice surface temperature
125      IF ( iom_use( "icecolf" ) )       CALL iom_put( "icecolf"     , hicol                  )  ! frazil ice collection thickness
126      !
127      CALL iom_put( "isst"        , sst_m               )        ! sea surface temperature
128      CALL iom_put( "isss"        , sss_m               )        ! sea surface salinity
129      CALL iom_put( "iceconc"     , at_i  * zswi        )        ! ice concentration
130      CALL iom_put( "icevolu"     , vt_i  * zswi        )        ! ice volume = mean ice thickness over the cell
131      CALL iom_put( "icehc"       , et_i  * zswi        )        ! ice total heat content
132      CALL iom_put( "isnowhc"     , et_s  * zswi        )        ! snow total heat content
133      CALL iom_put( "ibrinv"      , bvm_i * zswi * 100. )        ! brine volume
134      CALL iom_put( "utau_ice"    , utau_ice            )        ! wind stress over ice along i-axis at I-point
135      CALL iom_put( "vtau_ice"    , vtau_ice            )        ! wind stress over ice along j-axis at I-point
136      CALL iom_put( "snowpre"     , sprecip * 86400.    )        ! snow precipitation
137      CALL iom_put( "micesalt"    , smt_i   * zswi      )        ! mean ice salinity
138
139      CALL iom_put( "icestr"      , strength * zswi )    ! ice strength
140      CALL iom_put( "idive"       , divu_i * 1.0e8      )    ! divergence
141      CALL iom_put( "ishear"      , shear_i * 1.0e8     )    ! shear
142      CALL iom_put( "snowvol"     , vt_s   * zswi       )        ! snow volume
143     
144      CALL iom_put( "icetrp"      , diag_trp_vi * rday  )        ! ice volume transport
145      CALL iom_put( "snwtrp"      , diag_trp_vs * rday  )        ! snw volume transport
146      CALL iom_put( "saltrp"      , diag_trp_smv * rday * rhoic ) ! salt content transport
147      CALL iom_put( "deitrp"      , diag_trp_ei         )        ! advected ice enthalpy (W/m2)
148      CALL iom_put( "destrp"      , diag_trp_es         )        ! advected snw enthalpy (W/m2)
149
150      CALL iom_put( "sfxbog"      , sfx_bog * rday      )        ! salt flux from bottom growth
151      CALL iom_put( "sfxbom"      , sfx_bom * rday      )        ! salt flux from bottom melting
152      CALL iom_put( "sfxsum"      , sfx_sum * rday      )        ! salt flux from surface melting
153      CALL iom_put( "sfxlam"      , sfx_lam * rday      )        ! salt flux from lateral melting
154      CALL iom_put( "sfxsni"      , sfx_sni * rday      )        ! salt flux from snow ice formation
155      CALL iom_put( "sfxopw"      , sfx_opw * rday      )        ! salt flux from open water formation
156      CALL iom_put( "sfxdyn"      , sfx_dyn * rday      )        ! salt flux from ridging rafting
157      CALL iom_put( "sfxres"      , sfx_res * rday      )        ! salt flux from limupdate (resultant)
158      CALL iom_put( "sfxbri"      , sfx_bri * rday      )        ! salt flux from brines
159      CALL iom_put( "sfxsub"      , sfx_sub * rday      )        ! salt flux from sublimation
160      CALL iom_put( "sfx"         , sfx     * rday      )        ! total salt flux
161
162      ztmp = rday / rhoic
163      CALL iom_put( "vfxres"     , wfx_res * ztmp       )        ! daily prod./melting due to limupdate
164      CALL iom_put( "vfxopw"     , wfx_opw * ztmp       )        ! daily lateral thermodynamic ice production
165      CALL iom_put( "vfxsni"     , wfx_sni * ztmp       )        ! daily snowice ice production
166      CALL iom_put( "vfxbog"     , wfx_bog * ztmp       )        ! daily bottom thermodynamic ice production
167      CALL iom_put( "vfxdyn"     , wfx_dyn * ztmp       )        ! daily dynamic ice production (rid/raft)
168      CALL iom_put( "vfxsum"     , wfx_sum * ztmp       )        ! surface melt
169      CALL iom_put( "vfxbom"     , wfx_bom * ztmp       )        ! bottom melt
170      CALL iom_put( "vfxlam"     , wfx_lam * ztmp       )        ! lateral melt
171      CALL iom_put( "vfxice"     , wfx_ice * ztmp       )        ! total ice growth/melt
172
173      IF ( ln_pnd ) &
174         CALL iom_put( "vfxpnd"  , wfx_pnd * ztmp       )        ! melt pond water flux
175
176      IF ( iom_use( "vfxthin" ) ) THEN   ! ice production for open water + thin ice (<20cm) => comparable to observations 
177         WHERE( htm_i(:,:) < 0.2 .AND. htm_i(:,:) > 0. ) ; z2d = wfx_bog
178         ELSEWHERE                                       ; z2d = 0._wp
179         END WHERE
180         CALL iom_put( "vfxthin", ( wfx_opw + z2d ) * ztmp )
181      ENDIF
182
183      ztmp = rday / rhosn
184      CALL iom_put( "vfxspr"     , wfx_spr * ztmp       )        ! precip (snow)
185      CALL iom_put( "vfxsnw"     , wfx_snw * ztmp       )        ! total snw growth/melt
186      CALL iom_put( "vfxsub"     , wfx_sub * ztmp       )        ! sublimation (snow/ice)
187      CALL iom_put( "vfxsub_err" , wfx_err_sub * ztmp   )        ! "excess" of sublimation sent to ocean
188     
189      CALL iom_put( "afxtot"     , afx_tot * rday       )        ! concentration tendency (total)
190      CALL iom_put( "afxdyn"     , afx_dyn * rday       )        ! concentration tendency (dynamics)
191      CALL iom_put( "afxthd"     , afx_thd * rday       )        ! concentration tendency (thermo)
192
193      CALL iom_put ('hfxthd'     , hfx_thd(:,:)         )   
194      CALL iom_put ('hfxdyn'     , hfx_dyn(:,:)         )   
195      CALL iom_put ('hfxres'     , hfx_res(:,:)         )   
196      CALL iom_put ('hfxout'     , hfx_out(:,:)         )   
197      CALL iom_put ('hfxin'      , hfx_in(:,:)          )   
198      CALL iom_put ('hfxsnw'     , hfx_snw(:,:)         )   
199      CALL iom_put ('hfxsub'     , hfx_sub(:,:)         )   
200      CALL iom_put ('hfxerr'     , hfx_err(:,:)         )   
201      CALL iom_put ('hfxerr_rem' , hfx_err_rem(:,:)     )   
202     
203      CALL iom_put ('hfxsum'     , hfx_sum(:,:)         )   
204      CALL iom_put ('hfxbom'     , hfx_bom(:,:)         )   
205      CALL iom_put ('hfxbog'     , hfx_bog(:,:)         )   
206      CALL iom_put ('hfxdif'     , hfx_dif(:,:)         )   
207      CALL iom_put ('hfxopw'     , hfx_opw(:,:)         )   
208      CALL iom_put ('hfxtur'     , fhtur(:,:) * at_i_b(:,:) ) ! turbulent heat flux at ice base
209      CALL iom_put ('hfxdhc'     , diag_heat(:,:)       )   ! Heat content variation in snow and ice
210      CALL iom_put ('hfxspr'     , hfx_spr(:,:)         )   ! Heat content of snow precip
211
212      ! MV MP 2016
213      IF ( ln_pnd ) THEN
214         CALL iom_put( "iceamp"  , at_ip  * zswi        )   ! melt pond total fraction
215         CALL iom_put( "icevmp"  , vt_ip  * zswi        )   ! melt pond total volume per unit area
216      ENDIF
217      ! END MV MP 2016
218
219     
220      !--------------------------------
221      ! Output values for each category
222      !--------------------------------
223      IF ( iom_use( "iceconc_cat"  ) )  CALL iom_put( "iceconc_cat"      , a_i   * zswi2   )        ! area for categories
224      IF ( iom_use( "icethic_cat"  ) )  CALL iom_put( "icethic_cat"      , ht_i  * zswi2   )        ! thickness for categories
225      IF ( iom_use( "snowthic_cat" ) )  CALL iom_put( "snowthic_cat"     , ht_s  * zswi2   )        ! snow depth for categories
226      IF ( iom_use( "salinity_cat" ) )  CALL iom_put( "salinity_cat"     , sm_i  * zswi2   )        ! salinity for categories
227      ! ice temperature
228      IF ( iom_use( "icetemp_cat"  ) )  CALL iom_put( "icetemp_cat", ( SUM( t_i(:,:,:,:), dim=3 ) * r1_nlay_i - rt0 ) * zswi2 )
229      ! snow temperature
230      IF ( iom_use( "snwtemp_cat"  ) )  CALL iom_put( "snwtemp_cat", ( SUM( t_s(:,:,:,:), dim=3 ) * r1_nlay_s - rt0 ) * zswi2 )
231      ! ice age
232      IF ( iom_use( "iceage_cat"   ) )  CALL iom_put( "iceage_cat" , o_i * zswi2 * z1_365 )
233      ! brine volume
234      IF ( iom_use( "brinevol_cat" ) )  CALL iom_put( "brinevol_cat", bv_i * 100. * zswi2 )
235
236      ! MV MP 2016
237      IF ( ln_pnd ) THEN
238         IF ( iom_use( "iceamp_cat"  ) )  CALL iom_put( "iceamp_cat"     , a_ip       * zswi2   )       ! melt pond frac for categories
239         IF ( iom_use( "icevmp_cat"  ) )  CALL iom_put( "icevmp_cat"     , v_ip       * zswi2   )       ! melt pond frac for categories
240         IF ( iom_use( "icehmp_cat"  ) )  CALL iom_put( "icehmp_cat"     , h_ip       * zswi2   )       ! melt pond frac for categories
241         IF ( iom_use( "iceafp_cat"  ) )  CALL iom_put( "iceafp_cat"     , a_ip_frac  * zswi2   )       ! melt pond frac for categories
242      ENDIF
243      ! END MV MP 2016
244
245      !     !  Create an output files (output.lim.abort.nc) if S < 0 or u > 20 m/s
246      !     IF( kindic < 0 )   CALL lim_wri_state( 'output.abort' )
247      !     not yet implemented
248     
249      CALL wrk_dealloc( jpi, jpj, jpl, zswi2 )
250      CALL wrk_dealloc( jpi, jpj     , z2d, zswi )
251
252      IF( nn_timing == 1 )  CALL timing_stop('limwri')
253     
254   END SUBROUTINE lim_wri
255
256 
257   SUBROUTINE lim_wri_state( kt, kid, kh_i )
258      !!---------------------------------------------------------------------
259      !!                 ***  ROUTINE lim_wri_state  ***
260      !!       
261      !! ** Purpose :   create a NetCDF file named cdfile_name which contains
262      !!      the instantaneous ice state and forcing fields for ice model
263      !!        Used to find errors in the initial state or save the last
264      !!      ocean state in case of abnormal end of a simulation
265      !!
266      !! History :
267      !!   4.0  !  2013-06  (C. Rousset)
268      !!----------------------------------------------------------------------
269      INTEGER, INTENT( in )   ::   kt               ! ocean time-step index)
270      INTEGER, INTENT( in )   ::   kid , kh_i
271      INTEGER                 ::   nz_i, jl
272      REAL(wp), DIMENSION(jpl) :: jcat
273      !!----------------------------------------------------------------------
274      DO jl = 1, jpl
275         jcat(jl) = REAL(jl)
276      ENDDO
277     
278      CALL histvert( kid, "ncatice", "Ice Categories","", jpl, jcat, nz_i, "up")
279
280      CALL histdef( kid, "sithic", "Ice thickness"           , "m"      ,   &
281      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
282      CALL histdef( kid, "siconc", "Ice concentration"       , "%"      ,   &
283      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
284      CALL histdef( kid, "sitemp", "Ice temperature"         , "C"      ,   &
285      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
286      CALL histdef( kid, "sivelu", "i-Ice speed "            , "m/s"    ,   &
287      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
288      CALL histdef( kid, "sivelv", "j-Ice speed "            , "m/s"    ,   &
289      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
290      CALL histdef( kid, "sistru", "i-Wind stress over ice " , "Pa"     ,   &
291      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
292      CALL histdef( kid, "sistrv", "j-Wind stress over ice " , "Pa"     ,   &
293      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
294      CALL histdef( kid, "sisflx", "Solar flux over ocean"     , "w/m2" ,   &
295      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
296      CALL histdef( kid, "sinflx", "Non-solar flux over ocean" , "w/m2" ,   &
297      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
298      CALL histdef( kid, "isnowpre", "Snow precipitation"      , "kg/m2/s",   &
299      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
300      CALL histdef( kid, "sisali", "Ice salinity"            , "PSU"    ,   &
301      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
302      CALL histdef( kid, "sivolu", "Ice volume"              , "m"      ,   &
303      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
304      CALL histdef( kid, "sidive", "Ice divergence"          , "10-8s-1",   &
305      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
306
307      ! MV MP 2016
308      IF ( ln_pnd ) THEN
309         CALL histdef( kid, "si_amp", "Melt pond fraction"      , "%"      ,   &
310      &         jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
311         CALL histdef( kid, "si_vmp", "Melt pond volume"        ,  "m"     ,   &
312      &         jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
313      ENDIF
314      ! END MV MP 2016
315
316      CALL histdef( kid, "vfxbog", "Ice bottom production"   , "m/s"    ,   &
317      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
318      CALL histdef( kid, "vfxdyn", "Ice dynamic production"  , "m/s"    ,   &
319      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
320      CALL histdef( kid, "vfxopw", "Ice open water prod"     , "m/s"    ,   &
321      &       jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
322      CALL histdef( kid, "vfxsni", "Snow ice production "    , "m/s"    ,   &
323      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
324      CALL histdef( kid, "vfxres", "Ice prod from limupdate" , "m/s"    ,   &
325      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
326      CALL histdef( kid, "vfxbom", "Ice bottom melt"         , "m/s"    ,   &
327      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
328      CALL histdef( kid, "vfxsum", "Ice surface melt"        , "m/s"    ,   &
329      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
330
331      CALL histdef( kid, "sithicat", "Ice thickness"         , "m"      ,   &
332      &      jpi, jpj, kh_i, jpl, 1, jpl, nz_i, 32, "inst(x)", rdt, rdt )
333      CALL histdef( kid, "siconcat", "Ice concentration"     , "%"      ,   &
334      &      jpi, jpj, kh_i, jpl, 1, jpl, nz_i, 32, "inst(x)", rdt, rdt )
335      CALL histdef( kid, "sisalcat", "Ice salinity"           , ""      ,   &
336      &      jpi, jpj, kh_i, jpl, 1, jpl, nz_i, 32, "inst(x)", rdt, rdt )
337      CALL histdef( kid, "sitemcat", "Ice temperature"       , "C"      ,   &
338      &      jpi, jpj, kh_i, jpl, 1, jpl, nz_i, 32, "inst(x)", rdt, rdt )
339      CALL histdef( kid, "snthicat", "Snw thickness"         , "m"      ,   &
340      &      jpi, jpj, kh_i, jpl, 1, jpl, nz_i, 32, "inst(x)", rdt, rdt )
341      CALL histdef( kid, "sntemcat", "Snw temperature"       , "C"      ,   &
342      &      jpi, jpj, kh_i, jpl, 1, jpl, nz_i, 32, "inst(x)", rdt, rdt )
343
344      CALL histend( kid, snc4set )   ! end of the file definition
345
346      CALL histwrite( kid, "sithic", kt, htm_i         , jpi*jpj, (/1/) )   
347      CALL histwrite( kid, "siconc", kt, at_i          , jpi*jpj, (/1/) )
348      CALL histwrite( kid, "sitemp", kt, tm_i - rt0    , jpi*jpj, (/1/) )
349      CALL histwrite( kid, "sivelu", kt, u_ice          , jpi*jpj, (/1/) )
350      CALL histwrite( kid, "sivelv", kt, v_ice          , jpi*jpj, (/1/) )
351      CALL histwrite( kid, "sistru", kt, utau_ice       , jpi*jpj, (/1/) )
352      CALL histwrite( kid, "sistrv", kt, vtau_ice       , jpi*jpj, (/1/) )
353      CALL histwrite( kid, "sisflx", kt, qsr , jpi*jpj, (/1/) )
354      CALL histwrite( kid, "sinflx", kt, qns , jpi*jpj, (/1/) )
355      CALL histwrite( kid, "isnowpre", kt, sprecip        , jpi*jpj, (/1/) )
356      CALL histwrite( kid, "sisali", kt, smt_i          , jpi*jpj, (/1/) )
357      CALL histwrite( kid, "sivolu", kt, vt_i           , jpi*jpj, (/1/) )
358      CALL histwrite( kid, "sidive", kt, divu_i*1.0e8   , jpi*jpj, (/1/) )
359
360      ! MV MP 2016
361      IF ( ln_pnd ) THEN
362         CALL histwrite( kid, "si_amp", kt, at_ip         , jpi*jpj, (/1/) )
363         CALL histwrite( kid, "si_vmp", kt, vt_ip         , jpi*jpj, (/1/) )
364      ENDIF
365      ! END MV MP 2016
366
367      CALL histwrite( kid, "vfxbog", kt, wfx_bog        , jpi*jpj, (/1/) )
368      CALL histwrite( kid, "vfxdyn", kt, wfx_dyn        , jpi*jpj, (/1/) )
369      CALL histwrite( kid, "vfxopw", kt, wfx_opw        , jpi*jpj, (/1/) )
370      CALL histwrite( kid, "vfxsni", kt, wfx_sni        , jpi*jpj, (/1/) )
371      CALL histwrite( kid, "vfxres", kt, wfx_res        , jpi*jpj, (/1/) )
372      CALL histwrite( kid, "vfxbom", kt, wfx_bom        , jpi*jpj, (/1/) )
373      CALL histwrite( kid, "vfxsum", kt, wfx_sum        , jpi*jpj, (/1/) )
374      IF ( ln_pnd ) &
375         CALL histwrite( kid, "vfxpnd", kt, wfx_pnd     , jpi*jpj, (/1/) )
376
377      CALL histwrite( kid, "sithicat", kt, ht_i        , jpi*jpj*jpl, (/1/) )   
378      CALL histwrite( kid, "siconcat", kt, a_i         , jpi*jpj*jpl, (/1/) )   
379      CALL histwrite( kid, "sisalcat", kt, sm_i        , jpi*jpj*jpl, (/1/) )   
380      CALL histwrite( kid, "sitemcat", kt, tm_i - rt0  , jpi*jpj*jpl, (/1/) )   
381      CALL histwrite( kid, "snthicat", kt, ht_s        , jpi*jpj*jpl, (/1/) )   
382      CALL histwrite( kid, "sntemcat", kt, tm_su - rt0 , jpi*jpj*jpl, (/1/) )   
383
384      ! Close the file
385      ! -----------------
386      !CALL histclo( kid )
387
388    END SUBROUTINE lim_wri_state
389
390#else
391   !!----------------------------------------------------------------------
392   !!   Default option :         Empty module          NO LIM sea-ice model
393   !!----------------------------------------------------------------------
394CONTAINS
395   SUBROUTINE lim_wri          ! Empty routine
396   END SUBROUTINE lim_wri
397#endif
398
399   !!======================================================================
400END MODULE limwri
Note: See TracBrowser for help on using the repository browser.