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.
Changeset 3577 for branches/2012/dev_INGV/NEMOGCM/NEMO/LIM_SRC_2/limdmp_2.F90 – NEMO

Ignore:
Timestamp:
2012-11-16T12:47:14+01:00 (11 years ago)
Author:
adani
Message:

ticket #998. Step 5: Add in changes from the trunk between revisions 3521 and 3555.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2012/dev_INGV/NEMOGCM/NEMO/LIM_SRC_2/limdmp_2.F90

    r2715 r3577  
    1111   !!   'key_lim2'                                    LIM 2.0 sea-ice model 
    1212   !!---------------------------------------------------------------------- 
    13    !!   lim_dmp_2      : ice model damping 
     13   !!   lim_dmp_2     : ice model damping 
    1414   !!---------------------------------------------------------------------- 
    15    USE ice_2           ! ice variables  
     15   USE ice_2          ! ice variables  
    1616   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 
     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 
    2121 
    2222   IMPLICIT NONE 
     
    2525   PUBLIC   lim_dmp_2     ! called by sbc_ice_lim2 
    2626 
    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 
     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 
    3130    
    3231   !! * Substitution 
     
    4342      !!                   ***  ROUTINE lim_dmp_2  *** 
    4443      !! 
    45       !! ** purpose : ice model damping : restoring ice thickness and fraction leads 
     44      !! ** purpose :   restore ice thickness and lead fraction 
    4645      !! 
    47       !! ** method  : the key_tradmp must be used to compute resto(:,:,1) coef. 
     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      !! 
    4851      !!--------------------------------------------------------------------- 
    4952      INTEGER, INTENT(in) ::   kt   ! ocean time-step 
     
    5356      !!--------------------------------------------------------------------- 
    5457      ! 
    55       IF (kt == nit000) THEN  
     58      IF( kt == nit000 ) THEN  
    5659         IF(lwp) WRITE(numout,*) 
    5760         IF(lwp) WRITE(numout,*) 'lim_dmp_2 : Ice thickness and ice concentration restoring' 
     
    7174            &         hicif(:,:) - rdt_ice * resto_ice(:,:,1) * ( hicif(:,:) - sf_icedmp(jp_hicif)%fnow(:,:,1) )  )  
    7275!CDIR COLLAPSE 
    73          hicif(:,:) = MAX( 0._wp, MIN( 1._wp,         &        ! 0<= frld<=1    values which blow the run up 
     76         frld (:,:) = MAX( 0._wp, MIN( 1._wp,         &        ! 0<= frld<=1    values which blow the run up 
    7477            &         frld (:,:) - rdt_ice * resto_ice(:,:,1) * ( frld (:,:) - sf_icedmp(jp_frld )%fnow(:,:,1) )  )  ) 
    7578         ! 
     
    8386      !!                   ***  ROUTINE lim_dmp_init  *** 
    8487      !! 
    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. 
     88      !! ** Purpose :   set the coefficient for the ice thickness and lead fraction restoring 
    8989      !! 
    90       !! ** Method  :  ????? 
     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 
    9193      !!       
    9294      !! ** Action  :   define resto_ice(:,:,1) 
Note: See TracChangeset for help on using the changeset viewer.