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.
limdmp_2.F90 in trunk/NEMOGCM/NEMO/LIM_SRC_2 – NEMO

source: trunk/NEMOGCM/NEMO/LIM_SRC_2/limdmp_2.F90 @ 7738

Last change on this file since 7738 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.7 KB
RevLine 
[821]1MODULE limdmp_2
[420]2   !!======================================================================
[821]3   !!                       ***  MODULE limdmp_2   ***
[2528]4   !!  LIM-2 ice model : restoring Ice thickness and Fraction leads
[420]5   !!======================================================================
[2528]6   !! History :   2.0  !  2004-04 (S. Theetten) Original code
7   !!             3.3  !  2010-06 (J.-M. Molines) use of fldread
[420]8   !!----------------------------------------------------------------------
[2528]9#if defined key_lim2
[420]10   !!----------------------------------------------------------------------
[2528]11   !!   'key_lim2'                                    LIM 2.0 sea-ice model
[508]12   !!----------------------------------------------------------------------
[3635]13   !!   lim_dmp_2     : ice model damping
[420]14   !!----------------------------------------------------------------------
[3635]15   USE ice_2          ! ice variables
[2528]16   USE sbc_oce, ONLY : nn_fsbc ! for fldread
[3635]17   USE dom_oce        ! for mi0; mi1 etc ...
18   USE fldread        ! read input fields
19   USE in_out_manager ! I/O manager
20   USE lib_mpp        ! MPP library
[3625]21   USE lib_fortran     ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined) 
[2715]22
[420]23   IMPLICIT NONE
24   PRIVATE
25
[2528]26   PUBLIC   lim_dmp_2     ! called by sbc_ice_lim2
27
[3635]28   INTEGER  , PARAMETER :: jp_hicif = 1 , jp_frld = 2
29   REAL(wp) , ALLOCATABLE, DIMENSION(:,:,:) ::   resto_ice   ! restoring coeff. on ICE   [s-1]
30   TYPE(FLD), ALLOCATABLE, DIMENSION(:)     ::   sf_icedmp   ! structure of ice damping input
[420]31   
32   !! * Substitution
33#  include "vectopt_loop_substitute.h90"
34   !!----------------------------------------------------------------------
[2528]35   !! NEMO/LIM 3.3 , UCL-NEMO-consortium (2010)
[1156]36   !! $Id$
[2528]37   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
[420]38   !!----------------------------------------------------------------------
39CONTAINS
40
[2528]41   SUBROUTINE lim_dmp_2( kt )
[420]42      !!-------------------------------------------------------------------
[2528]43      !!                   ***  ROUTINE lim_dmp_2  ***
[420]44      !!
[3635]45      !! ** purpose :   restore ice thickness and lead fraction
[420]46      !!
[3635]47      !! ** method  :   restore ice thickness and lead fraction using a restoring
48      !!              coefficient defined by the user in lim_dmp_init
49      !!
50      !! ** Action  : - update hicif and frld 
51      !!
[420]52      !!---------------------------------------------------------------------
[2528]53      INTEGER, INTENT(in) ::   kt   ! ocean time-step
[508]54      !
[2528]55      INTEGER  ::   ji, jj         ! dummy loop indices
56      REAL(wp) ::   zfrld, zhice   ! local scalars
[420]57      !!---------------------------------------------------------------------
[508]58      !
[3635]59      IF( kt == nit000 ) THEN
[2528]60         IF(lwp) WRITE(numout,*)
61         IF(lwp) WRITE(numout,*) 'lim_dmp_2 : Ice thickness and ice concentration restoring'
62         IF(lwp) WRITE(numout,*) '~~~~~~~~~~'
63         !
64         ! ice_resto_init create resto_ice (in 1/s) for restoring ice parameters near open boundaries.
65         ! Double check this routine to verify if it corresponds to your config
66         CALL lim_dmp_init
67      ENDIF
[508]68      !
[2528]69      IF( ln_limdmp ) THEN   ! ice restoring in this case
70         !
71         CALL fld_read( kt, nn_fsbc, sf_icedmp )
72         !
73         hicif(:,:) = MAX( 0._wp,                     &        ! h >= 0         avoid spurious out of physical range
74            &         hicif(:,:) - rdt_ice * resto_ice(:,:,1) * ( hicif(:,:) - sf_icedmp(jp_hicif)%fnow(:,:,1) )  ) 
[3635]75         frld (:,:) = MAX( 0._wp, MIN( 1._wp,         &        ! 0<= frld<=1    values which blow the run up
[2528]76            &         frld (:,:) - rdt_ice * resto_ice(:,:,1) * ( frld (:,:) - sf_icedmp(jp_frld )%fnow(:,:,1) )  )  )
77         !
78      ENDIF
79      !
[821]80   END SUBROUTINE lim_dmp_2
[420]81
82
[2528]83   SUBROUTINE lim_dmp_init
[420]84      !!----------------------------------------------------------------------
[2528]85      !!                   ***  ROUTINE lim_dmp_init  ***
[420]86      !!
[3635]87      !! ** Purpose :   set the coefficient for the ice thickness and lead fraction restoring
[420]88      !!
[3635]89      !! ** Method  :   restoring is used to mimic ice open boundaries.
90      !!              the restoring coef. (a 2D array) has to be defined by the user.
91      !!              here is given as an example a restoring along north and south boundaries
[420]92      !!     
[2528]93      !! ** Action  :   define resto_ice(:,:,1)
[420]94      !!----------------------------------------------------------------------
[2528]95      INTEGER  :: ji, jj, jk       ! dummy loop indices
96      INTEGER  :: irelax, ierror   ! error flag for allocation
[4147]97      INTEGER  ::   ios            ! Local integer output status for namelist read
[508]98      !
[2528]99      REAL(wp) :: zdmpmax, zdmpmin, zfactor, zreltim ! temporary scalar
100      !
101      CHARACTER(len=100)           ::   cn_dir       ! Root directory for location of ssr files
102      TYPE(FLD_N), DIMENSION (2)   ::   sl_icedmp    ! informations about the icedmp  field to be read
103      TYPE(FLD_N)                  ::   sn_hicif     !
104      TYPE(FLD_N)                  ::   sn_frld      !
105      NAMELIST/namice_dmp/ cn_dir, ln_limdmp, sn_hicif, sn_frld
[420]106      !!----------------------------------------------------------------------
[2528]107      !
108      ! 1)  initialize fld read structure for input data
109      !     --------------------------------------------
[4147]110                 
111      REWIND( numnam_ice_ref )              ! Namelist namice_dmp in reference namelist : Ice restoring
112      READ  ( numnam_ice_ref, namice_dmp, IOSTAT = ios, ERR = 901)
113901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namice_dmp in reference namelist', lwp )
[420]114
[4147]115      REWIND( numnam_ice_cfg )              ! Namelist  namice_dmp in configuration namelist : Ice restoring
116      READ  ( numnam_ice_cfg, namice_dmp, IOSTAT = ios, ERR = 902 )
117902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namice_dmp in configuration namelist', lwp )
[4624]118      IF(lwm) WRITE ( numoni, namice_dmp )
[2528]119      !
120      IF ( lwp ) THEN                     !* control print
121         WRITE (numout,*)'     lim_dmp_init : lim_dmp initialization ' 
122         WRITE (numout,*)'       Namelist namicedmp read '
123         WRITE (numout,*)'         Ice restoring (T) or not (F) ln_limdmp =', ln_limdmp 
124         WRITE (numout,*)
125         WRITE (numout,*)'     CAUTION : here hard coded ice restoring along northern and southern boundaries'
126         WRITE (numout,*)'               adapt the lim_dmp_init routine to your needs'
[420]127      ENDIF
128
[2528]129      ! 2)  initialise resto_ice    ==>  config dependant !
130      !     --------------------         ++++++++++++++++
131      !
132      IF( ln_limdmp ) THEN                !* ice restoring is used, follow initialization
133         !
134         sl_icedmp ( jp_hicif ) = sn_hicif
135         sl_icedmp ( jp_frld  ) = sn_frld
136         ALLOCATE ( sf_icedmp (2) , resto_ice(jpi,jpj,1), STAT=ierror )
137         IF( ierror > 0 ) THEN
138            CALL ctl_stop( 'lim_dmp_init: unable to allocate sf_icedmp structure or resto_ice array' )   ;   RETURN
139         ENDIF
140         ALLOCATE( sf_icedmp(jp_hicif)%fnow(jpi,jpj,1) , sf_icedmp(jp_hicif)%fdta(jpi,jpj,1,2) )
141         ALLOCATE( sf_icedmp(jp_frld )%fnow(jpi,jpj,1) , sf_icedmp(jp_frld )%fdta(jpi,jpj,1,2) )
142         !                         ! fill sf_icedmp with sn_icedmp and control print
143         CALL fld_fill( sf_icedmp, sl_icedmp, cn_dir, 'lim_dmp_init', 'Ice  restoring input data', 'namicedmp' )
144     
145         resto_ice(:,:,:) = 0._wp
[508]146         !
[2528]147         irelax  = 16                     ! width of buffer zone with respect to close boundary
148         zdmpmax = 10._wp                 ! max restoring time scale  (days) (low restoring)
149         zdmpmin = rdt_ice / 86400._wp    ! min restoring time scale  (days) (high restoring)
150         !                                ! days / grid-point
151         zfactor = ( zdmpmax - zdmpmin ) / REAL( irelax, wp )
[420]152
[2528]153         !    South boundary restoring term
154         ! REM: if there is no ice in the model and in the data,
155         !      no restoring even with non zero resto_ice
[7646]156         DO jj = mj0(1), mj1( irelax)
157            zreltim = zdmpmin + zfactor * mjg(jj)
[2528]158            resto_ice(:,jj,:) = 1._wp / ( zreltim * 86400._wp )
159         END DO
[674]160
[2528]161         ! North boundary restoring term
[7646]162         DO jj =  mj0(jpjglo - irelax), mj1(jpjglo)
163            zreltim = zdmpmin + zfactor * (jpjglo - mjg(jj))
[2528]164            resto_ice(:,jj,:) = 1.e0 / ( zreltim * 86400 )
165         END DO
[420]166      ENDIF
[508]167      !
[2528]168   END SUBROUTINE lim_dmp_init
169   
[420]170#else
171   !!----------------------------------------------------------------------
172   !!   Default option         Empty Module                  No ice damping
173   !!----------------------------------------------------------------------
174CONTAINS
[821]175   SUBROUTINE lim_dmp_2( kt )        ! Dummy routine
176      WRITE(*,*) 'lim_dmp_2: You should not see this print! error? ', kt
177   END SUBROUTINE lim_dmp_2
[420]178#endif
179
180   !!======================================================================
[821]181END MODULE limdmp_2
Note: See TracBrowser for help on using the repository browser.