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/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3 – NEMO

source: branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/limwri.F90 @ 8266

Last change on this file since 8266 was 8266, checked in by clem, 7 years ago

update outputs following simip requirements

  • Property svn:keywords set to Id
File size: 34.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 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
43   SUBROUTINE lim_wri( kindic )
44      !!-------------------------------------------------------------------
45      !!  This routine computes the average of some variables and write it
46      !!  on the ouput files.
47      !!  ATTENTION cette routine n'est valable que si le pas de temps est
48      !!  egale a une fraction entiere de 1 jours.
49      !!  Diff 1-D 3-D : suppress common also included in etat
50      !!                 suppress cmoymo 11-18
51      !!  modif : 03/06/98
52      !!-------------------------------------------------------------------
53      INTEGER, INTENT(in) ::   kindic   ! if kindic < 0 there has been an error somewhere
54      !
55      INTEGER  ::  ji, jj, jk, jl  ! dummy loop indices
56      REAL(wp) ::  z2da, z2db, ztmp, zrho1, zrho2, zmiss_val
57      REAL(wp), POINTER, DIMENSION(:,:,:) ::  zswi2, zmiss2
58      REAL(wp), POINTER, DIMENSION(:,:)   ::  z2d, zswi, zmiss !  2D workspace
59      REAL(wp), POINTER, DIMENSION(:,:)   ::  zfb              ! ice freeboard
60      REAL(wp), POINTER, DIMENSION(:,:)   ::  zamask, zamask15 ! 15% concentration mask
61
62      ! Global ice diagnostics (SIMIP)
63      REAL(wp) ::  zdiag_area_nh, &   ! area, extent, volume
64         &         zdiag_extt_nh, &
65         &         zdiag_area_sh, & 
66         &         zdiag_extt_sh, & 
67         &         zdiag_volu_nh, & 
68         &         zdiag_volu_sh 
69
70      !!-------------------------------------------------------------------
71
72      IF( nn_timing == 1 )  CALL timing_start('limwri')
73
74      CALL wrk_alloc( jpi, jpj, jpl, zswi2, zmiss2 )
75      CALL wrk_alloc( jpi, jpj     , z2d, zswi, zmiss )
76      CALL wrk_alloc( jpi, jpj     , zfb, zamask, zamask15 )
77
78      !----------------------------------------
79      ! Brine volume, switches, missing values
80      !----------------------------------------
81
82      ! brine volume
83      CALL lim_var_bv 
84
85      ! tresholds for outputs
86      DO jj = 1, jpj
87         DO ji = 1, jpi
88            zswi(ji,jj)      = MAX( 0._wp , SIGN( 1._wp , at_i(ji,jj) - epsi06 ) ) ! 1 if ice, 0 if no ice
89            zamask(ji,jj)    = MAX( 0._wp , SIGN( 1._wp , at_i(ji,jj) - 0.05   ) ) ! 1 if 5% ice, 0 if less - required to mask thickness and snow depth
90            zamask15(ji,jj)  = MAX( 0._wp , SIGN( 1._wp , at_i(ji,jj) - 0.15   ) ) ! 1 if 15% ice, 0 if less
91         END DO
92      END DO
93      DO jl = 1, jpl
94         DO jj = 1, jpj
95            DO ji = 1, jpi
96               zswi2(ji,jj,jl)  = MAX( 0._wp , SIGN( 1._wp , a_i(ji,jj,jl) - epsi06 ) )
97            END DO
98         END DO
99      END DO
100
101      zmiss_val     = -1.0e20
102      zmiss(:,:)    = zmiss_val * ( 1. - zswi(:,:) )
103      zmiss2(:,:,:) = zmiss_val * ( 1. - zswi2(:,:,:) )
104
105      !----------------------------------------
106      ! Standard outputs
107      !----------------------------------------
108      ! fluxes
109      ! pfrld is the lead fraction at the previous time step (actually between TRP and THD)
110      IF( iom_use('qsr_oce') )   CALL iom_put( "qsr_oce" , qsr_oce(:,:) * pfrld(:,:) )                                   !     solar flux at ocean surface
111      IF( iom_use('qns_oce') )   CALL iom_put( "qns_oce" , qns_oce(:,:) * pfrld(:,:) + qemp_oce(:,:) )                   ! non-solar flux at ocean surface
112      IF( iom_use('qsr_ice') )   CALL iom_put( "qsr_ice" , SUM( qsr_ice(:,:,:) * a_i_b(:,:,:), dim=3 ) )                 !     solar flux at ice surface
113      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
114      IF( iom_use('qtr_ice') )   CALL iom_put( "qtr_ice" , SUM( ftr_ice(:,:,:) * a_i_b(:,:,:), dim=3 ) )                 !     solar flux transmitted thru ice
115      IF( iom_use('qt_oce' ) )   CALL iom_put( "qt_oce"  , ( qsr_oce(:,:) + qns_oce(:,:) ) * pfrld(:,:) + qemp_oce(:,:) ) 
116      IF( iom_use('qt_ice' ) )   CALL iom_put( "qt_ice"  , SUM( ( qns_ice(:,:,:) + qsr_ice(:,:,:) )   &
117         &                                                      * a_i_b(:,:,:), dim=3 ) + qemp_ice(:,:) )
118      IF( iom_use('qemp_oce') )  CALL iom_put( "qemp_oce" , qemp_oce(:,:) ) 
119      IF( iom_use('qemp_ice') )  CALL iom_put( "qemp_ice" , qemp_ice(:,:) ) 
120      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)
121      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)
122
123      ! velocity
124      IF ( iom_use('uice_ipa') ) CALL iom_put( "uice_ipa"     , u_ice      )       ! ice velocity u component
125      IF ( iom_use('vice_ipa') ) CALL iom_put( "vice_ipa"     , v_ice      )       ! ice velocity v component
126
127      IF ( ( iom_use( "icevel" ) ) .OR. ( iom_use( "icevel_mv" ) ) ) THEN
128         DO jj = 2 , jpjm1
129            DO ji = 2 , jpim1
130               z2da  = ( u_ice(ji,jj) * umask(ji,jj,1) + u_ice(ji-1,jj) * umask(ji-1,jj,1) ) * 0.5_wp
131               z2db  = ( v_ice(ji,jj) * vmask(ji,jj,1) + v_ice(ji,jj-1) * vmask(ji,jj-1,1) ) * 0.5_wp
132               z2d(ji,jj) = SQRT( z2da * z2da + z2db * z2db )
133           END DO
134         END DO
135         CALL lbc_lnk( z2d, 'T', 1. )
136         IF ( iom_use( "icevel" )  )   CALL iom_put( "icevel"       , z2d        )                                            ! ice velocity module
137         IF ( iom_use( "icevel_mv" ) ) CALL iom_put( "icevel_mv"    , z2d(:,:) * zswi(:,:) + zmiss(:,:) )                     ! ice velocity module (missing value)
138      ENDIF
139
140      IF ( iom_use( "tau_icebfr" ) )    CALL iom_put( "tau_icebfr"  , tau_icebfr             )  ! ice friction with ocean bottom (landfast ice) 
141      !
142      IF ( iom_use( "miceage" ) )       CALL iom_put( "miceage"     , om_i * zswi * zamask15 )  ! mean ice age
143      IF ( iom_use( "micet" ) )         CALL iom_put( "micet"       , ( tm_i  - rt0 ) * zswi )  ! ice mean    temperature
144      IF ( iom_use( "icest" ) )         CALL iom_put( "icest"       , ( tm_su - rt0 ) * zswi )  ! ice surface temperature
145      IF ( iom_use( "icecolf" ) )       CALL iom_put( "icecolf"     , hicol                  )  ! frazil ice collection thickness
146      !
147      CALL iom_put( "isst"        , sst_m               )        ! sea surface temperature
148      CALL iom_put( "isss"        , sss_m               )        ! sea surface salinity
149      CALL iom_put( "iceconc"     , at_i  * zswi        )        ! ice concentration
150      CALL iom_put( "icevolu"     , vt_i  * zswi        )        ! ice volume = mean ice thickness over the cell
151      CALL iom_put( "icehc"       , et_i  * zswi        )        ! ice total heat content
152      CALL iom_put( "isnowhc"     , et_s  * zswi        )        ! snow total heat content
153      CALL iom_put( "ibrinv"      , bvm_i * zswi * 100. )        ! brine volume
154      CALL iom_put( "snowpre"     , sprecip * 86400.    )        ! snow precipitation
155      CALL iom_put( "micesalt"    , smt_i   * zswi      )        ! mean ice salinity
156
157      CALL iom_put( "idive"       , divu_i              )        ! divergence
158      CALL iom_put( "ishear"      , shear_i             )        ! shear
159      CALL iom_put( "snowvol"     , vt_s   * zswi       )        ! snow volume
160     
161      CALL iom_put( "icetrp"      , diag_trp_vi * rday  )        ! ice volume transport
162      CALL iom_put( "snwtrp"      , diag_trp_vs * rday  )        ! snw volume transport
163      CALL iom_put( "saltrp"      , diag_trp_smv * rday * rhoic ) ! salt content transport
164      CALL iom_put( "deitrp"      , diag_trp_ei         )        ! advected ice enthalpy (W/m2)
165      CALL iom_put( "destrp"      , diag_trp_es         )        ! advected snw enthalpy (W/m2)
166
167      CALL iom_put( "sfxbog"      , sfx_bog * rday      )        ! salt flux from bottom growth
168      CALL iom_put( "sfxbom"      , sfx_bom * rday      )        ! salt flux from bottom melting
169      CALL iom_put( "sfxsum"      , sfx_sum * rday      )        ! salt flux from surface melting
170      CALL iom_put( "sfxlam"      , sfx_lam * rday      )        ! salt flux from lateral melting
171      CALL iom_put( "sfxsni"      , sfx_sni * rday      )        ! salt flux from snow ice formation
172      CALL iom_put( "sfxopw"      , sfx_opw * rday      )        ! salt flux from open water formation
173      CALL iom_put( "sfxdyn"      , sfx_dyn * rday      )        ! salt flux from ridging rafting
174      CALL iom_put( "sfxres"      , sfx_res * rday      )        ! salt flux from limupdate (resultant)
175      CALL iom_put( "sfxbri"      , sfx_bri * rday      )        ! salt flux from brines
176      CALL iom_put( "sfxsub"      , sfx_sub * rday      )        ! salt flux from sublimation
177      CALL iom_put( "sfx"         , sfx     * rday      )        ! total salt flux
178
179      ztmp = rday / rhoic
180      CALL iom_put( "vfxres"     , wfx_res * ztmp       )        ! daily prod./melting due to limupdate
181      CALL iom_put( "vfxopw"     , wfx_opw * ztmp       )        ! daily lateral thermodynamic ice production
182      CALL iom_put( "vfxsni"     , wfx_sni * ztmp       )        ! daily snowice ice production
183      CALL iom_put( "vfxbog"     , wfx_bog * ztmp       )        ! daily bottom thermodynamic ice production
184      CALL iom_put( "vfxdyn"     , wfx_dyn * ztmp       )        ! daily dynamic ice production (rid/raft)
185      CALL iom_put( "vfxsum"     , wfx_sum * ztmp       )        ! surface melt
186      CALL iom_put( "vfxbom"     , wfx_bom * ztmp       )        ! bottom melt
187      CALL iom_put( "vfxlam"     , wfx_lam * ztmp       )        ! lateral melt
188      CALL iom_put( "vfxice"     , wfx_ice * ztmp       )        ! total ice growth/melt
189
190      IF ( ln_pnd ) &
191         CALL iom_put( "vfxpnd"  , wfx_pnd * ztmp       )        ! melt pond water flux
192
193      IF ( iom_use( "vfxthin" ) ) THEN   ! ice production for open water + thin ice (<20cm) => comparable to observations 
194         WHERE( htm_i(:,:) < 0.2 .AND. htm_i(:,:) > 0. ) ; z2d = wfx_bog
195         ELSEWHERE                                       ; z2d = 0._wp
196         END WHERE
197         CALL iom_put( "vfxthin", ( wfx_opw + z2d ) * ztmp )
198      ENDIF
199
200      ztmp = rday / rhosn
201      CALL iom_put( "vfxspr"     , wfx_spr * ztmp       )        ! precip (snow)
202      CALL iom_put( "vfxsnw"     , wfx_snw * ztmp       )        ! total snw growth/melt
203      CALL iom_put( "vfxsub"     , wfx_sub * ztmp       )        ! sublimation (snow/ice)
204      CALL iom_put( "vfxsub_err" , wfx_err_sub * ztmp   )        ! "excess" of sublimation sent to ocean     
205 
206      CALL iom_put( "afxtot"     , afx_tot              )        ! concentration tendency (total)
207      CALL iom_put( "afxdyn"     , afx_dyn              )        ! concentration tendency (dynamics)
208      CALL iom_put( "afxthd"     , afx_thd              )        ! concentration tendency (thermo)
209
210      CALL iom_put ('hfxthd'     , hfx_thd(:,:)         )   
211      CALL iom_put ('hfxdyn'     , hfx_dyn(:,:)         )   
212      CALL iom_put ('hfxres'     , hfx_res(:,:)         )   
213      CALL iom_put ('hfxout'     , hfx_out(:,:)         )   
214      CALL iom_put ('hfxin'      , hfx_in(:,:)          )   
215      CALL iom_put ('hfxsnw'     , hfx_snw(:,:)         )   
216      CALL iom_put ('hfxsub'     , hfx_sub(:,:)         )   
217      CALL iom_put ('hfxerr'     , hfx_err(:,:)         )   
218      CALL iom_put ('hfxerr_rem' , hfx_err_rem(:,:)     )   
219     
220      CALL iom_put ('hfxsum'     , hfx_sum(:,:)         )   
221      CALL iom_put ('hfxbom'     , hfx_bom(:,:)         )   
222      CALL iom_put ('hfxbog'     , hfx_bog(:,:)         )   
223      CALL iom_put ('hfxdif'     , hfx_dif(:,:)         )   
224      CALL iom_put ('hfxopw'     , hfx_opw(:,:)         )   
225      CALL iom_put ('hfxtur'     , fhtur(:,:) * at_i_b(:,:) ) ! turbulent heat flux at ice base
226      CALL iom_put ('hfxdhc'     , diag_heat(:,:)       )   ! Heat content variation in snow and ice
227      CALL iom_put ('hfxspr'     , hfx_spr(:,:)         )   ! Heat content of snow precip
228
229      ! MV MP 2016
230      IF ( ln_pnd ) THEN
231         CALL iom_put( "iceamp"  , at_ip  * zswi        )   ! melt pond total fraction
232         CALL iom_put( "icevmp"  , vt_ip  * zswi        )   ! melt pond total volume per unit area
233      ENDIF
234      ! END MV MP 2016
235
236      !----------------------------------
237      ! Output category-dependent fields
238      !----------------------------------
239      IF ( iom_use( "iceconc_cat"  ) )  CALL iom_put( "iceconc_cat"      , a_i   * zswi2   )        ! area for categories
240      IF ( iom_use( "icethic_cat"  ) )  CALL iom_put( "icethic_cat"      , ht_i  * zswi2   )        ! thickness for categories
241      IF ( iom_use( "snowthic_cat" ) )  CALL iom_put( "snowthic_cat"     , ht_s  * zswi2   )        ! snow depth for categories
242      IF ( iom_use( "salinity_cat" ) )  CALL iom_put( "salinity_cat"     , sm_i  * zswi2   )        ! salinity for categories
243      ! ice temperature
244      IF ( iom_use( "icetemp_cat"  ) )  CALL iom_put( "icetemp_cat", ( SUM( t_i(:,:,:,:), dim=3 ) * r1_nlay_i - rt0 ) * zswi2 )
245      ! snow temperature
246      IF ( iom_use( "snwtemp_cat"  ) )  CALL iom_put( "snwtemp_cat", ( SUM( t_s(:,:,:,:), dim=3 ) * r1_nlay_s - rt0 ) * zswi2 )
247      ! ice age
248      IF ( iom_use( "iceage_cat"   ) )  CALL iom_put( "iceage_cat" , o_i * zswi2 ) 
249      ! brine volume
250      IF ( iom_use( "brinevol_cat" ) )  CALL iom_put( "brinevol_cat", bv_i * 100. * zswi2 )
251
252      ! MV MP 2016
253      IF ( ln_pnd ) THEN
254         IF ( iom_use( "iceamp_cat"  ) )  CALL iom_put( "iceamp_cat"     , a_ip       * zswi2   )       ! melt pond frac for categories
255         IF ( iom_use( "icevmp_cat"  ) )  CALL iom_put( "icevmp_cat"     , v_ip       * zswi2   )       ! melt pond frac for categories
256         IF ( iom_use( "icehmp_cat"  ) )  CALL iom_put( "icehmp_cat"     , h_ip       * zswi2   )       ! melt pond frac for categories
257         IF ( iom_use( "iceafp_cat"  ) )  CALL iom_put( "iceafp_cat"     , a_ip_frac  * zswi2   )       ! melt pond frac for categories
258      ENDIF
259      ! END MV MP 2016
260
261      !--------------------------------
262      ! Add-ons for SIMIP
263      !--------------------------------
264      zrho1 = ( rau0 - rhoic ) / rau0; zrho2 = rhosn / rau0
265
266      IF  ( iom_use( "icepres"  ) ) CALL iom_put( "icepres"     , zswi(:,:)                     )                         ! Ice presence (1 or 0)
267      IF  ( iom_use( "icemass"  ) ) CALL iom_put( "icemass"     , rhoic * vt_i(:,:) * zswi(:,:) )                         ! Ice mass per cell area
268      IF  ( iom_use( "icethic"  ) ) CALL iom_put( "icethic"     , htm_i(:,:) * zamask(:,:)  * zswi(:,:) + zmiss(:,:) )    ! Ice thickness
269      IF  ( iom_use( "snomass"  ) ) CALL iom_put( "snomass"     , rhosn * vt_s(:,:)         * zswi(:,:) + zmiss(:,:) )    ! Snow mass per cell area
270      IF  ( iom_use( "snothic"  ) ) CALL iom_put( "snothic"     , htm_s(:,:) * zamask(:,:)  * zswi(:,:) + zmiss(:,:) )    ! Snow thickness       
271
272      IF  ( iom_use( "iceconc_cat_mv"  ) )  CALL iom_put( "iceconc_cat_mv" , a_i(:,:,:)  * zswi2(:,:,:) + zmiss2(:,:,:) ) ! Area for categories
273      IF  ( iom_use( "icethic_cat_mv"  ) )  CALL iom_put( "icethic_cat_mv" , ht_i(:,:,:) * zswi2(:,:,:) + zmiss2(:,:,:) ) ! Thickness for categories
274      IF  ( iom_use( "snowthic_cat_mv" ) )  CALL iom_put( "snowthic_cat_mv", ht_s(:,:,:) * zswi2(:,:,:) + zmiss2(:,:,:) ) ! Snow depth for categories
275
276      IF  ( iom_use( "icestK"   ) ) CALL iom_put( "icestK"      , tm_su(:,:)                * zswi(:,:) + zmiss(:,:) )    ! Ice surface temperature
277      IF  ( iom_use( "icesntK"  ) ) CALL iom_put( "icesntK"     , tm_si(:,:)                * zswi(:,:) + zmiss(:,:) )    ! Snow-ice interface temperature
278      IF  ( iom_use( "icebotK"  ) ) CALL iom_put( "icebotK"     , t_bo(:,:)                 * zswi(:,:) + zmiss(:,:) )    ! Ice bottom temperature
279      IF  ( iom_use( "iceage"   ) ) CALL iom_put( "iceage"      , om_i(:,:) * zamask15(:,:) * zswi(:,:) + zmiss(:,:) )    ! Ice age
280      IF  ( iom_use( "icesmass" ) ) CALL iom_put( "icesmass"    , SUM( smv_i, dim=3 ) * rhoic * 1.0e-3 * zswi(:,:)   )    ! Mass of salt in sea ice per cell area
281      IF  ( iom_use( "icesal"   ) ) CALL iom_put( "icesal"      , smt_i(:,:)                * zswi(:,:) + zmiss(:,:) )    ! Ice salinity
282
283      IF  ( iom_use( "icefb"    ) ) THEN
284         zfb(:,:) = ( zrho1 * htm_i(:,:) - zrho2 * htm_s(:,:) )                                         
285         WHERE( zfb < 0._wp ) ;   zfb = 0._wp ;   END WHERE
286                                    CALL iom_put( "icefb"       , zfb(:,:)                  * zswi(:,:) + zmiss(:,:) )    ! Ice freeboard
287      ENDIF
288
289      IF  ( iom_use( "isnhcneg" ) ) CALL iom_put( "isnhcneg"    , - et_s(:,:)               * zswi(:,:) + zmiss(:,:) )    ! Snow total heat content
290
291      IF  ( iom_use( "dmithd"   ) ) CALL iom_put( "dmithd"      , - wfx_bog - wfx_bom - wfx_sum   &                       ! Sea-ice mass change from thermodynamics
292              &                     - wfx_sni - wfx_opw - wfx_res )
293      IF  ( iom_use( "dmidyn"   ) ) CALL iom_put( "dmidyn"      ,   diag_dmi_dyn             )                            ! Sea-ice mass change from dynamics
294      IF  ( iom_use( "dmiopw"   ) ) CALL iom_put( "dmiopw"      , - wfx_opw                  )                            ! Sea-ice mass change through growth in open water
295      IF  ( iom_use( "dmibog"   ) ) CALL iom_put( "dmibog"      , - wfx_bog                  )                            ! Sea-ice mass change through basal growth
296      IF  ( iom_use( "dmisni"   ) ) CALL iom_put( "dmisni"      , - wfx_sni                  )                            ! Sea-ice mass change through snow-to-ice conversion
297      IF  ( iom_use( "dmisum"   ) ) CALL iom_put( "dmisum"      , - wfx_sum                  )                            ! Sea-ice mass change through surface melting
298      IF  ( iom_use( "dmibom"   ) ) CALL iom_put( "dmibom"      , - wfx_bom                  )                            ! Sea-ice mass change through bottom melting
299
300      IF  ( iom_use( "dmtsub"   ) ) CALL iom_put( "dmtsub"      , - wfx_sub                  )                            ! Sea-ice mass change through evaporation and sublimation
301      IF  ( iom_use( "dmssub"   ) ) CALL iom_put( "dmssub"      , - wfx_snw_sub              )                            ! Snow mass change through sublimation
302      IF  ( iom_use( "dmisub"   ) ) CALL iom_put( "dmisub"      , - wfx_ice_sub              )                            ! Sea-ice mass change through sublimation
303
304      IF  ( iom_use( "dmsspr"   ) ) CALL iom_put( "dmsspr"      , - wfx_spr                  )                            ! Snow mass change through snow fall
305      IF  ( iom_use( "dmsssi"   ) ) CALL iom_put( "dmsssi"      ,   wfx_sni*rhosn/rhoic      )                            ! Snow mass change through snow-to-ice conversion
306
307      IF  ( iom_use( "dmsmel"   ) ) CALL iom_put( "dmsmel"      , - wfx_snw_sum              )                            ! Snow mass change through melt
308      IF  ( iom_use( "dmsdyn"   ) ) CALL iom_put( "dmsdyn"      ,   diag_dms_dyn             )                            ! Snow mass change through dynamics
309
310      IF  ( iom_use( "hfxsenso" ) ) CALL iom_put( "hfxsenso"    ,   -fhtur(:,:)              * zswi(:,:) + zmiss(:,:) )   ! Sensible oceanic heat flux
311      IF  ( iom_use( "hfxconbo" ) ) CALL iom_put( "hfxconbo"    ,   diag_fc_bo               * zswi(:,:) + zmiss(:,:) )   ! Bottom conduction flux
312      IF  ( iom_use( "hfxconsu" ) ) CALL iom_put( "hfxconsu"    ,   diag_fc_su               * zswi(:,:) + zmiss(:,:) )   ! Surface conduction flux
313
314      IF  ( iom_use( "wfxtot"   ) ) CALL iom_put( "wfxtot"      ,   wfx_ice(:,:)             * zswi(:,:) + zmiss(:,:) )   ! Total freshwater flux from sea ice
315      IF  ( iom_use( "wfxsum"   ) ) CALL iom_put( "wfxsum"      ,   wfx_sum(:,:)             * zswi(:,:) + zmiss(:,:) )   ! Freshwater flux from sea-ice surface
316      IF  ( iom_use( "sfx_mv"   ) ) CALL iom_put( "sfx_mv"      ,   sfx(:,:) * 0.001         * zswi(:,:) + zmiss(:,:) )   ! Total salt flux
317
318      IF  ( iom_use( "uice_mv"  ) ) CALL iom_put( "uice_mv"     ,   u_ice(:,:)               * zswi(:,:) + zmiss(:,:) )   ! ice velocity u component
319      IF  ( iom_use( "vice_mv"  ) ) CALL iom_put( "vice_mv"     ,   v_ice(:,:)               * zswi(:,:) + zmiss(:,:) )   ! ice velocity v component
320     
321      IF  ( iom_use( "xmtrpice" ) ) CALL iom_put( "xmtrpice"     ,  diag_xmtrp_ice(:,:)      )                            ! X-component of sea-ice mass transport (kg/s)
322      IF  ( iom_use( "ymtrpice" ) ) CALL iom_put( "ymtrpice"     ,  diag_ymtrp_ice(:,:)      )                            ! Y-component of sea-ice mass transport
323
324      IF  ( iom_use( "xmtrpsnw" ) ) CALL iom_put( "xmtrpsnw"     ,  diag_xmtrp_snw(:,:)      )                            ! X-component of snow mass transport (kg/s)
325      IF  ( iom_use( "ymtrpsnw" ) ) CALL iom_put( "ymtrpsnw"     ,  diag_ymtrp_snw(:,:)      )                            ! Y-component of snow mass transport
326
327      IF  ( iom_use( "xatrp"    ) ) CALL iom_put( "xatrp"        ,  diag_xatrp(:,:)              )                        ! X-component of ice area transport
328      IF  ( iom_use( "yatrp"    ) ) CALL iom_put( "yatrp"        ,  diag_yatrp(:,:)              )                        ! Y-component of ice area transport
329
330      IF  ( iom_use( "utau_ice" ) ) CALL iom_put( "utau_ice"     ,  utau_ice(:,:)            * zswi(:,:) + zmiss(:,:) )   ! Wind stress term in force balance (x)
331      IF  ( iom_use( "vtau_ice" ) ) CALL iom_put( "vtau_ice"     ,  vtau_ice(:,:)            * zswi(:,:) + zmiss(:,:) )   ! Wind stress term in force balance (y)
332
333      IF  ( iom_use( "utau_oi"  ) ) CALL iom_put( "utau_oi"     ,   diag_utau_oi(:,:)        * zswi(:,:) + zmiss(:,:) )   ! Ocean stress term in force balance (x)
334      IF  ( iom_use( "vtau_oi"  ) ) CALL iom_put( "vtau_oi"     ,   diag_vtau_oi(:,:)        * zswi(:,:) + zmiss(:,:) )   ! Ocean stress term in force balance (y)
335
336      IF  ( iom_use( "icestr"   ) ) CALL iom_put( "icestr"      ,   strength(:,:)            * zswi(:,:) + zmiss(:,:) )   ! Ice strength
337
338      IF  ( iom_use( "dssh_dx"  ) ) CALL iom_put( "dssh_dx"     ,   diag_dssh_dx(:,:)        * zswi(:,:) + zmiss(:,:) )   ! Sea-surface tilt term in force balance (x)
339      IF  ( iom_use( "dssh_dy"  ) ) CALL iom_put( "dssh_dy"     ,   diag_dssh_dy(:,:)        * zswi(:,:) + zmiss(:,:) )   ! Sea-surface tilt term in force balance (y)
340
341      IF  ( iom_use( "corstrx"  ) ) CALL iom_put( "corstrx"     ,   diag_corstrx(:,:)        * zswi(:,:) + zmiss(:,:) )   ! Coriolis force term in force balance (x)
342      IF  ( iom_use( "corstry"  ) ) CALL iom_put( "corstry"     ,   diag_corstry(:,:)        * zswi(:,:) + zmiss(:,:) )   ! Coriolis force term in force balance (y)
343
344      IF  ( iom_use( "intstrx"  ) ) CALL iom_put( "intstrx"     ,   diag_intstrx(:,:)        * zswi(:,:) + zmiss(:,:) )   ! Internal force term in force balance (x)
345      IF  ( iom_use( "intstry"  ) ) CALL iom_put( "intstry"     ,   diag_intstry(:,:)        * zswi(:,:) + zmiss(:,:) )   ! Internal force term in force balance (y)
346
347      IF  ( iom_use( "normstr"  ) ) CALL iom_put( "normstr"     ,   diag_sig1(:,:) * zswi(:,:)   )                        ! Normal stress
348      IF  ( iom_use( "sheastr"  ) ) CALL iom_put( "sheastr"     ,   diag_sig2(:,:) * zswi(:,:)   )                        ! Shear stress
349
350      !--------------------------------
351      ! Global ice diagnostics (SIMIP)
352      !--------------------------------
353
354      IF ( iom_use( "NH_icearea" ) .OR. iom_use( "NH_icevolu" ) .OR. iom_use( "NH_iceextt" ) )   THEN   ! NH integrated diagnostics
355 
356         WHERE( ff_t > 0._wp ); zswi(:,:) = 1.0e-12
357         ELSEWHERE            ; zswi(:,:) = 0.
358         END WHERE
359
360         zdiag_area_nh = glob_sum( at_i(:,:) * zswi(:,:) * e1e2t(:,:) )
361         zdiag_volu_nh = glob_sum( vt_i(:,:) * zswi(:,:) * e1e2t(:,:) )
362
363         WHERE( ff_t > 0._wp .AND. at_i > 0.15 ); zswi(:,:) = 1.0e-12
364         ELSEWHERE                              ; zswi(:,:) = 0.
365         END WHERE
366
367         zdiag_extt_nh = glob_sum( zswi(:,:) * e1e2t(:,:) )
368
369         IF ( iom_use( "NH_icearea" ) ) CALL iom_put( "NH_icearea" ,  zdiag_area_nh  )
370         IF ( iom_use( "NH_icevolu" ) ) CALL iom_put( "NH_icevolu" ,  zdiag_volu_nh  )
371         IF ( iom_use( "NH_iceextt" ) ) CALL iom_put( "NH_iceextt" ,  zdiag_extt_nh  )
372
373      ENDIF
374
375      IF ( iom_use( "SH_icearea" ) .OR. iom_use( "SH_icevolu" ) .OR. iom_use( "SH_iceextt" ) )   THEN   ! SH integrated diagnostics
376
377         WHERE( ff_t < 0._wp ); zswi(:,:) = 1.0e-12; 
378         ELSEWHERE            ; zswi(:,:) = 0.
379         END WHERE
380
381         zdiag_area_sh = glob_sum( at_i(:,:) * zswi(:,:) * e1e2t(:,:) ) 
382         zdiag_volu_sh = glob_sum( vt_i(:,:) * zswi(:,:) * e1e2t(:,:) )
383
384         WHERE( ff_t < 0._wp .AND. at_i > 0.15 ); zswi(:,:) = 1.0e-12
385         ELSEWHERE                              ; zswi(:,:) = 0.
386         END WHERE
387
388         zdiag_extt_sh = glob_sum( zswi(:,:) * e1e2t(:,:) )
389
390         IF ( iom_use( "SH_icearea" ) ) CALL iom_put( "SH_icearea", zdiag_area_sh )
391         IF ( iom_use( "SH_icevolu" ) ) CALL iom_put( "SH_icevolu", zdiag_volu_sh )
392         IF ( iom_use( "SH_iceextt" ) ) CALL iom_put( "SH_iceextt", zdiag_extt_sh )
393
394      ENDIF 
395
396      !     !  Create an output files (output.lim.abort.nc) if S < 0 or u > 20 m/s
397      !     IF( kindic < 0 )   CALL lim_wri_state( 'output.abort' )
398      !     not yet implemented
399     
400      CALL wrk_dealloc( jpi, jpj, jpl, zswi2, zmiss2 )
401      CALL wrk_dealloc( jpi, jpj     , z2d, zswi, zmiss )
402      CALL wrk_dealloc( jpi, jpj     , zfb, zamask, zamask15 )
403
404      IF( nn_timing == 1 )  CALL timing_stop('limwri')
405     
406   END SUBROUTINE lim_wri
407
408 
409   SUBROUTINE lim_wri_state( kt, kid, kh_i )
410      !!---------------------------------------------------------------------
411      !!                 ***  ROUTINE lim_wri_state  ***
412      !!       
413      !! ** Purpose :   create a NetCDF file named cdfile_name which contains
414      !!      the instantaneous ice state and forcing fields for ice model
415      !!        Used to find errors in the initial state or save the last
416      !!      ocean state in case of abnormal end of a simulation
417      !!
418      !! History :
419      !!   4.0  !  2013-06  (C. Rousset)
420      !!----------------------------------------------------------------------
421      INTEGER, INTENT( in )   ::   kt               ! ocean time-step index)
422      INTEGER, INTENT( in )   ::   kid , kh_i
423      INTEGER                 ::   nz_i, jl
424      REAL(wp), DIMENSION(jpl) :: jcat
425      !!----------------------------------------------------------------------
426      DO jl = 1, jpl
427         jcat(jl) = REAL(jl)
428      ENDDO
429     
430      CALL histvert( kid, "ncatice", "Ice Categories","", jpl, jcat, nz_i, "up")
431
432      CALL histdef( kid, "sithic", "Ice thickness"           , "m"      ,   &
433      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
434      CALL histdef( kid, "siconc", "Ice concentration"       , "%"      ,   &
435      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
436      CALL histdef( kid, "sitemp", "Ice temperature"         , "C"      ,   &
437      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
438      CALL histdef( kid, "sivelu", "i-Ice speed "            , "m/s"    ,   &
439      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
440      CALL histdef( kid, "sivelv", "j-Ice speed "            , "m/s"    ,   &
441      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
442      CALL histdef( kid, "sistru", "i-Wind stress over ice " , "Pa"     ,   &
443      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
444      CALL histdef( kid, "sistrv", "j-Wind stress over ice " , "Pa"     ,   &
445      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
446      CALL histdef( kid, "sisflx", "Solar flux over ocean"     , "w/m2" ,   &
447      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
448      CALL histdef( kid, "sinflx", "Non-solar flux over ocean" , "w/m2" ,   &
449      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
450      CALL histdef( kid, "isnowpre", "Snow precipitation"      , "kg/m2/s",   &
451      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
452      CALL histdef( kid, "sisali", "Ice salinity"            , "PSU"    ,   &
453      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
454      CALL histdef( kid, "sivolu", "Ice volume"              , "m"      ,   &
455      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
456      CALL histdef( kid, "sidive", "Ice divergence"          , "10-8s-1",   &
457      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
458
459      ! MV MP 2016
460      IF ( ln_pnd ) THEN
461         CALL histdef( kid, "si_amp", "Melt pond fraction"      , "%"      ,   &
462      &         jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
463         CALL histdef( kid, "si_vmp", "Melt pond volume"        ,  "m"     ,   &
464      &         jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
465      ENDIF
466      ! END MV MP 2016
467
468      CALL histdef( kid, "vfxbog", "Ice bottom production"   , "m/s"    ,   &
469      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
470      CALL histdef( kid, "vfxdyn", "Ice dynamic production"  , "m/s"    ,   &
471      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
472      CALL histdef( kid, "vfxopw", "Ice open water prod"     , "m/s"    ,   &
473      &       jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
474      CALL histdef( kid, "vfxsni", "Snow ice production "    , "m/s"    ,   &
475      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
476      CALL histdef( kid, "vfxres", "Ice prod from limupdate" , "m/s"    ,   &
477      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
478      CALL histdef( kid, "vfxbom", "Ice bottom melt"         , "m/s"    ,   &
479      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
480      CALL histdef( kid, "vfxsum", "Ice surface melt"        , "m/s"    ,   &
481      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
482
483      CALL histdef( kid, "sithicat", "Ice thickness"         , "m"      ,   &
484      &      jpi, jpj, kh_i, jpl, 1, jpl, nz_i, 32, "inst(x)", rdt, rdt )
485      CALL histdef( kid, "siconcat", "Ice concentration"     , "%"      ,   &
486      &      jpi, jpj, kh_i, jpl, 1, jpl, nz_i, 32, "inst(x)", rdt, rdt )
487      CALL histdef( kid, "sisalcat", "Ice salinity"           , ""      ,   &
488      &      jpi, jpj, kh_i, jpl, 1, jpl, nz_i, 32, "inst(x)", rdt, rdt )
489      CALL histdef( kid, "sitemcat", "Ice temperature"       , "C"      ,   &
490      &      jpi, jpj, kh_i, jpl, 1, jpl, nz_i, 32, "inst(x)", rdt, rdt )
491      CALL histdef( kid, "snthicat", "Snw thickness"         , "m"      ,   &
492      &      jpi, jpj, kh_i, jpl, 1, jpl, nz_i, 32, "inst(x)", rdt, rdt )
493      CALL histdef( kid, "sntemcat", "Snw temperature"       , "C"      ,   &
494      &      jpi, jpj, kh_i, jpl, 1, jpl, nz_i, 32, "inst(x)", rdt, rdt )
495
496      CALL histend( kid, snc4set )   ! end of the file definition
497
498      CALL histwrite( kid, "sithic", kt, htm_i         , jpi*jpj, (/1/) )   
499      CALL histwrite( kid, "siconc", kt, at_i          , jpi*jpj, (/1/) )
500      CALL histwrite( kid, "sitemp", kt, tm_i - rt0    , jpi*jpj, (/1/) )
501      CALL histwrite( kid, "sivelu", kt, u_ice          , jpi*jpj, (/1/) )
502      CALL histwrite( kid, "sivelv", kt, v_ice          , jpi*jpj, (/1/) )
503      CALL histwrite( kid, "sistru", kt, utau_ice       , jpi*jpj, (/1/) )
504      CALL histwrite( kid, "sistrv", kt, vtau_ice       , jpi*jpj, (/1/) )
505      CALL histwrite( kid, "sisflx", kt, qsr , jpi*jpj, (/1/) )
506      CALL histwrite( kid, "sinflx", kt, qns , jpi*jpj, (/1/) )
507      CALL histwrite( kid, "isnowpre", kt, sprecip        , jpi*jpj, (/1/) )
508      CALL histwrite( kid, "sisali", kt, smt_i          , jpi*jpj, (/1/) )
509      CALL histwrite( kid, "sivolu", kt, vt_i           , jpi*jpj, (/1/) )
510      CALL histwrite( kid, "sidive", kt, divu_i*1.0e8   , jpi*jpj, (/1/) )
511
512      ! MV MP 2016
513      IF ( ln_pnd ) THEN
514         CALL histwrite( kid, "si_amp", kt, at_ip         , jpi*jpj, (/1/) )
515         CALL histwrite( kid, "si_vmp", kt, vt_ip         , jpi*jpj, (/1/) )
516      ENDIF
517      ! END MV MP 2016
518
519      CALL histwrite( kid, "vfxbog", kt, wfx_bog        , jpi*jpj, (/1/) )
520      CALL histwrite( kid, "vfxdyn", kt, wfx_dyn        , jpi*jpj, (/1/) )
521      CALL histwrite( kid, "vfxopw", kt, wfx_opw        , jpi*jpj, (/1/) )
522      CALL histwrite( kid, "vfxsni", kt, wfx_sni        , jpi*jpj, (/1/) )
523      CALL histwrite( kid, "vfxres", kt, wfx_res        , jpi*jpj, (/1/) )
524      CALL histwrite( kid, "vfxbom", kt, wfx_bom        , jpi*jpj, (/1/) )
525      CALL histwrite( kid, "vfxsum", kt, wfx_sum        , jpi*jpj, (/1/) )
526      IF ( ln_pnd ) &
527         CALL histwrite( kid, "vfxpnd", kt, wfx_pnd     , jpi*jpj, (/1/) )
528
529      CALL histwrite( kid, "sithicat", kt, ht_i        , jpi*jpj*jpl, (/1/) )   
530      CALL histwrite( kid, "siconcat", kt, a_i         , jpi*jpj*jpl, (/1/) )   
531      CALL histwrite( kid, "sisalcat", kt, sm_i        , jpi*jpj*jpl, (/1/) )   
532      CALL histwrite( kid, "sitemcat", kt, tm_i - rt0  , jpi*jpj*jpl, (/1/) )   
533      CALL histwrite( kid, "snthicat", kt, ht_s        , jpi*jpj*jpl, (/1/) )   
534      CALL histwrite( kid, "sntemcat", kt, tm_su - rt0 , jpi*jpj*jpl, (/1/) )   
535
536      ! Close the file
537      ! -----------------
538      !CALL histclo( kid )
539
540    END SUBROUTINE lim_wri_state
541
542#else
543   !!----------------------------------------------------------------------
544   !!   Default option :         Empty module          NO LIM sea-ice model
545   !!----------------------------------------------------------------------
546CONTAINS
547   SUBROUTINE lim_wri          ! Empty routine
548   END SUBROUTINE lim_wri
549#endif
550
551   !!======================================================================
552END MODULE limwri
Note: See TracBrowser for help on using the repository browser.