1 | MODULE icethd_sal |
---|
2 | !!====================================================================== |
---|
3 | !! *** MODULE icethd_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 | !! ice_thd_sal : salinity variations in the ice |
---|
15 | !!---------------------------------------------------------------------- |
---|
16 | USE par_oce ! ocean parameters |
---|
17 | USE phycst ! physical constants (ocean directory) |
---|
18 | USE ice ! LIM variables |
---|
19 | USE ice1D ! LIM thermodynamics |
---|
20 | USE icevar ! LIM variables |
---|
21 | ! |
---|
22 | USE in_out_manager ! I/O manager |
---|
23 | USE lib_mpp ! MPP library |
---|
24 | USE lib_fortran ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined) |
---|
25 | |
---|
26 | IMPLICIT NONE |
---|
27 | PRIVATE |
---|
28 | |
---|
29 | PUBLIC ice_thd_sal ! called by icethd module |
---|
30 | PUBLIC ice_thd_sal_init ! called by ice_init |
---|
31 | |
---|
32 | !!---------------------------------------------------------------------- |
---|
33 | !! NEMO/LIM3 4.0 , UCL - NEMO Consortium (2011) |
---|
34 | !! $Id: icethd_sal.F90 8420 2017-08-08 12:18:46Z clem $ |
---|
35 | !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) |
---|
36 | !!---------------------------------------------------------------------- |
---|
37 | CONTAINS |
---|
38 | |
---|
39 | SUBROUTINE ice_thd_sal |
---|
40 | !!------------------------------------------------------------------- |
---|
41 | !! *** ROUTINE ice_thd_sal *** |
---|
42 | !! |
---|
43 | !! ** Purpose : computes new salinities in the ice |
---|
44 | !! |
---|
45 | !! ** Method : 3 possibilities |
---|
46 | !! -> nn_icesal = 1 -> Sice = cst [ice salinity constant in both time & space] |
---|
47 | !! -> nn_icesal = 2 -> Sice = S(z,t) [Vancoppenolle et al. 2005] |
---|
48 | !! -> nn_icesal = 3 -> Sice = S(z) [multiyear ice] |
---|
49 | !!--------------------------------------------------------------------- |
---|
50 | INTEGER :: ji, jk ! dummy loop indices |
---|
51 | REAL(wp) :: iflush, igravdr ! local scalars |
---|
52 | REAL(wp) :: zs_sni, zsm_i_gd, zsm_i_fl, zsm_i_si, zsm_i_bg ! local scalars |
---|
53 | !!--------------------------------------------------------------------- |
---|
54 | |
---|
55 | !--------------------------------------------------------------------| |
---|
56 | ! 1) salinity constant in time | |
---|
57 | !--------------------------------------------------------------------| |
---|
58 | ! do nothing |
---|
59 | |
---|
60 | !----------------------------------------------------------------------| |
---|
61 | ! 2) salinity varying in time | |
---|
62 | !----------------------------------------------------------------------| |
---|
63 | IF( nn_icesal == 2 ) THEN |
---|
64 | |
---|
65 | DO ji = 1, nidx |
---|
66 | |
---|
67 | !--------------------------------------------------------- |
---|
68 | ! Update ice salinity from snow-ice and bottom growth |
---|
69 | !--------------------------------------------------------- |
---|
70 | zs_sni = sss_1d(ji) * ( rhoic - rhosn ) * r1_rhoic ! Salinity of snow ice |
---|
71 | rswitch = MAX( 0._wp , SIGN( 1._wp , ht_i_1d(ji) - epsi20 ) ) |
---|
72 | zsm_i_si = ( zs_sni - sm_i_1d(ji) ) * dh_snowice(ji) / MAX( ht_i_1d(ji), epsi20 ) * rswitch ! snow-ice |
---|
73 | zsm_i_bg = ( s_i_new(ji) - sm_i_1d(ji) ) * MAX( 0._wp, dh_i_bott(ji) ) / MAX( ht_i_1d(ji), epsi20 ) * rswitch ! bottom growth |
---|
74 | |
---|
75 | ! Update salinity (nb: salt flux already included in icethd_dh) |
---|
76 | sm_i_1d(ji) = sm_i_1d(ji) + zsm_i_bg + zsm_i_si |
---|
77 | |
---|
78 | IF( ln_limdS ) THEN |
---|
79 | !--------------------------------------------------------- |
---|
80 | ! Update ice salinity from brine drainage and flushing |
---|
81 | !--------------------------------------------------------- |
---|
82 | iflush = MAX( 0._wp , SIGN( 1._wp , t_su_1d(ji) - rt0 ) ) ! =1 if summer |
---|
83 | igravdr = MAX( 0._wp , SIGN( 1._wp , t_bo_1d(ji) - t_su_1d(ji) ) ) ! =1 if t_su < t_bo |
---|
84 | zsm_i_gd = - igravdr * MAX( sm_i_1d(ji) - rn_sal_gd , 0._wp ) / rn_time_gd * rdt_ice ! gravity drainage |
---|
85 | zsm_i_fl = - iflush * MAX( sm_i_1d(ji) - rn_sal_fl , 0._wp ) / rn_time_fl * rdt_ice ! flushing |
---|
86 | |
---|
87 | ! Update salinity |
---|
88 | sm_i_1d(ji) = sm_i_1d(ji) + zsm_i_fl + zsm_i_gd |
---|
89 | |
---|
90 | ! Salt flux |
---|
91 | sfx_bri_1d(ji) = sfx_bri_1d(ji) - rhoic * a_i_1d(ji) * ht_i_1d(ji) * ( zsm_i_fl + zsm_i_gd ) * r1_rdtice |
---|
92 | ENDIF |
---|
93 | END DO |
---|
94 | |
---|
95 | ! Salinity profile |
---|
96 | CALL ice_var_salprof1d |
---|
97 | ! |
---|
98 | ENDIF |
---|
99 | |
---|
100 | !------------------------------------------------------------------------------| |
---|
101 | ! 3) vertical profile of salinity, constant in time | |
---|
102 | !------------------------------------------------------------------------------| |
---|
103 | IF( nn_icesal == 3 ) CALL ice_var_salprof1d |
---|
104 | |
---|
105 | ! |
---|
106 | END SUBROUTINE ice_thd_sal |
---|
107 | |
---|
108 | |
---|
109 | SUBROUTINE ice_thd_sal_init |
---|
110 | !!------------------------------------------------------------------- |
---|
111 | !! *** ROUTINE ice_thd_sal_init *** |
---|
112 | !! |
---|
113 | !! ** Purpose : initialization of ice salinity parameters |
---|
114 | !! |
---|
115 | !! ** Method : Read the namicesal namelist and check the parameter |
---|
116 | !! values called at the first timestep (nit000) |
---|
117 | !! |
---|
118 | !! ** input : Namelist namicesal |
---|
119 | !!------------------------------------------------------------------- |
---|
120 | INTEGER :: ios ! Local integer output status for namelist read |
---|
121 | NAMELIST/namicesal/ ln_limdS, nn_icesal, rn_icesal, rn_sal_gd, rn_time_gd, & |
---|
122 | & rn_sal_fl, rn_time_fl, rn_simax, rn_simin |
---|
123 | !!------------------------------------------------------------------- |
---|
124 | ! |
---|
125 | REWIND( numnam_ice_ref ) ! Namelist namicesal in reference namelist : Ice salinity |
---|
126 | READ ( numnam_ice_ref, namicesal, IOSTAT = ios, ERR = 901) |
---|
127 | 901 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namicesal in reference namelist', lwp ) |
---|
128 | |
---|
129 | REWIND( numnam_ice_cfg ) ! Namelist namicesal in configuration namelist : Ice salinity |
---|
130 | READ ( numnam_ice_cfg, namicesal, IOSTAT = ios, ERR = 902 ) |
---|
131 | 902 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namicesal in configuration namelist', lwp ) |
---|
132 | IF(lwm) WRITE ( numoni, namicesal ) |
---|
133 | ! |
---|
134 | IF(lwp) THEN ! control print |
---|
135 | WRITE(numout,*) |
---|
136 | WRITE(numout,*) 'ice_thd_sal_init : Ice parameters for salinity ' |
---|
137 | WRITE(numout,*) '~~~~~~~~~~~~~~~~' |
---|
138 | WRITE(numout,*) ' activate gravity drainage and flushing (T) or not (F) ln_limdS = ', ln_limdS |
---|
139 | WRITE(numout,*) ' switch for salinity nn_icesal = ', nn_icesal |
---|
140 | WRITE(numout,*) ' bulk salinity value if nn_icesal = 1 rn_icesal = ', rn_icesal |
---|
141 | WRITE(numout,*) ' restoring salinity for gravity drainage rn_sal_gd = ', rn_sal_gd |
---|
142 | WRITE(numout,*) ' restoring time for for gravity drainage rn_time_gd = ', rn_time_gd |
---|
143 | WRITE(numout,*) ' restoring salinity for flushing rn_sal_fl = ', rn_sal_fl |
---|
144 | WRITE(numout,*) ' restoring time for flushing rn_time_fl = ', rn_time_fl |
---|
145 | WRITE(numout,*) ' Maximum tolerated ice salinity rn_simax = ', rn_simax |
---|
146 | WRITE(numout,*) ' Minimum tolerated ice salinity rn_simin = ', rn_simin |
---|
147 | ENDIF |
---|
148 | ! |
---|
149 | END SUBROUTINE ice_thd_sal_init |
---|
150 | |
---|
151 | #else |
---|
152 | !!---------------------------------------------------------------------- |
---|
153 | !! Default option Dummy Module No LIM-3 sea-ice model |
---|
154 | !!---------------------------------------------------------------------- |
---|
155 | #endif |
---|
156 | !!====================================================================== |
---|
157 | END MODULE icethd_sal |
---|