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/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3 – NEMO

source: branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/limcons.F90 @ 8409

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

change calls in icestp.F90 for advection

  • Property svn:keywords set to Id
File size: 11.8 KB
RevLine 
[825]1MODULE limcons
[2715]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
[5123]8   !!            3.5  ! 2011-02  (G. Madec)  add mpp considerations
[4688]9   !!             -   ! 2014-05  (C. Rousset) add lim_cons_hsm
[5176]10   !!             -   ! 2015-03  (C. Rousset) add lim_cons_final
[2715]11   !!----------------------------------------------------------------------
[834]12#if defined key_lim3
13   !!----------------------------------------------------------------------
[3625]14   !!   'key_lim3'                                      LIM-3 sea-ice model
[834]15   !!----------------------------------------------------------------------
[3625]16   !!    lim_cons     :   checks whether energy, mass and salt are conserved
[825]17   !!----------------------------------------------------------------------
[4688]18   USE phycst         ! physical constants
[3625]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) 
[5167]24   USE sbc_oce , ONLY : sfx  ! Surface boundary condition: ocean fields
[6416]25   USE sbc_ice , ONLY : qevap_ice
26   
[825]27   IMPLICIT NONE
28   PRIVATE
29
[4688]30   PUBLIC   lim_cons_hsm
[5167]31   PUBLIC   lim_cons_final
[825]32
33   !!----------------------------------------------------------------------
[4161]34   !! NEMO/LIM3 4.0 , UCL - NEMO Consortium (2011)
[1156]35   !! $Id$
[2715]36   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
[825]37   !!----------------------------------------------------------------------
38CONTAINS
39
[4688]40   SUBROUTINE lim_cons_hsm( icount, cd_routine, zvi_b, zsmv_b, zei_b, zfw_b, zfs_b, zft_b )
[5176]41      !!--------------------------------------------------------------------------------------------------------
42      !!                                        ***  ROUTINE lim_cons_hsm ***
[4688]43      !!
[5176]44      !! ** Purpose : Test the conservation of heat, salt and mass for each ice routine
45      !!                     + test if ice concentration and volume are > 0
[4688]46      !!
[7646]47      !! ** Method  : This is an online diagnostics which can be activated with ln_limdiachk=true
[5176]48      !!              It prints in ocean.output if there is a violation of conservation at each time-step
49      !!              The thresholds (zv_sill, zs_sill, zh_sill) which determine violations are set to
50      !!              a minimum of 1 mm of ice (over the ice area) that is lost/gained spuriously during 100 years.
51      !!              For salt and heat thresholds, ice is considered to have a salinity of 10
52      !!              and a heat content of 3e5 J/kg (=latent heat of fusion)
53      !!--------------------------------------------------------------------------------------------------------
54      INTEGER         , INTENT(in)    :: icount        ! determine wether this is the beggining of the routine (0) or the end (1)
55      CHARACTER(len=*), INTENT(in)    :: cd_routine    ! name of the routine
[4688]56      REAL(wp)        , INTENT(inout) :: zvi_b, zsmv_b, zei_b, zfs_b, zfw_b, zft_b 
57      REAL(wp)                        :: zvi,   zsmv,   zei,   zfs,   zfw,   zft
58      REAL(wp)                        :: zvmin, zamin, zamax 
[5167]59      REAL(wp)                        :: zvtrp, zetrp
[5176]60      REAL(wp)                        :: zarea, zv_sill, zs_sill, zh_sill
61      REAL(wp), PARAMETER             :: zconv = 1.e-9 ! convert W to GW and kg to Mt
[4688]62
63      IF( icount == 0 ) THEN
64
[5176]65         ! salt flux
[5123]66         zfs_b  = glob_sum(  ( sfx_bri(:,:) + sfx_bog(:,:) + sfx_bom(:,:) + sfx_sum(:,:) + sfx_sni(:,:) +  &
[7646]67            &                  sfx_opw(:,:) + sfx_res(:,:) + sfx_dyn(:,:) + sfx_sub(:,:) + sfx_lam(:,:)    &
[5836]68            &                ) *  e1e2t(:,:) * tmask(:,:,1) * zconv )
[4688]69
[5176]70         ! water flux
[8341]71         zfw_b  = glob_sum( -( wfx_bog(:,:) + wfx_bom(:,:)     + wfx_sum(:,:)     + wfx_sni(:,:)     +                     &
72            &                  wfx_opw(:,:) + wfx_res(:,:)     + wfx_dyn(:,:)     + wfx_lam(:,:)     + wfx_ice_sub(:,:) +  &
73            &                  wfx_snw_sni(:,:) + wfx_snw_sum(:,:) + wfx_snw_dyn(:,:) + wfx_snw_sub(:,:) + wfx_spr(:,:)        &
74            &                ) * e1e2t(:,:) * tmask(:,:,1) * zconv )
[5123]75
[5176]76         ! heat flux
[5123]77         zft_b  = glob_sum(  ( hfx_sum(:,:) + hfx_bom(:,:) + hfx_bog(:,:) + hfx_dif(:,:) + hfx_opw(:,:) + hfx_snw(:,:)  & 
78            &                - hfx_thd(:,:) - hfx_dyn(:,:) - hfx_res(:,:) - hfx_sub(:,:) - hfx_spr(:,:)   &
[5836]79            &                ) *  e1e2t(:,:) * tmask(:,:,1) * zconv )
[5123]80
[5836]81         zvi_b  = glob_sum( SUM( v_i * rhoic + v_s * rhosn, dim=3 ) * e1e2t * tmask(:,:,1) * zconv )
[5123]82
[5836]83         zsmv_b = glob_sum( SUM( smv_i * rhoic            , dim=3 ) * e1e2t * tmask(:,:,1) * zconv )
[5123]84
85         zei_b  = glob_sum( ( SUM( SUM( e_i(:,:,1:nlay_i,:), dim=4 ), dim=3 ) +  &
86            &                 SUM( SUM( e_s(:,:,1:nlay_s,:), dim=4 ), dim=3 )    &
[5836]87                            ) * e1e2t * tmask(:,:,1) * zconv )
[5123]88
[4688]89      ELSEIF( icount == 1 ) THEN
90
[5176]91         ! salt flux
[5123]92         zfs  = glob_sum(  ( sfx_bri(:,:) + sfx_bog(:,:) + sfx_bom(:,:) + sfx_sum(:,:) + sfx_sni(:,:) +  &
[7646]93            &                sfx_opw(:,:) + sfx_res(:,:) + sfx_dyn(:,:) + sfx_sub(:,:) + sfx_lam(:,:)    & 
[5836]94            &              ) * e1e2t(:,:) * tmask(:,:,1) * zconv ) - zfs_b
[5123]95
[5176]96         ! water flux
[8341]97         zfw  = glob_sum( -( wfx_bog(:,:) + wfx_bom(:,:)     + wfx_sum(:,:)     + wfx_sni(:,:)     +                     &
98            &                wfx_opw(:,:) + wfx_res(:,:)     + wfx_dyn(:,:)     + wfx_lam(:,:)     + wfx_ice_sub(:,:) +  &
99            &                wfx_snw_sni(:,:) + wfx_snw_sum(:,:) + wfx_snw_dyn(:,:) + wfx_snw_sub(:,:) + wfx_spr(:,:)        &
[5836]100            &              ) * e1e2t(:,:) * tmask(:,:,1) * zconv ) - zfw_b
[5123]101
[5176]102         ! heat flux
[5123]103         zft  = glob_sum(  ( hfx_sum(:,:) + hfx_bom(:,:) + hfx_bog(:,:) + hfx_dif(:,:) + hfx_opw(:,:) + hfx_snw(:,:)  & 
104            &              - hfx_thd(:,:) - hfx_dyn(:,:) - hfx_res(:,:) - hfx_sub(:,:) - hfx_spr(:,:)   &
[5836]105            &              ) * e1e2t(:,:) * tmask(:,:,1) * zconv ) - zft_b
[4688]106 
[5176]107         ! outputs
108         zvi  = ( ( glob_sum( SUM( v_i * rhoic + v_s * rhosn, dim=3 )  &
[5836]109            &                    * e1e2t * tmask(:,:,1) * zconv ) - zvi_b ) * r1_rdtice - zfw ) * rday
[4688]110
[5176]111         zsmv = ( ( glob_sum( SUM( smv_i * rhoic            , dim=3 )  &
[5836]112            &                    * e1e2t * tmask(:,:,1) * zconv ) - zsmv_b ) * r1_rdtice + zfs ) * rday
[5123]113
[8341]114         zei  = ( glob_sum( ( SUM( SUM( e_i(:,:,1:nlay_i,:), dim=4 ), dim=3 ) +  &
[5123]115            &                 SUM( SUM( e_s(:,:,1:nlay_s,:), dim=4 ), dim=3 )    &
[8341]116            &                ) * e1e2t * tmask(:,:,1) * zconv ) - zei_b ) * r1_rdtice + zft
[5123]117
[5176]118         ! zvtrp and zetrp must be close to 0 if the advection scheme is conservative
[5836]119         zvtrp = glob_sum( ( diag_trp_vi * rhoic + diag_trp_vs * rhosn ) * e1e2t * tmask(:,:,1) * zconv ) * rday 
120         zetrp = glob_sum( ( diag_trp_ei         + diag_trp_es         ) * e1e2t * tmask(:,:,1) * zconv )
[5176]121
[5123]122         zvmin = glob_min( v_i )
123         zamax = glob_max( SUM( a_i, dim=3 ) )
124         zamin = glob_min( a_i )
[5167]125
[5176]126         ! set threshold values and calculate the ice area (+epsi10 to set a threshold > 0 when there is no ice)
[5836]127         zarea   = glob_sum( SUM( a_i + epsi10, dim=3 ) * e1e2t * zconv ) ! in 1.e9 m2
[5176]128         zv_sill = zarea * 2.5e-5
129         zs_sill = zarea * 25.e-5
130         zh_sill = zarea * 10.e-5
131
[4688]132         IF(lwp) THEN
[5176]133            IF ( ABS( zvi  ) > zv_sill ) WRITE(numout,*) 'violation volume [Mt/day]     (',cd_routine,') = ',zvi
134            IF ( ABS( zsmv ) > zs_sill ) WRITE(numout,*) 'violation saline [psu*Mt/day] (',cd_routine,') = ',zsmv
135            IF ( ABS( zei  ) > zh_sill ) WRITE(numout,*) 'violation enthalpy [GW]       (',cd_routine,') = ',zei
[8409]136            IF ( ABS(zvtrp ) > zv_sill .AND. cd_routine == 'iceadv' ) THEN
[5176]137                                         WRITE(numout,*) 'violation vtrp [Mt/day]       (',cd_routine,') = ',zvtrp
138                                         WRITE(numout,*) 'violation etrp [GW]           (',cd_routine,') = ',zetrp
[4688]139            ENDIF
[5176]140            IF (     zvmin   < -epsi10 ) WRITE(numout,*) 'violation v_i<0  [m]          (',cd_routine,') = ',zvmin
[6403]141            IF (     zamax   > MAX( rn_amax_n, rn_amax_s ) + epsi10 .AND. &
[8409]142               &                         cd_routine /= 'iceadv' .AND. cd_routine /= 'icerdgrft' ) THEN
[5176]143                                         WRITE(numout,*) 'violation a_i>amax            (',cd_routine,') = ',zamax
[7646]144            IF (     zamax   > 1._wp   ) WRITE(numout,*) 'violation a_i>1               (',cd_routine,') = ',zamax
[5167]145            ENDIF
[5176]146            IF (      zamin  < -epsi10 ) WRITE(numout,*) 'violation a_i<0               (',cd_routine,') = ',zamin
[4688]147         ENDIF
148
149      ENDIF
150
151   END SUBROUTINE lim_cons_hsm
152
[5167]153   SUBROUTINE lim_cons_final( cd_routine )
[5176]154      !!---------------------------------------------------------------------------------------------------------
155      !!                                   ***  ROUTINE lim_cons_final ***
156      !!
157      !! ** Purpose : Test the conservation of heat, salt and mass at the end of each ice time-step
158      !!
[7646]159      !! ** Method  : This is an online diagnostics which can be activated with ln_limdiachk=true
[5176]160      !!              It prints in ocean.output if there is a violation of conservation at each time-step
161      !!              The thresholds (zv_sill, zs_sill, zh_sill) which determine the violation are set to
162      !!              a minimum of 1 mm of ice (over the ice area) that is lost/gained spuriously during 100 years.
163      !!              For salt and heat thresholds, ice is considered to have a salinity of 10
164      !!              and a heat content of 3e5 J/kg (=latent heat of fusion)
165      !!--------------------------------------------------------------------------------------------------------
166      CHARACTER(len=*), INTENT(in)    :: cd_routine    ! name of the routine
[5167]167      REAL(wp)                        :: zhfx, zsfx, zvfx
[5176]168      REAL(wp)                        :: zarea, zv_sill, zs_sill, zh_sill
169      REAL(wp), PARAMETER             :: zconv = 1.e-9 ! convert W to GW and kg to Mt
[5167]170
[5176]171      ! heat flux
[7646]172      zhfx  = glob_sum( ( hfx_in - hfx_out - diag_heat - diag_trp_ei - diag_trp_es   &
173      !  &              - SUM( qevap_ice * a_i_b, dim=3 )                           & !!clem: I think this line must be commented (but need check)
174         &              ) * e1e2t * tmask(:,:,1) * zconv ) 
[5176]175      ! salt flux
[5836]176      zsfx  = glob_sum( ( sfx + diag_smvi ) * e1e2t * tmask(:,:,1) * zconv ) * rday
[5176]177      ! water flux
[5836]178      zvfx  = glob_sum( ( wfx_ice + wfx_snw + wfx_spr + wfx_sub + diag_vice + diag_vsnw ) * e1e2t * tmask(:,:,1) * zconv ) * rday
[5167]179
[5176]180      ! set threshold values and calculate the ice area (+epsi10 to set a threshold > 0 when there is no ice)
[5836]181      zarea   = glob_sum( SUM( a_i + epsi10, dim=3 ) * e1e2t * zconv ) ! in 1.e9 m2
[5176]182      zv_sill = zarea * 2.5e-5
183      zs_sill = zarea * 25.e-5
184      zh_sill = zarea * 10.e-5
[5167]185
[5176]186      IF( ABS( zvfx ) > zv_sill ) WRITE(numout,*) 'violation vfx    [Mt/day]       (',cd_routine,')  = ',(zvfx)
187      IF( ABS( zsfx ) > zs_sill ) WRITE(numout,*) 'violation sfx    [psu*Mt/day]   (',cd_routine,')  = ',(zsfx)
188      IF( ABS( zhfx ) > zh_sill ) WRITE(numout,*) 'violation hfx    [GW]           (',cd_routine,')  = ',(zhfx)
189
[5167]190   END SUBROUTINE lim_cons_final
191
[834]192#else
193   !!----------------------------------------------------------------------
194   !!   Default option         Empty module            NO LIM sea-ice model
195   !!----------------------------------------------------------------------
196#endif
197   !!======================================================================
198END MODULE limcons
Note: See TracBrowser for help on using the repository browser.