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.
limupdate2.F90 in trunk/NEMOGCM/NEMO/LIM_SRC_3 – NEMO

source: trunk/NEMOGCM/NEMO/LIM_SRC_3/limupdate2.F90 @ 7646

Last change on this file since 7646 was 7646, checked in by timgraham, 7 years ago

Merge of dev_merge_2016 into trunk. UPDATE TO ARCHFILES NEEDED for XIOS2.
LIM_SRC_s/limrhg.F90 to follow in next commit due to change of kind (I'm unable to do it in this commit).
Merged using the following steps:

1) svn merge --reintegrate svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/trunk .
2) Resolve minor conflicts in sette.sh and namelist_cfg for ORCA2LIM3 (due to a change in trunk after branch was created)
3) svn commit
4) svn switch svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/trunk
5) svn merge svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/branches/2016/dev_merge_2016 .
6) At this stage I checked out a clean copy of the branch to compare against what is about to be committed to the trunk.
6) svn commit #Commit code to the trunk

In this commit I have also reverted a change to Fcheck_archfile.sh which was causing problems on the Paris machine.

  • Property svn:keywords set to Id
File size: 8.3 KB
Line 
1MODULE limupdate2
2   !!======================================================================
3   !!                     ***  MODULE  limupdate2  ***
4   !!   LIM-3 : Update of sea-ice global variables at the end of the time step
5   !!======================================================================
6   !! History :  3.0  !  2006-04  (M. Vancoppenolle) Original code
7   !!            3.5  !  2014-06  (C. Rousset)       Complete rewriting/cleaning
8   !!----------------------------------------------------------------------
9#if defined key_lim3
10   !!----------------------------------------------------------------------
11   !!   'key_lim3'                                      LIM3 sea-ice model
12   !!----------------------------------------------------------------------
13   !!    lim_update2   : computes update of sea-ice global variables from trend terms
14   !!----------------------------------------------------------------------
15   USE sbc_oce         ! Surface boundary condition: ocean fields
16   USE sbc_ice         ! Surface boundary condition: ice fields
17   USE dom_oce
18   USE phycst          ! physical constants
19   USE ice
20   USE thd_ice         ! LIM thermodynamic sea-ice variables
21   USE limitd_th
22   USE limvar
23   USE lbclnk          ! lateral boundary condition - MPP exchanges
24   USE wrk_nemo        ! work arrays
25   USE timing          ! Timing
26   USE limcons         ! conservation tests
27   USE limctl
28   USE lib_mpp         ! MPP library
29   USE lib_fortran     ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined) 
30   USE in_out_manager
31
32   IMPLICIT NONE
33   PRIVATE
34
35   PUBLIC   lim_update2   ! routine called by ice_step
36
37   !! * Substitutions
38#  include "vectopt_loop_substitute.h90"
39   !!----------------------------------------------------------------------
40   !! NEMO/LIM3 4.0 , UCL - NEMO Consortium (2011)
41   !! $Id$
42   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
43   !!----------------------------------------------------------------------
44CONTAINS
45
46   SUBROUTINE lim_update2( kt )
47      !!-------------------------------------------------------------------
48      !!               ***  ROUTINE lim_update2  ***
49      !!               
50      !! ** Purpose :  Computes update of sea-ice global variables at
51      !!               the end of the time step.
52      !!
53      !!---------------------------------------------------------------------
54      INTEGER, INTENT(in) ::   kt    ! number of iteration
55      INTEGER  ::   ji, jj, jk, jl   ! dummy loop indices
56      REAL(wp) ::   zsal
57      REAL(wp) ::   zvi_b, zsmv_b, zei_b, zfs_b, zfw_b, zft_b 
58      !!-------------------------------------------------------------------
59      IF( nn_timing == 1 )  CALL timing_start('limupdate2')
60
61      IF( kt == nit000 .AND. lwp ) THEN
62         WRITE(numout,*)''
63         WRITE(numout,*)' lim_update2 '
64         WRITE(numout,*)' ~~~~~~~~~~~ '
65      ENDIF
66
67      ! conservation test
68      IF( ln_limdiachk ) CALL lim_cons_hsm(0, 'limupdate2', zvi_b, zsmv_b, zei_b, zfw_b, zfs_b, zft_b)
69
70      !----------------------------------------------------------------------
71      ! Constrain the thickness of the smallest category above himin
72      !----------------------------------------------------------------------
73      DO jj = 1, jpj 
74         DO ji = 1, jpi
75            rswitch = MAX( 0._wp , SIGN( 1._wp, a_i(ji,jj,1) - epsi20 ) )   !0 if no ice and 1 if yes
76            ht_i(ji,jj,1) = v_i (ji,jj,1) / MAX( a_i(ji,jj,1) , epsi20 ) * rswitch
77            IF( v_i(ji,jj,1) > 0._wp .AND. ht_i(ji,jj,1) < rn_himin ) THEN
78               a_i (ji,jj,1) = a_i (ji,jj,1) * ht_i(ji,jj,1) / rn_himin
79               oa_i(ji,jj,1) = oa_i(ji,jj,1) * ht_i(ji,jj,1) / rn_himin
80            ENDIF
81         END DO
82      END DO
83     
84      !-----------------------------------------------------
85      ! ice concentration should not exceed amax
86      !-----------------------------------------------------
87      at_i(:,:) = 0._wp
88      DO jl = 1, jpl
89         at_i(:,:) = a_i(:,:,jl) + at_i(:,:)
90      END DO
91
92      DO jl  = 1, jpl
93         DO jj = 1, jpj
94            DO ji = 1, jpi
95               IF( at_i(ji,jj) > rn_amax_2d(ji,jj) .AND. a_i(ji,jj,jl) > 0._wp ) THEN
96                  a_i (ji,jj,jl) = a_i (ji,jj,jl) * ( 1._wp - ( 1._wp - rn_amax_2d(ji,jj) / at_i(ji,jj) ) )
97                  oa_i(ji,jj,jl) = oa_i(ji,jj,jl) * ( 1._wp - ( 1._wp - rn_amax_2d(ji,jj) / at_i(ji,jj) ) )
98               ENDIF
99            END DO
100         END DO
101      END DO
102
103      !---------------------
104      ! Ice salinity
105      !---------------------
106      IF (  nn_icesal == 2  ) THEN
107         DO jl = 1, jpl
108            DO jj = 1, jpj 
109               DO ji = 1, jpi
110                  zsal            = smv_i(ji,jj,jl)
111                  ! salinity stays in bounds
112                  rswitch         = 1._wp - MAX( 0._wp, SIGN( 1._wp, - v_i(ji,jj,jl) ) )
113                  smv_i(ji,jj,jl) = rswitch * MAX( MIN( rn_simax * v_i(ji,jj,jl), smv_i(ji,jj,jl) ), rn_simin * v_i(ji,jj,jl) )
114                  ! associated salt flux
115                  sfx_res(ji,jj) = sfx_res(ji,jj) - ( smv_i(ji,jj,jl) - zsal ) * rhoic * r1_rdtice
116               END DO
117            END DO
118         END DO
119      ENDIF
120
121      !----------------------------------------------------
122      ! Rebin categories with thickness out of bounds
123      !----------------------------------------------------
124      IF ( jpl > 1 ) CALL lim_itd_th_reb( 1, jpl )
125
126      !-----------------
127      ! zap small values
128      !-----------------
129      CALL lim_var_zapsmall
130
131      !------------------------------------------------------------------------------
132      ! Corrections to avoid wrong values                                        |
133      !------------------------------------------------------------------------------
134      ! Ice drift
135      !------------
136      DO jj = 2, jpjm1
137         DO ji = 2, jpim1
138            IF ( at_i(ji,jj) == 0._wp ) THEN ! what to do if there is no ice
139               IF ( at_i(ji+1,jj) == 0._wp ) u_ice(ji,jj)   = 0._wp ! right side
140               IF ( at_i(ji-1,jj) == 0._wp ) u_ice(ji-1,jj) = 0._wp ! left side
141               IF ( at_i(ji,jj+1) == 0._wp ) v_ice(ji,jj)   = 0._wp ! upper side
142               IF ( at_i(ji,jj-1) == 0._wp ) v_ice(ji,jj-1) = 0._wp ! bottom side
143            ENDIF
144         END DO
145      END DO
146      !lateral boundary conditions
147      CALL lbc_lnk( u_ice(:,:), 'U', -1. )
148      CALL lbc_lnk( v_ice(:,:), 'V', -1. )
149      !mask velocities
150      u_ice(:,:) = u_ice(:,:) * umask(:,:,1)
151      v_ice(:,:) = v_ice(:,:) * vmask(:,:,1)
152 
153      ! -------------------------------------------------
154      ! Diagnostics
155      ! -------------------------------------------------
156      DO jl  = 1, jpl
157         oa_i(:,:,jl) = oa_i(:,:,jl) + a_i(:,:,jl) * rdt_ice / rday   ! ice natural aging
158         afx_thd(:,:) = afx_thd(:,:) + ( a_i(:,:,jl) - a_i_b(:,:,jl) ) * r1_rdtice
159      END DO
160      afx_tot = afx_thd + afx_dyn
161
162      DO jj = 1, jpj
163         DO ji = 1, jpi           
164            ! heat content variation (W.m-2)
165            diag_heat(ji,jj) = diag_heat(ji,jj) -  &
166               &               ( SUM( e_i(ji,jj,1:nlay_i,:) - e_i_b(ji,jj,1:nlay_i,:) ) +  & 
167               &                 SUM( e_s(ji,jj,1:nlay_s,:) - e_s_b(ji,jj,1:nlay_s,:) )    &
168               &               ) * r1_rdtice   
169            ! salt, volume
170            diag_smvi(ji,jj) = diag_smvi(ji,jj) + SUM( smv_i(ji,jj,:) - smv_i_b(ji,jj,:) ) * rhoic * r1_rdtice
171            diag_vice(ji,jj) = diag_vice(ji,jj) + SUM( v_i  (ji,jj,:) - v_i_b  (ji,jj,:) ) * rhoic * r1_rdtice
172            diag_vsnw(ji,jj) = diag_vsnw(ji,jj) + SUM( v_s  (ji,jj,:) - v_s_b  (ji,jj,:) ) * rhosn * r1_rdtice
173         END DO
174      END DO
175
176      ! conservation test
177      IF( ln_limdiachk ) CALL lim_cons_hsm(1, 'limupdate2', zvi_b, zsmv_b, zei_b, zfw_b, zfs_b, zft_b)
178
179      ! control prints
180      IF( ln_limctl )    CALL lim_prt( kt, iiceprt, jiceprt, 2, ' - Final state - ' )
181      IF( ln_ctl )       CALL lim_prt3D( 'limupdate2' )
182   
183      IF( nn_timing == 1 )  CALL timing_stop('limupdate2')
184
185   END SUBROUTINE lim_update2
186
187#else
188   !!----------------------------------------------------------------------
189   !!   Default option         Empty Module               No sea-ice model
190   !!----------------------------------------------------------------------
191CONTAINS
192   SUBROUTINE lim_update2     ! Empty routine
193   END SUBROUTINE lim_update2
194
195#endif
196
197END MODULE limupdate2
Note: See TracBrowser for help on using the repository browser.