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 branches/2017/dev_CNRS_2017/NEMOGCM/NEMO/LIM_SRC_3 – NEMO

source: branches/2017/dev_CNRS_2017/NEMOGCM/NEMO/LIM_SRC_3/icethd_sal.F90 @ 9012

Last change on this file since 9012 was 8882, checked in by flavoni, 6 years ago

dev_CNRS_2017 branch: merged dev_r7881_ENHANCE09_RK3 with trunk r8864

File size: 8.6 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) 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'                                       ESIM 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 (2017)
41   !! $Id: icethd_sal.F90 8420 2017-08-08 12:18:46Z clem $
42   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
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      INTEGER  ::   ji, jk                       ! dummy loop indices
59      REAL(wp) ::   iflush, igravdr              ! local scalars
60      REAL(wp) ::   zs_sni, zs_i_gd, zs_i_fl, zs_i_si, zs_i_bg   ! 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 = 1._wp / rn_time_gd * rdt_ice
70         z1_time_fl = 1._wp / rn_time_fl * rdt_ice
71         !
72         DO ji = 1, npti
73
74            !---------------------------------------------------------
75            !  Update ice salinity from snow-ice and bottom growth
76            !---------------------------------------------------------
77            IF( h_i_1d(ji) > 0._wp ) THEN
78               zs_sni   = sss_1d(ji) * ( rhoic - rhosn ) * r1_rhoic                                 ! Salinity of snow ice
79               zs_i_si = ( zs_sni      - s_i_1d(ji) ) *             dh_snowice(ji)  / h_i_1d(ji) ! snow-ice   
80               zs_i_bg = ( s_i_new(ji) - s_i_1d(ji) ) * MAX( 0._wp, dh_i_bott(ji) ) / h_i_1d(ji) ! bottom growth
81               ! Update salinity (nb: salt flux already included in icethd_dh)
82               s_i_1d(ji) = s_i_1d(ji) + zs_i_bg + zs_i_si
83            ENDIF
84
85            IF( ld_sal ) THEN
86               !---------------------------------------------------------
87               !  Update ice salinity from brine drainage and flushing
88               !---------------------------------------------------------
89               iflush   = MAX( 0._wp , SIGN( 1._wp , t_su_1d(ji) - rt0         ) )  ! =1 if summer
90               igravdr  = MAX( 0._wp , SIGN( 1._wp , t_bo_1d(ji) - t_su_1d(ji) ) )  ! =1 if t_su < t_bo
91
92               zs_i_gd = - igravdr * MAX( s_i_1d(ji) - rn_sal_gd , 0._wp ) * z1_time_gd  ! gravity drainage
93               zs_i_fl = - iflush  * MAX( s_i_1d(ji) - rn_sal_fl , 0._wp ) * z1_time_fl  ! flushing
94               
95               ! Update salinity   
96               s_i_1d(ji) = s_i_1d(ji) + zs_i_fl + zs_i_gd
97               
98               ! Salt flux
99               sfx_bri_1d(ji) = sfx_bri_1d(ji) - rhoic * a_i_1d(ji) * h_i_1d(ji) * ( zs_i_fl + zs_i_gd ) * r1_rdtice
100            ENDIF
101         END DO
102
103         ! Salinity profile
104         CALL ice_var_salprof1d
105         !
106      !         !---------------------------------------------!
107      CASE( 3 ) ! constant salinity with a fixed profile      ! (Schwarzacher (1959) multiyear salinity profile(mean = 2.30)
108      !         !---------------------------------------------!
109         CALL ice_var_salprof1d
110      !
111   END SELECT
112   !
113   END SUBROUTINE ice_thd_sal
114
115
116   SUBROUTINE ice_thd_sal_init
117      !!-------------------------------------------------------------------
118      !!                  ***  ROUTINE ice_thd_sal_init  ***
119      !!
120      !! ** Purpose :   initialization of ice salinity parameters
121      !!
122      !! ** Method  :   Read the namthd_sal namelist and check the parameter
123      !!                values called at the first timestep (nit000)
124      !!
125      !! ** input   :   Namelist namthd_sal
126      !!-------------------------------------------------------------------
127      INTEGER  ::   ios                 ! Local integer output status for namelist read
128      !!
129      NAMELIST/namthd_sal/ nn_icesal, rn_icesal, rn_sal_gd, rn_time_gd,   &
130         &                 rn_sal_fl, rn_time_fl, rn_simax , rn_simin 
131      !!-------------------------------------------------------------------
132      !
133      REWIND( numnam_ice_ref )              ! Namelist namthd_sal in reference namelist : Ice salinity
134      READ  ( numnam_ice_ref, namthd_sal, IOSTAT = ios, ERR = 901)
135901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namthd_sal in reference namelist', lwp )
136      !
137      REWIND( numnam_ice_cfg )              ! Namelist namthd_sal in configuration namelist : Ice salinity
138      READ  ( numnam_ice_cfg, namthd_sal, IOSTAT = ios, ERR = 902 )
139902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namthd_sal in configuration namelist', lwp )
140      IF(lwm) WRITE ( numoni, namthd_sal )
141      !
142      IF(lwp) THEN                           ! control print
143         WRITE(numout,*)
144         WRITE(numout,*) 'ice_thd_sal_init : Ice parameters for salinity '
145         WRITE(numout,*) '~~~~~~~~~~~~~~~~'
146         WRITE(numout,*) '   Namelist namthd_sal:'
147         WRITE(numout,*) '      switch for salinity                                     nn_icesal  = ', nn_icesal
148         WRITE(numout,*) '      bulk salinity value if nn_icesal = 1                    rn_icesal  = ', rn_icesal
149         WRITE(numout,*) '      restoring salinity for gravity drainage                 rn_sal_gd  = ', rn_sal_gd
150         WRITE(numout,*) '      restoring time for for gravity drainage                 rn_time_gd = ', rn_time_gd
151         WRITE(numout,*) '      restoring salinity for flushing                         rn_sal_fl  = ', rn_sal_fl
152         WRITE(numout,*) '      restoring time for flushing                             rn_time_fl = ', rn_time_fl
153         WRITE(numout,*) '      Maximum tolerated ice salinity                          rn_simax   = ', rn_simax
154         WRITE(numout,*) '      Minimum tolerated ice salinity                          rn_simin   = ', rn_simin
155      ENDIF
156      !
157   END SUBROUTINE ice_thd_sal_init
158
159#else
160   !!----------------------------------------------------------------------
161   !!   Default option         Dummy Module           No ESIM sea-ice model
162   !!----------------------------------------------------------------------
163#endif
164
165   !!======================================================================
166END MODULE icethd_sal
Note: See TracBrowser for help on using the repository browser.