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 @ 8239

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

merge with v3_6_CMIP6_ice_diagnostics@r8238

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