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/branches/2019/dev_r10984_HPC-13_IRRMANN_BDY_optimization/src/ICE – NEMO

source: NEMO/branches/2019/dev_r10984_HPC-13_IRRMANN_BDY_optimization/src/ICE/icewri.F90 @ 11362

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

debug the ice output by adding a missing value to the outputed fields. Unfortunately this method imposes a value of 1.e20 where there is no ice, which is annoying when using ncview for example, but this is the only way (from what I know) to output averages

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