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 2046 for branches – NEMO

Changeset 2046 for branches


Ignore:
Timestamp:
2010-08-13T09:42:03+02:00 (14 years ago)
Author:
cbricaud
Message:

commit modifications to add EVP rheology in LIM3

Location:
branches/dev_1784_EVP/NEMO
Files:
11 edited

Legend:

Unmodified
Added
Removed
  • branches/dev_1784_EVP/NEMO/LIM_SRC_2/dom_ice_2.F90

    r1228 r2046  
    55   !!====================================================================== 
    66   !! History :   2.0  !  03-08  (C. Ethe)  Free form and module 
     7   !!             3.3  !  09-05 (G.Garric) addition of the lim2_evp cas 
    78   !!---------------------------------------------------------------------- 
    89#if defined key_lim2 
     
    2627      &                                              area   ,         &  !: surface of grid cell  
    2728      &                                              tms    , tmu        !: temperature and velocity points masks 
    28    REAL(wp), PUBLIC, DIMENSION(jpi,jpj,2,2)     ::   wght   ,         &  !: weight of the 4 neighbours to compute averages 
     29   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,2,2)     ::   wght                !: weight of the 4 neighbours to compute averages 
     30 
     31#if defined key_lim2_vp 
     32   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,2,2)     ::                     & 
    2933      &                                              akappa , bkappa     !: first and third group of metric coefficients 
    30    REAL(wp), PUBLIC, DIMENSION(jpi,jpj,2,2,2,2) ::   alambd   !: second group of metric coefficients 
    31  
     34   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,2,2,2,2) ::   alambd              !: second group of metric coefficients 
     35#else 
     36   REAL(wp), PUBLIC, DIMENSION(jpi,jpj)         ::   tmv    , tmf        !: y-velocity and F-points masks 
     37   REAL(wp), PUBLIC, DIMENSION(jpi,jpj)         ::   tmi                 !: ice mask: =1 if ice thick > 0 
     38#endif 
    3239   !!====================================================================== 
    3340#endif 
  • branches/dev_1784_EVP/NEMO/LIM_SRC_2/ice_2.F90

    r1756 r2046  
    55   !!===================================================================== 
    66   !! History :  2.0  !  03-08  (C. Ethe)  F90: Free form and module 
     7   !!            3.3  !  09-05 (G.Garric) addition of the lim2_evp cas 
    78   !!---------------------------------------------------------------------- 
    89#if defined key_lim2 
     
    2526   LOGICAL               , PUBLIC ::   ln_limdyn     = .TRUE.             !: flag for ice dynamics (T) or not (F) 
    2627   LOGICAL               , PUBLIC ::   ln_limdmp     = .FALSE.            !: Ice damping 
     28   LOGICAL               , PUBLIC ::   ln_nicep      = .TRUE.             !: flag for sea-ice points output (T) or not (F) 
    2729   REAL(wp)              , PUBLIC ::   hsndif        = 0.e0               !: computation of temp. in snow (0) or not (9999) 
    2830   REAL(wp)              , PUBLIC ::   hicdif        = 0.e0               !: computation of temp. in ice (0) or not (9999) 
     
    4648   REAL(wp), PUBLIC ::   ecc    = 2.e0      !: eccentricity of the elliptical yield curve 
    4749   REAL(wp), PUBLIC ::   ahi0   = 350.e0    !: sea-ice hor. eddy diffusivity coeff. (m2/s) 
    48  
     50   INTEGER , PUBLIC ::   nevp   =   360     !: number of EVP subcycling iterations 
     51   INTEGER , PUBLIC ::   telast =  3600     !: timescale for EVP elastic waves 
     52   REAL(wp), PUBLIC ::   alphaevp = 1.e0    !: coefficient for the solution of EVP int. stresses 
    4953   REAL(wp), PUBLIC ::   usecc2             !:  = 1.0 / ( ecc * ecc ) 
    5054   REAL(wp), PUBLIC ::   rhoco              !: = rau0 * cw 
     
    5256   REAL(wp), PUBLIC ::   pstarh             !: pstar / 2.0 
    5357 
    54    REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   ahiu , ahiv   !: hor. diffusivity coeff. at ocean U- and V-points (m2/s) 
    55    REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   pahu , pahv   !: ice hor. eddy diffusivity coef. at ocean U- and V-points 
    56    REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   hsnm , hicm   !: mean snow and ice thicknesses 
    57    REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   ust2s                 !: friction velocity 
     58   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   ahiu , ahiv         !: hor. diffusivity coeff. at ocean U- and V-points (m2/s) 
     59   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   pahu , pahv         !: ice hor. eddy diffusivity coef. at ocean U- and V-points 
     60   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   ust2s               !: friction velocity 
     61 
     62#if  defined key_lim2_vp 
     63   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   hsnm , hicm         !: mean snow and ice thicknesses 
     64   CHARACTER(len=1), PUBLIC :: cl_grid =   'B'                   !: type of grid used in ice dynamics, 'C' or 'B' 
     65#else 
     66   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::                      & 
     67                                                   stress1_i ,  &!: first stress tensor element        
     68                                                   stress2_i ,  &!: second stress tensor element 
     69                                                   stress12_i,  &!: diagonal stress tensor element 
     70                                                   delta_i   ,  &!: Delta factor for the ice rheology (see Flato and Hibler 95) [s-1] -> limrhg.F90 
     71                                                   divu_i    ,  &!: Divergence of the velocity field [s-1] -> limrhg.F90 
     72                                                   shear_i       !: Shear of the velocity field [s-1] -> limrhg.F90 
     73 
     74   REAL(wp), PUBLIC, DIMENSION(jpi,jpj)         :: at_i          !: 
     75   REAL(wp), PUBLIC, DIMENSION(:,:)    ,POINTER :: vt_s ,vt_i    !: mean snow and ice thicknesses 
     76   REAL(wp), PUBLIC, DIMENSION(jpi,jpj),TARGET  :: hsnm , hicm   !: mean snow and ice thicknesses, target for pointers vt_s and vt_i  
     77   CHARACTER(len=1), PUBLIC :: cl_grid =   'C'                   !: type of grid used in ice dynamics, 'C' or 'B' 
     78#endif 
    5879 
    5980   !!* diagnostic quantities 
     81   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   rdvosif       !: Variation of volume at surface (only used for outputs) 
     82   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   rdvobif       !: Variation of ice volume at the bottom ice (only used for outputs) 
     83   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   fdvolif       !: Total variation of ice volume (only used for outputs) 
     84   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   rdvonif       !: Lateral Variation of ice volume (only used for outputs) 
    6085   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   sist          !: Sea-Ice Surface Temperature (Kelvin) 
    6186   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   tfu           !: Freezing/Melting point temperature of sea water at SSS 
  • branches/dev_1784_EVP/NEMO/LIM_SRC_2/iceini_2.F90

    r1581 r2046  
    66   !! History :   1.0  !  02-08  (G. Madec)  F90: Free form and modules 
    77   !!             2.0  !  03-08  (C. Ethe)  add ice_run 
     8   !!             3.3  !  09-05  (G.Garric) addition of the lim2_evp case 
    89   !!---------------------------------------------------------------------- 
    910#if defined key_lim2 
     
    3031 
    3132   PUBLIC   ice_init_2               ! called by sbcice_lim_2.F90 
     33 
     34   INTEGER , PUBLIC  ::     numit                  !: iteration number 
     35 
    3236 
    3337   !!---------------------------------------------------------------------- 
     
    6266      ENDIF 
    6367       
    64       tn_ice(:,:,1) = sist(:,:)         ! initialisation of ice temperature    
     68      tn_ice(:,:,1) = sist(:,:)       ! initialisation of ice temperature    
    6569      fr_i  (:,:) = 1.0 - frld(:,:)   ! initialisation of sea-ice fraction     
     70      ! 
     71      numit = nit000 - 1              !initialisation ice time-step 
     72 
    6673      ! 
    6774   END SUBROUTINE ice_init_2 
  • branches/dev_1784_EVP/NEMO/LIM_SRC_2/limdyn_2.F90

    r1694 r2046  
    88   !!             2.0  !  03-08  (C. Ethe) add lim_dyn_init 
    99   !!             2.0  !  06-07  (G. Madec)  Surface module 
     10   !!             3.3  !  09-05  (G.Garric) addition of the lim2_evp cas 
    1011   !!--------------------------------------------------------------------- 
    1112#if defined key_lim2 
     
    2223   USE dom_ice_2      ! 
    2324   USE limistate_2    ! 
     25#if defined key_lim2_vp 
    2426   USE limrhg_2       ! ice rheology 
    25  
     27#else 
     28   USE limrhg         ! ice rheology 
     29#endif 
    2630   USE lbclnk         ! 
    2731   USE lib_mpp        ! 
     
    8791            i_jpj = jpj 
    8892            IF(ln_ctl)   CALL prt_ctl_info( 'lim_dyn  :    i_j1 = ', ivar1=i_j1, clinfo2=' ij_jpj = ', ivar2=i_jpj ) 
     93#if defined key_lim2_vp 
    8994            CALL lim_rhg_2( i_j1, i_jpj ) 
     95#else 
     96            CALL lim_rhg( i_j1, i_jpj ) !!!!cbr CALL lim_rhg( i_j1, i_jpj, kt ) 
     97#endif 
    9098            ! 
    9199         ELSE                                 ! optimization of the computational area 
     
    105113                  i_j1 = i_j1 + 1 
    106114               END DO 
     115#if defined key_lim2_vp 
    107116               i_j1 = MAX( 1, i_j1-1 ) 
    108117               IF(ln_ctl)   WRITE(numout,*) 'lim_dyn : NH i_j1 = ', i_j1, ' ij_jpj = ', i_jpj 
    109118               !  
    110119               CALL lim_rhg_2( i_j1, i_jpj ) 
     120#else 
     121               i_j1 = MAX( 1, i_j1-2 ) 
     122               IF(ln_ctl)   WRITE(numout,*) 'lim_dyn : NH i_j1 = ', i_j1, ' ij_jpj = ', i_jpj 
     123               CALL lim_rhg( i_j1, i_jpj ) 
     124#endif 
    111125               !  
    112126               ! Southern hemisphere 
     
    116130                  i_jpj = i_jpj - 1 
    117131               END DO 
     132#if defined key_lim2_vp 
    118133               i_jpj = MIN( jpj, i_jpj+2 ) 
    119134               IF(ln_ctl)   WRITE(numout,*) 'lim_dyn : SH i_j1 = ', i_j1, ' ij_jpj = ', i_jpj 
    120135               !  
    121136               CALL lim_rhg_2( i_j1, i_jpj ) 
     137#else 
     138               i_jpj = MIN( jpj, i_jpj+1 ) 
     139               IF(ln_ctl)   WRITE(numout,*) 'lim_dyn : SH i_j1 = ', i_j1, ' ij_jpj = ', i_jpj 
     140               CALL lim_rhg( i_j1, i_jpj ) !!!!cbr CALL lim_rhg( i_j1, i_jpj, kt ) 
     141#endif 
    122142               !  
    123143            ELSE                                 ! local domain extends over one hemisphere only 
     
    134154                  i_jpj = i_jpj - 1 
    135155               END DO 
     156#if defined key_lim2_vp 
    136157               i_jpj = MIN( jpj, i_jpj+2) 
    137      
     158 
    138159               IF(ln_ctl)   WRITE(numout,*) 'lim_dyn : one hemisphere: i_j1 = ', i_j1, ' ij_jpj = ', i_jpj 
    139160               !  
    140161               CALL lim_rhg_2( i_j1, i_jpj ) 
     162#else 
     163               i_j1 = MAX( 1, i_j1-2 ) 
     164               i_jpj = MIN( jpj, i_jpj+1) 
     165               IF(ln_ctl)   WRITE(numout,*) 'lim_dyn : one hemisphere: i_j1 = ', i_j1, ' ij_jpj = ', i_jpj 
     166               CALL lim_rhg( i_j1, i_jpj ) !!!!cbr CALL lim_rhg( i_j1, i_jpj, kt ) 
     167#endif 
    141168               ! 
    142169            ENDIF 
     
    148175         ! computation of friction velocity 
    149176         ! -------------------------------- 
     177 
     178     SELECT CASE( cl_grid ) 
     179 
     180      CASE( 'C' )                          ! C-grid ice dynamics 
     181         !????????????????????????????????? 
     182         ! ice-ocean velocity at U & V-points (u_ice vi_ice at U- & V-points ; ssu_m, ssv_m at U- & V-points) 
     183         zu_io(:,:) = u_ice(:,:) - ssu_m(:,:) 
     184         zv_io(:,:) = v_ice(:,:) - ssv_m(:,:) 
     185 
     186 
     187      CASE( 'B' )                          ! B-grid ice dynamics 
    150188         ! ice-ocean velocity at U & V-points (u_ice v_ice at I-point ; ssu_m, ssv_m at U- & V-points) 
    151189          
     
    156194            END DO 
    157195         END DO 
     196 
     197      END SELECT 
     198 
    158199         ! frictional velocity at T-point 
    159200         DO jj = 2, jpjm1 
     
    198239      NAMELIST/namicedyn/ epsd, alpha,     & 
    199240         &                dm, nbiter, nbitdr, om, resl, cw, angvg, pstar,   & 
    200          &                c_rhg, etamn, creepl, ecc, ahi0 
     241         &                c_rhg, etamn, creepl, ecc, ahi0, & 
     242         &                nevp, telast, alphaevp 
    201243      !!------------------------------------------------------------------- 
    202244 
     
    223265         WRITE(numout,*) '       eccentricity of the elliptical yield curve       ecc    = ', ecc 
    224266         WRITE(numout,*) '       horizontal diffusivity coeff. for sea-ice        ahi0   = ', ahi0 
     267         WRITE(numout,*) '       number of iterations for subcycling              nevp   = ', nevp 
     268         WRITE(numout,*) '       timescale for elastic waves                      telast = ', telast 
     269         WRITE(numout,*) '       coefficient for the solution of int. stresses  alphaevp = ', alphaevp 
    225270      ENDIF 
    226271 
  • branches/dev_1784_EVP/NEMO/LIM_SRC_2/limmsh_2.F90

    r1694 r2046  
    4747      !!         original    : 01-04 (LIM) 
    4848      !!         addition    : 02-08 (C. Ethe, G. Madec) 
     49      !!         additions   : 2009-05 (addition of the lim2_evp case, G. Garric) 
    4950      !!---------------------------------------------------------------------  
    5051      !! * Local variables 
    5152      INTEGER :: ji, jj      ! dummy loop indices 
    5253 
     54      REAL(wp) ::         & 
     55         zusden              ! temporary scalars 
     56#if defined key_lim2_vp 
    5357      REAL(wp), DIMENSION(jpi,jpj) ::  & 
    5458         zd2d1 , zd1d2       ! Derivative of zh2 (resp. zh1) in the x direction 
     
    5761         zh1p  , zh2p   , &  ! Idem zh1, zh2 for the bottom left corner of the grid 
    5862         zd2d1p, zd1d2p , &  ! Idem zd2d1, zd1d2 for the bottom left corner of the grid 
    59          zusden, zusden2     ! temporary scalars 
     63         zusden2             ! temporary scalars 
     64#endif 
    6065      !!--------------------------------------------------------------------- 
    6166 
     
    112117      !------------------- 
    113118!!ibug ??? 
    114       akappa(:,:,:,:) = 0.e0 
    115119      wght(:,:,:,:) = 0.e0 
     120      tmu(:,:)      = 0.e0 
     121#if defined key_lim2_vp  
     122      akappa(:,:,:,:)     = 0.e0 
    116123      alambd(:,:,:,:,:,:) = 0.e0 
    117       tmu(:,:) = 0.e0 
     124#else 
     125      tmv(:,:) = 0.e0 
     126      tmf(:,:) = 0.e0 
     127#endif 
    118128!!i 
    119129       
    120        
     130#if defined key_lim2_vp 
    121131      ! metric coefficients for sea ice dynamic 
    122132      !---------------------------------------- 
     
    152162      CALL lbc_lnk( wght(:,:,2,1), 'I', 1. )      ! but it is never used 
    153163      CALL lbc_lnk( wght(:,:,2,2), 'I', 1. ) 
     164#else 
     165      !                                                      ! weights (wght) 
     166      DO jj = 2, jpj-1 
     167         DO ji = 2, jpi-1 
     168            zusden = 1. / (  ( e1t(ji+1,jj) + e1t(ji,jj  ) )   & 
     169               &           * ( e2t(ji,jj+1) + e2t(ji  ,jj) ) )  
     170            wght(ji,jj,1,1) = zusden * e1t(ji+1,jj) * e2t(ji,jj+1) 
     171            wght(ji,jj,1,2) = zusden * e1t(ji+1,jj) * e2t(ji,jj  ) 
     172            wght(ji,jj,2,1) = zusden * e1t(ji  ,jj) * e2t(ji,jj+1) 
     173            wght(ji,jj,2,2) = zusden * e1t(ji  ,jj) * e2t(ji,jj  ) 
     174         END DO 
     175      END DO 
     176 
     177      !With EVP, the weights are calculated on 'F' points 
     178      CALL lbc_lnk( wght(:,:,1,1), 'F', 1. )      ! CAUTION: even with the lbc_lnk at ice U-V-point 
     179      CALL lbc_lnk( wght(:,:,1,2), 'F', 1. )      ! the value of wght at jpj is wrong 
     180      CALL lbc_lnk( wght(:,:,2,1), 'F', 1. )      ! but it is never used 
     181      CALL lbc_lnk( wght(:,:,2,2), 'F', 1. ) 
     182 
     183#endif 
    154184     
    155185      ! Coefficients for divergence of the stress tensor 
    156186      !------------------------------------------------- 
    157187 
     188#if defined key_lim2_vp 
    158189      DO jj = 2, jpj 
    159190         DO ji = 2, jpi   ! NO vector opt. 
     
    223254      CALL lbc_lnk( alambd(:,:,2,1,1,1), 'I', 1. )      ! 
    224255      CALL lbc_lnk( alambd(:,:,2,1,1,2), 'I', 1. )      ! 
     256#endif 
    225257             
    226258 
     
    233265      tmu(:,1) = 0.e0 
    234266      tmu(1,:) = 0.e0 
     267 
     268#if defined key_lim2_vp 
    235269      DO jj = 2, jpj               ! ice U.V-point: computed from ice T-point mask 
    236270         DO ji = 2, jpim1   ! NO vector opt. 
     
    241275      !--lateral boundary conditions     
    242276      CALL lbc_lnk( tmu(:,:), 'I', 1. ) 
     277#else 
     278      tmv(:,1) = 0.e0 !SB 
     279      tmv(1,:) = 0.e0 !SB 
     280      tmf(1,:) = 0.e0 
     281      tmf(:,1) = 0.e0 
     282      DO jj = 1, jpj - 1 
     283         DO ji = 1 , jpi - 1 
     284            tmu(ji,jj) =  tms(ji,jj) * tms(ji+1,jj) 
     285            tmv(ji,jj) =  tms(ji,jj) * tms(ji,jj+1) 
     286            tmf(ji,jj) =  tms(ji,jj) * tms(ji+1,jj) * tms(ji,jj+1) * & 
     287               tms(ji+1,jj+1) 
     288         END DO 
     289      END DO 
     290 
     291      !--lateral boundary conditions 
     292      CALL lbc_lnk( tmu(:,:), 'U', 1. ) 
     293      CALL lbc_lnk( tmv(:,:), 'V', 1. ) 
     294      CALL lbc_lnk( tmf(:,:), 'F', 1. ) 
     295#endif 
    243296       
    244297      ! unmasked and masked area of T-grid cell 
  • branches/dev_1784_EVP/NEMO/LIM_SRC_2/limrhg_2.F90

    r1774 r2046  
    99   !!            " "  !  06-08  (G. Madec)  surface module, ice-stress at I-point 
    1010   !!            " "  !  09-09  (G. Madec)  Huge verctor optimisation 
    11    !!---------------------------------------------------------------------- 
    12 #if defined key_lim2 
     11   !!            3.3  !  09-05  (G.Garric) addition of the lim2_evp case 
     12   !!---------------------------------------------------------------------- 
     13#if defined key_lim2 &&  defined key_lim2_vp 
    1314   !!---------------------------------------------------------------------- 
    1415   !!   'key_lim2'                                    LIM 2.0 sea-ice model 
  • branches/dev_1784_EVP/NEMO/LIM_SRC_2/limrst_2.F90

    r1715 r2046  
    66   !! History :  2.0  !  01-04  (C. Ethe, G. Madec)  Original code 
    77   !!                 !  06-07  (S. Masson)  use IOM for restart read/write 
     8   !!            3.3  !  09-05  (G.Garric) addition of the lim2_evp case 
    89   !!---------------------------------------------------------------------- 
    910#if defined key_lim2 
     
    108109      CALL iom_rstput( iter, nitrst, numriw, 'kt_ice', REAL( iter, wp) )  
    109110       
    110       CALL iom_rstput( iter, nitrst, numriw, 'hicif' , hicif (:,:)   )      ! prognostic variables  
    111       CALL iom_rstput( iter, nitrst, numriw, 'hsnif' , hsnif (:,:)   ) 
    112       CALL iom_rstput( iter, nitrst, numriw, 'frld'  , frld  (:,:)   ) 
    113       CALL iom_rstput( iter, nitrst, numriw, 'sist'  , sist  (:,:)   ) 
    114       CALL iom_rstput( iter, nitrst, numriw, 'tbif1' , tbif  (:,:,1) ) 
    115       CALL iom_rstput( iter, nitrst, numriw, 'tbif2' , tbif  (:,:,2) ) 
    116       CALL iom_rstput( iter, nitrst, numriw, 'tbif3' , tbif  (:,:,3) ) 
    117       CALL iom_rstput( iter, nitrst, numriw, 'u_ice' , u_ice (:,:)   ) 
    118       CALL iom_rstput( iter, nitrst, numriw, 'v_ice' , v_ice (:,:)   ) 
    119       CALL iom_rstput( iter, nitrst, numriw, 'qstoif', qstoif(:,:)   ) 
    120       CALL iom_rstput( iter, nitrst, numriw, 'fsbbq' , fsbbq (:,:)   ) 
    121       CALL iom_rstput( iter, nitrst, numriw, 'sxice' , sxice (:,:)   ) 
    122       CALL iom_rstput( iter, nitrst, numriw, 'syice' , syice (:,:)   ) 
    123       CALL iom_rstput( iter, nitrst, numriw, 'sxxice', sxxice(:,:)   ) 
    124       CALL iom_rstput( iter, nitrst, numriw, 'syyice', syyice(:,:)   ) 
    125       CALL iom_rstput( iter, nitrst, numriw, 'sxyice', sxyice(:,:)   ) 
    126       CALL iom_rstput( iter, nitrst, numriw, 'sxsn'  , sxsn  (:,:)   ) 
    127       CALL iom_rstput( iter, nitrst, numriw, 'sysn'  , sysn  (:,:)   ) 
    128       CALL iom_rstput( iter, nitrst, numriw, 'sxxsn' , sxxsn (:,:)   ) 
    129       CALL iom_rstput( iter, nitrst, numriw, 'syysn' , syysn (:,:)   ) 
    130       CALL iom_rstput( iter, nitrst, numriw, 'sxysn' , sxysn (:,:)   ) 
    131       CALL iom_rstput( iter, nitrst, numriw, 'sxa'   , sxa   (:,:)   ) 
    132       CALL iom_rstput( iter, nitrst, numriw, 'sya'   , sya   (:,:)   ) 
    133       CALL iom_rstput( iter, nitrst, numriw, 'sxxa'  , sxxa  (:,:)   ) 
    134       CALL iom_rstput( iter, nitrst, numriw, 'syya'  , syya  (:,:)   ) 
    135       CALL iom_rstput( iter, nitrst, numriw, 'sxya'  , sxya  (:,:)   ) 
    136       CALL iom_rstput( iter, nitrst, numriw, 'sxc0'  , sxc0  (:,:)   ) 
    137       CALL iom_rstput( iter, nitrst, numriw, 'syc0'  , syc0  (:,:)   ) 
    138       CALL iom_rstput( iter, nitrst, numriw, 'sxxc0' , sxxc0 (:,:)   ) 
    139       CALL iom_rstput( iter, nitrst, numriw, 'syyc0' , syyc0 (:,:)   ) 
    140       CALL iom_rstput( iter, nitrst, numriw, 'sxyc0' , sxyc0 (:,:)   ) 
    141       CALL iom_rstput( iter, nitrst, numriw, 'sxc1'  , sxc1  (:,:)   ) 
    142       CALL iom_rstput( iter, nitrst, numriw, 'syc1'  , syc1  (:,:)   ) 
    143       CALL iom_rstput( iter, nitrst, numriw, 'sxxc1' , sxxc1 (:,:)   ) 
    144       CALL iom_rstput( iter, nitrst, numriw, 'syyc1' , syyc1 (:,:)   ) 
    145       CALL iom_rstput( iter, nitrst, numriw, 'sxyc1' , sxyc1 (:,:)   ) 
    146       CALL iom_rstput( iter, nitrst, numriw, 'sxc2'  , sxc2  (:,:)   ) 
    147       CALL iom_rstput( iter, nitrst, numriw, 'syc2'  , syc2  (:,:)   ) 
    148       CALL iom_rstput( iter, nitrst, numriw, 'sxxc2' , sxxc2 (:,:)   ) 
    149       CALL iom_rstput( iter, nitrst, numriw, 'syyc2' , syyc2 (:,:)   ) 
    150       CALL iom_rstput( iter, nitrst, numriw, 'sxyc2' , sxyc2 (:,:)   ) 
    151       CALL iom_rstput( iter, nitrst, numriw, 'sxst'  , sxst  (:,:)   ) 
    152       CALL iom_rstput( iter, nitrst, numriw, 'syst'  , syst  (:,:)   ) 
    153       CALL iom_rstput( iter, nitrst, numriw, 'sxxst' , sxxst (:,:)   ) 
    154       CALL iom_rstput( iter, nitrst, numriw, 'syyst' , syyst (:,:)   ) 
    155       CALL iom_rstput( iter, nitrst, numriw, 'sxyst' , sxyst (:,:)   ) 
     111      CALL iom_rstput( iter, nitrst, numriw, 'hicif'      , hicif     (:,:)   )      ! prognostic variables  
     112      CALL iom_rstput( iter, nitrst, numriw, 'hsnif'      , hsnif     (:,:)   ) 
     113      CALL iom_rstput( iter, nitrst, numriw, 'frld'       , frld      (:,:)   ) 
     114      CALL iom_rstput( iter, nitrst, numriw, 'sist'       , sist      (:,:)   ) 
     115      CALL iom_rstput( iter, nitrst, numriw, 'tbif1'      , tbif      (:,:,1) ) 
     116      CALL iom_rstput( iter, nitrst, numriw, 'tbif2'      , tbif      (:,:,2) ) 
     117      CALL iom_rstput( iter, nitrst, numriw, 'tbif3'      , tbif      (:,:,3) ) 
     118      CALL iom_rstput( iter, nitrst, numriw, 'u_ice'      , u_ice     (:,:)   ) 
     119      CALL iom_rstput( iter, nitrst, numriw, 'v_ice'      , v_ice     (:,:)   ) 
     120      CALL iom_rstput( iter, nitrst, numriw, 'qstoif'     , qstoif    (:,:)   ) 
     121      CALL iom_rstput( iter, nitrst, numriw, 'fsbbq'      , fsbbq     (:,:)   ) 
     122#if ! defined key_lim2_vp 
     123      CALL iom_rstput( iter, nitrst, numriw, 'stress1_i'  , stress1_i (:,:)   ) 
     124      CALL iom_rstput( iter, nitrst, numriw, 'stress2_i'  , stress2_i (:,:)   ) 
     125      CALL iom_rstput( iter, nitrst, numriw, 'stress12_i' , stress12_i(:,:)   ) 
     126#endif 
     127      CALL iom_rstput( iter, nitrst, numriw, 'sxice' ,      sxice     (:,:)   ) 
     128      CALL iom_rstput( iter, nitrst, numriw, 'syice' ,      syice     (:,:)   ) 
     129      CALL iom_rstput( iter, nitrst, numriw, 'sxxice',      sxxice    (:,:)   ) 
     130      CALL iom_rstput( iter, nitrst, numriw, 'syyice',      syyice    (:,:)   ) 
     131      CALL iom_rstput( iter, nitrst, numriw, 'sxyice',      sxyice    (:,:)   ) 
     132      CALL iom_rstput( iter, nitrst, numriw, 'sxsn'  ,      sxsn      (:,:)   ) 
     133      CALL iom_rstput( iter, nitrst, numriw, 'sysn'  ,      sysn      (:,:)   ) 
     134      CALL iom_rstput( iter, nitrst, numriw, 'sxxsn' ,      sxxsn     (:,:)   ) 
     135      CALL iom_rstput( iter, nitrst, numriw, 'syysn' ,      syysn     (:,:)   ) 
     136      CALL iom_rstput( iter, nitrst, numriw, 'sxysn' ,      sxysn     (:,:)   ) 
     137      CALL iom_rstput( iter, nitrst, numriw, 'sxa'   ,      sxa       (:,:)   ) 
     138      CALL iom_rstput( iter, nitrst, numriw, 'sya'   ,      sya       (:,:)   ) 
     139      CALL iom_rstput( iter, nitrst, numriw, 'sxxa'  ,      sxxa      (:,:)   ) 
     140      CALL iom_rstput( iter, nitrst, numriw, 'syya'  ,      syya      (:,:)   ) 
     141      CALL iom_rstput( iter, nitrst, numriw, 'sxya'  ,      sxya      (:,:)   ) 
     142      CALL iom_rstput( iter, nitrst, numriw, 'sxc0'  ,      sxc0      (:,:)   ) 
     143      CALL iom_rstput( iter, nitrst, numriw, 'syc0'  ,      syc0      (:,:)   ) 
     144      CALL iom_rstput( iter, nitrst, numriw, 'sxxc0' ,      sxxc0     (:,:)   ) 
     145      CALL iom_rstput( iter, nitrst, numriw, 'syyc0' ,      syyc0     (:,:)   ) 
     146      CALL iom_rstput( iter, nitrst, numriw, 'sxyc0' ,      sxyc0     (:,:)   ) 
     147      CALL iom_rstput( iter, nitrst, numriw, 'sxc1'  ,      sxc1      (:,:)   ) 
     148      CALL iom_rstput( iter, nitrst, numriw, 'syc1'  ,      syc1      (:,:)   ) 
     149      CALL iom_rstput( iter, nitrst, numriw, 'sxxc1' ,      sxxc1     (:,:)   ) 
     150      CALL iom_rstput( iter, nitrst, numriw, 'syyc1' ,      syyc1     (:,:)   ) 
     151      CALL iom_rstput( iter, nitrst, numriw, 'sxyc1' ,      sxyc1     (:,:)   ) 
     152      CALL iom_rstput( iter, nitrst, numriw, 'sxc2'  ,      sxc2      (:,:)   ) 
     153      CALL iom_rstput( iter, nitrst, numriw, 'syc2'  ,      syc2      (:,:)   ) 
     154      CALL iom_rstput( iter, nitrst, numriw, 'sxxc2' ,      sxxc2     (:,:)   ) 
     155      CALL iom_rstput( iter, nitrst, numriw, 'syyc2' ,      syyc2     (:,:)   ) 
     156      CALL iom_rstput( iter, nitrst, numriw, 'sxyc2' ,      sxyc2     (:,:)   ) 
     157      CALL iom_rstput( iter, nitrst, numriw, 'sxst'  ,      sxst      (:,:)   ) 
     158      CALL iom_rstput( iter, nitrst, numriw, 'syst'  ,      syst      (:,:)   ) 
     159      CALL iom_rstput( iter, nitrst, numriw, 'sxxst' ,      sxxst     (:,:)   ) 
     160      CALL iom_rstput( iter, nitrst, numriw, 'syyst' ,      syyst     (:,:)   ) 
     161      CALL iom_rstput( iter, nitrst, numriw, 'sxyst' ,      sxyst     (:,:)   ) 
    156162       
    157163      IF( iter == nitrst ) THEN 
     
    218224      ENDIF 
    219225 
    220       CALL iom_get( numrir, jpdom_autoglo, 'qstoif', qstoif )     
    221       CALL iom_get( numrir, jpdom_autoglo, 'fsbbq' , fsbbq  )     
    222       CALL iom_get( numrir, jpdom_autoglo, 'sxice' , sxice  ) 
    223       CALL iom_get( numrir, jpdom_autoglo, 'syice' , syice  ) 
    224       CALL iom_get( numrir, jpdom_autoglo, 'sxxice', sxxice ) 
    225       CALL iom_get( numrir, jpdom_autoglo, 'syyice', syyice ) 
    226       CALL iom_get( numrir, jpdom_autoglo, 'sxyice', sxyice ) 
    227       CALL iom_get( numrir, jpdom_autoglo, 'sxsn'  , sxsn   ) 
    228       CALL iom_get( numrir, jpdom_autoglo, 'sysn'  , sysn   ) 
    229       CALL iom_get( numrir, jpdom_autoglo, 'sxxsn' , sxxsn  ) 
    230       CALL iom_get( numrir, jpdom_autoglo, 'syysn' , syysn  ) 
    231       CALL iom_get( numrir, jpdom_autoglo, 'sxysn' , sxysn  ) 
    232       CALL iom_get( numrir, jpdom_autoglo, 'sxa'   , sxa    ) 
    233       CALL iom_get( numrir, jpdom_autoglo, 'sya'   , sya    ) 
    234       CALL iom_get( numrir, jpdom_autoglo, 'sxxa'  , sxxa   ) 
    235       CALL iom_get( numrir, jpdom_autoglo, 'syya'  , syya   ) 
    236       CALL iom_get( numrir, jpdom_autoglo, 'sxya'  , sxya   ) 
    237       CALL iom_get( numrir, jpdom_autoglo, 'sxc0'  , sxc0   ) 
    238       CALL iom_get( numrir, jpdom_autoglo, 'syc0'  , syc0   ) 
    239       CALL iom_get( numrir, jpdom_autoglo, 'sxxc0' , sxxc0  ) 
    240       CALL iom_get( numrir, jpdom_autoglo, 'syyc0' , syyc0  ) 
    241       CALL iom_get( numrir, jpdom_autoglo, 'sxyc0' , sxyc0  ) 
    242       CALL iom_get( numrir, jpdom_autoglo, 'sxc1'  , sxc1   ) 
    243       CALL iom_get( numrir, jpdom_autoglo, 'syc1'  , syc1   ) 
    244       CALL iom_get( numrir, jpdom_autoglo, 'sxxc1' , sxxc1  ) 
    245       CALL iom_get( numrir, jpdom_autoglo, 'syyc1' , syyc1  ) 
    246       CALL iom_get( numrir, jpdom_autoglo, 'sxyc1' , sxyc1  ) 
    247       CALL iom_get( numrir, jpdom_autoglo, 'sxc2'  , sxc2   ) 
    248       CALL iom_get( numrir, jpdom_autoglo, 'syc2'  , syc2   ) 
    249       CALL iom_get( numrir, jpdom_autoglo, 'sxxc2' , sxxc2  ) 
    250       CALL iom_get( numrir, jpdom_autoglo, 'syyc2' , syyc2  ) 
    251       CALL iom_get( numrir, jpdom_autoglo, 'sxyc2' , sxyc2  ) 
    252       CALL iom_get( numrir, jpdom_autoglo, 'sxst'  , sxst   ) 
    253       CALL iom_get( numrir, jpdom_autoglo, 'syst'  , syst   ) 
    254       CALL iom_get( numrir, jpdom_autoglo, 'sxxst' , sxxst  ) 
    255       CALL iom_get( numrir, jpdom_autoglo, 'syyst' , syyst  ) 
    256       CALL iom_get( numrir, jpdom_autoglo, 'sxyst' , sxyst  ) 
     226      CALL iom_get( numrir, jpdom_autoglo, 'qstoif'     , qstoif     )     
     227      CALL iom_get( numrir, jpdom_autoglo, 'fsbbq'      , fsbbq      )     
     228#if ! defined key_lim2_vp 
     229      CALL iom_get( numrir, jpdom_autoglo, 'stress1_i'  , stress1_i  ) 
     230      CALL iom_get( numrir, jpdom_autoglo, 'stress2_i'  , stress2_i  ) 
     231      CALL iom_get( numrir, jpdom_autoglo, 'stress12_i' , stress12_i ) 
     232#endif 
     233      CALL iom_get( numrir, jpdom_autoglo, 'sxice'      , sxice      ) 
     234      CALL iom_get( numrir, jpdom_autoglo, 'syice'      , syice      ) 
     235      CALL iom_get( numrir, jpdom_autoglo, 'sxxice'     , sxxice     ) 
     236      CALL iom_get( numrir, jpdom_autoglo, 'syyice'     , syyice     ) 
     237      CALL iom_get( numrir, jpdom_autoglo, 'sxyice'     , sxyice     ) 
     238      CALL iom_get( numrir, jpdom_autoglo, 'sxsn'       , sxsn       ) 
     239      CALL iom_get( numrir, jpdom_autoglo, 'sysn'       , sysn       ) 
     240      CALL iom_get( numrir, jpdom_autoglo, 'sxxsn'      , sxxsn      ) 
     241      CALL iom_get( numrir, jpdom_autoglo, 'syysn'      , syysn      ) 
     242      CALL iom_get( numrir, jpdom_autoglo, 'sxysn'      , sxysn      ) 
     243      CALL iom_get( numrir, jpdom_autoglo, 'sxa'        , sxa        ) 
     244      CALL iom_get( numrir, jpdom_autoglo, 'sya'        , sya        ) 
     245      CALL iom_get( numrir, jpdom_autoglo, 'sxxa'       , sxxa       ) 
     246      CALL iom_get( numrir, jpdom_autoglo, 'syya'       , syya       ) 
     247      CALL iom_get( numrir, jpdom_autoglo, 'sxya'       , sxya       ) 
     248      CALL iom_get( numrir, jpdom_autoglo, 'sxc0'       , sxc0       ) 
     249      CALL iom_get( numrir, jpdom_autoglo, 'syc0'       , syc0       ) 
     250      CALL iom_get( numrir, jpdom_autoglo, 'sxxc0'      , sxxc0      ) 
     251      CALL iom_get( numrir, jpdom_autoglo, 'syyc0'      , syyc0      ) 
     252      CALL iom_get( numrir, jpdom_autoglo, 'sxyc0'      , sxyc0      ) 
     253      CALL iom_get( numrir, jpdom_autoglo, 'sxc1'       , sxc1       ) 
     254      CALL iom_get( numrir, jpdom_autoglo, 'syc1'       , syc1       ) 
     255      CALL iom_get( numrir, jpdom_autoglo, 'sxxc1'      , sxxc1      ) 
     256      CALL iom_get( numrir, jpdom_autoglo, 'syyc1'      , syyc1      ) 
     257      CALL iom_get( numrir, jpdom_autoglo, 'sxyc1'      , sxyc1      ) 
     258      CALL iom_get( numrir, jpdom_autoglo, 'sxc2'       , sxc2       ) 
     259      CALL iom_get( numrir, jpdom_autoglo, 'syc2'       , syc2       ) 
     260      CALL iom_get( numrir, jpdom_autoglo, 'sxxc2'      , sxxc2      ) 
     261      CALL iom_get( numrir, jpdom_autoglo, 'syyc2'      , syyc2      ) 
     262      CALL iom_get( numrir, jpdom_autoglo, 'sxyc2'      , sxyc2      ) 
     263      CALL iom_get( numrir, jpdom_autoglo, 'sxst'       , sxst       ) 
     264      CALL iom_get( numrir, jpdom_autoglo, 'syst'       , syst       ) 
     265      CALL iom_get( numrir, jpdom_autoglo, 'sxxst'      , sxxst      ) 
     266      CALL iom_get( numrir, jpdom_autoglo, 'syyst'      , syyst      ) 
     267      CALL iom_get( numrir, jpdom_autoglo, 'sxyst'      , sxyst      ) 
    257268       
    258269      CALL iom_close( numrir ) 
  • branches/dev_1784_EVP/NEMO/LIM_SRC_2/limsbc_2.F90

    r1756 r2046  
    77   !!           02-07 (C. Ethe, G. Madec) re-writing F90 
    88   !!           06-07 (G. Madec) surface module 
     9   !!           09-05 (G.Garric) addition of the lim2_evp case 
    910   !!---------------------------------------------------------------------- 
    1011#if defined key_lim2 
     
    8889      REAL(wp) ::   zfrldu, zfrldv   ! lead fraction at U- & V-points 
    8990      REAL(wp) ::   zutau , zvtau    ! lead fraction at U- & V-points 
     91!!!      REAL(wp) ::   zutaui , zvtaui  ! lead fraction at U- & V-points 
    9092      REAL(wp) ::   zu_io , zv_io    ! 2 components of the ice-ocean velocity 
    9193! interface 2D --> 3D 
     
    275277            DO ji = 2, jpim1   ! NO vector opt. 
    276278               ! ... components of ice-ocean stress at U and V-points  (from I-point values) 
     279#if defined key_lim2_vp 
    277280               zutau  = 0.5 * ( ztio_u(ji+1,jj) + ztio_u(ji+1,jj+1) ) 
    278281               zvtau  = 0.5 * ( ztio_v(ji,jj+1) + ztio_v(ji+1,jj+1) ) 
     282#else 
     283               zutau  = ztio_u(ji,jj) 
     284               zvtau  = ztio_v(ji,jj) 
     285#endif 
    279286               ! ... open-ocean (lead) fraction at U- & V-points (from T-point values) 
    280287               zfrldu = 0.5 * ( frld(ji,jj) + frld(ji+1,jj  ) ) 
  • branches/dev_1784_EVP/NEMO/LIM_SRC_2/limtrp_2.F90

    r1715 r2046  
    6767      !!        !  01-05 (G. Madec, R. Hordoir) opa norm 
    6868      !!   2.0  !  04-01 (G. Madec, C. Ethe)  F90, mpp 
     69      !!   3.3  !  09-05  (G.Garric) addition of the lim2_evp case 
    6970      !!--------------------------------------------------------------------- 
    7071      INTEGER, INTENT(in) ::   kt     ! number of iteration 
     
    107108         ! zvbord factor between 1 and 2 to take into account slip or no-slip boundary conditions.         
    108109         zvbord = 1.0 + ( 1.0 - bound ) 
     110#if defined key_lim2_vp 
    109111         DO jj = 1, jpjm1 
    110112            DO ji = 1, jpim1   ! NO vector opt. 
     
    116118         CALL lbc_lnk( zui_u, 'U', -1. ) 
    117119         CALL lbc_lnk( zvi_v, 'V', -1. ) 
     120#else 
     121        zui_u(:,:)=u_ice(:,:) 
     122        zvi_v(:,:)=v_ice(:,:) 
     123#endif 
    118124 
    119125         ! CFL test for stability 
  • branches/dev_1784_EVP/NEMO/LIM_SRC_3/limrhg.F90

    r1469 r2046  
    77   !!            3.0  !  2008-03  (M. Vancoppenolle) LIM3 
    88   !!             -   !  2008-11  (M. Vancoppenolle, S. Bouillon, Y. Aksenov) add surface tilt in ice rheolohy  
     9   !!             -   !  2009-05  (G.Garric) addition of the lim2_evp cas 
    910   !!---------------------------------------------------------------------- 
    10 #if defined key_lim3 
     11#if defined key_lim3 || (  defined key_lim2 && ! defined key_lim2_vp ) 
    1112   !!---------------------------------------------------------------------- 
    1213   !!   'key_lim3'                                      LIM3 sea-ice model 
     
    1819   USE par_oce 
    1920   USE dom_oce 
    20    USE dom_ice 
    2121   USE sbc_oce         ! Surface boundary condition: ocean fields 
    2222   USE sbc_ice         ! Surface boundary condition: ice fields 
    23    USE ice 
    24    USE iceini 
    2523   USE lbclnk 
    2624   USE lib_mpp 
     
    2826   USE limitd_me 
    2927   USE prtctl          ! Print control 
    30  
     28#if defined key_lim3 
     29   USE dom_ice 
     30   USE ice 
     31   USE iceini 
     32#endif 
     33#if defined key_lim2 && ! defined key_lim2_vp 
     34   USE dom_ice_2 
     35   USE ice_2 
     36   USE iceini_2 
     37#endif 
    3138 
    3239   IMPLICIT NONE 
     
    180187         zresr                         !: Local error on velocity 
    181188 
     189#if  defined key_lim2 && ! defined key_lim2_vp 
     190     vt_s => hsnm 
     191     vt_i => hicm 
     192     at_i(:,:) = 1. - frld(:,:) 
     193#endif 
    182194      ! 
    183195      !------------------------------------------------------------------------------! 
     
    190202      u_ice2(:,:)  = 0.0 ; v_ice1(:,:)  = 0.0 
    191203      zdd(:,:)     = 0.0 ; zdt(:,:)     = 0.0 ; zds(:,:)     = 0.0 
    192  
     204#if defined key_lim3 
    193205      ! Ice strength on T-points 
    194206      CALL lim_itd_me_icestrength(ridge_scheme_swi) 
     207#endif 
    195208 
    196209      ! Ice mass and temp variables 
     
    200213         DO ji = 1 , jpi 
    201214            zc1(ji,jj)    = tms(ji,jj) * ( rhosn * vt_s(ji,jj) + rhoic * vt_i(ji,jj) ) 
     215#if defined key_lim3 
    202216            zpresh(ji,jj) = tms(ji,jj) *  strength(ji,jj) / 2. 
     217#else 
     218            zpresh(ji,jj) = tms(ji,jj) *  2. * pstar * hicm(ji,jj) * EXP( -c_rhg * frld(ji,jj) ) 
     219#endif 
    203220            ! tmi = 1 where there is ice or on land 
    204221            tmi(ji,jj)    = 1.0 - ( 1.0 - MAX( 0.0 , SIGN ( 1.0 , vt_i(ji,jj) - & 
     
    269286               / ( e2t(ji,jj+1) + e2t(ji,jj) + epsd ) 
    270287            ! 
     288            ! Mass, coriolis coeff. and currents 
    271289            u_oce1(ji,jj)  = u_oce(ji,jj) 
    272290            v_oce2(ji,jj)  = v_oce(ji,jj) 
  • branches/dev_1784_EVP/NEMO/OPA_SRC/SBC/sbcice_lim_2.F90

    r1715 r2046  
    88   !! History :  1.0   !  06-2006  (G. Madec)  from icestp_2.F90 
    99   !!            3.0   !  08-2008  (S. Masson, E. .... ) coupled interface 
     10   !!            3.3   !  05-2009  (G.Garric) addition of the lim2_evp case 
    1011   !!---------------------------------------------------------------------- 
    1112#if defined key_lim2 
     
    5354   PUBLIC sbc_ice_lim_2 ! routine called by sbcmod.F90 
    5455    
    55    CHARACTER(len=1) ::   cl_grid = 'B'     ! type of grid used in ice dynamics 
    56  
    5756   !! * Substitutions 
    5857#  include "domzgr_substitute.h90" 
     
    172171         !  Ice model step  ! 
    173172         ! ---------------- ! 
    174  
    175                                         CALL lim_rst_opn_2  ( kt )      ! Open Ice restart file 
    176          IF( .NOT. lk_c1d ) THEN                                        ! Ice dynamics & transport (not in 1D case) 
     173         numit = numit + nn_fsbc                                             ! Ice model time step 
     174 
     175                                        CALL lim_rst_opn_2  ( kt )           ! Open Ice restart file 
     176         IF( .NOT. lk_c1d ) THEN                                             ! Ice dynamics & transport (not in 1D case) 
    177177                                        CALL lim_dyn_2      ( kt )           ! Ice dynamics    ( rheology/dynamics ) 
    178178                                        CALL lim_trp_2      ( kt )           ! Ice transport   ( Advection/diffusion ) 
Note: See TracChangeset for help on using the changeset viewer.