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_CMCC_INGV_2013/NEMOGCM/NEMO/LIM_SRC_2 – NEMO

source: branches/2013/dev_CMCC_INGV_2013/NEMOGCM/NEMO/LIM_SRC_2/limdmp_2.F90 @ 4217

Last change on this file since 4217 was 4217, checked in by poddo, 11 years ago

Solved problems with namelist parameter land/sea mask

  • Property svn:keywords set to Id
File size: 9.2 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!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
[3635]77         frld (:,:) = MAX( 0._wp, MIN( 1._wp,         &        ! 0<= frld<=1    values which blow the run up
[2528]78            &         frld (:,:) - rdt_ice * resto_ice(:,:,1) * ( frld (:,:) - sf_icedmp(jp_frld )%fnow(:,:,1) )  )  )
79         !
80      ENDIF
81      !
[821]82   END SUBROUTINE lim_dmp_2
[420]83
84
[2528]85   SUBROUTINE lim_dmp_init
[420]86      !!----------------------------------------------------------------------
[2528]87      !!                   ***  ROUTINE lim_dmp_init  ***
[420]88      !!
[3635]89      !! ** Purpose :   set the coefficient for the ice thickness and lead fraction restoring
[420]90      !!
[3635]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
[420]94      !!     
[2528]95      !! ** Action  :   define resto_ice(:,:,1)
[420]96      !!----------------------------------------------------------------------
[2528]97      INTEGER  :: ji, jj, jk       ! dummy loop indices
98      INTEGER  :: irelax, ierror   ! error flag for allocation
[508]99      !
[2528]100      REAL(wp) :: zdmpmax, zdmpmin, zfactor, zreltim ! temporary scalar
101      !
102      CHARACTER(len=100)           ::   cn_dir       ! Root directory for location of ssr files
103      TYPE(FLD_N), DIMENSION (2)   ::   sl_icedmp    ! informations about the icedmp  field to be read
104      TYPE(FLD_N)                  ::   sn_hicif     !
105      TYPE(FLD_N)                  ::   sn_frld      !
106      NAMELIST/namice_dmp/ cn_dir, ln_limdmp, sn_hicif, sn_frld
[420]107      !!----------------------------------------------------------------------
[2528]108      !
109      ! 1)  initialize fld read structure for input data
110      !     --------------------------------------------
111      ln_limdmp = .false.                 !* set file information (default values)
112      cn_dir    = './'
113      ! (NB: frequency positive => hours, negative => months)
[4217]114      !                !    file     ! frequency ! variable ! time intep !  clim   ! 'yearly' or ! weights  ! rotation ! land/sea mask !
115      !                !    name     !  (hours)  !  name    !   (T/F)    !  (T/F)  !  'monthly'  ! filename ! pairs    ! filename      !
116      sn_hicif = FLD_N( 'ice_damping ', -1       , 'hicif'  ,  .true.    , .true.  ,  'yearly'   ,  ''      ,  &
117           & ''      , ''            )
118      sn_frld  = FLD_N( 'ice_damping ', -1       , 'frld'   ,  .true.    , .true.  ,  'yearly'   ,  ''      ,  &
119           & ''      , ''            )
[420]120
[2528]121      REWIND( numnam_ice )                !* read in namelist_ice namicedmp
122      READ  ( numnam_ice, namice_dmp )
123      !
124      IF ( lwp ) THEN                     !* control print
125         WRITE (numout,*)'     lim_dmp_init : lim_dmp initialization ' 
126         WRITE (numout,*)'       Namelist namicedmp read '
127         WRITE (numout,*)'         Ice restoring (T) or not (F) ln_limdmp =', ln_limdmp 
128         WRITE (numout,*)
129         WRITE (numout,*)'     CAUTION : here hard coded ice restoring along northern and southern boundaries'
130         WRITE (numout,*)'               adapt the lim_dmp_init routine to your needs'
[420]131      ENDIF
132
[2528]133      ! 2)  initialise resto_ice    ==>  config dependant !
134      !     --------------------         ++++++++++++++++
135      !
136      IF( ln_limdmp ) THEN                !* ice restoring is used, follow initialization
137         !
138         sl_icedmp ( jp_hicif ) = sn_hicif
139         sl_icedmp ( jp_frld  ) = sn_frld
140         ALLOCATE ( sf_icedmp (2) , resto_ice(jpi,jpj,1), STAT=ierror )
141         IF( ierror > 0 ) THEN
142            CALL ctl_stop( 'lim_dmp_init: unable to allocate sf_icedmp structure or resto_ice array' )   ;   RETURN
143         ENDIF
144         ALLOCATE( sf_icedmp(jp_hicif)%fnow(jpi,jpj,1) , sf_icedmp(jp_hicif)%fdta(jpi,jpj,1,2) )
145         ALLOCATE( sf_icedmp(jp_frld )%fnow(jpi,jpj,1) , sf_icedmp(jp_frld )%fdta(jpi,jpj,1,2) )
146         !                         ! fill sf_icedmp with sn_icedmp and control print
147         CALL fld_fill( sf_icedmp, sl_icedmp, cn_dir, 'lim_dmp_init', 'Ice  restoring input data', 'namicedmp' )
148     
149         resto_ice(:,:,:) = 0._wp
150         !      Re-calculate the North and South boundary restoring term
151         !      because those boundaries may change with the prescribed zoom area.
[508]152         !
[2528]153         irelax  = 16                     ! width of buffer zone with respect to close boundary
154         zdmpmax = 10._wp                 ! max restoring time scale  (days) (low restoring)
155         zdmpmin = rdt_ice / 86400._wp    ! min restoring time scale  (days) (high restoring)
156         !                                ! days / grid-point
157         zfactor = ( zdmpmax - zdmpmin ) / REAL( irelax, wp )
[420]158
[2528]159         !    South boundary restoring term
160         ! REM: if there is no ice in the model and in the data,
161         !      no restoring even with non zero resto_ice
162         DO jj = mj0(jpjzoom - 1 + 1), mj1(jpjzoom -1 + irelax)
163            zreltim = zdmpmin + zfactor * ( mjg(jj) - jpjzoom + 1 )
164            resto_ice(:,jj,:) = 1._wp / ( zreltim * 86400._wp )
165         END DO
[674]166
[2528]167         ! North boundary restoring term
168         DO jj =  mj0(jpjzoom -1 + jpjglo - irelax), mj1(jpjzoom - 1 + jpjglo)
169            zreltim = zdmpmin + zfactor * (jpjglo - ( mjg(jj) - jpjzoom + 1 ))
170            resto_ice(:,jj,:) = 1.e0 / ( zreltim * 86400 )
171         END DO
[420]172      ENDIF
[508]173      !
[2528]174   END SUBROUTINE lim_dmp_init
175   
[420]176#else
177   !!----------------------------------------------------------------------
178   !!   Default option         Empty Module                  No ice damping
179   !!----------------------------------------------------------------------
180CONTAINS
[821]181   SUBROUTINE lim_dmp_2( kt )        ! Dummy routine
182      WRITE(*,*) 'lim_dmp_2: You should not see this print! error? ', kt
183   END SUBROUTINE lim_dmp_2
[420]184#endif
185
186   !!======================================================================
[821]187END MODULE limdmp_2
Note: See TracBrowser for help on using the repository browser.