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 1218 for trunk/NEMO/LIM_SRC_2/limsbc_2.F90 – NEMO

Ignore:
Timestamp:
2008-10-28T10:12:16+01:00 (16 years ago)
Author:
smasson
Message:

first implementation of the new coupling interface in the trunk, see ticket:155

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMO/LIM_SRC_2/limsbc_2.F90

    r1173 r1218  
    2929   USE albedo           ! albedo parameters 
    3030   USE prtctl           ! Print control 
     31   USE cpl_oasis3, ONLY : lk_cpl 
    3132 
    3233   IMPLICIT NONE 
     
    8586      REAL(wp) ::   zutau , zvtau    ! lead fraction at U- & V-points 
    8687      REAL(wp) ::   zu_io , zv_io    ! 2 components of the ice-ocean velocity 
    87 #if defined key_coupled     
    88       REAL(wp), DIMENSION(jpi,jpj) ::   zalb     ! albedo of ice under overcast sky 
    89       REAL(wp), DIMENSION(jpi,jpj) ::   zalbp    ! albedo of ice under clear sky 
    90 #endif 
     88! interface 2D --> 3D 
     89      REAL(wp), DIMENSION(jpi,jpj,1) ::   zalb     ! albedo of ice under overcast sky 
     90      REAL(wp), DIMENSION(jpi,jpj,1) ::   zalbp    ! albedo of ice under clear sky 
     91      REAL(wp), DIMENSION(jpi,jpj,1) ::   zsist    ! surface ice temperature (K) 
     92      REAL(wp), DIMENSION(jpi,jpj,1) ::   zhicif   ! ice thickness 
     93      REAL(wp), DIMENSION(jpi,jpj,1) ::   zhsnif   ! snow thickness 
    9194      REAL(wp) ::   zsang, zmod, zfm 
    9295      REAL(wp), DIMENSION(jpi,jpj) ::   ztio_u, ztio_v   ! ocean stress below sea-ice 
     
    119122            ifral   = ( 1  - i1mfr * ( 1 - ial ) )    
    120123            ifrdv   = ( 1  - ifral * ( 1 - ial ) ) * iadv  
     124 
     125!!$            zinda   = 1.0 - AINT( pfrld(ji,jj) )                   !   = 0. if pure ocean else 1. (at previous time) 
     126!!$ 
     127!!$            i1mfr   = 1.0 - AINT(  frld(ji,jj) )                   !   = 0. if pure ocean else 1. (at current  time) 
     128!!$ 
     129!!$            IF( phicif(ji,jj) <= 0. ) THEN   ;   ifvt = zinda      !   = 1. if (snow and no ice at previous time) else 0. ??? 
     130!!$            ELSE                             ;   ifvt = 0. 
     131!!$            ENDIF 
     132!!$ 
     133!!$            IF( frld(ji,jj) >= pfrld(ji,jj) ) THEN   ;   idfr = 0.  !   = 0. if lead fraction increases from previous to current 
     134!!$            ELSE                                     ;   idfr = 1.    
     135!!$            ENDIF 
     136!!$ 
     137!!$            iflt    = zinda  * (1 - i1mfr) * (1 - ifvt )    !   = 1. if ice (not only snow) at previous and pure ocean at current 
     138!!$ 
     139!!$            ial     = ifvt   * i1mfr    +    ( 1 - ifvt ) * idfr 
     140!!$!                 snow no ice   ice         ice or nothing  lead fraction increases 
     141!!$!                 at previous   now           at previous 
     142!!$!                -> ice aera increases  ???         -> ice aera decreases ??? 
     143!!$ 
     144!!$            iadv    = ( 1  - i1mfr ) * zinda   
     145!!$!                     pure ocean      ice at 
     146!!$!                     at current      previous 
     147!!$!                        -> = 1. if ice disapear between previous and current 
     148!!$ 
     149!!$            ifral   = ( 1  - i1mfr * ( 1 - ial ) )   
     150!!$!                            ice at     ??? 
     151!!$!                            current          
     152!!$!                         -> ??? 
     153!!$  
     154!!$            ifrdv   = ( 1  - ifral * ( 1 - ial ) ) * iadv  
     155!!$!                                                    ice disapear                            
     156!!$ 
     157!!$ 
     158 
    121159            !   computation the solar flux at ocean surface 
    122             zqsr    = pfrld(ji,jj) * qsr(ji,jj)  + ( 1. - pfrld(ji,jj) ) * fstric(ji,jj) 
     160#if defined key_coupled  
     161            zqsr = tqsr(ji,jj) + ( fstric(ji,jj) - qsr_ice(ji,jj) ) * ( 1.0 - pfrld(ji,jj) ) 
     162#else 
     163            zqsr = pfrld(ji,jj) * qsr(ji,jj)  + ( 1.  - pfrld(ji,jj) ) * fstric(ji,jj) 
     164#endif             
    123165            !  computation the non solar heat flux at ocean surface 
    124166            zqns    =  - ( 1. - thcm(ji,jj) ) * zqsr   &   ! part of the solar energy used in leads 
     
    145187         DO ji = 1, jpi 
    146188             
     189#if defined key_coupled 
     190          zemp = emp_tot(ji,jj) - emp_ice(ji,jj) * ( 1. - pfrld(ji,jj) )    &   !  
     191             &   + rdmsnif(ji,jj) / rdt_ice                                     !  freshwaterflux due to snow melting  
     192#else 
     193!!$            !  computing freshwater exchanges at the ice/ocean interface 
     194!!$            zpme = - evap(ji,jj)    *   frld(ji,jj)           &   !  evaporation over oceanic fraction 
     195!!$               &   + tprecip(ji,jj)                           &   !  total precipitation 
     196!!$               &   - sprecip(ji,jj) * ( 1. - pfrld(ji,jj) )   &   !  remov. snow precip over ice 
     197!!$               &   - rdmsnif(ji,jj) / rdt_ice                     !  freshwaterflux due to snow melting  
    147198            !  computing freshwater exchanges at the ice/ocean interface 
    148199            zemp = + emp(ji,jj)     *         frld(ji,jj)      &   !  e-p budget over open ocean fraction  
     
    151202               &   + rdmsnif(ji,jj) / rdt_ice                      !  freshwaterflux due to snow melting  
    152203               !                                                   !  ice-covered fraction: 
     204#endif             
    153205 
    154206            !  computing salt exchanges at the ice/ocean interface 
     
    217269 
    218270      fr_i  (:,:) = 1.0 - frld(:,:)       ! sea-ice fraction 
    219       tn_ice(:,:) = sist(:,:)             ! sea-ice surface temperature                       
    220  
    221 #if defined key_coupled             
    222       !------------------------------------------------! 
    223       !    Computation of snow/ice and ocean albedo    ! 
    224       !------------------------------------------------! 
    225       zalb  (:,:) = 0.e0 
    226       zalbp (:,:) = 0.e0 
    227  
    228       CALL albedo_ice( sist, hicif, hsnif, zalbp, zalb ) 
    229  
    230       alb_ice(:,:) =  0.5 * zalbp(:,:) + 0.5 * zalb (:,:)   ! Ice albedo (mean clear and overcast skys) 
    231 #endif 
     271 
     272      IF ( lk_cpl ) THEN            
     273         ! Ice surface temperature  
     274         tn_ice(:,:) = sist(:,:)          ! sea-ice surface temperature        
     275         ! Computation of snow/ice and ocean albedo 
     276         ! INTERFACE 3D versus 2D 
     277         zsist (:,:,1) = sist (:,:) 
     278         zhicif(:,:,1) = hicif(:,:)   ;   zhsnif(:,:,1) = hsnif(:,:) 
     279         CALL albedo_ice( zsist, zhicif, zhsnif, zalbp, zalb ) 
     280         alb_ice(:,:) =  0.5 * ( zalbp(:,:,1) + zalb (:,:,1) )   ! Ice albedo (mean clear and overcast skys) 
     281      ENDIF 
    232282 
    233283      IF(ln_ctl) THEN 
Note: See TracChangeset for help on using the changeset viewer.