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/branches/2019/dev_r11613_ENHANCE-04_namelists_as_internalfiles/src/ICE – NEMO

source: NEMO/branches/2019/dev_r11613_ENHANCE-04_namelists_as_internalfiles/src/ICE/icethd_sal.F90 @ 11954

Last change on this file since 11954 was 11671, checked in by acc, 5 years ago

Branch 2019/dev_r11613_ENHANCE-04_namelists_as_internalfiles. Final, non-substantive changes to complete this branch. These changes remove all REWIND statements on the old namelist fortran units (now character variables for internal files). These changes have been left until last since they are easily repeated via a script and it may be preferable to use the previous revision for merge purposes and reapply these last changes separately. This branch has been fully SETTE tested.

  • Property svn:keywords set to Id
File size: 8.3 KB
RevLine 
[8586]1MODULE icethd_sal
2   !!======================================================================
3   !!                       ***  MODULE icethd_sal ***
4   !!   sea-ice : computation of salinity variations in the ice
5   !!======================================================================
[9656]6   !! History :   -   !  2003-05  (M. Vancoppenolle) original code 1-D
[9604]7   !!            3.0  !  2005-12  (M. Vancoppenolle) adapted to the 3-D version
8   !!            4.0  !  2018     (many people)      SI3 [aka Sea Ice cube]
[8586]9   !!---------------------------------------------------------------------
[9570]10#if defined key_si3
[8586]11   !!----------------------------------------------------------------------
[9570]12   !!   'key_si3'                                       SI3 sea-ice model
[8586]13   !!----------------------------------------------------------------------
[9169]14   !!   ice_thd_sal      : salinity variations in the ice
15   !!   ice_thd_sal_init : initialization
[8586]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) **
[9169]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]
[8586]38
39   !!----------------------------------------------------------------------
[9598]40   !! NEMO/ICE 4.0 , NEMO Consortium (2018)
[10069]41   !! $Id$
[10068]42   !! Software governed by the CeCILL license (see ./LICENSE)
[8586]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
[9169]58      !
[8586]59      INTEGER  ::   ji, jk                       ! dummy loop indices
60      REAL(wp) ::   iflush, igravdr              ! local scalars
61      REAL(wp) ::   zs_sni, zs_i_gd, zs_i_fl, zs_i_si, zs_i_bg   ! local scalars
62      REAL(wp) ::   z1_time_gd, z1_time_fl
63      !!---------------------------------------------------------------------
64
65      SELECT CASE ( nn_icesal )
66      !
67      !               !---------------------------------------------!
68      CASE( 2 )       !  time varying salinity with linear profile  !
[9169]69         !            !---------------------------------------------!
[8586]70         z1_time_gd = 1._wp / rn_time_gd * rdt_ice
71         z1_time_fl = 1._wp / rn_time_fl * rdt_ice
72         !
73         DO ji = 1, npti
[9169]74            !
[8586]75            !---------------------------------------------------------
76            !  Update ice salinity from snow-ice and bottom growth
77            !---------------------------------------------------------
78            IF( h_i_1d(ji) > 0._wp ) THEN
[9935]79               zs_sni  = sss_1d(ji) * ( rhoi - rhos ) * r1_rhoi                     ! Salinity of snow ice
[9750]80               zs_i_si = ( zs_sni      - s_i_1d(ji) ) * dh_snowice(ji) / h_i_1d(ji) ! snow-ice   
81               zs_i_bg = ( s_i_new(ji) - s_i_1d(ji) ) * dh_i_bog  (ji) / h_i_1d(ji) ! bottom growth
[8586]82               ! Update salinity (nb: salt flux already included in icethd_dh)
83               s_i_1d(ji) = s_i_1d(ji) + zs_i_bg + zs_i_si
84            ENDIF
[9169]85            !
[8586]86            IF( ld_sal ) THEN
87               !---------------------------------------------------------
88               !  Update ice salinity from brine drainage and flushing
89               !---------------------------------------------------------
90               iflush   = MAX( 0._wp , SIGN( 1._wp , t_su_1d(ji) - rt0         ) )  ! =1 if summer
91               igravdr  = MAX( 0._wp , SIGN( 1._wp , t_bo_1d(ji) - t_su_1d(ji) ) )  ! =1 if t_su < t_bo
92
93               zs_i_gd = - igravdr * MAX( s_i_1d(ji) - rn_sal_gd , 0._wp ) * z1_time_gd  ! gravity drainage
94               zs_i_fl = - iflush  * MAX( s_i_1d(ji) - rn_sal_fl , 0._wp ) * z1_time_fl  ! flushing
95               
96               ! Update salinity   
97               s_i_1d(ji) = s_i_1d(ji) + zs_i_fl + zs_i_gd
98               
99               ! Salt flux
[9935]100               sfx_bri_1d(ji) = sfx_bri_1d(ji) - rhoi * a_i_1d(ji) * h_i_1d(ji) * ( zs_i_fl + zs_i_gd ) * r1_rdtice
[8586]101            ENDIF
102         END DO
[9169]103         !
[8586]104         ! Salinity profile
105         CALL ice_var_salprof1d
106         !
[9169]107         !             !----------------------------------------!
108      CASE( 3 )        ! constant salinity with a fixed profile ! (Schwarzacher (1959) multiyear salinity profile (mean = 2.30)
109         !             !----------------------------------------!
[8586]110         CALL ice_var_salprof1d
[9169]111         !
112      END SELECT
[8586]113      !
114   END SUBROUTINE ice_thd_sal
115
116
117   SUBROUTINE ice_thd_sal_init
118      !!-------------------------------------------------------------------
119      !!                  ***  ROUTINE ice_thd_sal_init  ***
120      !!
121      !! ** Purpose :   initialization of ice salinity parameters
122      !!
123      !! ** Method  :   Read the namthd_sal namelist and check the parameter
124      !!                values called at the first timestep (nit000)
125      !!
126      !! ** input   :   Namelist namthd_sal
127      !!-------------------------------------------------------------------
[9169]128      INTEGER  ::   ios   ! Local integer
[8586]129      !!
130      NAMELIST/namthd_sal/ nn_icesal, rn_icesal, rn_sal_gd, rn_time_gd,   &
131         &                 rn_sal_fl, rn_time_fl, rn_simax , rn_simin 
132      !!-------------------------------------------------------------------
133      !
134      READ  ( numnam_ice_ref, namthd_sal, IOSTAT = ios, ERR = 901)
[11536]135901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namthd_sal in reference namelist' )
[8586]136      READ  ( numnam_ice_cfg, namthd_sal, IOSTAT = ios, ERR = 902 )
[11536]137902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namthd_sal in configuration namelist' )
[8586]138      IF(lwm) WRITE ( numoni, namthd_sal )
139      !
140      IF(lwp) THEN                           ! control print
141         WRITE(numout,*)
142         WRITE(numout,*) 'ice_thd_sal_init : Ice parameters for salinity '
143         WRITE(numout,*) '~~~~~~~~~~~~~~~~'
144         WRITE(numout,*) '   Namelist namthd_sal:'
145         WRITE(numout,*) '      switch for salinity                                     nn_icesal  = ', nn_icesal
146         WRITE(numout,*) '      bulk salinity value if nn_icesal = 1                    rn_icesal  = ', rn_icesal
147         WRITE(numout,*) '      restoring salinity for gravity drainage                 rn_sal_gd  = ', rn_sal_gd
148         WRITE(numout,*) '      restoring time for for gravity drainage                 rn_time_gd = ', rn_time_gd
149         WRITE(numout,*) '      restoring salinity for flushing                         rn_sal_fl  = ', rn_sal_fl
150         WRITE(numout,*) '      restoring time for flushing                             rn_time_fl = ', rn_time_fl
151         WRITE(numout,*) '      Maximum tolerated ice salinity                          rn_simax   = ', rn_simax
152         WRITE(numout,*) '      Minimum tolerated ice salinity                          rn_simin   = ', rn_simin
153      ENDIF
154      !
155   END SUBROUTINE ice_thd_sal_init
156
157#else
158   !!----------------------------------------------------------------------
[9570]159   !!   Default option         Dummy Module           No SI3 sea-ice model
[8586]160   !!----------------------------------------------------------------------
161#endif
162
163   !!======================================================================
164END MODULE icethd_sal
Note: See TracBrowser for help on using the repository browser.