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_sal.F90 in branches/2014/dev_r4650_UKMO2_ice_shelves/NEMOGCM/NEMO/LIM_SRC_3 – NEMO

source: branches/2014/dev_r4650_UKMO2_ice_shelves/NEMOGCM/NEMO/LIM_SRC_3/limthd_sal.F90 @ 4657

Last change on this file since 4657 was 4624, checked in by acc, 10 years ago

#1305. Fix slow start-up problems on some systems by introducing and using lwm logical to restrict output of merged namelists to the first (or only) processor. lwm is true only on the first processor regardless of ln_ctl. Small changes to all flavours of nemogcm.F90 are also required to write namctl and namcfg after the call to mynode which now opens output.namelist.dyn and writes nammpp.

  • Property svn:keywords set to Id
File size: 10.4 KB
Line 
1MODULE limthd_sal
2   !!======================================================================
3   !!                       ***  MODULE limthd_sal ***
4   !! LIM-3 sea-ice :  computation of salinity variations in the ice
5   !!======================================================================
6   !! History :   -   ! 2003-05 (M. Vancoppenolle) UCL-ASTR first coding for LIM3-1D
7   !!            3.0  ! 2005-12 (M. Vancoppenolle) adapted to the 3-D version
8   !!            4.0  ! 2011-02 (G. Madec) dynamical allocation
9   !!---------------------------------------------------------------------
10#if defined key_lim3
11   !!----------------------------------------------------------------------
12   !!   'key_lim3'                                      LIM-3 sea-ice model
13   !!----------------------------------------------------------------------
14   !!   lim_thd_sal   : salinity variations in the ice
15   !!----------------------------------------------------------------------
16   USE par_oce        ! ocean parameters
17   USE phycst         ! physical constants (ocean directory)
18   USE sbc_oce        ! Surface boundary condition: ocean fields
19   USE ice            ! LIM variables
20   USE par_ice        ! LIM parameters
21   USE thd_ice        ! LIM thermodynamics
22   USE limvar         ! LIM variables
23   USE in_out_manager ! I/O manager
24   USE lib_mpp        ! MPP library
25   USE wrk_nemo       ! work arrays
26   USE lib_fortran    ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined) 
27
28   IMPLICIT NONE
29   PRIVATE
30
31   PUBLIC   lim_thd_sal        ! called by limthd module
32   PUBLIC   lim_thd_sal_init   ! called by iceini module
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_thd_sal( kideb, kiut )
42      !!-------------------------------------------------------------------
43      !!                ***  ROUTINE lim_thd_sal  ***   
44      !!   
45      !! ** Purpose :   computes new salinities in the ice
46      !!
47      !! ** Method  :  3 possibilities
48      !!               -> num_sal = 1 -> Sice = cst    [ice salinity constant in both time & space]
49      !!               -> num_sal = 2 -> Sice = S(z,t) [Vancoppenolle et al. 2005]
50      !!               -> num_sal = 3 -> Sice = S(z)   [multiyear ice]
51      !!---------------------------------------------------------------------
52      INTEGER, INTENT(in) ::   kideb, kiut   ! thickness category index
53      !
54      INTEGER  ::   ji, jk     ! dummy loop indices
55      REAL(wp) ::   zsold, iflush, iaccrbo, igravdr, isnowic, i_ice_switch,  ztmelts   ! local scalars
56      REAL(wp) ::   zaaa, zbbb, zccc, zdiscrim   ! local scalars
57      REAL(wp), POINTER, DIMENSION(:) ::   ze_init, zhiold, zsiold
58      !!---------------------------------------------------------------------
59
60      CALL wrk_alloc( jpij, ze_init, zhiold, zsiold )
61
62      !------------------------------------------------------------------------------|
63      ! 1) Constant salinity, constant in time                                       |
64      !------------------------------------------------------------------------------|
65!!gm comment: if num_sal = 1 s_i_new, s_i_b and sm_i_b can be set to bulk_sal one for all in the initialisation phase !!
66!!gm           ===>>>   simplification of almost all test on num_sal value
67      IF(  num_sal == 1  ) THEN
68            s_i_b  (kideb:kiut,1:nlay_i) =  bulk_sal
69            sm_i_b (kideb:kiut)          =  bulk_sal 
70            s_i_new(kideb:kiut)          =  bulk_sal
71      ENDIF
72
73      !------------------------------------------------------------------------------|
74      !  Module 2 : Constant salinity varying in time                                |
75      !------------------------------------------------------------------------------|
76
77      IF(  num_sal == 2  ) THEN
78
79         !---------------------------------
80         ! Thickness at previous time step
81         !---------------------------------
82         DO ji = kideb, kiut
83            zhiold(ji) = ht_i_b(ji) - dh_i_bott(ji) - dh_snowice(ji) - dh_i_surf(ji)
84            zsiold(ji) = sm_i_b(ji)
85         END DO
86
87         !---------------------
88         ! Global heat content
89         !---------------------
90         ze_init(:)  =  0._wp
91         DO jk = 1, nlay_i
92            DO ji = kideb, kiut
93               ze_init(ji) = ze_init(ji) + q_i_b(ji,jk) * ht_i_b(ji) / REAL (nlay_i )
94            END DO
95         END DO
96
97         DO ji = kideb, kiut
98            !
99            ! Switches
100            !----------
101            iflush       =         MAX( 0._wp , SIGN( 1.0 , t_su_b(ji) - rtt )        )    ! =1 if summer
102            igravdr      =         MAX( 0._wp , SIGN( 1.0 , t_bo_b(ji) - t_su_b(ji) ) )    ! =1 if t_su < t_bo
103            iaccrbo      =         MAX( 0._wp , SIGN( 1.0 , dh_i_bott(ji) )           )    ! =1 if bottom accretion
104            i_ice_switch = 1._wp - MAX ( 0._wp , SIGN( 1._wp , - ht_i_b(ji) + 1.e-2 ) )
105            isnowic      = 1._wp - MAX ( 0._wp , SIGN( 1._wp , - dh_snowice(ji) ) ) * i_ice_switch   ! =1 if snow ice formation
106
107            !---------------------
108            ! Salinity tendencies
109            !---------------------
110            !                                   ! drainage by gravity drainage
111            dsm_i_gd_1d(ji) = - igravdr * MAX( sm_i_b(ji) - sal_G , 0._wp ) / time_G * rdt_ice 
112            !                                   ! drainage by flushing 
113            dsm_i_fl_1d(ji) = - iflush  * MAX( sm_i_b(ji) - sal_F , 0._wp ) / time_F * rdt_ice
114
115            !-----------------
116            ! Update salinity   
117            !-----------------
118            ! only drainage terms ( gravity drainage and flushing )
119            ! snow ice / bottom sources are added in lim_thd_ent to conserve energy
120            sm_i_b(ji) = sm_i_b(ji) + dsm_i_fl_1d(ji) + dsm_i_gd_1d(ji)
121
122            ! if no ice, salinity = 0.1
123            i_ice_switch = 1._wp - MAX ( 0._wp, SIGN( 1._wp , - ht_i_b(ji) ) )
124            sm_i_b(ji)   = i_ice_switch * sm_i_b(ji) + s_i_min * ( 1._wp - i_ice_switch )
125
126            !----------------------------
127            ! Heat flux - brine drainage
128            !----------------------------
129            fhbri_1d(ji) = 0._wp
130
131            !----------------------------
132            ! Salt flux - brine drainage
133            !----------------------------
134            sfx_bri_1d(ji) = sfx_bri_1d(ji) - i_ice_switch * rhoic * a_i_b(ji) * ht_i_b(ji) * ( sm_i_b(ji) - zsiold(ji) ) * r1_rdtice
135
136         END DO
137
138         ! Salinity profile
139         CALL lim_var_salprof1d( kideb, kiut )
140
141
142         ! Only necessary for conservation check since salinity is modified
143         !--------------------
144         ! Temperature update
145         !--------------------
146         DO jk = 1, nlay_i
147            DO ji = kideb, kiut
148               ztmelts    =  -tmut*s_i_b(ji,jk) + rtt
149               !Conversion q(S,T) -> T (second order equation)
150               zaaa         =  cpic
151               zbbb         =  ( rcp - cpic ) * ( ztmelts - rtt ) + q_i_b(ji,jk) / rhoic - lfus
152               zccc         =  lfus * ( ztmelts - rtt )
153               zdiscrim     =  SQRT(  MAX( zbbb*zbbb - 4.0*zaaa*zccc, 0._wp )  )
154               t_i_b(ji,jk) =  rtt - ( zbbb + zdiscrim ) / ( 2.0 *zaaa )
155            END DO
156         END DO
157         !
158      ENDIF 
159
160      !------------------------------------------------------------------------------|
161      !  Module 3 : Profile of salinity, constant in time                            |
162      !------------------------------------------------------------------------------|
163
164      IF(  num_sal == 3  )   CALL lim_var_salprof1d( kideb, kiut )
165
166      !
167      CALL wrk_dealloc( jpij, ze_init, zhiold, zsiold )
168      !
169   END SUBROUTINE lim_thd_sal
170
171
172   SUBROUTINE lim_thd_sal_init
173      !!-------------------------------------------------------------------
174      !!                  ***  ROUTINE lim_thd_sal_init  ***
175      !!
176      !! ** Purpose :   initialization of ice salinity parameters
177      !!
178      !! ** Method  :   Read the namicesal namelist and check the parameter
179      !!              values called at the first timestep (nit000)
180      !!
181      !! ** input   :   Namelist namicesal
182      !!-------------------------------------------------------------------
183      INTEGER  ::   ios                 ! Local integer output status for namelist read
184      NAMELIST/namicesal/ num_sal, bulk_sal, sal_G, time_G, sal_F, time_F,   &
185         &                s_i_max, s_i_min, s_i_0, s_i_1
186      !!-------------------------------------------------------------------
187      !
188      REWIND( numnam_ice_ref )              ! Namelist namicesal in reference namelist : Ice salinity
189      READ  ( numnam_ice_ref, namicesal, IOSTAT = ios, ERR = 901)
190901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namicesal in reference namelist', lwp )
191
192      REWIND( numnam_ice_cfg )              ! Namelist namicesal in configuration namelist : Ice salinity
193      READ  ( numnam_ice_cfg, namicesal, IOSTAT = ios, ERR = 902 )
194902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namicesal in configuration namelist', lwp )
195      IF(lwm) WRITE ( numoni, namicesal )
196      !
197      IF(lwp) THEN                           ! control print
198         WRITE(numout,*)
199         WRITE(numout,*) 'lim_thd_sal_init : Ice parameters for salinity '
200         WRITE(numout,*) '~~~~~~~~~~~~~~~~'
201         WRITE(numout,*) ' switch for salinity num_sal        : ', num_sal
202         WRITE(numout,*) ' bulk salinity value if num_sal = 1 : ', bulk_sal
203         WRITE(numout,*) ' restoring salinity for GD          : ', sal_G
204         WRITE(numout,*) ' restoring time for GD              : ', time_G
205         WRITE(numout,*) ' restoring salinity for flushing    : ', sal_F
206         WRITE(numout,*) ' restoring time for flushing        : ', time_F
207         WRITE(numout,*) ' Maximum tolerated ice salinity     : ', s_i_max
208         WRITE(numout,*) ' Minimum tolerated ice salinity     : ', s_i_min
209         WRITE(numout,*) ' 1st salinity for salinity profile  : ', s_i_0
210         WRITE(numout,*) ' 2nd salinity for salinity profile  : ', s_i_1
211      ENDIF
212      !
213   END SUBROUTINE lim_thd_sal_init
214
215#else
216   !!----------------------------------------------------------------------
217   !!   Default option         Dummy Module          No LIM-3 sea-ice model
218   !!----------------------------------------------------------------------
219#endif
220   !!======================================================================
221END MODULE limthd_sal
Note: See TracBrowser for help on using the repository browser.