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.
limcons.F90 in branches/UKMO/dev_r8183_ICEMODEL_svn_removed/NEMOGCM/NEMO/LIM_SRC_3 – NEMO

source: branches/UKMO/dev_r8183_ICEMODEL_svn_removed/NEMOGCM/NEMO/LIM_SRC_3/limcons.F90 @ 8733

Last change on this file since 8733 was 8733, checked in by dancopsey, 6 years ago

Remove svn keywords.

File size: 16.6 KB
Line 
1MODULE limcons
2   !!======================================================================
3   !!                   ***  MODULE  limcons  ***
4   !! LIM-3 Sea Ice :   conservation check
5   !!======================================================================
6   !! History :   -   ! Original code from William H. Lipscomb, LANL
7   !!            3.0  ! 2004-06  (M. Vancoppenolle)   Energy Conservation
8   !!            3.5  ! 2011-02  (G. Madec)  add mpp considerations
9   !!             -   ! 2014-05  (C. Rousset) add lim_cons_hsm
10   !!             -   ! 2015-03  (C. Rousset) add lim_cons_final
11   !!----------------------------------------------------------------------
12#if defined key_lim3
13   !!----------------------------------------------------------------------
14   !!   'key_lim3'                                      LIM-3 sea-ice model
15   !!----------------------------------------------------------------------
16   !!    lim_cons     :   checks whether energy, mass and salt are conserved
17   !!----------------------------------------------------------------------
18   USE phycst         ! physical constants
19   USE ice            ! LIM-3 variables
20   USE dom_oce        ! ocean domain
21   USE in_out_manager ! I/O manager
22   USE lib_mpp        ! MPP library
23   USE lib_fortran    ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined) 
24   USE sbc_oce , ONLY : sfx  ! Surface boundary condition: ocean fields
25   USE sbc_ice , ONLY : qevap_ice
26   
27   IMPLICIT NONE
28   PRIVATE
29
30   PUBLIC   lim_column_sum
31   PUBLIC   lim_column_sum_energy
32   PUBLIC   lim_cons_check
33   PUBLIC   lim_cons_hsm
34   PUBLIC   lim_cons_final
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_column_sum( ksum, pin, pout )
44      !!-------------------------------------------------------------------
45      !!               ***  ROUTINE lim_column_sum ***
46      !!
47      !! ** Purpose : Compute the sum of xin over nsum categories
48      !!
49      !! ** Method  : Arithmetics
50      !!
51      !! ** Action  : Gets xin(ji,jj,jl) and computes xout(ji,jj)
52      !!---------------------------------------------------------------------
53      INTEGER                   , INTENT(in   ) ::   ksum   ! number of categories/layers
54      REAL(wp), DIMENSION(:,:,:), INTENT(in   ) ::   pin    ! input field
55      REAL(wp), DIMENSION(:,:)  , INTENT(  out) ::   pout   ! output field
56      !
57      INTEGER ::   jl   ! dummy loop indices
58      !!---------------------------------------------------------------------
59      !
60      pout(:,:) = pin(:,:,1)
61      DO jl = 2, ksum
62         pout(:,:) = pout(:,:) + pin(:,:,jl)
63      END DO
64      !
65   END SUBROUTINE lim_column_sum
66
67
68   SUBROUTINE lim_column_sum_energy( ksum, klay, pin, pout)
69      !!-------------------------------------------------------------------
70      !!               ***  ROUTINE lim_column_sum_energy ***
71      !!
72      !! ** Purpose : Compute the sum of xin over nsum categories
73      !!              and nlay layers
74      !!
75      !! ** Method  : Arithmetics
76      !!---------------------------------------------------------------------
77      INTEGER                                , INTENT(in   ) ::   ksum   !: number of categories
78      INTEGER                                , INTENT(in   ) ::   klay   !: number of vertical layers
79      REAL(wp), DIMENSION(jpi,jpj,nlay_i,jpl), INTENT(in   ) ::   pin    !: input field
80      REAL(wp), DIMENSION(jpi,jpj)           , INTENT(  out) ::   pout   !: output field
81      !
82      INTEGER ::   jk, jl   ! dummy loop indices
83      !!---------------------------------------------------------------------
84      !
85      pout(:,:) = 0._wp
86      DO jl = 1, ksum
87         DO jk = 2, klay 
88            pout(:,:) = pout(:,:) + pin(:,:,jk,jl)
89         END DO
90      END DO
91      !
92   END SUBROUTINE lim_column_sum_energy
93
94
95   SUBROUTINE lim_cons_check( px1, px2, pmax_err, cd_fieldid )
96      !!-------------------------------------------------------------------
97      !!               ***  ROUTINE lim_cons_check ***
98      !!
99      !! ** Purpose : Test the conservation of a certain variable
100      !!              For each physical grid cell, check that initial
101      !!              and final values
102      !!              of a conserved field are equal to within a small value.
103      !!
104      !! ** Method  :
105      !!---------------------------------------------------------------------
106      REAL(wp), DIMENSION(:,:), INTENT(in   ) ::   px1          !: initial field
107      REAL(wp), DIMENSION(:,:), INTENT(in   ) ::   px2          !: final field
108      REAL(wp)                , INTENT(in   ) ::   pmax_err     !: max allowed error
109      CHARACTER(len=15)       , INTENT(in   ) ::   cd_fieldid   !: field identifyer
110      !
111      INTEGER  ::   ji, jj          ! dummy loop indices
112      INTEGER  ::   inb_error       ! number of g.c where there is a cons. error
113      LOGICAL  ::   llconserv_err   ! = .true. if conservation check failed
114      REAL(wp) ::   zmean_error     ! mean error on error points
115      !!---------------------------------------------------------------------
116      !
117      IF(lwp) WRITE(numout,*) ' lim_cons_check '
118      IF(lwp) WRITE(numout,*) ' ~~~~~~~~~~~~~~ '
119
120      llconserv_err = .FALSE.
121      inb_error     = 0
122      zmean_error   = 0._wp
123      IF( MAXVAL( px2(:,:) - px1(:,:) ) > pmax_err )   llconserv_err = .TRUE.
124
125      IF( llconserv_err ) THEN
126         DO jj = 1, jpj 
127            DO ji = 1, jpi
128               IF( ABS( px2(ji,jj) - px1(ji,jj) ) > pmax_err ) THEN
129                  inb_error   = inb_error + 1
130                  zmean_error = zmean_error + ABS( px2(ji,jj) - px1(ji,jj) )
131                  !
132                  IF(lwp) THEN
133                     WRITE (numout,*) ' ALERTE 99 '
134                     WRITE (numout,*) ' Conservation error: ', cd_fieldid
135                     WRITE (numout,*) ' Point             : ', ji, jj 
136                     WRITE (numout,*) ' lat, lon          : ', gphit(ji,jj), glamt(ji,jj)
137                     WRITE (numout,*) ' Initial value     : ', px1(ji,jj)
138                     WRITE (numout,*) ' Final value       : ', px2(ji,jj)
139                     WRITE (numout,*) ' Difference        : ', px2(ji,jj) - px1(ji,jj)
140                  ENDIF
141               ENDIF
142            END DO
143         END DO
144         !
145      ENDIF
146      IF(lk_mpp)   CALL mpp_sum( inb_error   )
147      IF(lk_mpp)   CALL mpp_sum( zmean_error )
148      !
149      IF( inb_error > 0 .AND. lwp ) THEN
150         zmean_error = zmean_error / REAL( inb_error, wp )
151         WRITE(numout,*) ' Conservation check for : ', cd_fieldid
152         WRITE(numout,*) ' Number of error points : ', inb_error
153         WRITE(numout,*) ' Mean error on these pts: ', zmean_error
154      ENDIF
155      !
156   END SUBROUTINE lim_cons_check
157
158
159   SUBROUTINE lim_cons_hsm( icount, cd_routine, zvi_b, zsmv_b, zei_b, zfw_b, zfs_b, zft_b )
160      !!--------------------------------------------------------------------------------------------------------
161      !!                                        ***  ROUTINE lim_cons_hsm ***
162      !!
163      !! ** Purpose : Test the conservation of heat, salt and mass for each ice routine
164      !!                     + test if ice concentration and volume are > 0
165      !!
166      !! ** Method  : This is an online diagnostics which can be activated with ln_limdiachk=true
167      !!              It prints in ocean.output if there is a violation of conservation at each time-step
168      !!              The thresholds (zv_sill, zs_sill, zh_sill) which determine violations are set to
169      !!              a minimum of 1 mm of ice (over the ice area) that is lost/gained spuriously during 100 years.
170      !!              For salt and heat thresholds, ice is considered to have a salinity of 10
171      !!              and a heat content of 3e5 J/kg (=latent heat of fusion)
172      !!--------------------------------------------------------------------------------------------------------
173      INTEGER         , INTENT(in)    :: icount        ! determine wether this is the beggining of the routine (0) or the end (1)
174      CHARACTER(len=*), INTENT(in)    :: cd_routine    ! name of the routine
175      REAL(wp)        , INTENT(inout) :: zvi_b, zsmv_b, zei_b, zfs_b, zfw_b, zft_b 
176      REAL(wp)                        :: zvi,   zsmv,   zei,   zfs,   zfw,   zft
177      REAL(wp)                        :: zvmin, zamin, zamax 
178      REAL(wp)                        :: zvtrp, zetrp
179      REAL(wp)                        :: zarea, zv_sill, zs_sill, zh_sill
180      REAL(wp), PARAMETER             :: zconv = 1.e-9 ! convert W to GW and kg to Mt
181
182      IF( icount == 0 ) THEN
183
184         ! salt flux
185         zfs_b  = glob_sum(  ( sfx_bri(:,:) + sfx_bog(:,:) + sfx_bom(:,:) + sfx_sum(:,:) + sfx_sni(:,:) +  &
186            &                  sfx_opw(:,:) + sfx_res(:,:) + sfx_dyn(:,:) + sfx_sub(:,:) + sfx_lam(:,:)    &
187            &                ) *  e1e2t(:,:) * tmask(:,:,1) * zconv )
188
189         ! water flux
190         zfw_b  = glob_sum( -( wfx_bog(:,:) + wfx_bom(:,:) + wfx_sum(:,:) + wfx_sni(:,:) + wfx_opw(:,:) +               &
191            &                  wfx_res(:,:) + wfx_dyn(:,:) + wfx_snw(:,:) + wfx_sub(:,:) + wfx_spr(:,:) + wfx_lam(:,:)  &
192            &                ) *  e1e2t(:,:) * tmask(:,:,1) * zconv )
193
194         ! heat flux
195         zft_b  = glob_sum(  ( hfx_sum(:,:) + hfx_bom(:,:) + hfx_bog(:,:) + hfx_dif(:,:) + hfx_opw(:,:) + hfx_snw(:,:)  & 
196            &                - hfx_thd(:,:) - hfx_dyn(:,:) - hfx_res(:,:) - hfx_sub(:,:) - hfx_spr(:,:)   &
197            &                ) *  e1e2t(:,:) * tmask(:,:,1) * zconv )
198
199         zvi_b  = glob_sum( SUM( v_i * rhoic + v_s * rhosn, dim=3 ) * e1e2t * tmask(:,:,1) * zconv )
200
201         zsmv_b = glob_sum( SUM( smv_i * rhoic            , dim=3 ) * e1e2t * tmask(:,:,1) * zconv )
202
203         zei_b  = glob_sum( ( SUM( SUM( e_i(:,:,1:nlay_i,:), dim=4 ), dim=3 ) +  &
204            &                 SUM( SUM( e_s(:,:,1:nlay_s,:), dim=4 ), dim=3 )    &
205                            ) * e1e2t * tmask(:,:,1) * zconv )
206
207      ELSEIF( icount == 1 ) THEN
208
209         ! salt flux
210         zfs  = glob_sum(  ( sfx_bri(:,:) + sfx_bog(:,:) + sfx_bom(:,:) + sfx_sum(:,:) + sfx_sni(:,:) +  &
211            &                sfx_opw(:,:) + sfx_res(:,:) + sfx_dyn(:,:) + sfx_sub(:,:) + sfx_lam(:,:)    & 
212            &              ) * e1e2t(:,:) * tmask(:,:,1) * zconv ) - zfs_b
213
214         ! water flux
215         zfw  = glob_sum( -( wfx_bog(:,:) + wfx_bom(:,:) + wfx_sum(:,:) + wfx_sni(:,:) + wfx_opw(:,:) +                &
216            &                wfx_res(:,:) + wfx_dyn(:,:) + wfx_snw(:,:) + wfx_sub(:,:) + wfx_spr(:,:) + wfx_lam(:,:)   &
217            &              ) * e1e2t(:,:) * tmask(:,:,1) * zconv ) - zfw_b
218
219         ! heat flux
220         zft  = glob_sum(  ( hfx_sum(:,:) + hfx_bom(:,:) + hfx_bog(:,:) + hfx_dif(:,:) + hfx_opw(:,:) + hfx_snw(:,:)  & 
221            &              - hfx_thd(:,:) - hfx_dyn(:,:) - hfx_res(:,:) - hfx_sub(:,:) - hfx_spr(:,:)   &
222            &              ) * e1e2t(:,:) * tmask(:,:,1) * zconv ) - zft_b
223 
224         ! outputs
225         zvi  = ( ( glob_sum( SUM( v_i * rhoic + v_s * rhosn, dim=3 )  &
226            &                    * e1e2t * tmask(:,:,1) * zconv ) - zvi_b ) * r1_rdtice - zfw ) * rday
227
228         zsmv = ( ( glob_sum( SUM( smv_i * rhoic            , dim=3 )  &
229            &                    * e1e2t * tmask(:,:,1) * zconv ) - zsmv_b ) * r1_rdtice + zfs ) * rday
230
231         zei  =   glob_sum( ( SUM( SUM( e_i(:,:,1:nlay_i,:), dim=4 ), dim=3 ) +  &
232            &                 SUM( SUM( e_s(:,:,1:nlay_s,:), dim=4 ), dim=3 )    &
233            &                ) * e1e2t * tmask(:,:,1) * zconv ) * r1_rdtice - zei_b * r1_rdtice + zft
234
235         ! zvtrp and zetrp must be close to 0 if the advection scheme is conservative
236         zvtrp = glob_sum( ( diag_trp_vi * rhoic + diag_trp_vs * rhosn ) * e1e2t * tmask(:,:,1) * zconv ) * rday 
237         zetrp = glob_sum( ( diag_trp_ei         + diag_trp_es         ) * e1e2t * tmask(:,:,1) * zconv )
238
239         zvmin = glob_min( v_i )
240         zamax = glob_max( SUM( a_i, dim=3 ) )
241         zamin = glob_min( a_i )
242
243         ! set threshold values and calculate the ice area (+epsi10 to set a threshold > 0 when there is no ice)
244         zarea   = glob_sum( SUM( a_i + epsi10, dim=3 ) * e1e2t * zconv ) ! in 1.e9 m2
245         zv_sill = zarea * 2.5e-5
246         zs_sill = zarea * 25.e-5
247         zh_sill = zarea * 10.e-5
248
249         IF(lwp) THEN
250            IF ( ABS( zvi  ) > zv_sill ) WRITE(numout,*) 'violation volume [Mt/day]     (',cd_routine,') = ',zvi
251            IF ( ABS( zsmv ) > zs_sill ) WRITE(numout,*) 'violation saline [psu*Mt/day] (',cd_routine,') = ',zsmv
252            IF ( ABS( zei  ) > zh_sill ) WRITE(numout,*) 'violation enthalpy [GW]       (',cd_routine,') = ',zei
253            IF ( ABS(zvtrp ) > zv_sill .AND. cd_routine == 'limtrp' ) THEN
254                                         WRITE(numout,*) 'violation vtrp [Mt/day]       (',cd_routine,') = ',zvtrp
255                                         WRITE(numout,*) 'violation etrp [GW]           (',cd_routine,') = ',zetrp
256            ENDIF
257            IF (     zvmin   < -epsi10 ) WRITE(numout,*) 'violation v_i<0  [m]          (',cd_routine,') = ',zvmin
258            IF (     zamax   > MAX( rn_amax_n, rn_amax_s ) + epsi10 .AND. &
259               &                         cd_routine /= 'limtrp' .AND. cd_routine /= 'limitd_me' ) THEN
260                                         WRITE(numout,*) 'violation a_i>amax            (',cd_routine,') = ',zamax
261            IF (     zamax   > 1._wp   ) WRITE(numout,*) 'violation a_i>1               (',cd_routine,') = ',zamax
262            ENDIF
263            IF (      zamin  < -epsi10 ) WRITE(numout,*) 'violation a_i<0               (',cd_routine,') = ',zamin
264         ENDIF
265
266      ENDIF
267
268   END SUBROUTINE lim_cons_hsm
269
270   SUBROUTINE lim_cons_final( cd_routine )
271      !!---------------------------------------------------------------------------------------------------------
272      !!                                   ***  ROUTINE lim_cons_final ***
273      !!
274      !! ** Purpose : Test the conservation of heat, salt and mass at the end of each ice time-step
275      !!
276      !! ** Method  : This is an online diagnostics which can be activated with ln_limdiachk=true
277      !!              It prints in ocean.output if there is a violation of conservation at each time-step
278      !!              The thresholds (zv_sill, zs_sill, zh_sill) which determine the violation are set to
279      !!              a minimum of 1 mm of ice (over the ice area) that is lost/gained spuriously during 100 years.
280      !!              For salt and heat thresholds, ice is considered to have a salinity of 10
281      !!              and a heat content of 3e5 J/kg (=latent heat of fusion)
282      !!--------------------------------------------------------------------------------------------------------
283      CHARACTER(len=*), INTENT(in)    :: cd_routine    ! name of the routine
284      REAL(wp)                        :: zhfx, zsfx, zvfx
285      REAL(wp)                        :: zarea, zv_sill, zs_sill, zh_sill
286      REAL(wp), PARAMETER             :: zconv = 1.e-9 ! convert W to GW and kg to Mt
287
288      ! heat flux
289      zhfx  = glob_sum( ( hfx_in - hfx_out - diag_heat - diag_trp_ei - diag_trp_es   &
290      !  &              - SUM( qevap_ice * a_i_b, dim=3 )                           & !!clem: I think this line must be commented (but need check)
291         &              ) * e1e2t * tmask(:,:,1) * zconv ) 
292      ! salt flux
293      zsfx  = glob_sum( ( sfx + diag_smvi ) * e1e2t * tmask(:,:,1) * zconv ) * rday
294      ! water flux
295      zvfx  = glob_sum( ( wfx_ice + wfx_snw + wfx_spr + wfx_sub + diag_vice + diag_vsnw ) * e1e2t * tmask(:,:,1) * zconv ) * rday
296
297      ! set threshold values and calculate the ice area (+epsi10 to set a threshold > 0 when there is no ice)
298      zarea   = glob_sum( SUM( a_i + epsi10, dim=3 ) * e1e2t * zconv ) ! in 1.e9 m2
299      zv_sill = zarea * 2.5e-5
300      zs_sill = zarea * 25.e-5
301      zh_sill = zarea * 10.e-5
302
303      IF( ABS( zvfx ) > zv_sill ) WRITE(numout,*) 'violation vfx    [Mt/day]       (',cd_routine,')  = ',(zvfx)
304      IF( ABS( zsfx ) > zs_sill ) WRITE(numout,*) 'violation sfx    [psu*Mt/day]   (',cd_routine,')  = ',(zsfx)
305      IF( ABS( zhfx ) > zh_sill ) WRITE(numout,*) 'violation hfx    [GW]           (',cd_routine,')  = ',(zhfx)
306
307   END SUBROUTINE lim_cons_final
308
309#else
310   !!----------------------------------------------------------------------
311   !!   Default option         Empty module            NO LIM sea-ice model
312   !!----------------------------------------------------------------------
313#endif
314   !!======================================================================
315END MODULE limcons
Note: See TracBrowser for help on using the repository browser.