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.
limthd_lac_2.F90 in branches/2015/dev_r5803_NOC_WAD/NEMOGCM/NEMO/LIM_SRC_2 – NEMO

source: branches/2015/dev_r5803_NOC_WAD/NEMOGCM/NEMO/LIM_SRC_2/limthd_lac_2.F90 @ 5870

Last change on this file since 5870 was 5870, checked in by acc, 8 years ago

Branch 2015/dev_r5803_NOC_WAD. Merge in trunk changes from 5803 to 5869 in preparation for merge. Also tidied and reorganised some wetting and drying code. Renamed wadlmt.F90 to wetdry.F90. Wetting drying code changes restricted to domzgr.F90, domvvl.F90 nemogcm.F90 sshwzv.F90, dynspg_ts.F90, wetdry.F90 and dynhpg.F90. Code passes full SETTE tests with ln_wd=.false.. Still awaiting test case for checking with ln_wd=.false.

  • Property svn:keywords set to Id
File size: 12.6 KB
Line 
1MODULE limthd_lac_2
2#if defined key_lim2
3   !!======================================================================
4   !!                       ***  MODULE limthd_lac_2   ***
5   !!                lateral thermodynamic growth of the ice
6   !!======================================================================
7
8   !!----------------------------------------------------------------------
9   !!   lim_lat_acr_2 : lateral accretion of ice
10   !!----------------------------------------------------------------------
11   USE par_oce        ! ocean parameters
12   USE phycst
13   USE thd_ice_2
14   USE ice_2
15   USE limistate_2 
16   USE lib_mpp        ! MPP library
17   USE wrk_nemo       ! work arrays
18   USE lib_fortran    ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined) 
19
20   IMPLICIT NONE
21   PRIVATE
22
23   PUBLIC   lim_thd_lac_2   ! called by lim_thd_2
24
25   REAL(wp)  ::           &  ! constant values
26      epsi20 = 1.e-20  ,  &
27      epsi13 = 1.e-13  ,  &
28      zzero  = 0.e0    ,  &
29      zone   = 1.e0
30
31   !!----------------------------------------------------------------------
32   !! NEMO/LIM2 3.3 , UCL - NEMO Consortium (2010)
33   !! $Id$
34   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
35   !!----------------------------------------------------------------------
36CONTAINS
37   
38   SUBROUTINE lim_thd_lac_2( kideb, kiut )
39      !!-------------------------------------------------------------------
40      !!               ***   ROUTINE lim_thd_lac_2  ***
41      !! 
42      !! ** Purpose : Computation of the evolution of the ice thickness and
43      !!      concentration as a function of the heat balance in the leads.
44      !!      It is only used for lateral accretion
45      !!       
46      !! ** Method  : Ice is formed in the open water when ocean lose heat
47      !!      (heat budget of open water Bl is negative) .
48      !!      Computation of the increase of 1-A (ice concentration) fol-
49      !!      lowing the law :
50      !!      (dA/dt)acc = F[ (1-A)/(1-a) ] * [ Bl / (Li*h0) ]
51      !!       where - h0 is the thickness of ice created in the lead
52      !!             - a is a minimum fraction for leads
53      !!             - F is a monotonic non-increasing function defined as:
54      !!                  F(X)=( 1 - X**exld )**(1.0/exld)
55      !!             - exld is the exponent closure rate (=2 default val.)
56      !!
57      !! ** Action : - Adjustment of snow and ice thicknesses and heat
58      !!                content in brine pockets
59      !!             - Updating ice internal temperature
60      !!             - Computation of variation of ice volume and mass
61      !!             - Computation of frldb after lateral accretion and
62      !!               update h_snow_1d, h_ice_1d and tbif_1d(:,:)     
63      !!
64      !! ** References :
65      !!      M. Maqueda, 1995, PhD Thesis, Univesidad Complutense Madrid
66      !!      Fichefet T. and M. Maqueda 1997, J. Geo. Res., 102(C6),
67      !!                                                12609 -12646   
68      !! History :
69      !!   1.0  !  01-04 (LIM)  original code
70      !!   2.0  !  02-08 (C. Ethe, G. Madec)  F90, mpp
71      !!-------------------------------------------------------------------
72      INTEGER , INTENT(IN)::  &
73         kideb          ,   &  ! start point on which the the computation is applied
74         kiut                  ! end point on which the the computation is applied
75
76      ! * Local variables
77      INTEGER ::            &
78         ji             ,   &  !  dummy loop indices
79         iicefr         ,   &  !  1 = existing ice ; 0 = no ice
80         iiceform       ,   &  !  1 = ice formed   ; 0 = no ice formed
81         ihemis                !  dummy indice
82      REAL(wp), POINTER, DIMENSION(:) ::   zqbgow      !  heat budget of the open water (negative)
83      REAL(wp), POINTER, DIMENSION(:) ::   zfrl_old    !  previous sea/ice fraction
84      REAL(wp), POINTER, DIMENSION(:) ::   zhice_old   !  previous ice thickness
85      REAL(wp), POINTER, DIMENSION(:) ::   zhice0      !  thickness of newly formed ice in leads
86      REAL(wp), POINTER, DIMENSION(:) ::   zfrlmin     !  minimum fraction for leads
87      REAL(wp), POINTER, DIMENSION(:) ::   zdhicbot    !  part of thickness of newly formed ice in leads which
88                                !  has been already used in transport for example
89      REAL(wp)  ::  &
90         zhemis           ,  &  !  hemisphere (0 = North, 1 = South)
91         zhicenew         ,  &  !  new ice thickness
92         zholds2          ,  &  !  ratio of previous ice thickness and 2
93         zhnews2          ,  &  !  ratio of new ice thickness and 2
94         zfrlnew          ,  &  !  new sea/ice fraction
95         zfrld            ,  &  !  ratio of sea/ice fraction and minimum fraction for leads
96         zfrrate          ,  &  !  leads-closure rate
97         zdfrl                  !  sea-ice fraction increment
98      REAL(wp)  ::  &
99         zdh1 , zdh2 , zdh3 , zdh4, zdh5   , &   ! tempory scalars
100         ztint , zta1 , zta2 , zta3 , zta4 , &
101         zah, zalpha , zbeta
102      !!---------------------------------------------------------------------     
103               
104      CALL wrk_alloc( jpij, zqbgow, zfrl_old, zhice_old, zhice0, zfrlmin, zdhicbot )
105     
106      !--------------------------------------------------------------
107      !   Computation of the heat budget of the open water (negative)
108      !--------------------------------------------------------------
109     
110      DO ji = kideb , kiut     
111         zqbgow(ji) = qldif_1d(ji) - qcmif_1d(ji)
112      END DO
113     
114      !-----------------------------------------------------------------
115      !   Taking the appropriate values for the corresponding hemisphere
116      !-----------------------------------------------------------------
117      DO ji = kideb , kiut
118         zhemis       = MAX( zzero , SIGN( zone , frld_1d(ji) - 2.0 ) ) 
119         ihemis       = INT( 1 + zhemis )
120         zhice0  (ji) = hiccrit( ihemis ) 
121         zfrlmin (ji) = acrit  ( ihemis )   
122         frld_1d (ji) = frld_1d(ji) - 2.0 * zhemis
123         zfrl_old(ji) = frld_1d(ji)
124      END DO
125     
126      !-------------------------------------------------------------------
127      !     Lateral Accretion (modification of the fraction of open water)
128      !     The ice formed in the leads has always a thickness zhice0, but
129      !     only a fraction zfrrate of the ice formed contributes to the
130      !     increase of the ice fraction. The remaining part (1-zfrrate)
131      !     is rather assumed to lead to an increase in the thickness of the
132      !     pre-existing ice (transport for example).
133      !     Morales Maqueda, 1995 - Fichefet and Morales Maqueda, 1997
134      !---------------------------------------------------------------------
135     
136      DO ji = kideb , kiut
137         iicefr       = 1 - MAX( 0, INT( SIGN( 1.5 * zone , zfrl_old(ji) - 1.0 + epsi13 ) ) )
138         !---computation of the leads-closure rate
139         zfrld        = MIN( zone , ( 1.0 - frld_1d(ji) ) / ( 1.0 - zfrlmin(ji) ) )
140         zfrrate      = ( 1.0 - zfrld**exld )**( 1.0 / exld )
141         !--computation of the sea-ice fraction increment and the new fraction
142         zdfrl        = ( zfrrate / zhice0(ji) )  * ( zqbgow(ji) / xlic )
143         zfrlnew      = zfrl_old(ji) + zdfrl
144         !--update the sea-ice fraction
145         frld_1d   (ji) = MAX( zfrlnew , zfrlmin(ji) )
146         !--computation of the remaining part of ice thickness which has been already used
147         zdhicbot(ji) =  ( frld_1d(ji) - zfrlnew ) * zhice0(ji) / ( 1.0 - zfrlmin(ji) )   & 
148            &         -  (  ( 1.0 - zfrrate ) / ( 1.0 - frld_1d(ji) ) )  * ( zqbgow(ji) / xlic ) 
149      END DO
150 
151      !----------------------------------------------------------------------------------------
152      !      Ajustement of snow and ice thicknesses and updating the total heat stored in brine pockets 
153      !      The thickness of newly formed ice is averaged with that of the pre-existing
154      !         (1-Anew) * hinew = (1-Aold) * hiold + ((1-Anew)-(1-Aold)) * h0
155      !      Snow is distributed over the new ice-covered area
156      !         (1-Anew) * hsnew = (1-Aold) * hsold           
157      !--------------------------------------------------------------------------------------------
158     
159      DO ji = kideb , kiut
160         iicefr       = 1 - MAX( 0, INT( SIGN( 1.5 * zone , zfrl_old(ji) - 1.0 + epsi13 ) ) )
161         zhice_old(ji) = h_ice_1d(ji)
162         zhicenew      = iicefr * zhice_old(ji) + ( 1 - iicefr ) * zhice0(ji)
163         zalpha        = ( 1. - zfrl_old(ji) ) / ( 1.- frld_1d(ji) )
164         h_snow_1d(ji) = zalpha * h_snow_1d(ji)
165         h_ice_1d (ji) = zalpha * zhicenew + ( 1.0 - zalpha ) * zhice0(ji)
166         qstbif_1d(ji) = zalpha * qstbif_1d(ji) 
167      END DO
168     
169      !-------------------------------------------------------
170      !   Ajustement of ice internal temperatures
171      !-------------------------------------------------------
172     
173      DO ji = kideb , kiut
174         iicefr      = 1 - MAX( 0, INT( SIGN( 1.5 * zone , zfrl_old(ji) - 1.0 + epsi13 ) ) )
175         iiceform    = 1 - MAX( 0 ,INT( SIGN( 1.5 * zone , zhice0(ji) - h_ice_1d(ji) ) ) )
176         zholds2     = zhice_old(ji)/ 2.
177         zhnews2     = h_ice_1d(ji) / 2.
178         zdh1        = MAX( zzero ,  zhice_old(ji)   - zhnews2 )
179         zdh2        = MAX( zzero , -zhice_old(ji)   + zhnews2 )
180         zdh3        = MAX( zzero ,  h_ice_1d(ji) - zholds2 )
181         zdh4        = MAX( zzero , -h_ice_1d(ji) + zholds2 )
182         zdh5        = MAX( zzero , zhice0(ji)      - zholds2 )
183         ztint       =       iiceform   * (  ( zholds2 - zdh3 ) * tbif_1d(ji,3) + zdh4 * tbif_1d(ji,2) )      &
184            &                           / MAX( epsi20 , h_ice_1d(ji) - zhice0(ji) )                           &
185            &                 + ( 1 - iiceform ) * tfu_1d(ji)
186         zta1        = iicefr * ( 1.  - zfrl_old(ji) ) * tbif_1d(ji,2) 
187         zta2        = iicefr * ( 1.  - zfrl_old(ji) ) * tbif_1d(ji,3)
188         zta3        = iicefr * ( 1.  - zfrl_old(ji) ) * ztint
189         zta4        = ( zfrl_old(ji) - frld_1d   (ji) ) * tfu_1d(ji)
190         zah         = ( 1. - frld_1d(ji) ) * zhnews2 
191
192         tbif_1d(ji,2) = (  MIN( zhnews2 , zholds2 )                                              * zta1   &
193            &          + ( 1 - iiceform ) * ( zholds2 - zdh1 )                                    * zta2   &
194            &          + ( iiceform * ( zhnews2 - zhice0(ji) + zdh5 ) + ( 1 - iiceform ) * zdh2 ) * zta3   & 
195            &          + MIN ( zhnews2 , zhice0(ji) )                                             * zta4   &
196            &          ) / zah
197         
198         tbif_1d(ji,3) =     ( iiceform * ( zhnews2 - zdh3 )                                           * zta1  &
199            &              + ( iiceform * zdh3 + ( 1 - iiceform ) * zdh1 )                             * zta2  &
200            &              + ( iiceform * ( zhnews2 - zdh5 ) + ( 1 - iiceform ) * ( zhnews2 - zdh1 ) ) * zta3  & 
201            &              + ( iiceform * zdh5 + ( 1 - iiceform ) * zhnews2 )                          * zta4  &
202            &            ) / zah
203         !---removing the remaining part of ice formed which has been already used
204         zbeta         = h_ice_1d(ji) / ( h_ice_1d(ji) + zdhicbot(ji) )
205         h_ice_1d(ji)  = h_ice_1d(ji) + zdhicbot(ji)
206         tbif_1d (ji,2)= zbeta * tbif_1d(ji,2) + ( 1.0 - zbeta ) * tbif_1d(ji,3)
207         tbif_1d (ji,3)= ( 2. * zbeta - 1.0 ) * tbif_1d(ji,3) + ( 2. * zdhicbot(ji) / h_ice_1d(ji) ) * tfu_1d(ji)
208         
209      END DO
210     
211      !-------------------------------------------------------------
212      !    Computation of variation of ice volume and ice mass
213      !           Vold = (1-Aold) * hiold ; Vnew = (1-Anew) * hinew
214      !           dV = Vnew - Vold
215      !-------------------------------------------------------------
216     
217      DO ji = kideb , kiut
218         dvlbq_1d  (ji) = ( 1. - frld_1d(ji) ) * h_ice_1d(ji) - ( 1. - zfrl_old(ji) ) * zhice_old(ji)
219         rdm_ice_1d(ji) = rdm_ice_1d(ji) + rhoic * dvlbq_1d(ji)
220         rdq_ice_1d(ji) = rdq_ice_1d(ji) + rcpic * dvlbq_1d(ji) * ( tfu_1d(ji) - rt0 )      ! heat content relative to rt0
221      END DO
222     
223      CALL wrk_dealloc( jpij, zqbgow, zfrl_old, zhice_old, zhice0, zfrlmin, zdhicbot )
224      !
225   END SUBROUTINE lim_thd_lac_2
226#else
227   !!----------------------------------------------------------------------
228   !!                       ***  MODULE limthd_lac_2   ***
229   !!                           no sea ice model
230   !!----------------------------------------------------------------------
231CONTAINS
232   SUBROUTINE lim_thd_lac_2           ! Empty routine
233   END SUBROUTINE lim_thd_lac_2
234#endif
235   !!======================================================================
236END MODULE limthd_lac_2
Note: See TracBrowser for help on using the repository browser.