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

source: branches/NERC/dev_r3874_FASTNEt/NEMOGCM/NEMO/LIM_SRC_2/limdmp_2.F90 @ 6736

Last change on this file since 6736 was 6736, checked in by jamesharle, 8 years ago

FASTNEt code modifications

  • Property svn:keywords set to Id
File size: 9.0 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
22   IMPLICIT NONE
23   PRIVATE
24
25   PUBLIC   lim_dmp_2     ! called by sbc_ice_lim2
26
27   INTEGER  , PARAMETER :: jp_hicif = 1 , jp_frld = 2
28   REAL(wp) , ALLOCATABLE, DIMENSION(:,:,:) ::   resto_ice   ! restoring coeff. on ICE   [s-1]
29   TYPE(FLD), ALLOCATABLE, DIMENSION(:)     ::   sf_icedmp   ! structure of ice damping input
30   
31   !! * Substitution
32#  include "vectopt_loop_substitute.h90"
33   !!----------------------------------------------------------------------
34   !! NEMO/LIM 3.3 , UCL-NEMO-consortium (2010)
35   !! $Id$
36   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
37   !!----------------------------------------------------------------------
38CONTAINS
39
40   SUBROUTINE lim_dmp_2( kt )
41      !!-------------------------------------------------------------------
42      !!                   ***  ROUTINE lim_dmp_2  ***
43      !!
44      !! ** purpose :   restore ice thickness and lead fraction
45      !!
46      !! ** method  :   restore ice thickness and lead fraction using a restoring
47      !!              coefficient defined by the user in lim_dmp_init
48      !!
49      !! ** Action  : - update hicif and frld 
50      !!
51      !!---------------------------------------------------------------------
52      INTEGER, INTENT(in) ::   kt   ! ocean time-step
53      !
54      INTEGER  ::   ji, jj         ! dummy loop indices
55      REAL(wp) ::   zfrld, zhice   ! local scalars
56      !!---------------------------------------------------------------------
57      !
58      IF( kt == nit000 ) THEN
59         IF(lwp) WRITE(numout,*)
60         IF(lwp) WRITE(numout,*) 'lim_dmp_2 : Ice thickness and ice concentration restoring'
61         IF(lwp) WRITE(numout,*) '~~~~~~~~~~'
62         !
63         ! ice_resto_init create resto_ice (in 1/s) for restoring ice parameters near open boundaries.
64         ! Double check this routine to verify if it corresponds to your config
65         CALL lim_dmp_init
66      ENDIF
67      !
68      IF( ln_limdmp ) THEN   ! ice restoring in this case
69         !
70         CALL fld_read( kt, nn_fsbc, sf_icedmp )
71         !
72!CDIR COLLAPSE
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) )  ) 
75!CDIR COLLAPSE
76         frld (:,:) = MAX( 0._wp, MIN( 1._wp,         &        ! 0<= frld<=1    values which blow the run up
77            &         frld (:,:) - rdt_ice * resto_ice(:,:,1) * ( frld (:,:) - sf_icedmp(jp_frld )%fnow(:,:,1) )  )  )
78         !
79      ENDIF
80      !
81   END SUBROUTINE lim_dmp_2
82
83
84   SUBROUTINE lim_dmp_init
85      !!----------------------------------------------------------------------
86      !!                   ***  ROUTINE lim_dmp_init  ***
87      !!
88      !! ** Purpose :   set the coefficient for the ice thickness and lead fraction restoring
89      !!
90      !! ** Method  :   restoring is used to mimic ice open boundaries.
91      !!              the restoring coef. (a 2D array) has to be defined by the user.
92      !!              here is given as an example a restoring along north and south boundaries
93      !!     
94      !! ** Action  :   define resto_ice(:,:,1)
95      !!----------------------------------------------------------------------
96      INTEGER  :: ji, jj, jk       ! dummy loop indices
97      INTEGER  :: irelax, ierror   ! error flag for allocation
98      !
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
106      !!----------------------------------------------------------------------
107      !
108      ! 1)  initialize fld read structure for input data
109      !     --------------------------------------------
110      ln_limdmp = .false.                 !* set file information (default values)
111      cn_dir    = './'
112      ! (NB: frequency positive => hours, negative => months)
113      !                !    file     ! frequency ! variable ! time intep !  clim   ! 'yearly' or ! weights  ! rotation !
114      !                !    name     !  (hours)  !  name    !   (T/F)    !  (T/F)  !  'monthly'  ! filename ! pairs    !
115      sn_hicif = FLD_N( 'ice_damping ', -1       , 'hicif'  ,  .true.    , .true.  ,  'yearly'   ,  ''      ,  ''      )
116      sn_frld  = FLD_N( 'ice_damping ', -1       , 'frld'   ,  .true.    , .true.  ,  'yearly'   ,  ''      ,  ''      )
117
118      REWIND( numnam_ice )                !* read in namelist_ice namicedmp
119      READ  ( numnam_ice, namice_dmp )
120      !
121      IF ( lwp ) THEN                     !* control print
122         WRITE (numout,*)'     lim_dmp_init : lim_dmp initialization ' 
123         WRITE (numout,*)'       Namelist namicedmp read '
124         WRITE (numout,*)'         Ice restoring (T) or not (F) ln_limdmp =', ln_limdmp 
125         WRITE (numout,*)
126         WRITE (numout,*)'     CAUTION : here hard coded ice restoring along northern and southern boundaries'
127         WRITE (numout,*)'               adapt the lim_dmp_init routine to your needs'
128      ENDIF
129
130      ! 2)  initialise resto_ice    ==>  config dependant !
131      !     --------------------         ++++++++++++++++
132      !
133      IF( ln_limdmp ) THEN                !* ice restoring is used, follow initialization
134         !
135         sl_icedmp ( jp_hicif ) = sn_hicif
136         sl_icedmp ( jp_frld  ) = sn_frld
137         ALLOCATE ( sf_icedmp (2) , resto_ice(jpi,jpj,1), STAT=ierror )
138         IF( ierror > 0 ) THEN
139            CALL ctl_stop( 'lim_dmp_init: unable to allocate sf_icedmp structure or resto_ice array' )   ;   RETURN
140         ENDIF
141         ALLOCATE( sf_icedmp(jp_hicif)%fnow(jpi,jpj,1) , sf_icedmp(jp_hicif)%fdta(jpi,jpj,1,2) )
142         ALLOCATE( sf_icedmp(jp_frld )%fnow(jpi,jpj,1) , sf_icedmp(jp_frld )%fdta(jpi,jpj,1,2) )
143         !                         ! fill sf_icedmp with sn_icedmp and control print
144         CALL fld_fill( sf_icedmp, sl_icedmp, cn_dir, 'lim_dmp_init', 'Ice  restoring input data', 'namicedmp' )
145     
146         resto_ice(:,:,:) = 0._wp
147         !      Re-calculate the North and South boundary restoring term
148         !      because those boundaries may change with the prescribed zoom area.
149         !
150         irelax  = 16                     ! width of buffer zone with respect to close boundary
151         zdmpmax = 10._wp                 ! max restoring time scale  (days) (low restoring)
152         zdmpmin = rdt_ice / 86400._wp    ! min restoring time scale  (days) (high restoring)
153         !                                ! days / grid-point
154         zfactor = ( zdmpmax - zdmpmin ) / REAL( irelax, wp )
155
156         !    South boundary restoring term
157         ! REM: if there is no ice in the model and in the data,
158         !      no restoring even with non zero resto_ice
159         DO jj = mj0(jpjzoom - 1 + 1), mj1(jpjzoom -1 + irelax)
160            zreltim = zdmpmin + zfactor * ( mjg(jj) - jpjzoom + 1 )
161            resto_ice(:,jj,:) = 1._wp / ( zreltim * 86400._wp )
162         END DO
163
164         ! North boundary restoring term
165         DO jj =  mj0(jpjzoom -1 + jpjglo - irelax), mj1(jpjzoom - 1 + jpjglo)
166            zreltim = zdmpmin + zfactor * (jpjglo - ( mjg(jj) - jpjzoom + 1 ))
167            resto_ice(:,jj,:) = 1.e0 / ( zreltim * 86400 )
168         END DO
169      ENDIF
170      !
171   END SUBROUTINE lim_dmp_init
172   
173#else
174   !!----------------------------------------------------------------------
175   !!   Default option         Empty Module                  No ice damping
176   !!----------------------------------------------------------------------
177CONTAINS
178   SUBROUTINE lim_dmp_2( kt )        ! Dummy routine
179      WRITE(*,*) 'lim_dmp_2: You should not see this print! error? ', kt
180   END SUBROUTINE lim_dmp_2
181#endif
182
183   !!======================================================================
184END MODULE limdmp_2
Note: See TracBrowser for help on using the repository browser.