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 2319 – NEMO

Changeset 2319


Ignore:
Timestamp:
2010-10-27T15:18:11+02:00 (14 years ago)
Author:
cbricaud
Message:

put new EVP rheology lost during the merge

Location:
branches/nemo_v3_3_beta/NEMOGCM/NEMO
Files:
1 added
11 edited

Legend:

Unmodified
Added
Removed
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/LIM_SRC_2/dom_ice_2.F90

    r2287 r2319  
    55   !!====================================================================== 
    66   !! History :   2.0  !  03-08  (C. Ethe)  Free form and module 
     7   !!             3.3  !  2009-05 (G.Garric, C. Bricaud) addition of lim2_evp case 
    78   !!---------------------------------------------------------------------- 
    89#if defined key_lim2 
     10   !!---------------------------------------------------------------------- 
     11   !!   'key_lim2'                                       LIM2 sea-ice model 
    912   !!---------------------------------------------------------------------- 
    1013   !! NEMO/LIM2 3.3 , UCL - NEMO Consortium (2010) 
     
    2225      !                                        !  (otherwise = jpj+10 (SH) or -10 (SH) ) 
    2326 
    24    REAL(wp), PUBLIC, DIMENSION(jpi,jpj)         ::   fs2cor , fcor,   &  !: coriolis factor and coeficient 
    25       &                                              covrai ,         &  !: sine of geographic latitude 
    26       &                                              area   ,         &  !: surface of grid cell  
    27       &                                              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       &                                              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 
     27   REAL(wp), PUBLIC, DIMENSION(jpi,jpj)         ::   fs2cor , fcor     !: coriolis factor and coeficient 
     28   REAL(wp), PUBLIC, DIMENSION(jpi,jpj)         ::   covrai            !: sine of geographic latitude 
     29   REAL(wp), PUBLIC, DIMENSION(jpi,jpj)         ::   area              !: surface of grid cell  
     30   REAL(wp), PUBLIC, DIMENSION(jpi,jpj)         ::   tms    , tmu      !: temperature and velocity points masks 
     31   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,2,2)     ::   wght              !: weight of the 4 neighbours to compute averages 
    3132 
     33 
     34# if defined key_lim2_vp 
     35   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,2,2)     ::   akappa , bkappa   !: first and third group of metric coefficients 
     36   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,2,2,2,2) ::   alambd            !: second group of metric coefficients 
     37# else 
     38   REAL(wp), PUBLIC, DIMENSION(jpi,jpj)         ::   tmv    , tmf      !: y-velocity and F-points masks 
     39   REAL(wp), PUBLIC, DIMENSION(jpi,jpj)         ::   tmi               !: ice mask: =1 if ice thick > 0 
     40# endif 
     41 
     42#else 
     43   !!---------------------------------------------------------------------- 
     44   !!   Default option          Empty module         NO LIM-2 sea-ice model 
     45   !!---------------------------------------------------------------------- 
     46#endif 
    3247   !!====================================================================== 
    33 #endif 
    3448END MODULE dom_ice_2 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/LIM_SRC_2/ice_2.F90

    r2287 r2319  
    55   !!===================================================================== 
    66   !! History :  2.0  !  03-08  (C. Ethe)  F90: Free form and module 
     7   !!            3.3  !  2009-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 grid 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) 
     
    3234   INTEGER , PUBLIC ::   nbiter = 1         !: number of sub-time steps for relaxation 
    3335   INTEGER , PUBLIC ::   nbitdr = 250       !: maximum number of iterations for relaxation 
     36   INTEGER , PUBLIC ::   nevp   =   360     !: number of EVP subcycling iterations 
     37   INTEGER , PUBLIC ::   telast =  3600     !: timescale for EVP elastic waves 
    3438   REAL(wp), PUBLIC ::   rdt_ice            !: ice time step 
    3539   REAL(wp), PUBLIC ::   epsd   = 1.0e-20   !: tolerance parameter for dynamic 
     
    4650   REAL(wp), PUBLIC ::   ecc    = 2.e0      !: eccentricity of the elliptical yield curve 
    4751   REAL(wp), PUBLIC ::   ahi0   = 350.e0    !: sea-ice hor. eddy diffusivity coeff. (m2/s) 
     52   REAL(wp), PUBLIC ::   alphaevp = 1.e0    !: coefficient for the solution of EVP int. stresses 
    4853 
    4954   REAL(wp), PUBLIC ::   usecc2             !:  = 1.0 / ( ecc * ecc ) 
     
    5459   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   ahiu , ahiv   !: hor. diffusivity coeff. at ocean U- and V-points (m2/s) 
    5560   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 
     61   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   ust2s         !: friction velocity 
    5862 
    5963   !!* diagnostic quantities 
    60    REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   sist          !: Sea-Ice Surface Temperature (Kelvin) 
     64# if defined key_lim2_vp 
     65   !                                                       !!* VP rheology * 
     66   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   hsnm , hicm   !: mean snow and ice thicknesses 
     67   CHARACTER(len=1), PUBLIC             ::   cl_grid = 'B' !: type of grid used in ice dynamics, 'C' or 'B' 
     68   ! 
     69# else 
     70   !                                                       !!* EVP rheology * 
     71   CHARACTER(len=1), PUBLIC             ::   cl_grid = 'C' !: type of grid used in ice dynamics, 'C' or 'B' 
     72   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   stress1_i     !: first stress tensor element        
     73   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   stress2_i     !: second stress tensor element 
     74   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   stress12_i    !: diagonal stress tensor element 
     75   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   delta_i       !: rheology delta factor (see Flato and Hibler 95) [s-1] 
     76   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   divu_i        !: Divergence of the velocity field [s-1] -> limrhg.F90 
     77   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   shear_i       !: Shear of the velocity field [s-1] -> limrhg.F90 
     78   ! 
     79   REAL(wp), PUBLIC, DIMENSION(jpi,jpj)          :: at_i          !: 
     80   REAL(wp), PUBLIC, DIMENSION(:,:)    , POINTER :: vt_s ,vt_i    !: mean snow and ice thicknesses 
     81   REAL(wp), PUBLIC, DIMENSION(jpi,jpj), TARGET  :: hsnm , hicm   !: target vt_s,vt_i pointers  
     82   !   
     83#endif 
     84 
     85   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   rdvosif       !: ice volume change at ice surface (only used for outputs) 
     86   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   rdvobif       !: ice volume change at ice bottom  (only used for outputs) 
     87   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   fdvolif       !: Total   ice volume change (only used for outputs) 
     88   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   rdvonif       !: Lateral ice volume change (only used for outputs) 
     89   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   sist          !: Sea-Ice Surface Temperature [Kelvin] 
    6190   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   tfu           !: Freezing/Melting point temperature of sea water at SSS 
    6291   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   hicif         !: Ice thickness 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/LIM_SRC_2/iceini_2.F90

    r2287 r2319  
    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, C. Bricaud) addition of the lim2_evp case 
    89   !!---------------------------------------------------------------------- 
    910#if defined key_lim2 
     
    1516   !!   ice_run_2        : Definition some run parameter for ice model 
    1617   !!---------------------------------------------------------------------- 
    17    USE dom_oce 
    18    USE dom_ice_2 
    19    USE sbc_oce         ! surface boundary condition: ocean 
    20    USE sbc_ice         ! surface boundary condition: ice 
    21    USE phycst          ! Define parameters for the routines 
    22    USE ice_2 
    23    USE limmsh_2 
    24    USE limistate_2 
    25    USE limrst_2    
    26    USE in_out_manager 
     18   USE dom_oce          ! ocean domain 
     19   USE dom_ice_2        ! LIM2: ice domain 
     20   USE sbc_oce          ! surface boundary condition: ocean 
     21   USE sbc_ice          ! surface boundary condition: ice 
     22   USE phycst           ! Define parameters for the routines 
     23   USE ice_2            ! LIM2: ice variable 
     24   USE limmsh_2         ! LIM2: mesh 
     25   USE limistate_2      ! LIM2: initial state 
     26   USE limrst_2         ! LIM2: restart 
     27   USE in_out_manager   ! I/O manager 
    2728       
    2829   IMPLICIT NONE 
     
    3031 
    3132   PUBLIC   ice_init_2               ! called by sbcice_lim_2.F90 
     33 
     34   INTEGER, PUBLIC ::   numit   !: iteration number 
    3235 
    3336   !!---------------------------------------------------------------------- 
     
    4346      !!                  ***  ROUTINE ice_init_2  *** 
    4447      !! 
    45       !! ** purpose :    
     48      !! ** purpose :   initialisation of LIM-2 domain and variables   
    4649      !!---------------------------------------------------------------------- 
    4750      ! 
     
    5255      ! Louvain la Neuve Ice model 
    5356      rdt_ice = nn_fsbc * rdttra(1) 
     57      numit   = nit000 - 1 
    5458 
    5559      CALL lim_msh_2                  ! ice mesh initialization 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/LIM_SRC_2/limdyn_2.F90

    r2287 r2319  
    2222   USE dom_ice_2      ! 
    2323   USE limistate_2    ! 
     24#if defined key_lim2_vp 
    2425   USE limrhg_2       ! ice rheology 
    25  
     26#else 
     27   USE limrhg         ! LIM : EVP ice rheology 
     28#endif 
    2629   USE lbclnk         ! 
    2730   USE lib_mpp        ! 
     
    8790            i_jpj = jpj 
    8891            IF(ln_ctl)   CALL prt_ctl_info( 'lim_dyn  :    i_j1 = ', ivar1=i_j1, clinfo2=' ij_jpj = ', ivar2=i_jpj ) 
    89             CALL lim_rhg_2( i_j1, i_jpj ) 
     92#if defined key_lim2_vp 
     93            CALL lim_rhg_2( i_j1, i_jpj )             !  VP rheology 
     94#else 
     95            CALL lim_rhg  ( i_j1, i_jpj )             ! EVP rheology 
     96#endif 
    9097            ! 
    9198         ELSE                                 ! optimization of the computational area 
     
    105112                  i_j1 = i_j1 + 1 
    106113               END DO 
     114#if defined key_lim2_vp 
    107115               i_j1 = MAX( 1, i_j1-1 ) 
    108116               IF(ln_ctl)   WRITE(numout,*) 'lim_dyn : NH i_j1 = ', i_j1, ' ij_jpj = ', i_jpj 
     
    110118               CALL lim_rhg_2( i_j1, i_jpj ) 
    111119               !  
     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               !  
     125#endif 
    112126               ! Southern hemisphere 
    113127               i_j1  =  1  
     
    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 
     
    121136               CALL lim_rhg_2( i_j1, i_jpj ) 
    122137               !  
     138#else 
     139               i_jpj = MIN( jpj, i_jpj+1 ) 
     140               IF(ln_ctl)   WRITE(numout,*) 'lim_dyn : SH i_j1 = ', i_j1, 'ij_jpj = ', i_jpj 
     141               CALL lim_rhg( i_j1, i_jpj ) 
     142               !  
     143#endif 
     144 
    123145            ELSE                                 ! local domain extends over one hemisphere only 
    124146               !                                 ! Rheology is computed only over the ice cover 
     
    138160               IF(ln_ctl)   WRITE(numout,*) 'lim_dyn : one hemisphere: i_j1 = ', i_j1, ' ij_jpj = ', i_jpj 
    139161               !  
    140                CALL lim_rhg_2( i_j1, i_jpj ) 
     162#if defined key_lim2_vp 
     163               i_jpj = MIN( jpj, i_jpj+2) 
     164               CALL lim_rhg_2( i_j1, i_jpj )                !  VP rheology 
     165#else 
     166               i_j1 = MAX( 1, i_j1-2 ) 
     167               i_jpj = MIN( jpj, i_jpj+1) 
     168               CALL lim_rhg  ( i_j1, i_jpj )                ! EVP rheology 
     169#endif 
    141170               ! 
    142171            ENDIF 
     
    148177         ! computation of friction velocity 
    149178         ! -------------------------------- 
    150          ! ice-ocean velocity at U & V-points (u_ice v_ice at I-point ; ssu_m, ssv_m at U- & V-points) 
    151           
    152          DO jj = 1, jpjm1 
    153             DO ji = 1, jpim1   ! NO vector opt. 
    154                zu_io(ji,jj) = 0.5 * ( u_ice(ji+1,jj+1) + u_ice(ji+1,jj  ) ) - ssu_m(ji,jj) 
    155                zv_io(ji,jj) = 0.5 * ( v_ice(ji+1,jj+1) + v_ice(ji  ,jj+1) ) - ssv_m(ji,jj) 
    156             END DO 
    157          END DO 
     179         SELECT CASE( cl_grid ) 
     180         CASE( 'C' )       ! C-grid ice dynamics (EVP) 
     181                           ! ice-ocean & ice velocity at  ocean velocity points 
     182            zu_io(:,:) = u_ice(:,:) - ssu_m(:,:)   
     183            zv_io(:,:) = v_ice(:,:) - ssv_m(:,:) 
     184            ! 
     185         CASE( 'B' )       ! B-grid ice dynamics (VP)  
     186                           ! ice-ocean velocity at U & V-points (u_ice v_ice at I-point ; ssu_m, ssv_m at U- & V-points) 
     187            DO jj = 1, jpjm1 
     188               DO ji = 1, jpim1   ! NO vector opt. 
     189                  zu_io(ji,jj) = 0.5 * ( u_ice(ji+1,jj+1) + u_ice(ji+1,jj  ) ) - ssu_m(ji,jj) 
     190                  zv_io(ji,jj) = 0.5 * ( v_ice(ji+1,jj+1) + v_ice(ji  ,jj+1) ) - ssv_m(ji,jj) 
     191               END DO 
     192            END DO 
     193         END SELECT 
     194 
    158195         ! frictional velocity at T-point 
    159196         DO jj = 2, jpjm1 
     
    198235      NAMELIST/namicedyn/ epsd, alpha,     & 
    199236         &                dm, nbiter, nbitdr, om, resl, cw, angvg, pstar,   & 
    200          &                c_rhg, etamn, creepl, ecc, ahi0 
     237         &                c_rhg, etamn, creepl, ecc, ahi0                   & 
     238         &                nevp, telast,alphaevp 
    201239      !!------------------------------------------------------------------- 
    202240 
     
    223261         WRITE(numout,*) '       eccentricity of the elliptical yield curve       ecc    = ', ecc 
    224262         WRITE(numout,*) '       horizontal diffusivity coeff. for sea-ice        ahi0   = ', ahi0 
     263         WRITE(numout,*) '       number of iterations for subcycling nevp   = ', nevp 
     264         WRITE(numout,*) '       timescale for elastic waves telast = ', telast 
     265         WRITE(numout,*) '       coefficient for the solution of int. stresses alphaevp = ', alphaevp 
    225266      ENDIF 
    226267 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/LIM_SRC_2/limmsh_2.F90

    r2287 r2319  
    5050      !! * Local variables 
    5151      INTEGER :: ji, jj      ! dummy loop indices 
    52  
    53       REAL(wp), DIMENSION(jpi,jpj) ::  & 
    54          zd2d1 , zd1d2       ! Derivative of zh2 (resp. zh1) in the x direction 
    55          !                   ! (resp. y direction) (defined at the center) 
    56       REAL(wp) ::         & 
    57          zh1p  , zh2p   , &  ! Idem zh1, zh2 for the bottom left corner of the grid 
    58          zd2d1p, zd1d2p , &  ! Idem zd2d1, zd1d2 for the bottom left corner of the grid 
    59          zusden, zusden2     ! temporary scalars 
     52      REAL(wp) ::   zusden   ! local scalars 
     53 
     54#if defined key_lim2_vp 
     55      REAL(wp) ::   zusden2           ! local scalars 
     56      REAL(wp) ::   zh1p  , zh2p      !   -      - 
     57      REAL(wp) ::   zd2d1p, zd1d2p    !   -      - 
     58      REAL(wp), DIMENSION(jpi,jpj) ::   zd2d1 , zd1d2   ! 2D workspace 
     59#endif 
    6060      !!--------------------------------------------------------------------- 
    6161 
     
    7676      njeqm1 = njeq - 1  
    7777 
    78       fcor(:,:) = 2. * omega * SIN( gphit(:,:) * rad )   !  coriolis factor 
     78      fcor(:,:) = 2. * omega * SIN( gphit(:,:) * rad )   !  coriolis factor at T-point 
    7979  
    8080!i    DO jj = 1, jpj 
     
    115115      !------------------- 
    116116!!ibug ??? 
    117       akappa(:,:,:,:) = 0.e0 
    118117      wght(:,:,:,:) = 0.e0 
     118      tmu(:,:)      = 0.e0 
     119#if defined key_lim2_vp  
     120      akappa(:,:,:,:)     = 0.e0 
    119121      alambd(:,:,:,:,:,:) = 0.e0 
    120       tmu(:,:) = 0.e0 
     122#else 
     123      tmv(:,:) = 0.e0 
     124      tmf(:,:) = 0.e0 
     125#endif 
    121126!!i 
    122127       
    123        
     128 
     129#if defined key_lim2_vp       
    124130      ! metric coefficients for sea ice dynamic 
    125131      !---------------------------------------- 
     
    155161      CALL lbc_lnk( wght(:,:,2,1), 'I', 1. )      ! but it is never used 
    156162      CALL lbc_lnk( wght(:,:,2,2), 'I', 1. ) 
     163#else 
     164      ! metric coefficients for sea ice dynamic (EVP rheology) 
     165      !---------------------------------------- 
     166      DO jj = 1, jpjm1                                       ! weights (wght) at F-points 
     167         DO ji = 1, jpim1 
     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      CALL lbc_lnk( wght(:,:,1,1), 'F', 1. )   ;   CALL lbc_lnk( wght(:,:,1,2),'F', 1. )       ! lateral boundary cond.    
     177      CALL lbc_lnk( wght(:,:,2,1), 'F', 1. )   ;   CALL lbc_lnk( wght(:,:,2,2),'F', 1. ) 
     178#endif 
    157179     
    158180      ! Coefficients for divergence of the stress tensor 
    159181      !------------------------------------------------- 
    160182 
     183#if defined key_lim2_vp 
    161184      DO jj = 2, jpj 
    162185         DO ji = 2, jpi   ! NO vector opt. 
     
    226249      CALL lbc_lnk( alambd(:,:,2,1,1,1), 'I', 1. )      ! 
    227250      CALL lbc_lnk( alambd(:,:,2,1,1,2), 'I', 1. )      ! 
     251#endif 
    228252             
    229253 
     
    233257      tms(:,:) = tmask(:,:,1)      ! ice T-point  : use surface tmask 
    234258 
     259#if defined key_lim2_vp 
     260      ! VP rheology : ice velocity point is I-point 
    235261!i here we can use umask with a i and j shift of -1,-1 
    236262      tmu(:,1) = 0.e0 
     
    244270      !--lateral boundary conditions     
    245271      CALL lbc_lnk( tmu(:,:), 'I', 1. ) 
     272#else 
     273      ! EVP rheology : ice velocity point are U- & V-points ; ice vorticity 
     274      ! point is F-point 
     275      tmu(:,:) = umask(:,:,1) 
     276      tmv(:,:) = vmask(:,:,1) 
     277      tmf(:,:) = 0.e0                        ! used of fmask except its special value along the coast (rn_shlat) 
     278      WHERE( fmask(:,:,1) == 1.e0 )   tmf(:,:) = 1.e0 
     279#endif 
    246280       
    247281      ! unmasked and masked area of T-grid cell 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/LIM_SRC_2/limrhg_2.F90

    r2287 r2319  
    44   !!   Ice rheology :  performs sea ice rheology 
    55   !!====================================================================== 
    6    !! History :  0.0  !  93-12  (M.A. Morales Maqueda.)  Original code 
    7    !!            1.0  !  94-12  (H. Goosse)  
    8    !!            2.0  !  03-12  (C. Ethe, G. Madec)  F90, mpp 
    9    !!            " "  !  06-08  (G. Madec)  surface module, ice-stress at I-point 
    10    !!            " "  !  09-09  (G. Madec)  Huge verctor optimisation 
    11    !!---------------------------------------------------------------------- 
    12 #if defined key_lim2 
    13    !!---------------------------------------------------------------------- 
    14    !!   'key_lim2'                                    LIM 2.0 sea-ice model 
     6   !! History :  0.0  !  1993-12  (M.A. Morales Maqueda.)  Original code 
     7   !!            1.0  !  1994-12  (H. Goosse)  
     8   !!            2.0  !  2003-12  (C. Ethe, G. Madec)  F90, mpp 
     9   !!            " "  !  2006-08  (G. Madec)  surface module, ice-stress at I-point 
     10   !!            " "  !  2009-09  (G. Madec)  Huge verctor optimisation 
     11   !!            3.3  !  2009-05  (G.Garric, C. Bricaud) addition of the lim2_evp case 
     12   !!---------------------------------------------------------------------- 
     13#if defined   key_lim2   &&   defined key_lim2_vp 
     14   !!---------------------------------------------------------------------- 
     15   !!   'key_lim2'                and                 LIM 2.0 sea-ice model 
     16   !!   'key_lim2_vp'                                       VP ice rheology 
    1517   !!---------------------------------------------------------------------- 
    1618   !!---------------------------------------------------------------------- 
     
    2123   USE sbc_oce        ! surface boundary condition: ocean variables 
    2224   USE sbc_ice        ! surface boundary condition: ice variables 
    23    USE dom_ice_2      ! domaine: ice variables 
     25   USE dom_ice_2      ! LIM2: ice domain 
    2426   USE phycst         ! physical constant 
    25    USE ice_2          ! ice variables 
    26    USE lbclnk         ! lateral boundary condition 
     27   USE ice_2          ! LIM2: ice variables 
     28   USE lbclnk         ! lateral boundary condition - MPP exchanges 
    2729   USE lib_mpp        ! MPP library 
    2830   USE in_out_manager ! I/O manager 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/LIM_SRC_2/limrst_2.F90

    r2287 r2319  
    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/nemo_v3_3_beta/NEMOGCM/NEMO/LIM_SRC_2/limsbc_2.F90

    r2287 r2319  
    44   !!           computation of the flux at the sea ice/ocean interface 
    55   !!====================================================================== 
    6    !! History : 00-01 (H. Goosse) Original code 
    7    !!           02-07 (C. Ethe, G. Madec) re-writing F90 
    8    !!           06-07 (G. Madec) surface module 
     6   !! History :  LIM  ! 2000-01 (H. Goosse) Original code 
     7   !!            1.0  ! 2002-07 (C. Ethe, G. Madec) re-writing F90 
     8   !!            3.0  ! 2006-07 (G. Madec) surface module 
     9   !!            3.3  ! 2009-05 (G.Garric, C. Bricaud) addition of the lim2_evp case 
    910   !!---------------------------------------------------------------------- 
    1011#if defined key_lim2 
     
    1718   USE par_oce          ! ocean parameters 
    1819   USE dom_oce          ! ocean domain 
    19    USE sbc_ice          ! surface boundary condition 
    20    USE sbc_oce          ! surface boundary condition 
     20   USE sbc_ice          ! surface boundary condition: ice 
     21   USE sbc_oce          ! surface boundary condition: ocean 
    2122   USE phycst           ! physical constants 
    22    USE ice_2            ! LIM sea-ice variables 
    23  
    24    USE lbclnk           ! ocean lateral boundary condition 
     23   USE ice_2            ! LIM2: ice variables 
     24 
     25   USE lbclnk           ! ocean lateral boundary condition - MPP exchanges 
    2526   USE in_out_manager   ! I/O manager 
    2627   USE diaar5, ONLY :   lk_diaar5 
     
    3536   PUBLIC lim_sbc_2     ! called by sbc_ice_lim_2 
    3637 
    37    REAL(wp)  ::   epsi16 = 1.e-16  ! constant values 
    38    REAL(wp)  ::   rzero  = 0.e0     
    39    REAL(wp)  ::   rone   = 1.e0 
    40    REAL(wp), DIMENSION(jpi,jpj)  ::   soce_r 
    41    REAL(wp), DIMENSION(jpi,jpj)  ::   sice_r 
     38   REAL(wp)  ::   r1_rdtice                    ! constant values 
     39   REAL(wp)  ::   epsi16 = 1.e-16              !     -      - 
     40   REAL(wp)  ::   rzero  = 0.e0                !     -      - 
     41   REAL(wp)  ::   rone   = 1.e0                !     -      - 
     42   ! 
     43   REAL(wp), DIMENSION(jpi,jpj) ::   soce_r, sice_r   ! constant SSS and ice salinity used in levitating sea-ice case 
    4244 
    4345   !! * Substitutions 
     
    7880      !! 
    7981      INTEGER  ::   ji, jj           ! dummy loop indices 
    80       INTEGER  ::   ifvt, i1mfr, idfr               ! some switches 
    81       INTEGER  ::   iflt, ial, iadv, ifral, ifrdv 
    82       REAL(wp) ::   zrdtir           ! 1. / rdt_ice 
    83       REAL(wp) ::   zqsr  , zqns     ! solar & non solar heat flux 
    84       REAL(wp) ::   zinda            ! switch for testing the values of ice concentration 
    85       REAL(wp) ::   zfons            ! salt exchanges at the ice/ocean interface 
    86       REAL(wp) ::   zemp             ! freshwater exchanges at the ice/ocean interface 
    87       REAL(wp) ::   zfrldu, zfrldv   ! lead fraction at U- & V-points 
    88       REAL(wp) ::   zutau , zvtau    ! lead fraction at U- & V-points 
    89       REAL(wp) ::   zu_io , zv_io    ! 2 components of the ice-ocean velocity 
    90 ! interface 2D --> 3D 
    91       REAL(wp), DIMENSION(jpi,jpj,1) ::   zalb     ! albedo of ice under overcast sky 
    92       REAL(wp), DIMENSION(jpi,jpj,1) ::   zalbp    ! albedo of ice under clear sky 
    93       REAL(wp) ::   zsang, zmod, zztmp, zfm 
    94       REAL(wp), DIMENSION(jpi,jpj) ::   ztio_u, ztio_v   ! component of ocean stress below sea-ice at I-point 
    95       REAL(wp), DIMENSION(jpi,jpj) ::   ztiomi           ! module    of ocean stress below sea-ice at I-point 
    96       REAL(wp), DIMENSION(jpi,jpj) ::   zqnsoce          ! save qns before its modification by ice model 
     82      INTEGER  ::   ii0, ii1, ij0, ij1         ! local integers 
     83      INTEGER  ::   ifvt, i1mfr, idfr, iflt    !   -       - 
     84      INTEGER  ::   ial, iadv, ifral, ifrdv    !   -       - 
     85      REAL(wp) ::   zqsr, zqns, zsang, zmod, zfm   ! local scalars 
     86      REAL(wp) ::   zinda, zfons, zemp, zztmp      !   -      - 
     87      REAL(wp) ::   zfrldu, zutau, zu_io           !   -      - 
     88      REAL(wp) ::   zfrldv, zvtau, zv_io           !   -      - 
     89      REAL(wp), DIMENSION(jpi,jpj)   ::   ztio_u, ztio_v    ! 2D workspace 
     90      REAL(wp), DIMENSION(jpi,jpj)   ::   ztiomi, zqnsoce   !  -     - 
     91      REAL(wp), DIMENSION(jpi,jpj,1) ::   zalb, zalbp   ! 2D/3D workspace 
    9792 
    9893      !!--------------------------------------------------------------------- 
    9994      
    100       zrdtir = 1. / rdt_ice 
    10195       
    10296      IF( kt == nit000 ) THEN 
    10397         IF(lwp) WRITE(numout,*) 
    104          IF(lwp) WRITE(numout,*) 'lim_sbc_2 : LIM 2.0 sea-ice - surface boundary condition' 
     98#if defined key_lim2_vp 
     99         IF(lwp) WRITE(numout,*) 'lim_sbc_2 : LIM 2.0 sea-ice (VP rheology)  - surface boundary condition' 
     100#else 
     101         IF(lwp) WRITE(numout,*) 'lim_sbc_2 : LIM 2.0 sea-ice (EVP rheology) - surface boundary condition' 
     102#endif 
    105103         IF(lwp) WRITE(numout,*) '~~~~~~~~~   ' 
    106  
     104         ! 
     105         r1_rdtice = 1. / rdt_ice 
     106         ! 
    107107         soce_r(:,:) = soce 
    108108         sice_r(:,:) = sice 
     
    186186            zqns    =  - ( 1. - thcm(ji,jj) ) * zqsr   &   ! part of the solar energy used in leads 
    187187               &       + iflt    * ( fscmbq(ji,jj) + ffltbif(ji,jj) )                            & 
    188                &       + ifral   * ( ial * qcmif(ji,jj) + (1 - ial) * qldif(ji,jj) ) * zrdtir    & 
    189                &       + ifrdv   * ( qfvbq(ji,jj) + qdtcn(ji,jj) ) * zrdtir 
     188               &       + ifral   * ( ial * qcmif(ji,jj) + (1 - ial) * qldif(ji,jj) ) * r1_rdtice    & 
     189               &       + ifrdv   * ( qfvbq(ji,jj) + qdtcn(ji,jj) )                   * r1_rdtice  
    190190 
    191191            fsbbq(ji,jj) = ( 1.0 - ( ifvt + iflt ) ) * fscmbq(ji,jj)     ! ??? 
     
    198198      CALL iom_put( 'hflx_ice_cea', - fdtcn(:,:) )       
    199199      CALL iom_put( 'qns_io_cea', qns(:,:) - zqnsoce(:,:) * pfrld(:,:) )       
    200       CALL iom_put( 'qsr_io_cea', fstric(:,:) * (1. - pfrld(:,:)) ) 
     200      CALL iom_put( 'qsr_io_cea', fstric(:,:) * (1.e0 - pfrld(:,:)) ) 
    201201 
    202202      !------------------------------------------! 
     
    212212             
    213213#if defined key_coupled 
    214           zemp = emp_tot(ji,jj) - emp_ice(ji,jj) * ( 1. - pfrld(ji,jj) )    &   !  
    215              &   + rdmsnif(ji,jj) * zrdtir                                      !  freshwaterflux due to snow melting  
    216 #else 
    217 !!$            !  computing freshwater exchanges at the ice/ocean interface 
    218 !!$            zpme = - evap(ji,jj)    *   frld(ji,jj)           &   !  evaporation over oceanic fraction 
    219 !!$               &   + tprecip(ji,jj)                           &   !  total precipitation 
    220 !!$               &   - sprecip(ji,jj) * ( 1. - pfrld(ji,jj) )   &   !  remov. snow precip over ice 
    221 !!$               &   - rdmsnif(ji,jj) / rdt_ice                     !  freshwaterflux due to snow melting  
     214            ! freshwater exchanges at the ice-atmosphere / ocean interface (coupled mode) 
     215            zemp = emp_tot(ji,jj) - emp_ice(ji,jj) * ( 1. - pfrld(ji,jj) )    &   !  
     216               &   + rdmsnif(ji,jj) * r1_rdtice                                   !  freshwaterflux due to snow melting  
     217#else 
    222218            !  computing freshwater exchanges at the ice/ocean interface 
    223219            zemp = + emp(ji,jj)     *         frld(ji,jj)      &   !  e-p budget over open ocean fraction  
    224220               &   - tprecip(ji,jj) * ( 1. -  frld(ji,jj) )    &   !  liquid precipitation reaches directly the ocean 
    225221               &   + sprecip(ji,jj) * ( 1. - pfrld(ji,jj) )    &   !  taking into account change in ice cover within the time step 
    226                &   + rdmsnif(ji,jj) * zrdtir                       !  freshwaterflux due to snow melting  
     222               &   + rdmsnif(ji,jj) * r1_rdtice                    !  freshwaterflux due to snow melting  
    227223               !                                                   !  ice-covered fraction: 
    228224#endif             
    229225 
    230226            !  computing salt exchanges at the ice/ocean interface 
    231             zfons =  ( soce_r(ji,jj) - sice_r(ji,jj) ) * ( rdmicif(ji,jj) * zrdtir )  
     227            zfons =  ( soce_r(ji,jj) - sice_r(ji,jj) ) * ( rdmicif(ji,jj) * r1_rdtice )  
    232228             
    233229            !  converting the salt flux from ice to a freshwater flux from ocean 
     
    241237 
    242238      IF( lk_diaar5 ) THEN 
    243          CALL iom_put( 'isnwmlt_cea'  ,                 rdmsnif(:,:) * zrdtir ) 
    244          CALL iom_put( 'fsal_virt_cea',   soce_r(:,:) * rdmicif(:,:) * zrdtir ) 
    245          CALL iom_put( 'fsal_real_cea', - sice_r(:,:) * rdmicif(:,:) * zrdtir ) 
     239         CALL iom_put( 'isnwmlt_cea'  ,                 rdmsnif(:,:) * r1_rdtice ) 
     240         CALL iom_put( 'fsal_virt_cea',   soce_r(:,:) * rdmicif(:,:) * r1_rdtice ) 
     241         CALL iom_put( 'fsal_real_cea', - sice_r(:,:) * rdmicif(:,:) * r1_rdtice ) 
    246242      ENDIF 
    247243 
     
    277273            DO ji = 2, jpim1   ! NO vector opt. 
    278274               ! ... components of ice-ocean stress at U and V-points  (from I-point values) 
    279                zutau  = 0.5 * ( ztio_u(ji+1,jj) + ztio_u(ji+1,jj+1) ) 
     275#if defined key_lim2_vp 
     276               zutau  = 0.5 * ( ztio_u(ji+1,jj) + ztio_u(ji+1,jj+1) )      ! VP rheology 
    280277               zvtau  = 0.5 * ( ztio_v(ji,jj+1) + ztio_v(ji+1,jj+1) ) 
     278#else 
     279               zutau  = ztio_u(ji,jj)                                      ! EVP rheology 
     280               zvtau  = ztio_v(ji,jj) 
     281#endif 
    281282               ! ... open-ocean (lead) fraction at U- & V-points (from T-point values) 
    282283               zfrldu = 0.5 * ( frld(ji,jj) + frld(ji+1,jj  ) ) 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/LIM_SRC_2/limtrp_2.F90

    r2287 r2319  
    77   !!            2.0  !  2001-05 (G. Madec, R. Hordoir) opa norm 
    88   !!             -   !  2004-01 (G. Madec, C. Ethe)  F90, mpp 
     9   !!            3.3  !  2009-05  (G.Garric, C. Bricaud) addition of the lim2_evp case 
    910   !!---------------------------------------------------------------------- 
    1011#if defined key_lim2 
     
    3233   PUBLIC   lim_trp_2   ! called by sbc_ice_lim_2 
    3334 
    34    REAL(wp), PUBLIC  ::   bound  = 0.e0   !: boundary condit. (0.0 no-slip, 1.0 free-slip) 
    35  
    36    REAL(wp)  ::           &  ! constant values 
    37       epsi06 = 1.e-06  ,  & 
    38       epsi03 = 1.e-03  ,  & 
    39       epsi16 = 1.e-16  ,  & 
    40       rzero  = 0.e0    ,  & 
    41       rone   = 1.e0 
     35   REAL(wp), PUBLIC ::   bound  = 0.e0          !: boundary condit. (0.0 no-slip, 1.0 free-slip) 
     36 
     37   REAL(wp)  ::   epsi06 = 1.e-06   ! constant values 
     38   REAL(wp)  ::   epsi03 = 1.e-03   
     39   REAL(wp)  ::   epsi16 = 1.e-16   
     40   REAL(wp)  ::   rzero  = 0.e0    
     41   REAL(wp)  ::   rone   = 1.e0 
     42 
    4243 
    4344   !! * Substitution 
     
    8889         ! --------------------------------------- 
    8990         zvbord = 1.0 + ( 1.0 - bound )      ! zvbord=2 no-slip, =0 free slip boundary conditions         
     91#if defined key_lim2_vp 
    9092         DO jj = 1, jpjm1 
    9193            DO ji = 1, jpim1   ! NO vector opt. 
     
    9597         END DO 
    9698         CALL lbc_lnk( zui_u, 'U', -1. )   ;   CALL lbc_lnk( zvi_v, 'V', -1. )         ! Lateral boundary conditions 
    97  
     99#else 
     100        zui_u(:,:) = u_ice(:,:)      ! EVP rheology: ice (u,v) at u- and v-points 
     101        zvi_v(:,:) = v_ice(:,:) 
     102#endif 
    98103 
    99104         ! CFL test for stability 
     
    109114         ! content of properties 
    110115         ! --------------------- 
    111          zs0sn (:,:) =  hsnm(:,:) * area(:,:)                 ! Snow volume. 
    112          zs0ice(:,:) =  hicm(:,:) * area(:,:)                 ! Ice volume. 
     116         zs0sn (:,:) =  hsnm(:,:)              * area  (:,:)  ! Snow volume. 
     117         zs0ice(:,:) =  hicm(:,:)              * area  (:,:)  ! Ice volume. 
    113118         zs0a  (:,:) =  ( 1.0 - frld(:,:) )    * area  (:,:)  ! Surface covered by ice. 
    114119         zs0c0 (:,:) =  tbif(:,:,1) / rt0_snow * zs0sn (:,:)  ! Heat content of the snow layer. 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/LIM_SRC_3/limrhg.F90

    r2287 r2319  
    77   !!            3.0  !  2008-03  (M. Vancoppenolle) LIM3 
    88   !!             -   !  2008-11  (M. Vancoppenolle, S. Bouillon, Y. Aksenov) add surface tilt in ice rheolohy  
     9   !!            3.3  !  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 
     28#if defined key_lim3 
     29   USE ice 
     30   USE dom_ice 
     31   USE iceini 
     32#endif 
     33#if defined key_lim2 && ! defined key_lim2_vp 
     34   USE ice_2            ! LIM2: ice variables 
     35   USE dom_ice_2        ! LIM2: ice domain 
     36   USE iceini_2         ! LIM2: ice initialisation 
     37#endif 
    3038 
    3139 
     
    179187         zv_ice           ,          & 
    180188         zresr                         !: Local error on velocity 
    181  
     189      !!------------------------------------------------------------------- 
     190 
     191#if  defined key_lim2 && ! defined key_lim2_vp 
     192     vt_s => hsnm 
     193     vt_i => hicm 
     194     at_i(:,:) = 1. - frld(:,:) 
     195#endif 
    182196      ! 
    183197      !------------------------------------------------------------------------------! 
     
    191205      zdd(:,:)     = 0.0 ; zdt(:,:)     = 0.0 ; zds(:,:)     = 0.0 
    192206 
     207#if defined key_lim3 
    193208      ! Ice strength on T-points 
    194209      CALL lim_itd_me_icestrength(ridge_scheme_swi) 
     210#endif 
    195211 
    196212      ! Ice mass and temp variables 
     
    200216         DO ji = 1 , jpi 
    201217            zc1(ji,jj)    = tms(ji,jj) * ( rhosn * vt_s(ji,jj) + rhoic * vt_i(ji,jj) ) 
     218#if defined key_lim3 
    202219            zpresh(ji,jj) = tms(ji,jj) *  strength(ji,jj) / 2. 
     220#endif 
    203221            ! tmi = 1 where there is ice or on land 
    204222            tmi(ji,jj)    = 1.0 - ( 1.0 - MAX( 0.0 , SIGN ( 1.0 , vt_i(ji,jj) - & 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/SBC/sbcice_lim_2.F90

    r2287 r2319  
    5353   PUBLIC sbc_ice_lim_2 ! routine called by sbcmod.F90 
    5454 
    55    CHARACTER(len=1) ::   cl_grid = 'B'     ! type of grid used in ice dynamics 
    56     
    5755   !! * Substitutions 
    5856#  include "domzgr_substitute.h90" 
     
    172170         !  Ice model step  ! 
    173171         ! ---------------- ! 
    174                                         CALL lim_rst_opn_2  ( kt )      ! Open Ice restart file 
     172         numit = numit + nn_fsbc                                             !Ice model time step 
     173 
     174                                        CALL lim_rst_opn_2  ( kt )           ! Open Ice restart file 
    175175#if ! defined key_c1d 
    176176            ! Ice dynamics & transport (not in 1D case) 
Note: See TracChangeset for help on using the changeset viewer.