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 @ 2715

Last change on this file since 2715 was 2715, checked in by rblod, 13 years ago

First attempt to put dynamic allocation on the trunk

  • Property svn:keywords set to Id
File size: 8.8 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   !!----------------------------------------------------------------------
[821]13   !!   lim_dmp_2      : ice model damping
[420]14   !!----------------------------------------------------------------------
[2528]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
[2715]19   USE in_out_manager  ! I/O manager
20   USE lib_mpp         ! MPP library
21
[420]22   IMPLICIT NONE
23   PRIVATE
24
[2528]25   PUBLIC   lim_dmp_2     ! called by sbc_ice_lim2
26
27   REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::   resto_ice   ! restoring coeff. on ICE   [s-1]
28
29   INTEGER, PARAMETER :: jp_hicif = 1 , jp_frld = 2
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      !!
[2528]45      !! ** purpose : ice model damping : restoring ice thickness and fraction leads
[420]46      !!
[2528]47      !! ** method  : the key_tradmp must be used to compute resto(:,:,1) coef.
[420]48      !!---------------------------------------------------------------------
[2528]49      INTEGER, INTENT(in) ::   kt   ! ocean time-step
[508]50      !
[2528]51      INTEGER  ::   ji, jj         ! dummy loop indices
52      REAL(wp) ::   zfrld, zhice   ! local scalars
[420]53      !!---------------------------------------------------------------------
[508]54      !
[2528]55      IF (kt == nit000)  THEN
56         IF(lwp) WRITE(numout,*)
57         IF(lwp) WRITE(numout,*) 'lim_dmp_2 : Ice thickness and ice concentration restoring'
58         IF(lwp) WRITE(numout,*) '~~~~~~~~~~'
59         !
60         ! ice_resto_init create resto_ice (in 1/s) for restoring ice parameters near open boundaries.
61         ! Double check this routine to verify if it corresponds to your config
62         CALL lim_dmp_init
63      ENDIF
[508]64      !
[2528]65      IF( ln_limdmp ) THEN   ! ice restoring in this case
66         !
67         CALL fld_read( kt, nn_fsbc, sf_icedmp )
68         !
69!CDIR COLLAPSE
70         hicif(:,:) = MAX( 0._wp,                     &        ! h >= 0         avoid spurious out of physical range
71            &         hicif(:,:) - rdt_ice * resto_ice(:,:,1) * ( hicif(:,:) - sf_icedmp(jp_hicif)%fnow(:,:,1) )  ) 
72!CDIR COLLAPSE
73         hicif(:,:) = MAX( 0._wp, MIN( 1._wp,         &        ! 0<= frld<=1    values which blow the run up
74            &         frld (:,:) - rdt_ice * resto_ice(:,:,1) * ( frld (:,:) - sf_icedmp(jp_frld )%fnow(:,:,1) )  )  )
75         !
76      ENDIF
77      !
[821]78   END SUBROUTINE lim_dmp_2
[420]79
80
[2528]81   SUBROUTINE lim_dmp_init
[420]82      !!----------------------------------------------------------------------
[2528]83      !!                   ***  ROUTINE lim_dmp_init  ***
[420]84      !!
[2528]85      !! ** Purpose :   Initialization for the ice thickness and concentration
86      !!                restoring
87      !!              restoring will be used. It is used to mimic ice open
88      !!              boundaries.
[420]89      !!
[2528]90      !! ** Method  :  ?????
[420]91      !!     
[2528]92      !! ** Action  :   define resto_ice(:,:,1)
[420]93      !!----------------------------------------------------------------------
[2528]94      INTEGER  :: ji, jj, jk       ! dummy loop indices
95      INTEGER  :: irelax, ierror   ! error flag for allocation
[508]96      !
[2528]97      REAL(wp) :: zdmpmax, zdmpmin, zfactor, zreltim ! temporary scalar
98      !
99      CHARACTER(len=100)           ::   cn_dir       ! Root directory for location of ssr files
100      TYPE(FLD_N), DIMENSION (2)   ::   sl_icedmp    ! informations about the icedmp  field to be read
101      TYPE(FLD_N)                  ::   sn_hicif     !
102      TYPE(FLD_N)                  ::   sn_frld      !
103      NAMELIST/namice_dmp/ cn_dir, ln_limdmp, sn_hicif, sn_frld
[420]104      !!----------------------------------------------------------------------
[2528]105      !
106      ! 1)  initialize fld read structure for input data
107      !     --------------------------------------------
108      ln_limdmp = .false.                 !* set file information (default values)
109      cn_dir    = './'
110      ! (NB: frequency positive => hours, negative => months)
111      !                !    file     ! frequency ! variable ! time intep !  clim   ! 'yearly' or ! weights  ! rotation !
112      !                !    name     !  (hours)  !  name    !   (T/F)    !  (T/F)  !  'monthly'  ! filename ! pairs    !
113      sn_hicif = FLD_N( 'ice_damping ', -1       , 'hicif'  ,  .true.    , .true.  ,  'yearly'   ,  ''      ,  ''      )
114      sn_frld  = FLD_N( 'ice_damping ', -1       , 'frld'   ,  .true.    , .true.  ,  'yearly'   ,  ''      ,  ''      )
[420]115
[2528]116      REWIND( numnam_ice )                !* read in namelist_ice namicedmp
117      READ  ( numnam_ice, namice_dmp )
118      !
119      IF ( lwp ) THEN                     !* control print
120         WRITE (numout,*)'     lim_dmp_init : lim_dmp initialization ' 
121         WRITE (numout,*)'       Namelist namicedmp read '
122         WRITE (numout,*)'         Ice restoring (T) or not (F) ln_limdmp =', ln_limdmp 
123         WRITE (numout,*)
124         WRITE (numout,*)'     CAUTION : here hard coded ice restoring along northern and southern boundaries'
125         WRITE (numout,*)'               adapt the lim_dmp_init routine to your needs'
[420]126      ENDIF
127
[2528]128      ! 2)  initialise resto_ice    ==>  config dependant !
129      !     --------------------         ++++++++++++++++
130      !
131      IF( ln_limdmp ) THEN                !* ice restoring is used, follow initialization
132         !
133         sl_icedmp ( jp_hicif ) = sn_hicif
134         sl_icedmp ( jp_frld  ) = sn_frld
135         ALLOCATE ( sf_icedmp (2) , resto_ice(jpi,jpj,1), STAT=ierror )
136         IF( ierror > 0 ) THEN
137            CALL ctl_stop( 'lim_dmp_init: unable to allocate sf_icedmp structure or resto_ice array' )   ;   RETURN
138         ENDIF
139         ALLOCATE( sf_icedmp(jp_hicif)%fnow(jpi,jpj,1) , sf_icedmp(jp_hicif)%fdta(jpi,jpj,1,2) )
140         ALLOCATE( sf_icedmp(jp_frld )%fnow(jpi,jpj,1) , sf_icedmp(jp_frld )%fdta(jpi,jpj,1,2) )
141         !                         ! fill sf_icedmp with sn_icedmp and control print
142         CALL fld_fill( sf_icedmp, sl_icedmp, cn_dir, 'lim_dmp_init', 'Ice  restoring input data', 'namicedmp' )
143     
144         resto_ice(:,:,:) = 0._wp
145         !      Re-calculate the North and South boundary restoring term
146         !      because those boundaries may change with the prescribed zoom area.
[508]147         !
[2528]148         irelax  = 16                     ! width of buffer zone with respect to close boundary
149         zdmpmax = 10._wp                 ! max restoring time scale  (days) (low restoring)
150         zdmpmin = rdt_ice / 86400._wp    ! min restoring time scale  (days) (high restoring)
151         !                                ! days / grid-point
152         zfactor = ( zdmpmax - zdmpmin ) / REAL( irelax, wp )
[420]153
[2528]154         !    South boundary restoring term
155         ! REM: if there is no ice in the model and in the data,
156         !      no restoring even with non zero resto_ice
157         DO jj = mj0(jpjzoom - 1 + 1), mj1(jpjzoom -1 + irelax)
158            zreltim = zdmpmin + zfactor * ( mjg(jj) - jpjzoom + 1 )
159            resto_ice(:,jj,:) = 1._wp / ( zreltim * 86400._wp )
160         END DO
[674]161
[2528]162         ! North boundary restoring term
163         DO jj =  mj0(jpjzoom -1 + jpjglo - irelax), mj1(jpjzoom - 1 + jpjglo)
164            zreltim = zdmpmin + zfactor * (jpjglo - ( mjg(jj) - jpjzoom + 1 ))
165            resto_ice(:,jj,:) = 1.e0 / ( zreltim * 86400 )
166         END DO
[420]167      ENDIF
[508]168      !
[2528]169   END SUBROUTINE lim_dmp_init
170   
[420]171#else
172   !!----------------------------------------------------------------------
173   !!   Default option         Empty Module                  No ice damping
174   !!----------------------------------------------------------------------
175CONTAINS
[821]176   SUBROUTINE lim_dmp_2( kt )        ! Dummy routine
177      WRITE(*,*) 'lim_dmp_2: You should not see this print! error? ', kt
178   END SUBROUTINE lim_dmp_2
[420]179#endif
180
181   !!======================================================================
[821]182END MODULE limdmp_2
Note: See TracBrowser for help on using the repository browser.