New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
icewri.F90 in branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3 – NEMO

source: branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icewri.F90 @ 8498

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

changes in style - part2 -

File size: 32.0 KB
Line 
1MODULE icewri
2   !!======================================================================
3   !!                     ***  MODULE  icewri  ***
4   !!         Ice diagnostics :  write ice output files
5   !!======================================================================
6#if defined key_lim3
7   !!----------------------------------------------------------------------
8   !!   'key_lim3'                                      LIM3 sea-ice model
9   !!----------------------------------------------------------------------
10   !!   ice_wri       : write of the diagnostics variables in ouput file
11   !!   ice_wri_state : write for initial state or/and abandon
12   !!----------------------------------------------------------------------
13   USE dianam         ! build name of file (routine)
14   USE phycst         ! physical constant
15   USE dom_oce        ! domain: ocean
16   USE sbc_oce        ! surf. boundary cond.: ocean
17   USE sbc_ice        ! Surface boundary condition: ice fields
18   USE ice            ! sea-ice: variables
19   USE icevar         ! sea-ice: operations
20   !
21   USE ioipsl         !
22   USE in_out_manager !
23   USE lbclnk         !
24   USE lib_mpp        ! MPP library
25   USE iom            !
26   USE timing         ! Timing
27   USE lib_fortran    ! Fortran utilities
28
29   IMPLICIT NONE
30   PRIVATE
31
32   PUBLIC ice_wri        ! called by ice_stp
33   PUBLIC ice_wri_state  ! called by dia_wri_state
34
35   !!----------------------------------------------------------------------
36   !! NEMO/ICE 4.0 , NEMO Consortium (2017)
37   !! $Id: icewri.F90 8409 2017-08-07 15:29:21Z clem $
38   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
39   !!----------------------------------------------------------------------
40CONTAINS
41
42   SUBROUTINE ice_wri( 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) ::  z2da, z2db, ztmp, zrho1, zrho2, zmiss_val
56      REAL(wp), DIMENSION(jpi,jpj)     ::  z2d, zswi, zmiss !  2D workspace
57      REAL(wp), DIMENSION(jpi,jpj)     ::  zfb              ! ice freeboard
58      REAL(wp), DIMENSION(jpi,jpj)     ::  zamask, zamask15 ! 15% concentration mask
59      REAL(wp), DIMENSION(jpi,jpj,jpl) ::  zswi2, zmiss2
60      !
61      ! Global ice diagnostics (SIMIP)
62      REAL(wp) ::  zdiag_area_nh, zdiag_extt_nh, zdiag_volu_nh   ! area, extent, volume
63      REAL(wp) ::  zdiag_area_sh, zdiag_extt_sh, zdiag_volu_sh 
64      !!-------------------------------------------------------------------
65
66      IF( nn_timing == 1 )   CALL timing_start('icewri')
67
68      !----------------------------------------
69      ! Brine volume, switches, missing values
70      !----------------------------------------
71
72      CALL ice_var_bv      ! brine volume
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 ) ) ! 1 if ice, 0 if no ice
78            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
79            zamask15(ji,jj)  = MAX( 0._wp , SIGN( 1._wp , at_i(ji,jj) - 0.15   ) ) ! 1 if 15% ice, 0 if less
80         END DO
81      END DO
82      DO jl = 1, jpl
83         DO jj = 1, jpj
84            DO ji = 1, jpi
85               zswi2(ji,jj,jl)  = MAX( 0._wp , SIGN( 1._wp , a_i(ji,jj,jl) - epsi06 ) )
86            END DO
87         END DO
88      END DO
89
90      zmiss_val     = 1.e20_wp
91      zmiss (:,:)   = zmiss_val * ( 1._wp - zswi (:,:) )
92      zmiss2(:,:,:) = zmiss_val * ( 1._wp - zswi2(:,:,:) )
93
94      !----------------------------------------
95      ! Standard outputs
96      !----------------------------------------
97      ! fluxes
98      IF( iom_use('qsr_oce') )   CALL iom_put( "qsr_oce" , qsr_oce(:,:) * ( 1._wp - at_i_b(:,:) ) )                      !     solar flux at ocean surface
99      IF( iom_use('qns_oce') )   CALL iom_put( "qns_oce" , qns_oce(:,:) * ( 1._wp - at_i_b(:,:) ) + qemp_oce(:,:) )      ! non-solar flux at ocean surface
100      IF( iom_use('qsr_ice') )   CALL iom_put( "qsr_ice" , SUM( qsr_ice(:,:,:) * a_i_b(:,:,:), dim=3 ) )                 !     solar flux at ice surface
101      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
102      IF( iom_use('qtr_ice') )   CALL iom_put( "qtr_ice" , SUM( ftr_ice(:,:,:) * a_i_b(:,:,:), dim=3 ) )                 !     solar flux transmitted thru ice
103      IF( iom_use('qt_oce' ) )   CALL iom_put( "qt_oce"  , ( qsr_oce(:,:) + qns_oce(:,:) ) * ( 1._wp - at_i_b(:,:) ) + qemp_oce(:,:) )
104      IF( iom_use('qt_ice' ) )   CALL iom_put( "qt_ice"  , SUM( ( qns_ice(:,:,:) + qsr_ice(:,:,:) )   &
105         &                                                      * a_i_b(:,:,:), dim=3 ) + qemp_ice(:,:) )
106!!gm I don't understand the variable below.... why not multiplied by a_i_b or (1-a_i_b) ???
107      IF( iom_use('qemp_oce') )  CALL iom_put( "qemp_oce" , qemp_oce(:,:) ) 
108      IF( iom_use('qemp_ice') )  CALL iom_put( "qemp_ice" , qemp_ice(:,:) ) 
109      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)
110      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)
111
112      ! velocity
113      IF( iom_use('uice_ipa') )  CALL iom_put( "uice_ipa" , u_ice         )   ! ice velocity u component
114      IF( iom_use('vice_ipa') )  CALL iom_put( "vice_ipa" , v_ice         )   ! ice velocity v component
115
116      IF( iom_use('icevel') .OR. iom_use('icevel_mv') ) THEN
117         DO jj = 2 , jpjm1
118            DO ji = 2 , jpim1
119               z2da  = ( u_ice(ji,jj) + u_ice(ji-1,jj) )
120               z2db  = ( v_ice(ji,jj) + v_ice(ji,jj-1) )
121               z2d(ji,jj) = 0.5_wp * SQRT( z2da * z2da + z2db * z2db )
122           END DO
123         END DO
124         CALL lbc_lnk( z2d, 'T', 1. )
125         IF( iom_use('icevel'   ) )   CALL iom_put( "icevel"       , z2d        )                          ! ice velocity module
126         IF( iom_use('icevel_mv') )   CALL iom_put( "icevel_mv"    , z2d(:,:) * zswi(:,:) + zmiss(:,:) )   ! ice velocity module (missing value)
127      ENDIF
128
129      IF( iom_use('tau_icebfr') )     CALL iom_put( "tau_icebfr"  , tau_icebfr             )  ! ice friction with ocean bottom (landfast ice) 
130      !
131      IF( iom_use('miceage')  )       CALL iom_put( "miceage"     , om_i * zswi * zamask15 )  ! mean ice age
132      IF( iom_use('micet')    )       CALL iom_put( "micet"       , ( tm_i  - rt0 ) * zswi )  ! ice mean    temperature
133      IF( iom_use('icest')    )       CALL iom_put( "icest"       , ( tm_su - rt0 ) * zswi )  ! ice surface temperature
134      IF( iom_use('icecolf')  )       CALL iom_put( "icecolf"     , hicol                  )  ! frazil ice collection thickness
135      !
136      CALL iom_put( "isst"        , sst_m               )        ! sea surface temperature
137      CALL iom_put( "isss"        , sss_m               )        ! sea surface salinity
138      CALL iom_put( "iceconc"     , at_i  * zswi        )        ! ice concentration
139      CALL iom_put( "icevolu"     , vt_i  * zswi        )        ! ice volume = mean ice thickness over the cell
140      CALL iom_put( "icethick"    , htm_i * zswi        )        ! ice thickness
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( "snowpre"     , sprecip * 86400.    )        ! snow precipitation [m/day]
145      CALL iom_put( "micesalt"    , smt_i   * zswi      )        ! mean ice salinity
146      CALL iom_put( "snowvol"     , vt_s    * zswi      )        ! snow volume
147
148      CALL iom_put( "idive"       , divu_i(:,:)  * zswi(:,:) + zmiss(:,:) )   ! divergence
149      CALL iom_put( "ishear"      , shear_i(:,:) * zswi(:,:) + zmiss(:,:) )   ! shear
150     
151      CALL iom_put( "icetrp"      , diag_trp_vi * rday  )        ! ice volume transport
152      CALL iom_put( "snwtrp"      , diag_trp_vs * rday  )        ! snw volume transport
153      CALL iom_put( "saltrp"      , diag_trp_smv * rday * rhoic ) ! salt content transport
154      CALL iom_put( "deitrp"      , diag_trp_ei         )        ! advected ice enthalpy (W/m2)
155      CALL iom_put( "destrp"      , diag_trp_es         )        ! advected snw enthalpy (W/m2)
156
157      CALL iom_put( "sfxbog"      , sfx_bog * rday      )        ! salt flux from bottom growth
158      CALL iom_put( "sfxbom"      , sfx_bom * rday      )        ! salt flux from bottom melting
159      CALL iom_put( "sfxsum"      , sfx_sum * rday      )        ! salt flux from surface melting
160      CALL iom_put( "sfxlam"      , sfx_lam * rday      )        ! salt flux from lateral melting
161      CALL iom_put( "sfxsni"      , sfx_sni * rday      )        ! salt flux from snow ice formation
162      CALL iom_put( "sfxopw"      , sfx_opw * rday      )        ! salt flux from open water formation
163      CALL iom_put( "sfxdyn"      , sfx_dyn * rday      )        ! salt flux from ridging rafting
164      CALL iom_put( "sfxres"      , sfx_res * rday      )        ! salt flux from corrections (resultant)
165      CALL iom_put( "sfxbri"      , sfx_bri * rday      )        ! salt flux from brines
166      CALL iom_put( "sfxsub"      , sfx_sub * rday      )        ! salt flux from sublimation
167      CALL iom_put( "sfx"         , sfx     * rday      )        ! total salt flux
168
169      ztmp = rday / rhoic
170      CALL iom_put( "vfxres"     , wfx_res * ztmp       )        ! daily prod./melting due to corrections
171      CALL iom_put( "vfxopw"     , wfx_opw * ztmp       )        ! daily lateral thermodynamic ice production
172      CALL iom_put( "vfxsni"     , wfx_sni * ztmp       )        ! daily snowice ice production
173      CALL iom_put( "vfxbog"     , wfx_bog * ztmp       )        ! daily bottom thermodynamic ice production
174      CALL iom_put( "vfxdyn"     , wfx_dyn * ztmp       )        ! daily dynamic ice production (rid/raft)
175      CALL iom_put( "vfxsum"     , wfx_sum * ztmp       )        ! surface melt
176      CALL iom_put( "vfxbom"     , wfx_bom * ztmp       )        ! bottom melt
177      CALL iom_put( "vfxlam"     , wfx_lam * ztmp       )        ! lateral melt
178      CALL iom_put( "vfxice"     , wfx_ice * ztmp       )        ! total ice growth/melt
179
180      IF ( ln_pnd ) &
181         CALL iom_put( "vfxpnd"  , wfx_pnd * ztmp       )        ! melt pond water flux
182
183      IF ( iom_use( "vfxthin" ) ) THEN   ! ice production for open water + thin ice (<20cm) => comparable to observations 
184         WHERE( htm_i(:,:) < 0.2 .AND. htm_i(:,:) > 0. ) ; z2d = wfx_bog
185         ELSEWHERE                                       ; z2d = 0._wp
186         END WHERE
187         CALL iom_put( "vfxthin", ( wfx_opw + z2d ) * ztmp )
188      ENDIF
189
190      ztmp = rday / rhosn
191      CALL iom_put( "vfxspr"     , wfx_spr * ztmp       )        ! precip (snow)
192      CALL iom_put( "vfxsnw"     , wfx_snw * ztmp       )        ! total snw growth/melt
193      CALL iom_put( "vfxsub"     , wfx_sub * ztmp       )        ! sublimation (snow/ice)
194      CALL iom_put( "vfxsub_err" , wfx_err_sub * ztmp   )        ! "excess" of sublimation sent to ocean     
195 
196      CALL iom_put ('hfxthd'     , hfx_thd(:,:)         )   
197      CALL iom_put ('hfxdyn'     , hfx_dyn(:,:)         )   
198      CALL iom_put ('hfxres'     , hfx_res(:,:)         )   
199      CALL iom_put ('hfxout'     , hfx_out(:,:)         )   
200      CALL iom_put ('hfxin'      , hfx_in(:,:)          )   
201      CALL iom_put ('hfxsnw'     , hfx_snw(:,:)         )   
202      CALL iom_put ('hfxsub'     , hfx_sub(:,:)         )   
203      CALL iom_put ('hfxerr'     , hfx_err(:,:)         )   
204      CALL iom_put ('hfxerr_rem' , hfx_err_rem(:,:)     )   
205     
206      CALL iom_put ('hfxsum'     , hfx_sum(:,:)         )   
207      CALL iom_put ('hfxbom'     , hfx_bom(:,:)         )   
208      CALL iom_put ('hfxbog'     , hfx_bog(:,:)         )   
209      CALL iom_put ('hfxdif'     , hfx_dif(:,:)         )   
210      CALL iom_put ('hfxopw'     , hfx_opw(:,:)         )   
211      CALL iom_put ('hfxtur'     , fhtur(:,:) * at_i_b(:,:) ) ! turbulent heat flux at ice base
212      CALL iom_put ('hfxdhc'     , diag_heat(:,:)       )   ! Heat content variation in snow and ice
213      CALL iom_put ('hfxspr'     , hfx_spr(:,:)         )   ! Heat content of snow precip
214
215!!gm ====>>>>>  THIS should be moved where at_ip, vt_ip are computed fro the last time in the time-step  (limmpd)
216      ! MV MP 2016
217      IF ( ln_pnd ) THEN
218         CALL iom_put( "iceamp"  , at_ip  * zswi        )   ! melt pond total fraction
219         CALL iom_put( "icevmp"  , vt_ip  * zswi        )   ! melt pond total volume per unit area
220      ENDIF
221      ! END MV MP 2016
222!!gm  <<<<<<======= end
223
224      !----------------------------------
225      ! Output category-dependent fields
226      !----------------------------------
227      IF ( iom_use('iceconc_cat' ) )  CALL iom_put( "iceconc_cat"      , a_i   * zswi2   )        ! area for categories
228      IF ( iom_use('icethic_cat' ) )  CALL iom_put( "icethic_cat"      , ht_i  * zswi2   )        ! thickness for categories
229      IF ( iom_use('snowthic_cat') )  CALL iom_put( "snowthic_cat"     , ht_s  * zswi2   )        ! snow depth for categories
230      IF ( iom_use('salinity_cat') )  CALL iom_put( "salinity_cat"     , sm_i  * zswi2   )        ! salinity for categories
231      IF ( iom_use('icetemp_cat' ) )  CALL iom_put( "icetemp_cat", ( SUM( t_i(:,:,:,:), dim=3 ) * r1_nlay_i - rt0 ) * zswi2 )    ! ice temperature
232      IF ( iom_use('snwtemp_cat' ) )  CALL iom_put( "snwtemp_cat", ( SUM( t_s(:,:,:,:), dim=3 ) * r1_nlay_s - rt0 ) * zswi2 )    ! snow temperature
233      IF ( iom_use('iceage_cat'  ) )  CALL iom_put( "iceage_cat" , o_i * zswi2 )                   ! ice age
234      IF ( iom_use('brinevol_cat') )  CALL iom_put( "brinevol_cat", bv_i * 100. * zswi2 )          ! brine volume
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      !--------------------------------
246      ! Add-ons for SIMIP
247      !--------------------------------
248      zrho1 = ( rau0 - rhoic ) / rau0; zrho2 = rhosn / rau0
249
250      IF ( iom_use( "icepres"  ) ) CALL iom_put( "icepres"     , zswi(:,:)                     )                                ! Ice presence (1 or 0)
251      IF ( iom_use( "icemass"  ) ) CALL iom_put( "icemass"     , rhoic * vt_i(:,:) * zswi(:,:) )                                ! Ice mass per cell area
252      IF ( iom_use( "icethic"  ) ) CALL iom_put( "icethic"     , htm_i(:,:) * zamask(:,:)  + ( 1. - zamask(:,:) ) * zmiss_val )     ! Ice thickness
253      IF ( iom_use( "snomass"  ) ) CALL iom_put( "snomass"     , rhosn * vt_s(:,:)         * zswi(:,:) + zmiss(:,:) )           ! Snow mass per cell area
254      IF ( iom_use( "snothic"  ) ) CALL iom_put( "snothic"     , htm_s(:,:) * zamask(:,:)  + ( 1. - zamask(:,:) ) * zmiss_val )     ! Snow thickness       
255
256      IF ( iom_use( "iceconc_cat_mv"  ) )  CALL iom_put( "iceconc_cat_mv" , a_i(:,:,:)  * zswi2(:,:,:) + zmiss2(:,:,:) )        ! Area for categories
257      IF ( iom_use( "icethic_cat_mv"  ) )  CALL iom_put( "icethic_cat_mv" , ht_i(:,:,:) * zswi2(:,:,:) + zmiss2(:,:,:) )        ! Thickness for categories
258      IF ( iom_use( "snowthic_cat_mv" ) )  CALL iom_put( "snowthic_cat_mv", ht_s(:,:,:) * zswi2(:,:,:) + zmiss2(:,:,:) )        ! Snow depth for categories
259
260      IF ( iom_use( "icestK"   ) ) CALL iom_put( "icestK"      , tm_su(:,:)                * zswi(:,:) + zmiss(:,:) )           ! Ice surface temperature
261      IF ( iom_use( "icesntK"  ) ) CALL iom_put( "icesntK"     , tm_si(:,:)                * zswi(:,:) + zmiss(:,:) )           ! Snow-ice interface temperature
262      IF ( iom_use( "icebotK"  ) ) CALL iom_put( "icebotK"     , t_bo(:,:)                 * zswi(:,:) + zmiss(:,:) )           ! Ice bottom temperature
263      IF ( iom_use( "iceage"   ) ) CALL iom_put( "iceage"      , om_i(:,:) * zamask15(:,:) + ( 1. - zamask15(:,:) ) * zmiss_val )   ! Ice age
264      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
265      IF ( iom_use( "icesal"   ) ) CALL iom_put( "icesal"      , smt_i(:,:)                * zswi(:,:) + zmiss(:,:) )           ! Ice salinity
266
267      IF ( iom_use( "icefb"    ) ) THEN
268         zfb(:,:) = ( zrho1 * htm_i(:,:) - zrho2 * htm_s(:,:) )                                         
269         WHERE( zfb < 0._wp ) ;   zfb = 0._wp ;   END WHERE
270                                   CALL iom_put( "icefb"       , zfb(:,:)                  * zswi(:,:) + zmiss(:,:) )           ! Ice freeboard
271      ENDIF
272
273      IF ( iom_use( "isnhcneg" ) ) CALL iom_put( "isnhcneg"    , - et_s(:,:)               * zswi(:,:) + zmiss(:,:) )           ! Snow total heat content
274
275      IF ( iom_use( "dmithd"   ) ) CALL iom_put( "dmithd"      , - wfx_bog - wfx_bom - wfx_sum   &                       ! Sea-ice mass change from thermodynamics
276              &                                                   - wfx_sni - wfx_opw - wfx_res )
277      IF ( iom_use( "dmidyn"   ) ) CALL iom_put( "dmidyn"      ,   diag_dmi_dyn             )                            ! Sea-ice mass change from dynamics
278      IF ( iom_use( "dmiopw"   ) ) CALL iom_put( "dmiopw"      , - wfx_opw                  )                            ! Sea-ice mass change through growth in open water
279      IF ( iom_use( "dmibog"   ) ) CALL iom_put( "dmibog"      , - wfx_bog                  )                            ! Sea-ice mass change through basal growth
280      IF ( iom_use( "dmisni"   ) ) CALL iom_put( "dmisni"      , - wfx_sni                  )                            ! Sea-ice mass change through snow-to-ice conversion
281      IF ( iom_use( "dmisum"   ) ) CALL iom_put( "dmisum"      , - wfx_sum                  )                            ! Sea-ice mass change through surface melting
282      IF ( iom_use( "dmibom"   ) ) CALL iom_put( "dmibom"      , - wfx_bom                  )                            ! Sea-ice mass change through bottom melting
283
284      IF ( iom_use( "dmtsub"   ) ) CALL iom_put( "dmtsub"      , - wfx_sub                  )                            ! Sea-ice mass change through evaporation and sublimation
285      IF ( iom_use( "dmssub"   ) ) CALL iom_put( "dmssub"      , - wfx_snw_sub              )                            ! Snow mass change through sublimation
286      IF ( iom_use( "dmisub"   ) ) CALL iom_put( "dmisub"      , - wfx_ice_sub              )                            ! Sea-ice mass change through sublimation
287
288      IF ( iom_use( "dmsspr"   ) ) CALL iom_put( "dmsspr"      , - wfx_spr                  )                            ! Snow mass change through snow fall
289      IF ( iom_use( "dmsssi"   ) ) CALL iom_put( "dmsssi"      ,   wfx_sni*rhosn/rhoic      )                            ! Snow mass change through snow-to-ice conversion
290
291      IF ( iom_use( "dmsmel"   ) ) CALL iom_put( "dmsmel"      , - wfx_snw_sum              )                            ! Snow mass change through melt
292      IF ( iom_use( "dmsdyn"   ) ) CALL iom_put( "dmsdyn"      ,   diag_dms_dyn             )                            ! Snow mass change through dynamics
293
294      IF ( iom_use( "hfxsenso" ) ) CALL iom_put( "hfxsenso"    ,   -fhtur(:,:)              * zswi(:,:) + zmiss(:,:) )   ! Sensible oceanic heat flux
295      IF ( iom_use( "hfxconbo" ) ) CALL iom_put( "hfxconbo"    ,   diag_fc_bo               * zswi(:,:) + zmiss(:,:) )   ! Bottom conduction flux
296      IF ( iom_use( "hfxconsu" ) ) CALL iom_put( "hfxconsu"    ,   diag_fc_su               * zswi(:,:) + zmiss(:,:) )   ! Surface conduction flux
297
298      IF ( iom_use( "wfxtot"   ) ) CALL iom_put( "wfxtot"      ,   wfx_ice(:,:)             * zswi(:,:) + zmiss(:,:) )   ! Total freshwater flux from sea ice
299      IF ( iom_use( "wfxsum"   ) ) CALL iom_put( "wfxsum"      ,   wfx_sum(:,:)             * zswi(:,:) + zmiss(:,:) )   ! Freshwater flux from sea-ice surface
300      IF ( iom_use( "sfx_mv"   ) ) CALL iom_put( "sfx_mv"      ,   sfx(:,:) * 0.001         * zswi(:,:) + zmiss(:,:) )   ! Total salt flux
301
302      IF ( iom_use( "uice_mv"  ) ) CALL iom_put( "uice_mv"     ,   u_ice(:,:)               * zswi(:,:) + zmiss(:,:) )   ! ice velocity u component
303      IF ( iom_use( "vice_mv"  ) ) CALL iom_put( "vice_mv"     ,   v_ice(:,:)               * zswi(:,:) + zmiss(:,:) )   ! ice velocity v component
304     
305      IF ( iom_use( "utau_ice" ) ) CALL iom_put( "utau_ice"     ,  utau_ice(:,:)            * zswi(:,:) + zmiss(:,:) )   ! Wind stress term in force balance (x)
306      IF ( iom_use( "vtau_ice" ) ) CALL iom_put( "vtau_ice"     ,  vtau_ice(:,:)            * zswi(:,:) + zmiss(:,:) )   ! Wind stress term in force balance (y)
307
308
309      IF ( iom_use( "icestr"   ) ) CALL iom_put( "icestr"      ,   strength(:,:)            * zswi(:,:) + zmiss(:,:) )   ! Ice strength
310
311      !--------------------------------
312      ! Global ice diagnostics (SIMIP)
313      !--------------------------------
314      !
315      IF ( iom_use( "NH_icearea" ) .OR. iom_use( "NH_icevolu" ) .OR. iom_use( "NH_iceextt" ) )   THEN   ! NH diagnostics
316         !
317         WHERE( ff_t > 0._wp )   ;   zswi(:,:) = 1.0e-12
318         ELSEWHERE               ;   zswi(:,:) = 0.
319         END WHERE
320         zdiag_area_nh = glob_sum( at_i(:,:) * zswi(:,:) * e1e2t(:,:) )
321         zdiag_volu_nh = glob_sum( vt_i(:,:) * zswi(:,:) * e1e2t(:,:) )
322         !
323         WHERE( ff_t > 0._wp .AND. at_i > 0.15 )   ; zswi(:,:) = 1.0e-12
324         ELSEWHERE                                 ; zswi(:,:) = 0.
325         END WHERE
326         zdiag_extt_nh = glob_sum( zswi(:,:) * e1e2t(:,:) )
327         !
328         IF ( iom_use( "NH_icearea" ) )   CALL iom_put( "NH_icearea" ,  zdiag_area_nh  )
329         IF ( iom_use( "NH_icevolu" ) )   CALL iom_put( "NH_icevolu" ,  zdiag_volu_nh  )
330         IF ( iom_use( "NH_iceextt" ) )   CALL iom_put( "NH_iceextt" ,  zdiag_extt_nh  )
331         !
332      ENDIF
333      !
334      IF ( iom_use( "SH_icearea" ) .OR. iom_use( "SH_icevolu" ) .OR. iom_use( "SH_iceextt" ) )   THEN   ! SH diagnostics
335         !
336         WHERE( ff_t < 0._wp ); zswi(:,:) = 1.0e-12; 
337         ELSEWHERE            ; zswi(:,:) = 0.
338         END WHERE
339         zdiag_area_sh = glob_sum( at_i(:,:) * zswi(:,:) * e1e2t(:,:) ) 
340         zdiag_volu_sh = glob_sum( vt_i(:,:) * zswi(:,:) * e1e2t(:,:) )
341         !
342         WHERE( ff_t < 0._wp .AND. at_i > 0.15 ); zswi(:,:) = 1.0e-12
343         ELSEWHERE                              ; zswi(:,:) = 0.
344         END WHERE
345         zdiag_extt_sh = glob_sum( zswi(:,:) * e1e2t(:,:) )
346         !
347         IF ( iom_use( "SH_icearea" ) ) CALL iom_put( "SH_icearea", zdiag_area_sh )
348         IF ( iom_use( "SH_icevolu" ) ) CALL iom_put( "SH_icevolu", zdiag_volu_sh )
349         IF ( iom_use( "SH_iceextt" ) ) CALL iom_put( "SH_iceextt", zdiag_extt_sh )
350         !
351      ENDIF 
352      !
353!!CR      !     !  Create an output files (output.lim.abort.nc) if S < 0 or u > 20 m/s
354!!CR      !     IF( kindic < 0 )   CALL ice_wri_state( 'output.abort' )
355!!CR      !     not yet implemented
356!!gm  idem for the ocean...  Ask Seb how to get read of ioipsl....
357      !
358      IF( nn_timing == 1 )  CALL timing_stop('icewri')
359      !
360   END SUBROUTINE ice_wri
361
362 
363   SUBROUTINE ice_wri_state( kt, kid, kh_i )
364      !!---------------------------------------------------------------------
365      !!                 ***  ROUTINE ice_wri_state  ***
366      !!       
367      !! ** Purpose :   create a NetCDF file named cdfile_name which contains
368      !!      the instantaneous ice state and forcing fields for ice model
369      !!        Used to find errors in the initial state or save the last
370      !!      ocean state in case of abnormal end of a simulation
371      !!
372      !! History :   4.0  !  2013-06  (C. Rousset)
373      !!----------------------------------------------------------------------
374      INTEGER, INTENT( in )   ::   kt               ! ocean time-step index)
375      INTEGER, INTENT( in )   ::   kid , kh_i
376      INTEGER                 ::   nz_i, jl
377      REAL(wp), DIMENSION(jpl) :: jcat
378      !!----------------------------------------------------------------------
379      !
380      DO jl = 1, jpl
381         jcat(jl) = REAL(jl)
382      END DO
383     
384      CALL histvert( kid, "ncatice", "Ice Categories","", jpl, jcat, nz_i, "up")
385
386      CALL histdef( kid, "sithic", "Ice thickness"           , "m"      ,   &
387      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
388      CALL histdef( kid, "siconc", "Ice concentration"       , "%"      ,   &
389      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
390      CALL histdef( kid, "sitemp", "Ice temperature"         , "C"      ,   &
391      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
392      CALL histdef( kid, "sivelu", "i-Ice speed "            , "m/s"    ,   &
393      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
394      CALL histdef( kid, "sivelv", "j-Ice speed "            , "m/s"    ,   &
395      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
396      CALL histdef( kid, "sistru", "i-Wind stress over ice " , "Pa"     ,   &
397      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
398      CALL histdef( kid, "sistrv", "j-Wind stress over ice " , "Pa"     ,   &
399      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
400      CALL histdef( kid, "sisflx", "Solar flux over ocean"     , "w/m2" ,   &
401      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
402      CALL histdef( kid, "sinflx", "Non-solar flux over ocean" , "w/m2" ,   &
403      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
404      CALL histdef( kid, "isnowpre", "Snow precipitation"      , "kg/m2/s",   &
405      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
406      CALL histdef( kid, "sisali", "Ice salinity"            , "PSU"    ,   &
407      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
408      CALL histdef( kid, "sivolu", "Ice volume"              , "m"      ,   &
409      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
410      CALL histdef( kid, "sidive", "Ice divergence"          , "10-8s-1",   &
411      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
412
413      ! MV MP 2016
414      IF ( ln_pnd ) THEN
415         CALL histdef( kid, "si_amp", "Melt pond fraction"      , "%"      ,   &
416      &         jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
417         CALL histdef( kid, "si_vmp", "Melt pond volume"        ,  "m"     ,   &
418      &         jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
419      ENDIF
420      ! END MV MP 2016
421
422      CALL histdef( kid, "vfxbog", "Ice bottom production"   , "m/s"    ,   &
423      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
424      CALL histdef( kid, "vfxdyn", "Ice dynamic production"  , "m/s"    ,   &
425      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
426      CALL histdef( kid, "vfxopw", "Ice open water prod"     , "m/s"    ,   &
427      &       jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
428      CALL histdef( kid, "vfxsni", "Snow ice production "    , "m/s"    ,   &
429      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
430      CALL histdef( kid, "vfxres", "Ice prod from corrections" , "m/s"  ,   &
431      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
432      CALL histdef( kid, "vfxbom", "Ice bottom melt"         , "m/s"    ,   &
433      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
434      CALL histdef( kid, "vfxsum", "Ice surface melt"        , "m/s"    ,   &
435      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )
436
437      CALL histdef( kid, "sithicat", "Ice thickness"         , "m"      ,   &
438      &      jpi, jpj, kh_i, jpl, 1, jpl, nz_i, 32, "inst(x)", rdt, rdt )
439      CALL histdef( kid, "siconcat", "Ice concentration"     , "%"      ,   &
440      &      jpi, jpj, kh_i, jpl, 1, jpl, nz_i, 32, "inst(x)", rdt, rdt )
441      CALL histdef( kid, "sisalcat", "Ice salinity"           , ""      ,   &
442      &      jpi, jpj, kh_i, jpl, 1, jpl, nz_i, 32, "inst(x)", rdt, rdt )
443      CALL histdef( kid, "sitemcat", "Ice temperature"       , "C"      ,   &
444      &      jpi, jpj, kh_i, jpl, 1, jpl, nz_i, 32, "inst(x)", rdt, rdt )
445      CALL histdef( kid, "snthicat", "Snw thickness"         , "m"      ,   &
446      &      jpi, jpj, kh_i, jpl, 1, jpl, nz_i, 32, "inst(x)", rdt, rdt )
447      CALL histdef( kid, "sntemcat", "Snw temperature"       , "C"      ,   &
448      &      jpi, jpj, kh_i, jpl, 1, jpl, nz_i, 32, "inst(x)", rdt, rdt )
449
450      CALL histend( kid, snc4set )   ! end of the file definition
451
452      CALL histwrite( kid, "sithic", kt, htm_i         , jpi*jpj, (/1/) )   
453      CALL histwrite( kid, "siconc", kt, at_i          , jpi*jpj, (/1/) )
454      CALL histwrite( kid, "sitemp", kt, tm_i - rt0    , jpi*jpj, (/1/) )
455      CALL histwrite( kid, "sivelu", kt, u_ice          , jpi*jpj, (/1/) )
456      CALL histwrite( kid, "sivelv", kt, v_ice          , jpi*jpj, (/1/) )
457      CALL histwrite( kid, "sistru", kt, utau_ice       , jpi*jpj, (/1/) )
458      CALL histwrite( kid, "sistrv", kt, vtau_ice       , jpi*jpj, (/1/) )
459      CALL histwrite( kid, "sisflx", kt, qsr , jpi*jpj, (/1/) )
460      CALL histwrite( kid, "sinflx", kt, qns , jpi*jpj, (/1/) )
461      CALL histwrite( kid, "isnowpre", kt, sprecip        , jpi*jpj, (/1/) )
462      CALL histwrite( kid, "sisali", kt, smt_i          , jpi*jpj, (/1/) )
463      CALL histwrite( kid, "sivolu", kt, vt_i           , jpi*jpj, (/1/) )
464      CALL histwrite( kid, "sidive", kt, divu_i*1.0e8   , jpi*jpj, (/1/) )
465
466      ! MV MP 2016
467      IF ( ln_pnd ) THEN
468         CALL histwrite( kid, "si_amp", kt, at_ip         , jpi*jpj, (/1/) )
469         CALL histwrite( kid, "si_vmp", kt, vt_ip         , jpi*jpj, (/1/) )
470      ENDIF
471      ! END MV MP 2016
472
473      CALL histwrite( kid, "vfxbog", kt, wfx_bog        , jpi*jpj, (/1/) )
474      CALL histwrite( kid, "vfxdyn", kt, wfx_dyn        , jpi*jpj, (/1/) )
475      CALL histwrite( kid, "vfxopw", kt, wfx_opw        , jpi*jpj, (/1/) )
476      CALL histwrite( kid, "vfxsni", kt, wfx_sni        , jpi*jpj, (/1/) )
477      CALL histwrite( kid, "vfxres", kt, wfx_res        , jpi*jpj, (/1/) )
478      CALL histwrite( kid, "vfxbom", kt, wfx_bom        , jpi*jpj, (/1/) )
479      CALL histwrite( kid, "vfxsum", kt, wfx_sum        , jpi*jpj, (/1/) )
480      IF ( ln_pnd ) &
481         CALL histwrite( kid, "vfxpnd", kt, wfx_pnd     , jpi*jpj, (/1/) )
482
483      CALL histwrite( kid, "sithicat", kt, ht_i        , jpi*jpj*jpl, (/1/) )   
484      CALL histwrite( kid, "siconcat", kt, a_i         , jpi*jpj*jpl, (/1/) )   
485      CALL histwrite( kid, "sisalcat", kt, sm_i        , jpi*jpj*jpl, (/1/) )   
486      CALL histwrite( kid, "sitemcat", kt, tm_i - rt0  , jpi*jpj*jpl, (/1/) )   
487      CALL histwrite( kid, "snthicat", kt, ht_s        , jpi*jpj*jpl, (/1/) )   
488      CALL histwrite( kid, "sntemcat", kt, tm_su - rt0 , jpi*jpj*jpl, (/1/) )   
489
490      ! Close the file
491      ! -----------------
492!!gm I don't understand why the file is not closed !
493      !CALL histclo( kid )
494      !
495    END SUBROUTINE ice_wri_state
496
497#else
498   !!----------------------------------------------------------------------
499   !!   Default option :         Empty module          NO LIM sea-ice model
500   !!----------------------------------------------------------------------
501#endif
502
503   !!======================================================================
504END MODULE icewri
Note: See TracBrowser for help on using the repository browser.