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 7351 for branches/2016/dev_INGV_UKMO_2016/NEMOGCM/NEMO/LIM_SRC_2/limsbc_2.F90 – NEMO

Ignore:
Timestamp:
2016-11-28T17:04:10+01:00 (7 years ago)
Author:
emanuelaclementi
Message:

ticket #1805 step 3: /2016/dev_INGV_UKMO_2016 aligned to the trunk at revision 7161

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2016/dev_INGV_UKMO_2016/NEMOGCM/NEMO/LIM_SRC_2/limsbc_2.F90

    r5836 r7351  
    2929   USE sbc_ice          ! surface boundary condition: ice 
    3030   USE sbc_oce          ! surface boundary condition: ocean 
    31    USE sbccpl 
     31   USE sbccpl           ! surface boundary condition: coupled interface 
    3232   USE oce       , ONLY : sshn, sshb, snwice_mass, snwice_mass_b, snwice_fmass  
    3333   USE albedo           ! albedo parameters 
     34   ! 
    3435   USE lbclnk           ! ocean lateral boundary condition - MPP exchanges 
    3536   USE lib_mpp          ! MPP library 
     
    4344   PRIVATE 
    4445 
    45    PUBLIC   lim_sbc_init_2     ! called by ice_init_2 
    46    PUBLIC   lim_sbc_flx_2      ! called by sbc_ice_lim_2 
    47    PUBLIC   lim_sbc_tau_2      ! called by sbc_ice_lim_2 
     46   PUBLIC   lim_sbc_init_2   ! called by ice_init_2 
     47   PUBLIC   lim_sbc_flx_2    ! called by sbc_ice_lim_2 
     48   PUBLIC   lim_sbc_tau_2    ! called by sbc_ice_lim_2 
    4849 
    4950   REAL(wp)  ::   r1_rdtice            ! = 1. / rdt_ice  
     
    5253   REAL(wp)  ::   rone   = 1._wp       !     -      - 
    5354   ! 
    54    REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   soce_0, sice_0   ! constant SSS and ice salinity used in levitating sea-ice case 
     55   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   soce_0, sice_0       ! fix SSS and ice salinity used in levitating case 0 
    5556   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   utau_oce, vtau_oce   ! air-ocean surface i- & j-stress              [N/m2] 
    5657   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   tmod_io              ! modulus of the ice-ocean relative velocity   [m/s] 
     
    5859   !! * Substitutions 
    5960#  include "vectopt_loop_substitute.h90" 
    60 #  include "domzgr_substitute.h90" 
    6161   !!---------------------------------------------------------------------- 
    6262   !! NEMO/LIM2 4.0 , UCL - NEMO Consortium (2011) 
     
    102102      !!--------------------------------------------------------------------- 
    103103      INTEGER, INTENT(in) ::   kt    ! number of iteration 
    104       !! 
     104      ! 
    105105      INTEGER  ::   ji, jj   ! dummy loop indices 
    106106      INTEGER  ::   ii0, ii1, ij0, ij1         ! local integers 
     
    114114      REAL(wp), POINTER, DIMENSION(:,:,:) ::   zalb, zalbp   ! 2D/3D workspace 
    115115      !!--------------------------------------------------------------------- 
    116       
     116      ! 
    117117      CALL wrk_alloc( jpi, jpj, zqnsoce ) 
    118118      CALL wrk_alloc( jpi, jpj, 1, zalb, zalbp ) 
    119  
    120       SELECT CASE( nn_ice_embd )                 ! levitating or embedded sea-ice option 
    121         CASE( 0    )   ;   zswitch = 1           ! (0) standard levitating sea-ice : salt exchange only 
    122         CASE( 1, 2 )   ;   zswitch = 0           ! (1) levitating sea-ice: salt and volume exchange but no pressure effect 
    123                                                  ! (2) embedded sea-ice : salt and volume fluxes and pressure 
    124       END SELECT                                 !     
     119      ! 
     120      SELECT CASE( nn_ice_embd )             ! levitating or embedded sea-ice option 
     121         CASE( 0    )   ;   zswitch = 1         ! (0) old levitating sea-ice : salt exchange only 
     122         CASE( 1, 2 )   ;   zswitch = 0         ! (1) levitating sea-ice: salt and volume exchange but no pressure effect 
     123         !                                      ! (2) embedded sea-ice : salt and volume fluxes and pressure 
     124      END SELECT 
    125125 
    126126      !------------------------------------------! 
     
    303303      INTEGER ,                     INTENT(in) ::   kt               ! ocean time-step index 
    304304      REAL(wp), DIMENSION(jpi,jpj), INTENT(in) ::   pu_oce, pv_oce   ! surface ocean currents 
    305       !! 
     305      ! 
    306306      INTEGER  ::   ji, jj   ! dummy loop indices 
    307307      REAL(wp) ::   zfrldu, zat_u, zu_i, zutau_ice, zu_t, zmodt   ! local scalar 
     
    435435      !! ** input   : Namelist namicedia 
    436436      !!------------------------------------------------------------------- 
    437       ! 
    438       INTEGER :: jk           ! local integer 
     437      INTEGER ::   jk   ! local integer 
     438      !!------------------------------------------------------------------- 
    439439      ! 
    440440      IF(lwp) WRITE(numout,*) 
     
    470470         sshn(:,:) = sshn(:,:) - snwice_mass(:,:) * r1_rau0 
    471471         sshb(:,:) = sshb(:,:) - snwice_mass(:,:) * r1_rau0 
    472          do jk = 1,jpkm1                     ! adjust initial vertical scale factors 
    473           fse3t_n(:,:,jk) = e3t_0(:,:,jk)*( 1._wp + sshn(:,:)*tmask(:,:,1)/(ht_0(:,:) + 1.0 - tmask(:,:,1)) ) 
    474           fse3t_b(:,:,jk) = e3t_0(:,:,jk)*( 1._wp + sshb(:,:)*tmask(:,:,1)/(ht_0(:,:) + 1.0 - tmask(:,:,1)) ) 
    475          end do 
    476          fse3t_a(:,:,:) = fse3t_b(:,:,:) 
    477          ! Reconstruction of all vertical scale factors at now and before time steps 
    478          ! ============================================================================= 
    479          ! Horizontal scale factor interpolations 
    480          ! -------------------------------------- 
    481          CALL dom_vvl_interpol( fse3t_b(:,:,:), fse3u_b(:,:,:), 'U' ) 
    482          CALL dom_vvl_interpol( fse3t_b(:,:,:), fse3v_b(:,:,:), 'V' ) 
    483          CALL dom_vvl_interpol( fse3t_n(:,:,:), fse3u_n(:,:,:), 'U' ) 
    484          CALL dom_vvl_interpol( fse3t_n(:,:,:), fse3v_n(:,:,:), 'V' ) 
    485          CALL dom_vvl_interpol( fse3u_n(:,:,:), fse3f_n(:,:,:), 'F' ) 
    486          ! Vertical scale factor interpolations 
    487          ! ------------------------------------ 
    488          CALL dom_vvl_interpol( fse3t_n(:,:,:), fse3w_n (:,:,:), 'W'  ) 
    489          CALL dom_vvl_interpol( fse3u_n(:,:,:), fse3uw_n(:,:,:), 'UW' ) 
    490          CALL dom_vvl_interpol( fse3v_n(:,:,:), fse3vw_n(:,:,:), 'VW' ) 
    491          CALL dom_vvl_interpol( fse3u_b(:,:,:), fse3uw_b(:,:,:), 'UW' ) 
    492          CALL dom_vvl_interpol( fse3v_b(:,:,:), fse3vw_b(:,:,:), 'VW' ) 
    493          ! t- and w- points depth 
    494          ! ---------------------- 
    495          fsdept_n(:,:,1) = 0.5_wp * fse3w_n(:,:,1) 
    496          fsdepw_n(:,:,1) = 0.0_wp 
    497          fsde3w_n(:,:,1) = fsdept_n(:,:,1) - sshn(:,:) 
    498          DO jk = 2, jpk 
    499             fsdept_n(:,:,jk) = fsdept_n(:,:,jk-1) + fse3w_n(:,:,jk) 
    500             fsdepw_n(:,:,jk) = fsdepw_n(:,:,jk-1) + fse3t_n(:,:,jk-1) 
    501             fsde3w_n(:,:,jk) = fsdept_n(:,:,jk  ) - sshn   (:,:) 
    502          END DO 
     472!!gm I really don't like this staff here...  Find a way to put that elsewhere or differently 
     473!!gm 
     474         IF( .NOT.ln_linssh ) THEN 
     475 
     476            do jk = 1,jpkm1                     ! adjust initial vertical scale factors 
     477               e3t_n(:,:,jk) = e3t_0(:,:,jk)*( 1._wp + sshn(:,:)*tmask(:,:,1)/(ht_0(:,:) + 1.0 - tmask(:,:,1)) ) 
     478               e3t_b(:,:,jk) = e3t_0(:,:,jk)*( 1._wp + sshb(:,:)*tmask(:,:,1)/(ht_0(:,:) + 1.0 - tmask(:,:,1)) ) 
     479            end do 
     480            e3t_a(:,:,:) = e3t_b(:,:,:) 
     481            ! Reconstruction of all vertical scale factors at now and before time steps 
     482            !        ! Horizontal scale factor interpolations 
     483            CALL dom_vvl_interpol( e3t_b(:,:,:), e3u_b(:,:,:), 'U' ) 
     484            CALL dom_vvl_interpol( e3t_b(:,:,:), e3v_b(:,:,:), 'V' ) 
     485            CALL dom_vvl_interpol( e3t_n(:,:,:), e3u_n(:,:,:), 'U' ) 
     486            CALL dom_vvl_interpol( e3t_n(:,:,:), e3v_n(:,:,:), 'V' ) 
     487            CALL dom_vvl_interpol( e3u_n(:,:,:), e3f_n(:,:,:), 'F' ) 
     488            !        ! Vertical scale factor interpolations 
     489            CALL dom_vvl_interpol( e3t_n(:,:,:), e3w_n (:,:,:), 'W'  ) 
     490            CALL dom_vvl_interpol( e3u_n(:,:,:), e3uw_n(:,:,:), 'UW' ) 
     491            CALL dom_vvl_interpol( e3v_n(:,:,:), e3vw_n(:,:,:), 'VW' ) 
     492            CALL dom_vvl_interpol( e3u_b(:,:,:), e3uw_b(:,:,:), 'UW' ) 
     493            CALL dom_vvl_interpol( e3v_b(:,:,:), e3vw_b(:,:,:), 'VW' ) 
     494            !        ! t- and w- points depth 
     495            gdept_n(:,:,1) = 0.5_wp * e3w_n(:,:,1) 
     496            gdepw_n(:,:,1) = 0.0_wp 
     497            gde3w_n(:,:,1) = gdept_n(:,:,1) - sshn(:,:) 
     498            DO jk = 2, jpk 
     499               gdept_n(:,:,jk) = gdept_n(:,:,jk-1) + e3w_n(:,:,jk) 
     500               gdepw_n(:,:,jk) = gdepw_n(:,:,jk-1) + e3t_n(:,:,jk-1) 
     501               gde3w_n(:,:,jk) = gdept_n(:,:,jk  ) - sshn   (:,:) 
     502            END DO 
     503         ENDIF 
     504!!gm end 
    503505      ENDIF 
    504506      ! 
Note: See TracChangeset for help on using the changeset viewer.