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

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

source: branches/2016/v3_6_CMIP6_ice_diagnostics/NEMOGCM/NEMO/LIM_SRC_3/limwri.F90 @ 8271

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

missing value sign

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