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 trunk/NEMOGCM/NEMO/LIM_SRC_3 – NEMO

source: trunk/NEMOGCM/NEMO/LIM_SRC_3/limthd_sal.F90 @ 7881

Last change on this file since 7881 was 7646, checked in by timgraham, 7 years ago

Merge of dev_merge_2016 into trunk. UPDATE TO ARCHFILES NEEDED for XIOS2.
LIM_SRC_s/limrhg.F90 to follow in next commit due to change of kind (I'm unable to do it in this commit).
Merged using the following steps:

1) svn merge --reintegrate svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/trunk .
2) Resolve minor conflicts in sette.sh and namelist_cfg for ORCA2LIM3 (due to a change in trunk after branch was created)
3) svn commit
4) svn switch svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/trunk
5) svn merge svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/branches/2016/dev_merge_2016 .
6) At this stage I checked out a clean copy of the branch to compare against what is about to be committed to the trunk.
6) svn commit #Commit code to the trunk

In this commit I have also reverted a change to Fcheck_archfile.sh which was causing problems on the Paris machine.

  • Property svn:keywords set to Id
File size: 8.6 KB
RevLine 
[825]1MODULE limthd_sal
2   !!======================================================================
3   !!                       ***  MODULE limthd_sal ***
[2528]4   !! LIM-3 sea-ice :  computation of salinity variations in the ice
[825]5   !!======================================================================
[2528]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
[2715]8   !!            4.0  ! 2011-02 (G. Madec) dynamical allocation
[2528]9   !!---------------------------------------------------------------------
[888]10#if defined key_lim3
[825]11   !!----------------------------------------------------------------------
[2528]12   !!   'key_lim3'                                      LIM-3 sea-ice model
13   !!----------------------------------------------------------------------
[3625]14   !!   lim_thd_sal   : salinity variations in the ice
[2528]15   !!----------------------------------------------------------------------
[3625]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 thd_ice        ! LIM thermodynamics
21   USE limvar         ! LIM variables
22   USE in_out_manager ! I/O manager
23   USE lib_mpp        ! MPP library
24   USE wrk_nemo       ! work arrays
25   USE lib_fortran    ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined) 
[825]26
27   IMPLICIT NONE
28   PRIVATE
29
[2528]30   PUBLIC   lim_thd_sal        ! called by limthd module
[5123]31   PUBLIC   lim_thd_sal_init   ! called by sbc_lim_init
[825]32
[1156]33   !!----------------------------------------------------------------------
[4161]34   !! NEMO/LIM3 4.0 , UCL - NEMO Consortium (2011)
[1156]35   !! $Id$
[2528]36   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
[1156]37   !!----------------------------------------------------------------------
[921]38CONTAINS
[825]39
[2528]40   SUBROUTINE lim_thd_sal( kideb, kiut )
[825]41      !!-------------------------------------------------------------------
[2528]42      !!                ***  ROUTINE lim_thd_sal  ***   
43      !!   
44      !! ** Purpose :   computes new salinities in the ice
[825]45      !!
[3625]46      !! ** Method  :  3 possibilities
[5123]47      !!               -> nn_icesal = 1 -> Sice = cst    [ice salinity constant in both time & space]
48      !!               -> nn_icesal = 2 -> Sice = S(z,t) [Vancoppenolle et al. 2005]
49      !!               -> nn_icesal = 3 -> Sice = S(z)   [multiyear ice]
[825]50      !!---------------------------------------------------------------------
[3625]51      INTEGER, INTENT(in) ::   kideb, kiut   ! thickness category index
[2528]52      !
[7646]53      INTEGER  ::   ii, ij, ji, jk               ! dummy loop indices
54      REAL(wp) ::   iflush, igravdr              ! local scalars
55      REAL(wp) ::   zs_sni, zsm_i_gd, zsm_i_fl, zsm_i_si, zsm_i_bg   ! local scalars
[2528]56      !!---------------------------------------------------------------------
[825]57
[6470]58      !--------------------------------------------------------------------|
59      ! 1) salinity constant in time                                       |
60      !--------------------------------------------------------------------|
61      ! do nothing
[825]62
[6470]63      !----------------------------------------------------------------------|
64      !  2) salinity varying in time                                         |
65      !----------------------------------------------------------------------|
[5123]66      IF(  nn_icesal == 2  ) THEN
[825]67
68         DO ji = kideb, kiut
69
[7646]70            ii = MOD( npb(ji) - 1, jpi ) + 1 ; ij = ( npb(ji) - 1 ) / jpi + 1
71            !---------------------------------------------------------
72            !  Update ice salinity from snow-ice and bottom growth
73            !---------------------------------------------------------
74            zs_sni   = sss_m(ii,ij) * ( rhoic - rhosn ) * r1_rhoic   ! Salinity of snow ice
75            rswitch  = MAX( 0._wp , SIGN( 1._wp , ht_i_1d(ji) - epsi20 ) )
76            zsm_i_si = ( zs_sni      - sm_i_1d(ji) ) *             dh_snowice(ji)  / MAX( ht_i_1d(ji), epsi20 ) * rswitch ! snow-ice   
77            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
[825]78
[7646]79            ! Update salinity (nb: salt flux already included in limthd_dh)
80            sm_i_1d(ji) = sm_i_1d(ji) + zsm_i_bg + zsm_i_si
[825]81
[7646]82            IF( ln_limdS ) THEN
83               !---------------------------------------------------------
84               !  Update ice salinity from brine drainage and flushing
85               !---------------------------------------------------------
86               iflush   = MAX( 0._wp , SIGN( 1._wp , t_su_1d(ji) - rt0         ) )  ! =1 if summer
87               igravdr  = MAX( 0._wp , SIGN( 1._wp , t_bo_1d(ji) - t_su_1d(ji) ) )  ! =1 if t_su < t_bo
88               zsm_i_gd = - igravdr * MAX( sm_i_1d(ji) - rn_sal_gd , 0._wp ) / rn_time_gd * rdt_ice  ! gravity drainage
89               zsm_i_fl = - iflush  * MAX( sm_i_1d(ji) - rn_sal_fl , 0._wp ) / rn_time_fl * rdt_ice  ! flushing
90               
91               ! Update salinity   
92               sm_i_1d(ji) = sm_i_1d(ji) + zsm_i_fl + zsm_i_gd
93               
94               ! Salt flux
95               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
96            ENDIF
[4161]97         END DO
[825]98
[4161]99         ! Salinity profile
100         CALL lim_var_salprof1d( kideb, kiut )
[2528]101         !
[3625]102      ENDIF 
[825]103
[921]104      !------------------------------------------------------------------------------|
[6470]105      !  3) vertical profile of salinity, constant in time                           |
[921]106      !------------------------------------------------------------------------------|
[5123]107      IF(  nn_icesal == 3  )   CALL lim_var_salprof1d( kideb, kiut )
[825]108
[2528]109      !
[825]110   END SUBROUTINE lim_thd_sal
111
[2528]112
[825]113   SUBROUTINE lim_thd_sal_init
114      !!-------------------------------------------------------------------
115      !!                  ***  ROUTINE lim_thd_sal_init  ***
116      !!
117      !! ** Purpose :   initialization of ice salinity parameters
118      !!
[2528]119      !! ** Method  :   Read the namicesal namelist and check the parameter
120      !!              values called at the first timestep (nit000)
[825]121      !!
122      !! ** input   :   Namelist namicesal
123      !!-------------------------------------------------------------------
[4147]124      INTEGER  ::   ios                 ! Local integer output status for namelist read
[7646]125      NAMELIST/namicesal/ ln_limdS, nn_icesal, rn_icesal, rn_sal_gd, rn_time_gd,   &
126         &                rn_sal_fl, rn_time_fl, rn_simax, rn_simin 
[825]127      !!-------------------------------------------------------------------
[2528]128      !
[4147]129      REWIND( numnam_ice_ref )              ! Namelist namicesal in reference namelist : Ice salinity
130      READ  ( numnam_ice_ref, namicesal, IOSTAT = ios, ERR = 901)
131901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namicesal in reference namelist', lwp )
132
133      REWIND( numnam_ice_cfg )              ! Namelist namicesal in configuration namelist : Ice salinity
134      READ  ( numnam_ice_cfg, namicesal, IOSTAT = ios, ERR = 902 )
135902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namicesal in configuration namelist', lwp )
[4624]136      IF(lwm) WRITE ( numoni, namicesal )
[2528]137      !
138      IF(lwp) THEN                           ! control print
[825]139         WRITE(numout,*)
140         WRITE(numout,*) 'lim_thd_sal_init : Ice parameters for salinity '
141         WRITE(numout,*) '~~~~~~~~~~~~~~~~'
[7646]142         WRITE(numout,*) '   activate gravity drainage and flushing (T) or not (F)   ln_limdS   = ', ln_limdS
143         WRITE(numout,*) '   switch for salinity                                     nn_icesal  = ', nn_icesal
144         WRITE(numout,*) '   bulk salinity value if nn_icesal = 1                    rn_icesal  = ', rn_icesal
145         WRITE(numout,*) '   restoring salinity for gravity drainage                 rn_sal_gd  = ', rn_sal_gd
146         WRITE(numout,*) '   restoring time for for gravity drainage                 rn_time_gd = ', rn_time_gd
147         WRITE(numout,*) '   restoring salinity for flushing                         rn_sal_fl  = ', rn_sal_fl
148         WRITE(numout,*) '   restoring time for flushing                             rn_time_fl = ', rn_time_fl
149         WRITE(numout,*) '   Maximum tolerated ice salinity                          rn_simax   = ', rn_simax
150         WRITE(numout,*) '   Minimum tolerated ice salinity                          rn_simin   = ', rn_simin
[825]151      ENDIF
[2528]152      !
[825]153   END SUBROUTINE lim_thd_sal_init
154
155#else
156   !!----------------------------------------------------------------------
[2528]157   !!   Default option         Dummy Module          No LIM-3 sea-ice model
[825]158   !!----------------------------------------------------------------------
159#endif
160   !!======================================================================
161END MODULE limthd_sal
Note: See TracBrowser for help on using the repository browser.