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 4730 for branches/2014/dev_4728_CNRS04_coupled_interface/NEMOGCM/NEMO/LIM_SRC_3 – NEMO

Ignore:
Timestamp:
2014-07-25T09:39:23+02:00 (10 years ago)
Author:
vancop
Message:

coupled interface modifications for LIM3

Location:
branches/2014/dev_4728_CNRS04_coupled_interface/NEMOGCM/NEMO/LIM_SRC_3
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • branches/2014/dev_4728_CNRS04_coupled_interface/NEMOGCM/NEMO/LIM_SRC_3/limistate.F90

    r4688 r4730  
    115115 
    116116      CALL lim_istate_init     !  reading the initials parameters of the ice 
    117  
    118 # if defined key_coupled 
    119       albege(:,:)   = 0.8 * tms(:,:) 
    120 # endif 
    121117 
    122118      ! surface temperature 
  • branches/2014/dev_4728_CNRS04_coupled_interface/NEMOGCM/NEMO/LIM_SRC_3/limsbc.F90

    r4688 r4730  
    102102      !! References : Goosse, H. et al. 1996, Bul. Soc. Roy. Sc. Liege, 65, 87-90. 
    103103      !!              Tartinville et al. 2001 Ocean Modelling, 3, 95-108. 
     104      !!              These refs are now obsolete since everything has been revised 
     105      !!              The ref should be Rousset et al., 2015? 
    104106      !!--------------------------------------------------------------------- 
    105       INTEGER, INTENT(in) ::   kt    ! number of iteration 
    106       ! 
    107       INTEGER  ::   ji, jj, jl, jk           ! dummy loop indices 
    108       REAL(wp) ::   zinda, zemp      ! local scalars 
    109       REAL(wp) ::   zf_mass         ! Heat flux associated with mass exchange ice->ocean (W.m-2) 
    110       REAL(wp) ::   zfcm1           ! New solar flux received by the ocean 
    111       REAL(wp), POINTER, DIMENSION(:,:,:) ::   zalb, zalbp     ! 2D/3D workspace 
     107      INTEGER, INTENT(in) ::   kt                                   ! number of iteration 
     108      ! 
     109      INTEGER  ::   ji, jj, jl, jk                                  ! dummy loop indices 
     110      ! 
     111      REAL(wp) ::   zinda, zemp                                     !  local scalars 
     112      REAL(wp) ::   zf_mass                                         ! Heat flux associated with mass exchange ice->ocean (W.m-2) 
     113      REAL(wp) ::   zfcm1                                           ! New solar flux received by the ocean 
     114      ! 
     115      REAL(wp), POINTER, DIMENSION(:,:,:) ::   zalb_cs, zalb_os     ! 2D/3D workspace 
    112116      !!--------------------------------------------------------------------- 
    113        
    114       IF( lk_cpl )   CALL wrk_alloc( jpi, jpj, jpl, zalb, zalbp ) 
    115117 
    116118      ! make calls for heat fluxes before it is modified 
     
    134136            ! Solar heat flux reaching the ocean = zfcm1 (W.m-2)  
    135137            !--------------------------------------------------- 
    136             IF( lk_cpl ) THEN ! be carfeful: not been tested yet 
     138            IF( lk_cpl ) THEN ! be careful: not been tested yet 
    137139               ! original line 
    138140               zfcm1 = qsr_tot(ji,jj) 
    139                !!!zfcm1 = qsr_tot(ji,jj) + ftr_ice(ji,jj) * ( 1._wp - pfrld(ji,jj) ) / ( 1._wp - zinda + zinda * iatte(ji,jj) ) 
     141               !!! LIM2 version zqsr = qsr_tot(ji,jj) + ( fstric(ji,jj) - qsr_ice(ji,jj,1) ) * ( 1.0 - pfrld(ji,jj) ) 
    140142               DO jl = 1, jpl 
    141                   zfcm1 = zfcm1 - ( qsr_ice(ji,jj,jl) - ftr_ice(ji,jj,jl) ) * old_a_i(ji,jj,jl) 
     143                  zfcm1 = zfcm1 + ( ftr_ice(ji,jj,jl) - qsr_ice(ji,jj,jl) ) * old_a_i(ji,jj,jl) 
    142144               END DO 
    143145            ELSE 
    144                !!!zfcm1   = pfrld(ji,jj) * qsr(ji,jj)  + & 
    145                !!!     &    ( 1._wp - pfrld(ji,jj) ) * ftr_ice(ji,jj) / ( 1._wp - zinda + zinda * iatte(ji,jj) ) 
     146               !!! LIM2 version zqsr = pfrld(ji,jj) * qsr(ji,jj)  + ( 1.  - pfrld(ji,jj) ) * fstric(ji,jj) 
    146147               zfcm1   = pfrld(ji,jj) * qsr(ji,jj) 
    147148               DO jl = 1, jpl 
     
    215216 
    216217      !------------------------------------------------! 
    217       !    Computation of snow/ice and ocean albedo    ! 
     218      !    Snow/ice albedo (only if sent to coupler)   ! 
    218219      !------------------------------------------------! 
    219220      IF( lk_cpl ) THEN          ! coupled case 
    220          CALL albedo_ice( t_su, ht_i, ht_s, zalbp, zalb )                  ! snow/ice albedo 
    221          alb_ice(:,:,:) =  0.5_wp * zalbp(:,:,:) + 0.5_wp * zalb (:,:,:)   ! Ice albedo (mean clear and overcast skys) 
     221 
     222            CALL wrk_alloc( jpi, jpj, jpl, zalb_cs, zalb_os ) 
     223 
     224            CALL albedo_ice( t_su, ht_i, ht_s, zalb_cs, zalb_os )  ! cloud-sky and overcast-sky ice albedos 
     225 
     226            alb_ice(:,:,:) = ( 1. - cldf_ice ) * zalb_cs(:,:,:) + cldf_ice * zalb_os(:,:,:) 
     227 
     228            CALL wrk_dealloc( jpi, jpj, jpl, zalb_cs, zalb_os ) 
     229 
    222230      ENDIF 
    223231 
     
    229237         CALL prt_ctl( tab3d_1=tn_ice, clinfo1=' lim_sbc: tn_ice : ', kdim=jpl ) 
    230238      ENDIF 
    231       ! 
    232       IF( lk_cpl )   CALL wrk_dealloc( jpi, jpj, jpl, zalb, zalbp ) 
    233       !  
     239 
    234240   END SUBROUTINE lim_sbc_flx 
    235241 
Note: See TracChangeset for help on using the changeset viewer.