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 branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/LIM_SRC_2 – NEMO

source: branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/LIM_SRC_2/limdmp_2.F90 @ 3875

Last change on this file since 3875 was 3875, checked in by clevy, 11 years ago

Configuration Setting/Step? 1, see ticket:#1074

  • Property svn:keywords set to Id
File size: 9.6 KB
Line 
1MODULE limdmp_2
2   !!======================================================================
3   !!                       ***  MODULE limdmp_2   ***
4   !!  LIM-2 ice model : restoring Ice thickness and Fraction leads
5   !!======================================================================
6   !! History :   2.0  !  2004-04 (S. Theetten) Original code
7   !!             3.3  !  2010-06 (J.-M. Molines) use of fldread
8   !!----------------------------------------------------------------------
9#if defined key_lim2
10   !!----------------------------------------------------------------------
11   !!   'key_lim2'                                    LIM 2.0 sea-ice model
12   !!----------------------------------------------------------------------
13   !!   lim_dmp_2     : ice model damping
14   !!----------------------------------------------------------------------
15   USE ice_2          ! ice variables
16   USE sbc_oce, ONLY : nn_fsbc ! for fldread
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
21   USE lib_fortran     ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined) 
22
23   IMPLICIT NONE
24   PRIVATE
25
26   PUBLIC   lim_dmp_2     ! called by sbc_ice_lim2
27
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
31   
32   !! * Substitution
33#  include "vectopt_loop_substitute.h90"
34   !!----------------------------------------------------------------------
35   !! NEMO/LIM 3.3 , UCL-NEMO-consortium (2010)
36   !! $Id$
37   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
38   !!----------------------------------------------------------------------
39CONTAINS
40
41   SUBROUTINE lim_dmp_2( kt )
42      !!-------------------------------------------------------------------
43      !!                   ***  ROUTINE lim_dmp_2  ***
44      !!
45      !! ** purpose :   restore ice thickness and lead fraction
46      !!
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      !!
52      !!---------------------------------------------------------------------
53      INTEGER, INTENT(in) ::   kt   ! ocean time-step
54      !
55      INTEGER  ::   ji, jj         ! dummy loop indices
56      REAL(wp) ::   zfrld, zhice   ! local scalars
57      !!---------------------------------------------------------------------
58      !
59      IF( kt == nit000 ) THEN
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
68      !
69      IF( ln_limdmp ) THEN   ! ice restoring in this case
70         !
71         CALL fld_read( kt, nn_fsbc, sf_icedmp )
72         !
73!CDIR COLLAPSE
74         hicif(:,:) = MAX( 0._wp,                     &        ! h >= 0         avoid spurious out of physical range
75            &         hicif(:,:) - rdt_ice * resto_ice(:,:,1) * ( hicif(:,:) - sf_icedmp(jp_hicif)%fnow(:,:,1) )  ) 
76!CDIR COLLAPSE
77         frld (:,:) = MAX( 0._wp, MIN( 1._wp,         &        ! 0<= frld<=1    values which blow the run up
78            &         frld (:,:) - rdt_ice * resto_ice(:,:,1) * ( frld (:,:) - sf_icedmp(jp_frld )%fnow(:,:,1) )  )  )
79         !
80      ENDIF
81      !
82   END SUBROUTINE lim_dmp_2
83
84
85   SUBROUTINE lim_dmp_init
86      !!----------------------------------------------------------------------
87      !!                   ***  ROUTINE lim_dmp_init  ***
88      !!
89      !! ** Purpose :   set the coefficient for the ice thickness and lead fraction restoring
90      !!
91      !! ** Method  :   restoring is used to mimic ice open boundaries.
92      !!              the restoring coef. (a 2D array) has to be defined by the user.
93      !!              here is given as an example a restoring along north and south boundaries
94      !!     
95      !! ** Action  :   define resto_ice(:,:,1)
96      !!----------------------------------------------------------------------
97      INTEGER  :: ji, jj, jk       ! dummy loop indices
98      INTEGER  :: irelax, ierror   ! error flag for allocation
99      INTEGER  ::   ios            ! Local integer output status for namelist read
100      !
101      REAL(wp) :: zdmpmax, zdmpmin, zfactor, zreltim ! temporary scalar
102      !
103      CHARACTER(len=100)           ::   cn_dir       ! Root directory for location of ssr files
104      TYPE(FLD_N), DIMENSION (2)   ::   sl_icedmp    ! informations about the icedmp  field to be read
105      TYPE(FLD_N)                  ::   sn_hicif     !
106      TYPE(FLD_N)                  ::   sn_frld      !
107      NAMELIST/namice_dmp/ cn_dir, ln_limdmp, sn_hicif, sn_frld
108      !!----------------------------------------------------------------------
109      !
110      ! 1)  initialize fld read structure for input data
111      !     --------------------------------------------
112      ln_limdmp = .false.                 !* set file information (default values)
113      cn_dir    = './'
114      ! (NB: frequency positive => hours, negative => months)
115      !                !    file     ! frequency ! variable ! time intep !  clim   ! 'yearly' or ! weights  ! rotation !
116      !                !    name     !  (hours)  !  name    !   (T/F)    !  (T/F)  !  'monthly'  ! filename ! pairs    !
117      sn_hicif = FLD_N( 'ice_damping ', -1       , 'hicif'  ,  .true.    , .true.  ,  'yearly'   ,  ''      ,  ''      )
118      sn_frld  = FLD_N( 'ice_damping ', -1       , 'frld'   ,  .true.    , .true.  ,  'yearly'   ,  ''      ,  ''      )
119                   
120      REWIND( numnam_ice_ref )              ! Namelist namice_dmp in reference namelist : Ice restoring
121      READ  ( numnam_ice_ref, namice_dmp, IOSTAT = ios, ERR = 901)
122901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namice_dmp in reference namelist', lwp )
123
124      REWIND( numnam_ice_cfg )              ! Namelist  namice_dmp in configuration namelist : Ice restoring
125      READ  ( numnam_ice_cfg, namice_dmp, IOSTAT = ios, ERR = 902 )
126902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namice_dmp in configuration namelist', lwp )
127      WRITE ( numoni, namice_dmp )
128      !
129      IF ( lwp ) THEN                     !* control print
130         WRITE (numout,*)'     lim_dmp_init : lim_dmp initialization ' 
131         WRITE (numout,*)'       Namelist namicedmp read '
132         WRITE (numout,*)'         Ice restoring (T) or not (F) ln_limdmp =', ln_limdmp 
133         WRITE (numout,*)
134         WRITE (numout,*)'     CAUTION : here hard coded ice restoring along northern and southern boundaries'
135         WRITE (numout,*)'               adapt the lim_dmp_init routine to your needs'
136      ENDIF
137
138      ! 2)  initialise resto_ice    ==>  config dependant !
139      !     --------------------         ++++++++++++++++
140      !
141      IF( ln_limdmp ) THEN                !* ice restoring is used, follow initialization
142         !
143         sl_icedmp ( jp_hicif ) = sn_hicif
144         sl_icedmp ( jp_frld  ) = sn_frld
145         ALLOCATE ( sf_icedmp (2) , resto_ice(jpi,jpj,1), STAT=ierror )
146         IF( ierror > 0 ) THEN
147            CALL ctl_stop( 'lim_dmp_init: unable to allocate sf_icedmp structure or resto_ice array' )   ;   RETURN
148         ENDIF
149         ALLOCATE( sf_icedmp(jp_hicif)%fnow(jpi,jpj,1) , sf_icedmp(jp_hicif)%fdta(jpi,jpj,1,2) )
150         ALLOCATE( sf_icedmp(jp_frld )%fnow(jpi,jpj,1) , sf_icedmp(jp_frld )%fdta(jpi,jpj,1,2) )
151         !                         ! fill sf_icedmp with sn_icedmp and control print
152         CALL fld_fill( sf_icedmp, sl_icedmp, cn_dir, 'lim_dmp_init', 'Ice  restoring input data', 'namicedmp' )
153     
154         resto_ice(:,:,:) = 0._wp
155         !      Re-calculate the North and South boundary restoring term
156         !      because those boundaries may change with the prescribed zoom area.
157         !
158         irelax  = 16                     ! width of buffer zone with respect to close boundary
159         zdmpmax = 10._wp                 ! max restoring time scale  (days) (low restoring)
160         zdmpmin = rdt_ice / 86400._wp    ! min restoring time scale  (days) (high restoring)
161         !                                ! days / grid-point
162         zfactor = ( zdmpmax - zdmpmin ) / REAL( irelax, wp )
163
164         !    South boundary restoring term
165         ! REM: if there is no ice in the model and in the data,
166         !      no restoring even with non zero resto_ice
167         DO jj = mj0(jpjzoom - 1 + 1), mj1(jpjzoom -1 + irelax)
168            zreltim = zdmpmin + zfactor * ( mjg(jj) - jpjzoom + 1 )
169            resto_ice(:,jj,:) = 1._wp / ( zreltim * 86400._wp )
170         END DO
171
172         ! North boundary restoring term
173         DO jj =  mj0(jpjzoom -1 + jpjglo - irelax), mj1(jpjzoom - 1 + jpjglo)
174            zreltim = zdmpmin + zfactor * (jpjglo - ( mjg(jj) - jpjzoom + 1 ))
175            resto_ice(:,jj,:) = 1.e0 / ( zreltim * 86400 )
176         END DO
177      ENDIF
178      !
179   END SUBROUTINE lim_dmp_init
180   
181#else
182   !!----------------------------------------------------------------------
183   !!   Default option         Empty Module                  No ice damping
184   !!----------------------------------------------------------------------
185CONTAINS
186   SUBROUTINE lim_dmp_2( kt )        ! Dummy routine
187      WRITE(*,*) 'lim_dmp_2: You should not see this print! error? ', kt
188   END SUBROUTINE lim_dmp_2
189#endif
190
191   !!======================================================================
192END MODULE limdmp_2
Note: See TracBrowser for help on using the repository browser.