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.
icethd_sal.F90 in NEMO/trunk/src/ICE – NEMO

source: NEMO/trunk/src/ICE/icethd_sal.F90

Last change on this file was 13472, checked in by smasson, 4 years ago

trunk: commit changes from r4.0-HEAD from 13284 to 13449, see #2523

  • Property svn:keywords set to Id
File size: 8.4 KB
Line 
1MODULE icethd_sal
2   !!======================================================================
3   !!                       ***  MODULE icethd_sal ***
4   !!   sea-ice : computation of salinity variations in the ice
5   !!======================================================================
6   !! History :   -   !  2003-05  (M. Vancoppenolle) original code 1-D
7   !!            3.0  !  2005-12  (M. Vancoppenolle) adapted to the 3-D version
8   !!            4.0  !  2018     (many people)      SI3 [aka Sea Ice cube]
9   !!---------------------------------------------------------------------
10#if defined key_si3
11   !!----------------------------------------------------------------------
12   !!   'key_si3'                                       SI3 sea-ice model
13   !!----------------------------------------------------------------------
14   !!   ice_thd_sal      : salinity variations in the ice
15   !!   ice_thd_sal_init : initialization
16   !!----------------------------------------------------------------------
17   USE dom_oce        ! ocean space and time domain
18   USE phycst         ! physical constants
19   USE ice            ! sea-ice: variables
20   USE ice1D          ! sea-ice: thermodynamics variables
21   USE icevar         ! sea-ice: operations
22   !
23   USE in_out_manager ! I/O manager
24   USE lib_mpp        ! MPP library
25   USE lib_fortran    ! fortran utilities (glob_sum + no signed zero)
26
27   IMPLICIT NONE
28   PRIVATE
29
30   PUBLIC   ice_thd_sal        ! called by icethd
31   PUBLIC   ice_thd_sal_init   ! called by ice_init
32   
33   ! ** namelist (namthd_sal) **
34   REAL(wp) ::   rn_sal_gd     ! restoring salinity for gravity drainage [PSU]
35   REAL(wp) ::   rn_time_gd    ! restoring time constant for gravity drainage (= 20 days) [s]
36   REAL(wp) ::   rn_sal_fl     ! restoring salinity for flushing [PSU]
37   REAL(wp) ::   rn_time_fl    ! restoring time constant for gravity drainage (= 10 days) [s]
38
39   !!----------------------------------------------------------------------
40   !! NEMO/ICE 4.0 , NEMO Consortium (2018)
41   !! $Id$
42   !! Software governed by the CeCILL license (see ./LICENSE)
43   !!----------------------------------------------------------------------
44CONTAINS
45
46   SUBROUTINE ice_thd_sal( ld_sal )
47      !!-------------------------------------------------------------------
48      !!                ***  ROUTINE ice_thd_sal  ***   
49      !!   
50      !! ** Purpose :   computes new salinities in the ice
51      !!
52      !! ** Method  :  3 possibilities
53      !!               -> nn_icesal = 1 -> Sice = cst    [ice salinity constant in both time & space]
54      !!               -> nn_icesal = 2 -> Sice = S(z,t) [Vancoppenolle et al. 2005]
55      !!               -> nn_icesal = 3 -> Sice = S(z)   [multiyear ice]
56      !!---------------------------------------------------------------------
57      LOGICAL, INTENT(in) ::   ld_sal          ! gravity drainage and flushing or not
58      !
59      INTEGER  ::   ji                         ! dummy loop indices
60      REAL(wp) ::   zs_sni, zds                ! local scalars
61      REAL(wp) ::   z1_time_gd, z1_time_fl
62      !!---------------------------------------------------------------------
63
64      SELECT CASE ( nn_icesal )
65      !
66      !               !---------------------------------------------!
67      CASE( 2 )       !  time varying salinity with linear profile  !
68         !            !---------------------------------------------!
69         z1_time_gd = rDt_ice / rn_time_gd
70         z1_time_fl = rDt_ice / rn_time_fl
71         !
72         DO ji = 1, npti
73            !
74            IF( h_i_1d(ji) > 0._wp ) THEN
75               !
76               ! --- Update ice salinity from snow-ice and bottom growth --- !
77               zs_sni = sss_1d(ji) * ( rhoi - rhos ) * r1_rhoi                           ! salinity of snow ice
78               zds    =       ( zs_sni      - s_i_1d(ji) ) * dh_snowice(ji) / h_i_1d(ji) ! snow-ice   
79               zds    = zds + ( s_i_new(ji) - s_i_1d(ji) ) * dh_i_bog  (ji) / h_i_1d(ji) ! bottom growth
80               ! update salinity (nb: salt flux already included in icethd_dh)
81               s_i_1d(ji) = s_i_1d(ji) + zds
82               !
83               ! --- Update ice salinity from brine drainage and flushing --- !
84               IF( ld_sal ) THEN
85                  IF( t_su_1d(ji) >= rt0 ) THEN             ! flushing (summer time)
86                     zds = - MAX( s_i_1d(ji) - rn_sal_fl , 0._wp ) * z1_time_fl
87                  ELSEIF( t_su_1d(ji) <= t_bo_1d(ji) ) THEN ! gravity drainage
88                     zds = - MAX( s_i_1d(ji) - rn_sal_gd , 0._wp ) * z1_time_gd
89                  ELSE
90                     zds = 0._wp
91                  ENDIF
92                  ! update salinity
93                  s_i_1d(ji) = s_i_1d(ji) + zds
94                  ! salt flux
95                  sfx_bri_1d(ji) = sfx_bri_1d(ji) - rhoi * a_i_1d(ji) * h_i_1d(ji) * zds * r1_Dt_ice
96               ENDIF
97               !
98               ! --- salinity must stay inbounds --- !
99               zds =       MAX( 0._wp, rn_simin - s_i_1d(ji) ) ! > 0 if s_i < simin
100               zds = zds + MIN( 0._wp, rn_simax - s_i_1d(ji) ) ! < 0 if s_i > simax
101               ! update salinity
102               s_i_1d(ji) = s_i_1d(ji) + zds
103               ! salt flux
104               sfx_res_1d(ji) = sfx_res_1d(ji) - rhoi * a_i_1d(ji) * h_i_1d(ji) * zds * r1_Dt_ice
105               !
106            ENDIF
107            !
108         END DO
109         !
110         ! Salinity profile
111         CALL ice_var_salprof1d
112         !
113         !             !----------------------------------------!
114      CASE( 3 )        ! constant salinity with a fixed profile ! (Schwarzacher (1959) multiyear salinity profile (mean = 2.30)
115         !             !----------------------------------------!
116         CALL ice_var_salprof1d
117         !
118      END SELECT
119      !
120   END SUBROUTINE ice_thd_sal
121
122
123   SUBROUTINE ice_thd_sal_init
124      !!-------------------------------------------------------------------
125      !!                  ***  ROUTINE ice_thd_sal_init  ***
126      !!
127      !! ** Purpose :   initialization of ice salinity parameters
128      !!
129      !! ** Method  :   Read the namthd_sal namelist and check the parameter
130      !!                values called at the first timestep (nit000)
131      !!
132      !! ** input   :   Namelist namthd_sal
133      !!-------------------------------------------------------------------
134      INTEGER  ::   ios   ! Local integer
135      !!
136      NAMELIST/namthd_sal/ nn_icesal, rn_icesal, rn_sal_gd, rn_time_gd,   &
137         &                 rn_sal_fl, rn_time_fl, rn_simax , rn_simin 
138      !!-------------------------------------------------------------------
139      !
140      READ  ( numnam_ice_ref, namthd_sal, IOSTAT = ios, ERR = 901)
141901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namthd_sal in reference namelist' )
142      READ  ( numnam_ice_cfg, namthd_sal, IOSTAT = ios, ERR = 902 )
143902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namthd_sal in configuration namelist' )
144      IF(lwm) WRITE ( numoni, namthd_sal )
145      !
146      IF(lwp) THEN                           ! control print
147         WRITE(numout,*)
148         WRITE(numout,*) 'ice_thd_sal_init : Ice parameters for salinity '
149         WRITE(numout,*) '~~~~~~~~~~~~~~~~'
150         WRITE(numout,*) '   Namelist namthd_sal:'
151         WRITE(numout,*) '      switch for salinity                                     nn_icesal  = ', nn_icesal
152         WRITE(numout,*) '      bulk salinity value if nn_icesal = 1                    rn_icesal  = ', rn_icesal
153         WRITE(numout,*) '      restoring salinity for gravity drainage                 rn_sal_gd  = ', rn_sal_gd
154         WRITE(numout,*) '      restoring time for for gravity drainage                 rn_time_gd = ', rn_time_gd
155         WRITE(numout,*) '      restoring salinity for flushing                         rn_sal_fl  = ', rn_sal_fl
156         WRITE(numout,*) '      restoring time for flushing                             rn_time_fl = ', rn_time_fl
157         WRITE(numout,*) '      Maximum tolerated ice salinity                          rn_simax   = ', rn_simax
158         WRITE(numout,*) '      Minimum tolerated ice salinity                          rn_simin   = ', rn_simin
159      ENDIF
160      !
161   END SUBROUTINE ice_thd_sal_init
162
163#else
164   !!----------------------------------------------------------------------
165   !!   Default option         Dummy Module           No SI3 sea-ice model
166   !!----------------------------------------------------------------------
167#endif
168
169   !!======================================================================
170END MODULE icethd_sal
Note: See TracBrowser for help on using the repository browser.