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 4859 for branches/2014/dev_4728_CNRS04_coupled_interface/NEMOGCM/NEMO/OPA_SRC/SBC/sbccpl.F90 – NEMO

Ignore:
Timestamp:
2014-11-14T21:43:49+01:00 (9 years ago)
Author:
smasson
Message:

dev_4728_CNRS04_coupled_interface: cleaning of the coupling interface for OASIS3-MCT. 2

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2014/dev_4728_CNRS04_coupled_interface/NEMOGCM/NEMO/OPA_SRC/SBC/sbccpl.F90

    r4857 r4859  
    133133   INTEGER , ALLOCATABLE, SAVE, DIMENSION(    :) ::   nrcvinfo           ! OASIS info argument 
    134134 
    135 #if ! defined key_lim2   &&   ! defined key_lim3 
    136    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   u_ice, v_ice,fr1_i0,fr2_i0          ! jpi, jpj 
    137    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   tn_ice, alb_ice, qns_ice, dqns_ice  ! (jpi,jpj,jpl) 
    138 #endif 
    139  
    140 #if defined key_cice 
    141    INTEGER, PARAMETER ::   jpl = ncat 
    142 #elif ! defined key_lim2   &&   ! defined key_lim3 
    143    INTEGER, PARAMETER ::   jpl = 1  
    144    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   emp_ice 
    145    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   qsr_ice 
    146 #endif 
    147  
    148 #if ! defined key_lim3   &&  ! defined key_cice 
    149    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::  a_i 
    150 #endif 
    151  
    152 #if ! defined key_lim3 
    153    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::  ht_i, ht_s 
    154 #endif 
    155  
    156 #if ! defined key_cice 
    157    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::  topmelt, botmelt 
    158 #endif 
    159  
    160135   !! Substitution 
    161136#  include "vectopt_loop_substitute.h90" 
     
    172147      !!             ***  FUNCTION sbc_cpl_alloc  *** 
    173148      !!---------------------------------------------------------------------- 
    174       INTEGER :: ierr(4),jn 
     149      INTEGER :: ierr(2),jn 
    175150      !!---------------------------------------------------------------------- 
    176151      ierr(:) = 0 
    177152      ! 
    178153      ALLOCATE( albedo_oce_mix(jpi,jpj), nrcvinfo(jprcv),  STAT=ierr(1) ) 
    179       ! 
    180 #if ! defined key_lim2 && ! defined key_lim3 
    181       ! quick patch to be able to run the coupled model without sea-ice... 
    182       ALLOCATE( u_ice(jpi,jpj) , fr1_i0(jpi,jpj) , tn_ice (jpi,jpj,1) ,     & 
    183                 v_ice(jpi,jpj) , fr2_i0(jpi,jpj) , alb_ice(jpi,jpj,1),      & 
    184                 emp_ice(jpi,jpj) , qns_ice(jpi,jpj,1) , dqns_ice(jpi,jpj,1) , STAT=ierr(2) ) 
     154       
     155#if ! defined key_lim3 && ! defined key_lim2 && ! defined key_cice 
     156      ALLOCATE( a_i(jpi,jpj,1) , STAT=ierr(2) ) 
    185157#endif 
    186  
    187 #if ! defined key_lim3 && ! defined key_cice 
    188       ALLOCATE( a_i(jpi,jpj,jpl) , STAT=ierr(3) ) 
    189 #endif 
    190  
    191 #if defined key_cice || defined key_lim2 
    192       ALLOCATE( ht_i(jpi,jpj,jpl) , ht_s(jpi,jpj,jpl) , STAT=ierr(4) ) 
    193 #endif 
     158      ! 
    194159      sbc_cpl_alloc = MAXVAL( ierr ) 
    195160      IF( lk_mpp            )   CALL mpp_sum ( sbc_cpl_alloc ) 
     
    904869      CALL wrk_alloc( jpi,jpj, ztx, zty ) 
    905870 
    906 !AC Pour eviter un stress nul sur la glace dans le cas mixed oce-ice 
    907       IF( srcv(jpr_itx1)%laction .AND. TRIM( sn_rcv_tau%cldes ) == 'oce and ice') THEN   ;   itx =  jpr_itx1    
     871      IF( srcv(jpr_itx1)%laction ) THEN   ;   itx =  jpr_itx1    
    908872      ELSE                                ;   itx =  jpr_otx1 
    909873      ENDIF 
     
    912876      IF(  nrcvinfo(itx) == OASIS_Rcv ) THEN 
    913877 
    914          !                                                                                              ! ======================= ! 
    915 !AC Pour eviter un stress nul sur la glace dans le cas mixes oce-ice 
    916          IF( srcv(jpr_itx1)%laction .AND. TRIM( sn_rcv_tau%cldes ) == 'oce and ice') THEN               !   ice stress received   ! 
    917             !                                                                                           ! ======================= ! 
     878         !                                                      ! ======================= ! 
     879         IF( srcv(jpr_itx1)%laction ) THEN                      !   ice stress received   ! 
     880            !                                                   ! ======================= ! 
    918881            !   
    919882            IF( TRIM( sn_rcv_tau%clvref ) == 'cartesian' ) THEN            ! 2 components on the sphere 
     
    12861249      ENDIF 
    12871250 
    1288       SELECT CASE( TRIM( sn_rcv_dqnsdt%cldes ) ) 
     1251      !                                                      ! ========================= ! 
     1252      SELECT CASE( TRIM( sn_rcv_dqnsdt%cldes ) )             !          d(qns)/dt        ! 
     1253      !                                                      ! ========================= ! 
    12891254      CASE ('coupled') 
    12901255         IF ( TRIM(sn_rcv_dqnsdt%clcat) == 'yes' ) THEN 
     
    12981263      END SELECT 
    12991264 
    1300       SELECT CASE( TRIM( sn_rcv_iceflx%cldes ) ) 
     1265      !                                                      ! ========================= ! 
     1266      SELECT CASE( TRIM( sn_rcv_iceflx%cldes ) )             !    topmelt and botmelt    ! 
     1267      !                                                      ! ========================= ! 
    13011268      CASE ('coupled') 
    13021269         topmelt(:,:,:)=frcv(jpr_topm)%z3(:,:,:) 
     
    13431310 
    13441311      zfr_l(:,:) = 1.- fr_i(:,:) 
    1345  
    13461312      !                                                      ! ------------------------- ! 
    13471313      !                                                      !    Surface temperature    !   in Kelvin 
     
    13721338         IF( ssnd(jps_tmix)%laction )   CALL cpl_snd( jps_tmix, isec, RESHAPE ( ztmp1, (/jpi,jpj,1/) ), info ) 
    13731339      ENDIF 
    1374       ! 
    13751340      !                                                      ! ------------------------- ! 
    13761341      !                                                      !           Albedo          ! 
Note: See TracChangeset for help on using the changeset viewer.