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 NEMO/releases/release-4.0/src/ICE – NEMO

source: NEMO/releases/release-4.0/src/ICE/icewri.F90 @ 10910

Last change on this file since 10910 was 10910, checked in by clem, 5 years ago

Major change: the advection scheme UMx has been revisited to clean all the unphysical values which occured. Minor change: the ref config SPITZ12 has been slightly modified to test more parameterizations that are available in the code (melt ponds and landfast)

  • Property svn:keywords set to Id
File size: 17.2 KB
RevLine 
[8586]1MODULE icewri
2   !!======================================================================
3   !!                     ***  MODULE  icewri  ***
4   !!   sea-ice : output ice variables
5   !!======================================================================
[9604]6   !! History :  4.0  !  2018     (many people)      SI3 [aka Sea Ice cube]
7   !!----------------------------------------------------------------------
[9570]8#if defined key_si3
[8586]9   !!----------------------------------------------------------------------
[9570]10   !!   'key_si3'                                       SI3 sea-ice model
[8586]11   !!----------------------------------------------------------------------
12   !!   ice_wri       : write of the diagnostics variables in ouput file
13   !!   ice_wri_state : write for initial state or/and abandon
14   !!----------------------------------------------------------------------
15   USE dianam         ! build name of file (routine)
16   USE phycst         ! physical constant
17   USE dom_oce        ! domain: ocean
18   USE sbc_oce        ! surf. boundary cond.: ocean
19   USE sbc_ice        ! Surface boundary condition: ice fields
20   USE ice            ! sea-ice: variables
21   USE icevar         ! sea-ice: operations
22   !
23   USE ioipsl         !
24   USE in_out_manager ! I/O manager
25   USE iom            ! I/O manager library
26   USE lib_mpp        ! MPP library
27   USE lib_fortran    ! fortran utilities (glob_sum + no signed zero)
28   USE lbclnk         ! lateral boundary conditions (or mpp links)
29   USE timing         ! Timing
30
31   IMPLICIT NONE
32   PRIVATE
33
34   PUBLIC ice_wri        ! called by ice_stp
35   PUBLIC ice_wri_state  ! called by dia_wri_state
36
37   !!----------------------------------------------------------------------
[9598]38   !! NEMO/ICE 4.0 , NEMO Consortium (2018)
[10069]39   !! $Id$
[10413]40   !! Software governed by the CeCILL licence     (./LICENSE)
[8586]41   !!----------------------------------------------------------------------
42CONTAINS
43
44   SUBROUTINE ice_wri( kt )
45      !!-------------------------------------------------------------------
[9604]46      !!  This routine ouputs some (most?) of the sea ice fields
[8586]47      !!-------------------------------------------------------------------
48      INTEGER, INTENT(in) ::   kt   ! time-step
49      !
[8884]50      INTEGER  ::   ji, jj, jk, jl  ! dummy loop indices
51      REAL(wp) ::   z2da, z2db, zrho1, zrho2
[10413]52      REAL(wp), DIMENSION(jpi,jpj)     ::   z2d, zfast !  2D workspace
[9433]53      REAL(wp), DIMENSION(jpi,jpj)     ::   zmsk00, zmsk05, zmsk15, zmsksn ! O%, 5% and 15% concentration mask and snow mask
54      REAL(wp), DIMENSION(jpi,jpj,jpl) ::   zmsk00l, zmsksnl               ! cat masks
[8586]55      !
56      ! Global ice diagnostics (SIMIP)
[8884]57      REAL(wp) ::   zdiag_area_nh, zdiag_extt_nh, zdiag_volu_nh   ! area, extent, volume
58      REAL(wp) ::   zdiag_area_sh, zdiag_extt_sh, zdiag_volu_sh 
[8586]59      !!-------------------------------------------------------------------
60
[9124]61      IF( ln_timing )   CALL timing_start('icewri')
[8586]62
[9604]63      ! brine volume
64      CALL ice_var_bv
[8586]65
66      ! tresholds for outputs
67      DO jj = 1, jpj
68         DO ji = 1, jpi
[8884]69            zmsk00(ji,jj) = MAX( 0._wp , SIGN( 1._wp , at_i(ji,jj) - epsi06  ) ) ! 1 if ice    , 0 if no ice
70            zmsk05(ji,jj) = MAX( 0._wp , SIGN( 1._wp , at_i(ji,jj) - 0.05_wp ) ) ! 1 if 5% ice , 0 if less
71            zmsk15(ji,jj) = MAX( 0._wp , SIGN( 1._wp , at_i(ji,jj) - 0.15_wp ) ) ! 1 if 15% ice, 0 if less
[9433]72            zmsksn(ji,jj) = MAX( 0._wp , SIGN( 1._wp , vt_s(ji,jj) - epsi06  ) ) ! 1 if snow   , 0 if no snow
[8586]73         END DO
74      END DO
75      DO jl = 1, jpl
76         DO jj = 1, jpj
77            DO ji = 1, jpi
[8884]78               zmsk00l(ji,jj,jl)  = MAX( 0._wp , SIGN( 1._wp , a_i(ji,jj,jl) - epsi06 ) )
[9433]79               zmsksnl(ji,jj,jl)  = MAX( 0._wp , SIGN( 1._wp , v_s(ji,jj,jl) - epsi06 ) )
[8586]80            END DO
81         END DO
82      END DO
83
[8884]84      !-----------------
[8586]85      ! Standard outputs
[8884]86      !-----------------
[9935]87      zrho1 = ( rau0 - rhoi ) * r1_rau0; zrho2 = rhos * r1_rau0
[8884]88      ! masks
89      IF( iom_use('icemask'  ) )   CALL iom_put( "icemask"  , zmsk00              )   ! ice mask 0%
90      IF( iom_use('icemask05') )   CALL iom_put( "icemask05", zmsk05              )   ! ice mask 5%
91      IF( iom_use('icemask15') )   CALL iom_put( "icemask15", zmsk15              )   ! ice mask 15%
92      !
93      ! general fields
[9935]94      IF( iom_use('icemass'  ) )   CALL iom_put( "icemass", rhoi * vt_i * zmsk00  )   ! Ice mass per cell area
95      IF( iom_use('snwmass'  ) )   CALL iom_put( "snwmass", rhos * vt_s * zmsksn  )   ! Snow mass per cell area
[8884]96      IF( iom_use('icepres'  ) )   CALL iom_put( "icepres", zmsk00                )   ! Ice presence (1 or 0)
97      IF( iom_use('iceconc'  ) )   CALL iom_put( "iceconc", at_i  * zmsk00        )   ! ice concentration
98      IF( iom_use('icevolu'  ) )   CALL iom_put( "icevolu", vt_i  * zmsk00        )   ! ice volume = mean ice thickness over the cell
99      IF( iom_use('icethic'  ) )   CALL iom_put( "icethic", hm_i  * zmsk00        )   ! ice thickness
100      IF( iom_use('snwthic'  ) )   CALL iom_put( "snwthic", hm_s  * zmsk00        )   ! snw thickness
101      IF( iom_use('icebrv'   ) )   CALL iom_put( "icebrv" , bvm_i * zmsk00 * 100. )   ! brine volume
[10785]102      IF( iom_use('iceage'   ) )   CALL iom_put( "iceage" , om_i  * zmsk15 / rday )   ! ice age
[8884]103      IF( iom_use('icehnew'  ) )   CALL iom_put( "icehnew", ht_i_new              )   ! new ice thickness formed in the leads
[9433]104      IF( iom_use('snwvolu'  ) )   CALL iom_put( "snwvolu", vt_s  * zmsksn        )   ! snow volume
[8884]105      IF( iom_use('icefrb') ) THEN
106         z2d(:,:) = ( zrho1 * hm_i(:,:) - zrho2 * hm_s(:,:) )                                         
107         WHERE( z2d < 0._wp )   z2d = 0._wp
108                                   CALL iom_put( "icefrb" , z2d * zmsk00          )   ! Ice freeboard
109      ENDIF
110      !
111      ! melt ponds
112      IF( iom_use('iceapnd'  ) )   CALL iom_put( "iceapnd", at_ip  * zmsk00       )   ! melt pond total fraction
113      IF( iom_use('icevpnd'  ) )   CALL iom_put( "icevpnd", vt_ip  * zmsk00       )   ! melt pond total volume per unit area
114      !
115      ! salt
116      IF( iom_use('icesalt'  ) )   CALL iom_put( "icesalt", sm_i  * zmsk00        )   ! mean ice salinity
[9935]117      IF( iom_use('icesalm'  ) )   CALL iom_put( "icesalm", SUM( sv_i, DIM = 3 ) * rhoi * 1.0e-3 * zmsk00 )   ! Mass of salt in sea ice per cell area
[8586]118
[8884]119      ! heat
120      IF( iom_use('icetemp'  ) )   CALL iom_put( "icetemp", ( tm_i  - rt0 ) * zmsk00 )   ! ice mean temperature
[9433]121      IF( iom_use('snwtemp'  ) )   CALL iom_put( "snwtemp", ( tm_s  - rt0 ) * zmsksn )   ! snw mean temperature
[8884]122      IF( iom_use('icettop'  ) )   CALL iom_put( "icettop", ( tm_su - rt0 ) * zmsk00 )   ! temperature at the ice surface
123      IF( iom_use('icetbot'  ) )   CALL iom_put( "icetbot", ( t_bo  - rt0 ) * zmsk00 )   ! temperature at the ice bottom
124      IF( iom_use('icetsni'  ) )   CALL iom_put( "icetsni", ( tm_si - rt0 ) * zmsk00 )   ! temperature at the snow-ice interface
125      IF( iom_use('icehc'    ) )   CALL iom_put( "icehc"  ,  -et_i          * zmsk00 )   ! ice heat content
[9433]126      IF( iom_use('snwhc'    ) )   CALL iom_put( "snwhc"  ,  -et_s          * zmsksn )   ! snow heat content
[8884]127
128      ! momentum
129      IF( iom_use('uice'     ) )   CALL iom_put( "uice"   , u_ice                 )   ! ice velocity u component
130      IF( iom_use('vice'     ) )   CALL iom_put( "vice"   , v_ice                 )   ! ice velocity v component
131      IF( iom_use('utau_ai'  ) )   CALL iom_put( "utau_ai", utau_ice * zmsk00     )   ! Wind stress term in force balance (x)
132      IF( iom_use('vtau_ai'  ) )   CALL iom_put( "vtau_ai", vtau_ice * zmsk00     )   ! Wind stress term in force balance (y)
133
[10413]134      IF( iom_use('icevel') .OR. iom_use('fasticepres') ) THEN 
135        ! module of ice velocity
[8586]136         DO jj = 2 , jpjm1
137            DO ji = 2 , jpim1
138               z2da  = ( u_ice(ji,jj) + u_ice(ji-1,jj) )
139               z2db  = ( v_ice(ji,jj) + v_ice(ji,jj-1) )
140               z2d(ji,jj) = 0.5_wp * SQRT( z2da * z2da + z2db * z2db )
141           END DO
142         END DO
[10425]143         CALL lbc_lnk( 'icewri', z2d, 'T', 1. )
[10413]144         IF( iom_use('icevel') )   CALL iom_put( "icevel" , z2d )
145
146        ! record presence of fast ice
[10910]147         WHERE( z2d(:,:) < 5.e-04_wp .AND. zmsk15(:,:) == 1._wp ) ; zfast(:,:) = 1._wp
[10413]148         ELSEWHERE                                                ; zfast(:,:) = 0._wp
149         END WHERE
150         IF( iom_use('fasticepres') )   CALL iom_put( "fasticepres" , zfast )
[8586]151      ENDIF
152
[8884]153      ! --- category-dependent fields --- !
154      IF( iom_use('icemask_cat' ) )   CALL iom_put( "icemask_cat" , zmsk00l                                                    )   ! ice mask 0%
155      IF( iom_use('iceconc_cat' ) )   CALL iom_put( "iceconc_cat" , a_i * zmsk00l                                              )   ! area for categories
156      IF( iom_use('icethic_cat' ) )   CALL iom_put( "icethic_cat" , h_i * zmsk00l                                              )   ! thickness for categories
[9433]157      IF( iom_use('snwthic_cat' ) )   CALL iom_put( "snwthic_cat" , h_s * zmsksnl                                              )   ! snow depth for categories
[8884]158      IF( iom_use('icesalt_cat' ) )   CALL iom_put( "icesalt_cat" , s_i * zmsk00l                                              )   ! salinity for categories
159      IF( iom_use('iceage_cat'  ) )   CALL iom_put( "iceage_cat"  , o_i * zmsk00l / rday                                       )   ! ice age
160      IF( iom_use('icetemp_cat' ) )   CALL iom_put( "icetemp_cat" , ( SUM( t_i(:,:,:,:), dim=3 ) * r1_nlay_i - rt0 ) * zmsk00l )   ! ice temperature
[9433]161      IF( iom_use('snwtemp_cat' ) )   CALL iom_put( "snwtemp_cat" , ( SUM( t_s(:,:,:,:), dim=3 ) * r1_nlay_s - rt0 ) * zmsksnl )   ! snow temperature
162      IF( iom_use('icettop_cat' ) )   CALL iom_put( "icettop_cat" , ( t_su - rt0 ) * zmsk00l                                   )   ! surface temperature
163      IF( iom_use('icebrv_cat'  ) )   CALL iom_put( "icebrv_cat"  ,   bv_i * 100.  * zmsk00l                                   )   ! brine volume
164      IF( iom_use('iceapnd_cat' ) )   CALL iom_put( "iceapnd_cat" ,   a_ip         * zmsk00l                                   )   ! melt pond frac for categories
165      IF( iom_use('icehpnd_cat' ) )   CALL iom_put( "icehpnd_cat" ,   h_ip         * zmsk00l                                   )   ! melt pond frac for categories
166      IF( iom_use('iceafpnd_cat') )   CALL iom_put( "iceafpnd_cat",   a_ip_frac    * zmsk00l                                   )   ! melt pond frac for categories
[8586]167
[8884]168      !------------------
[8586]169      ! Add-ons for SIMIP
[8884]170      !------------------
171      ! trends
172      IF( iom_use('dmithd') )   CALL iom_put( "dmithd", - wfx_bog - wfx_bom - wfx_sum - wfx_sni - wfx_opw - wfx_lam - wfx_res ) ! Sea-ice mass change from thermodynamics
[9935]173      IF( iom_use('dmidyn') )   CALL iom_put( "dmidyn", - wfx_dyn + rhoi * diag_trp_vi      )   ! Sea-ice mass change from dynamics(kg/m2/s)
[8884]174      IF( iom_use('dmiopw') )   CALL iom_put( "dmiopw", - wfx_opw                           )   ! Sea-ice mass change through growth in open water
175      IF( iom_use('dmibog') )   CALL iom_put( "dmibog", - wfx_bog                           )   ! Sea-ice mass change through basal growth
176      IF( iom_use('dmisni') )   CALL iom_put( "dmisni", - wfx_sni                           )   ! Sea-ice mass change through snow-to-ice conversion
177      IF( iom_use('dmisum') )   CALL iom_put( "dmisum", - wfx_sum                           )   ! Sea-ice mass change through surface melting
178      IF( iom_use('dmibom') )   CALL iom_put( "dmibom", - wfx_bom                           )   ! Sea-ice mass change through bottom melting
179      IF( iom_use('dmtsub') )   CALL iom_put( "dmtsub", - wfx_sub                           )   ! Sea-ice mass change through evaporation and sublimation
180      IF( iom_use('dmssub') )   CALL iom_put( "dmssub", - wfx_snw_sub                       )   ! Snow mass change through sublimation
181      IF( iom_use('dmisub') )   CALL iom_put( "dmisub", - wfx_ice_sub                       )   ! Sea-ice mass change through sublimation
182      IF( iom_use('dmsspr') )   CALL iom_put( "dmsspr", - wfx_spr                           )   ! Snow mass change through snow fall
[9935]183      IF( iom_use('dmsssi') )   CALL iom_put( "dmsssi",   wfx_sni*rhos*r1_rhoi              )   ! Snow mass change through snow-to-ice conversion
[8884]184      IF( iom_use('dmsmel') )   CALL iom_put( "dmsmel", - wfx_snw_sum                       )   ! Snow mass change through melt
[9935]185      IF( iom_use('dmsdyn') )   CALL iom_put( "dmsdyn", - wfx_snw_dyn + rhos * diag_trp_vs  )   ! Snow mass change through dynamics(kg/m2/s)
[8586]186
[8884]187      ! Global ice diagnostics
188      IF( iom_use('NH_icearea') .OR. iom_use('NH_icevolu') .OR. iom_use('NH_iceextt') )   THEN   ! NH diagnostics
[8586]189         !
[8884]190         WHERE( ff_t > 0._wp )   ;   zmsk00(:,:) = 1.0e-12
191         ELSEWHERE               ;   zmsk00(:,:) = 0.
[8586]192         END WHERE
[10425]193         zdiag_area_nh = glob_sum( 'icewri', at_i(:,:) * zmsk00(:,:) * e1e2t(:,:) )
194         zdiag_volu_nh = glob_sum( 'icewri', vt_i(:,:) * zmsk00(:,:) * e1e2t(:,:) )
[8586]195         !
[8884]196         WHERE( ff_t > 0._wp .AND. at_i > 0.15 )   ; zmsk00(:,:) = 1.0e-12
197         ELSEWHERE                                 ; zmsk00(:,:) = 0.
[8586]198         END WHERE
[10425]199         zdiag_extt_nh = glob_sum( 'icewri', zmsk00(:,:) * e1e2t(:,:) )
[8586]200         !
[8884]201         IF( iom_use('NH_icearea') )   CALL iom_put( "NH_icearea" ,  zdiag_area_nh )
202         IF( iom_use('NH_icevolu') )   CALL iom_put( "NH_icevolu" ,  zdiag_volu_nh )
203         IF( iom_use('NH_iceextt') )   CALL iom_put( "NH_iceextt" ,  zdiag_extt_nh )
[8586]204         !
205      ENDIF
206      !
[8884]207      IF( iom_use('SH_icearea') .OR. iom_use('SH_icevolu') .OR. iom_use('SH_iceextt') )   THEN   ! SH diagnostics
[8586]208         !
[8884]209         WHERE( ff_t < 0._wp ); zmsk00(:,:) = 1.0e-12; 
210         ELSEWHERE            ; zmsk00(:,:) = 0.
[8586]211         END WHERE
[10425]212         zdiag_area_sh = glob_sum( 'icewri', at_i(:,:) * zmsk00(:,:) * e1e2t(:,:) ) 
213         zdiag_volu_sh = glob_sum( 'icewri', vt_i(:,:) * zmsk00(:,:) * e1e2t(:,:) )
[8586]214         !
[8884]215         WHERE( ff_t < 0._wp .AND. at_i > 0.15 ); zmsk00(:,:) = 1.0e-12
216         ELSEWHERE                              ; zmsk00(:,:) = 0.
[8586]217         END WHERE
[10425]218         zdiag_extt_sh = glob_sum( 'icewri', zmsk00(:,:) * e1e2t(:,:) )
[8586]219         !
[8884]220         IF( iom_use('SH_icearea') ) CALL iom_put( "SH_icearea", zdiag_area_sh )
221         IF( iom_use('SH_icevolu') ) CALL iom_put( "SH_icevolu", zdiag_volu_sh )
222         IF( iom_use('SH_iceextt') ) CALL iom_put( "SH_iceextt", zdiag_extt_sh )
[8586]223         !
224      ENDIF 
225      !
226!!CR      !     !  Create an output files (output.lim.abort.nc) if S < 0 or u > 20 m/s
227!!CR      !     IF( kindic < 0 )   CALL ice_wri_state( 'output.abort' )
228!!CR      !     not yet implemented
229!!gm  idem for the ocean...  Ask Seb how to get read of ioipsl....
230      !
[9124]231      IF( ln_timing )  CALL timing_stop('icewri')
[8586]232      !
233   END SUBROUTINE ice_wri
234
235 
[10425]236   SUBROUTINE ice_wri_state( kid )
[8586]237      !!---------------------------------------------------------------------
238      !!                 ***  ROUTINE ice_wri_state  ***
239      !!       
240      !! ** Purpose :   create a NetCDF file named cdfile_name which contains
241      !!      the instantaneous ice state and forcing fields for ice model
242      !!        Used to find errors in the initial state or save the last
243      !!      ocean state in case of abnormal end of a simulation
244      !!
245      !! History :   4.0  !  2013-06  (C. Rousset)
246      !!----------------------------------------------------------------------
[10425]247      INTEGER, INTENT( in ) ::   kid 
[8586]248      !!----------------------------------------------------------------------
249      !
[10425]250      !! The file is open in dia_wri_state (ocean routine)
[8586]251
[10425]252      CALL iom_rstput( 0, 0, kid, 'sithic', hm_i         )   ! Ice thickness
253      CALL iom_rstput( 0, 0, kid, 'siconc', at_i         )   ! Ice concentration
254      CALL iom_rstput( 0, 0, kid, 'sitemp', tm_i - rt0   )   ! Ice temperature
255      CALL iom_rstput( 0, 0, kid, 'sivelu', u_ice        )   ! i-Ice speed
256      CALL iom_rstput( 0, 0, kid, 'sivelv', v_ice        )   ! j-Ice speed
257      CALL iom_rstput( 0, 0, kid, 'sistru', utau_ice     )   ! i-Wind stress over ice
258      CALL iom_rstput( 0, 0, kid, 'sistrv', vtau_ice     )   ! i-Wind stress over ice
259      CALL iom_rstput( 0, 0, kid, 'sisflx', qsr          )   ! Solar flx over ocean
260      CALL iom_rstput( 0, 0, kid, 'sinflx', qns          )   ! NonSolar flx over ocean
261      CALL iom_rstput( 0, 0, kid, 'snwpre', sprecip      )   ! Snow precipitation
262      CALL iom_rstput( 0, 0, kid, 'sisali', sm_i         )   ! Ice salinity
263      CALL iom_rstput( 0, 0, kid, 'sivolu', vt_i         )   ! Ice volume
264      CALL iom_rstput( 0, 0, kid, 'sidive', divu_i*1.0e8 )   ! Ice divergence
265      CALL iom_rstput( 0, 0, kid, 'si_amp', at_ip        )   ! Melt pond fraction
266      CALL iom_rstput( 0, 0, kid, 'si_vmp', vt_ip        )   ! Melt pond volume
267      CALL iom_rstput( 0, 0, kid, 'sithicat', h_i        )   ! Ice thickness
268      CALL iom_rstput( 0, 0, kid, 'siconcat', a_i        )   ! Ice concentration
269      CALL iom_rstput( 0, 0, kid, 'sisalcat', s_i        )   ! Ice salinity
270      CALL iom_rstput( 0, 0, kid, 'snthicat', h_s        )   ! Snw thickness
[8586]271
272    END SUBROUTINE ice_wri_state
273
274#else
275   !!----------------------------------------------------------------------
[9570]276   !!   Default option :         Empty module         NO SI3 sea-ice model
[8586]277   !!----------------------------------------------------------------------
278#endif
279
280   !!======================================================================
281END MODULE icewri
Note: See TracBrowser for help on using the repository browser.