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/2014/dev_r4650_UKMO7_STARTHOUR/NEMOGCM/NEMO/LIM_SRC_3 – NEMO

source: branches/2014/dev_r4650_UKMO7_STARTHOUR/NEMOGCM/NEMO/LIM_SRC_3/limcons.F90 @ 5075

Last change on this file since 5075 was 5075, checked in by timgraham, 9 years ago

Upgraded branch to current head of trunk (r5072) so it can be used with the trunk

  • Property svn:keywords set to Id
File size: 11.3 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   !!            4.0  ! 2011-02  (G. Madec)  add mpp considerations
9   !!             -   ! 2014-05  (C. Rousset) add lim_cons_hsm
10   !!----------------------------------------------------------------------
11#if defined key_lim3
12   !!----------------------------------------------------------------------
13   !!   'key_lim3'                                      LIM-3 sea-ice model
14   !!----------------------------------------------------------------------
15   !!    lim_cons     :   checks whether energy, mass and salt are conserved
16   !!----------------------------------------------------------------------
17   USE phycst         ! physical constants
18   USE par_ice        ! LIM-3 parameter
19   USE ice            ! LIM-3 variables
20   USE dom_ice        ! LIM-3 domain
21   USE dom_oce        ! ocean domain
22   USE in_out_manager ! I/O manager
23   USE lib_mpp        ! MPP library
24   USE lib_fortran    ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined) 
25
26   IMPLICIT NONE
27   PRIVATE
28
29   PUBLIC   lim_column_sum
30   PUBLIC   lim_column_sum_energy
31   PUBLIC   lim_cons_check
32   PUBLIC   lim_cons_hsm
33
34   !!----------------------------------------------------------------------
35   !! NEMO/LIM3 4.0 , UCL - NEMO Consortium (2011)
36   !! $Id$
37   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
38   !!----------------------------------------------------------------------
39CONTAINS
40
41   SUBROUTINE lim_column_sum( ksum, pin, pout )
42      !!-------------------------------------------------------------------
43      !!               ***  ROUTINE lim_column_sum ***
44      !!
45      !! ** Purpose : Compute the sum of xin over nsum categories
46      !!
47      !! ** Method  : Arithmetics
48      !!
49      !! ** Action  : Gets xin(ji,jj,jl) and computes xout(ji,jj)
50      !!---------------------------------------------------------------------
51      INTEGER                   , INTENT(in   ) ::   ksum   ! number of categories/layers
52      REAL(wp), DIMENSION(:,:,:), INTENT(in   ) ::   pin    ! input field
53      REAL(wp), DIMENSION(:,:)  , INTENT(  out) ::   pout   ! output field
54      !
55      INTEGER ::   jl   ! dummy loop indices
56      !!---------------------------------------------------------------------
57      !
58      pout(:,:) = pin(:,:,1)
59      DO jl = 2, ksum
60         pout(:,:) = pout(:,:) + pin(:,:,jl)
61      END DO
62      !
63   END SUBROUTINE lim_column_sum
64
65
66   SUBROUTINE lim_column_sum_energy( ksum, klay, pin, pout)
67      !!-------------------------------------------------------------------
68      !!               ***  ROUTINE lim_column_sum_energy ***
69      !!
70      !! ** Purpose : Compute the sum of xin over nsum categories
71      !!              and nlay layers
72      !!
73      !! ** Method  : Arithmetics
74      !!---------------------------------------------------------------------
75      INTEGER                                  , INTENT(in   ) ::   ksum   !: number of categories
76      INTEGER                                  , INTENT(in   ) ::   klay   !: number of vertical layers
77      REAL(wp), DIMENSION(jpi,jpj,nlay_i+1,jpl), INTENT(in   ) ::   pin   !: input field
78      REAL(wp), DIMENSION(jpi,jpj)             , INTENT(  out) ::   pout   !: output field
79      !
80      INTEGER ::   jk, jl   ! dummy loop indices
81      !!---------------------------------------------------------------------
82      !
83      pout(:,:) = 0._wp
84      DO jl = 1, ksum
85         DO jk = 2, klay 
86            pout(:,:) = pout(:,:) + pin(:,:,jk,jl)
87         END DO
88      END DO
89      !
90   END SUBROUTINE lim_column_sum_energy
91
92
93   SUBROUTINE lim_cons_check( px1, px2, pmax_err, cd_fieldid )
94      !!-------------------------------------------------------------------
95      !!               ***  ROUTINE lim_cons_check ***
96      !!
97      !! ** Purpose : Test the conservation of a certain variable
98      !!              For each physical grid cell, check that initial
99      !!              and final values
100      !!              of a conserved field are equal to within a small value.
101      !!
102      !! ** Method  :
103      !!---------------------------------------------------------------------
104      REAL(wp), DIMENSION(:,:), INTENT(in   ) ::   px1          !: initial field
105      REAL(wp), DIMENSION(:,:), INTENT(in   ) ::   px2          !: final field
106      REAL(wp)                , INTENT(in   ) ::   pmax_err     !: max allowed error
107      CHARACTER(len=15)       , INTENT(in   ) ::   cd_fieldid   !: field identifyer
108      !
109      INTEGER  ::   ji, jj          ! dummy loop indices
110      INTEGER  ::   inb_error       ! number of g.c where there is a cons. error
111      LOGICAL  ::   llconserv_err   ! = .true. if conservation check failed
112      REAL(wp) ::   zmean_error     ! mean error on error points
113      !!---------------------------------------------------------------------
114      !
115      IF(lwp) WRITE(numout,*) ' lim_cons_check '
116      IF(lwp) WRITE(numout,*) ' ~~~~~~~~~~~~~~ '
117
118      llconserv_err = .FALSE.
119      inb_error     = 0
120      zmean_error   = 0._wp
121      IF( MAXVAL( px2(:,:) - px1(:,:) ) > pmax_err )   llconserv_err = .TRUE.
122
123      IF( llconserv_err ) THEN
124         DO jj = 1, jpj 
125            DO ji = 1, jpi
126               IF( ABS( px2(ji,jj) - px1(ji,jj) ) > pmax_err ) THEN
127                  inb_error   = inb_error + 1
128                  zmean_error = zmean_error + ABS( px2(ji,jj) - px1(ji,jj) )
129                  !
130                  IF(lwp) THEN
131                     WRITE (numout,*) ' ALERTE 99 '
132                     WRITE (numout,*) ' Conservation error: ', cd_fieldid
133                     WRITE (numout,*) ' Point             : ', ji, jj 
134                     WRITE (numout,*) ' lat, lon          : ', gphit(ji,jj), glamt(ji,jj)
135                     WRITE (numout,*) ' Initial value     : ', px1(ji,jj)
136                     WRITE (numout,*) ' Final value       : ', px2(ji,jj)
137                     WRITE (numout,*) ' Difference        : ', px2(ji,jj) - px1(ji,jj)
138                  ENDIF
139               ENDIF
140            END DO
141         END DO
142         !
143      ENDIF
144      IF(lk_mpp)   CALL mpp_sum( inb_error   )
145      IF(lk_mpp)   CALL mpp_sum( zmean_error )
146      !
147      IF( inb_error > 0 .AND. lwp ) THEN
148         zmean_error = zmean_error / REAL( inb_error, wp )
149         WRITE(numout,*) ' Conservation check for : ', cd_fieldid
150         WRITE(numout,*) ' Number of error points : ', inb_error
151         WRITE(numout,*) ' Mean error on these pts: ', zmean_error
152      ENDIF
153      !
154   END SUBROUTINE lim_cons_check
155
156
157   SUBROUTINE lim_cons_hsm( icount, cd_routine, zvi_b, zsmv_b, zei_b, zfw_b, zfs_b, zft_b )
158      !!-------------------------------------------------------------------
159      !!               ***  ROUTINE lim_cons_hsm ***
160      !!
161      !! ** Purpose : Test the conservation of heat, salt and mass for each routine
162      !!
163      !! ** Method  :
164      !!---------------------------------------------------------------------
165      INTEGER         , INTENT(in)    :: icount      ! determine wether this is the beggining of the routine (0) or the end (1)
166      CHARACTER(len=*), INTENT(in)    :: cd_routine  ! name of the routine
167      REAL(wp)        , INTENT(inout) :: zvi_b, zsmv_b, zei_b, zfs_b, zfw_b, zft_b 
168      REAL(wp)                        :: zvi,   zsmv,   zei,   zfs,   zfw,   zft
169      REAL(wp)                        :: zvmin, zamin, zamax 
170
171      IF( icount == 0 ) THEN
172
173         zvi_b  = glob_sum( SUM(   v_i(:,:,:)*rhoic + v_s(:,:,:)*rhosn, dim=3 ) * area(:,:) * tms(:,:) )
174         zsmv_b = glob_sum( SUM( smv_i(:,:,:), dim=3 ) * area(:,:) * tms(:,:) )
175         zei_b  = glob_sum( SUM(   e_i(:,:,1:nlay_i,:), dim=3 ) + SUM( e_s(:,:,1:nlay_s,:), dim=3 ) )
176         zfw_b  = glob_sum( - ( wfx_bog(:,:) + wfx_bom(:,:) + wfx_sum(:,:) + wfx_sni(:,:) + wfx_opw(:,:) +  &
177            &                   wfx_res(:,:) + wfx_dyn(:,:) + wfx_snw(:,:) + wfx_sub(:,:) + wfx_spr(:,:)    &
178            &             ) * area(:,:) * tms(:,:) )
179         zfs_b  = glob_sum(   ( sfx_bri(:,:) + sfx_bog(:,:) + sfx_bom(:,:) + sfx_sum(:,:) + sfx_sni(:,:) +  &
180            &                   sfx_opw(:,:) + sfx_res(:,:) + sfx_dyn(:,:)                                  &
181            &                 ) * area(:,:) * tms(:,:) )
182         zft_b  = glob_sum(   ( hfx_sum(:,:) + hfx_bom(:,:) + hfx_bog(:,:) + hfx_dif(:,:) + hfx_opw(:,:) + hfx_snw(:,:)  & 
183            &                 - hfx_thd(:,:) - hfx_dyn(:,:) - hfx_res(:,:) - hfx_sub(:,:) - hfx_spr(:,:)   &
184            &                  ) * area(:,:) / unit_fac * tms(:,:) )
185
186      ELSEIF( icount == 1 ) THEN
187
188         zfs  = glob_sum(   ( sfx_bri(:,:) + sfx_bog(:,:) + sfx_bom(:,:) + sfx_sum(:,:) + sfx_sni(:,:) +  &
189            &                 sfx_opw(:,:) + sfx_res(:,:) + sfx_dyn(:,:)                                  & 
190            &                ) * area(:,:) * tms(:,:) ) - zfs_b
191         zfw  = glob_sum( - ( wfx_bog(:,:) + wfx_bom(:,:) + wfx_sum(:,:) + wfx_sni(:,:) + wfx_opw(:,:) +  &
192            &                 wfx_res(:,:) + wfx_dyn(:,:) + wfx_snw(:,:) + wfx_sub(:,:) + wfx_spr(:,:)    &
193            &                ) * area(:,:) * tms(:,:) ) - zfw_b
194         zft  = glob_sum(   ( hfx_sum(:,:) + hfx_bom(:,:) + hfx_bog(:,:) + hfx_dif(:,:) + hfx_opw(:,:) + hfx_snw(:,:)  & 
195            &               - hfx_thd(:,:) - hfx_dyn(:,:) - hfx_res(:,:) - hfx_sub(:,:) - hfx_spr(:,:)   &
196            &                ) * area(:,:) / unit_fac * tms(:,:) ) - zft_b
197 
198         zvi  = ( glob_sum( SUM(   v_i(:,:,:)*rhoic + v_s(:,:,:)*rhosn, dim=3 ) * area(:,:) * tms(:,:) ) - zvi_b ) * r1_rdtice - zfw 
199         zsmv = ( glob_sum( SUM( smv_i(:,:,:), dim=3 ) * area(:,:) * tms(:,:) ) - zsmv_b ) * r1_rdtice + ( zfs / rhoic )
200         zei  =   glob_sum( SUM( e_i(:,:,1:nlay_i,:), dim=3 ) + SUM( e_s(:,:,1:nlay_s,:), dim=3 ) ) * r1_rdtice - zei_b * r1_rdtice + zft
201
202         zvmin = glob_min(v_i)
203         zamax = glob_max(SUM(a_i,dim=3))
204         zamin = glob_min(a_i)
205       
206         IF(lwp) THEN
207            IF ( ABS( zvi    ) >  1.e-4 ) WRITE(numout,*) 'violation volume [kg/day]     (',cd_routine,') = ',(zvi * rday)
208            IF ( ABS( zsmv   ) >  1.e-4 ) WRITE(numout,*) 'violation saline [psu*m3/day] (',cd_routine,') = ',(zsmv * rday)
209            IF ( ABS( zei    ) >  1.    ) WRITE(numout,*) 'violation enthalpy [1e9 J]    (',cd_routine,') = ',(zei)
210            IF ( zvmin <  0.            ) WRITE(numout,*) 'violation v_i<0  [m]          (',cd_routine,') = ',(zvmin)
211            IF( cd_routine /= 'limtrp' .AND. cd_routine /= 'limitd_me' .AND. zamax > amax+1.e-10 ) THEN
212                                          WRITE(numout,*) 'violation a_i>amax            (',cd_routine,') = ',zamax
213            ENDIF
214            IF ( zamin <  0.            ) WRITE(numout,*) 'violation a_i<0               (',cd_routine,') = ',zamin
215         ENDIF
216
217      ENDIF
218
219   END SUBROUTINE lim_cons_hsm
220
221#else
222   !!----------------------------------------------------------------------
223   !!   Default option         Empty module            NO LIM sea-ice model
224   !!----------------------------------------------------------------------
225#endif
226   !!======================================================================
227END MODULE limcons
Note: See TracBrowser for help on using the repository browser.