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

Changeset 4935


Ignore:
Timestamp:
2014-12-01T12:12:26+01:00 (9 years ago)
Author:
smasson
Message:

dev_CNRS_CICE: small cleaning and bugfix

Location:
branches/2014/dev_CNRS_CICE/NEMOGCM/NEMO/OPA_SRC/SBC
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • branches/2014/dev_CNRS_CICE/NEMOGCM/NEMO/OPA_SRC/SBC/sbc_ice.F90

    r4933 r4935  
    5656# endif 
    5757 
    58 #if defined key_lim3 || defined key_lim2  
    5958   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   qns_ice        !: non solar heat flux over ice                  [W/m2] 
    6059   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   qsr_ice        !: solar heat flux over ice                      [W/m2] 
     
    7170   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   fr2_i0         !: Solar surface transmission parameter, thin ice   [-] 
    7271   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   emp_ice        !: sublimation - precip over sea ice            [kg/m2] 
    73    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   qemp_ice       !: heat associated with emp over sea ice         [W/m2] 
    7472 
    75 # if defined key_lim3 
    76    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   tatm_ice       !: air temperature [K] 
    77 # endif 
     73   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   topmelt            !: category topmelt 
     74   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   botmelt            !: category botmelt 
    7875 
    79 #elif defined key_cice 
     76#if defined key_cice 
    8077   ! 
    8178   ! for consistency with LIM, these are declared with three dimensions 
    8279   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   qlw_ice            !: incoming long-wave 
    83    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   qla_ice            !: latent flux over ice           [W/m2] 
    84    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   qsr_ice            !: solar heat flux over ice       [W/m2] 
    8580   ! 
    8681   ! other forcing arrays are two dimensional 
     
    8883   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   ss_iov             !: y ice-ocean surface stress at NEMO V point 
    8984   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   emp_ice            !: sublimation-snow budget over ice    [kg/m2] 
    90    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   tatm_ice           !: air temperature 
    9185   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   qatm_ice           !: specific humidity 
    9286   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   wndi_ice           !: i wind at T point 
     
    9589   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   fr_iu              !: ice fraction at NEMO U point 
    9690   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   fr_iv              !: ice fraction at NEMO V point 
    97    ! 
    98    ! finally, arrays corresponding to different ice categories 
    99    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   a_i                !: category ice fraction 
    100    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   topmelt            !: category topmelt 
    101    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   botmelt            !: category botmelt 
    102  
     91    
    10392   ! variables used in the coupled interface 
    10493   INTEGER , PUBLIC, PARAMETER ::   jpl = ncat 
    105    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   u_ice, v_ice,fr1_i0,fr2_i0          ! jpi, jpj 
    106    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   tn_ice, alb_ice, qns_ice, dqns_ice  ! (jpi,jpj,jpl) 
    107    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   emp_ice 
    108    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   qsr_ice 
     94   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   u_ice, v_ice          ! jpi, jpj 
    10995#endif 
    11096    
    111 #if defined key_lim2 
     97#if defined key_lim2 || defined key_cice 
     98   ! already defined in ice.F90 for LIM3 
    11299   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::  a_i 
    113 #endif 
    114  
    115 #if ! defined key_lim3 
    116100   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::  ht_i, ht_s 
    117101#endif 
    118102 
    119 #if ! defined key_cice 
    120    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::  topmelt, botmelt 
     103#if defined key_lim3 || defined key_cice 
     104   ! not used with LIM2 
     105   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   tatm_ice       !: air temperature [K] 
    121106#endif 
    122107 
     
    138123      ierr(:) = 0 
    139124 
    140 #if defined key_lim3 || defined key_lim2 
    141       ALLOCATE( qns_ice (jpi,jpj,jpl) , qsr_ice (jpi,jpj,jpl) ,     & 
     125      ALLOCATE( qsr_ice (jpi,jpj,jpl)                         ,     & 
    142126         &      qla_ice (jpi,jpj,jpl) , dqla_ice(jpi,jpj,jpl) ,     & 
    143          &      dqns_ice(jpi,jpj,jpl) , tn_ice  (jpi,jpj,jpl) ,     & 
    144          &      alb_ice (jpi,jpj,jpl) ,                             & 
    145127         &      utau_ice(jpi,jpj)     , vtau_ice(jpi,jpj)     ,     & 
    146          &      fr1_i0  (jpi,jpj)     , fr2_i0  (jpi,jpj)     ,     & 
    147 #if defined key_lim3 
     128#if defined key_lim3 || defined key_cice 
    148129         &      tatm_ice(jpi,jpj)     ,                             & 
    149130#endif 
    150          &      emp_ice(jpi,jpj)      , qemp_ice(jpi,jpj)     , STAT= ierr(1) ) 
    151 #elif defined key_cice 
    152       ALLOCATE( qla_ice(jpi,jpj,1)    , qlw_ice(jpi,jpj,1)    , qsr_ice(jpi,jpj,1)    , & 
    153                 wndi_ice(jpi,jpj)     , tatm_ice(jpi,jpj)     , qatm_ice(jpi,jpj)     , & 
     131         &      STAT= ierr(1) ) 
     132#if defined key_cice 
     133      ALLOCATE( qlw_ice(jpi,jpj,1)    , wndi_ice(jpi,jpj)     , qatm_ice(jpi,jpj)     , & 
    154134                wndj_ice(jpi,jpj)     , nfrzmlt(jpi,jpj)      , ss_iou(jpi,jpj)       , & 
    155135                ss_iov(jpi,jpj)       , fr_iu(jpi,jpj)        , fr_iv(jpi,jpj)        , & 
     
    161141         &                     STAT= ierr(2) ) 
    162142       
     143#else 
     144      ALLOCATE( fr1_i0(jpi,jpj)       , tn_ice (jpi,jpj,1)    , & 
     145         &      fr2_i0(jpi,jpj)       , alb_ice(jpi,jpj,1)    , & 
     146         &      emp_ice(jpi,jpj)      , qns_ice(jpi,jpj,1)    , dqns_ice(jpi,jpj,1)   , & 
     147         &      STAT= ierr(2) ) 
    163148#endif 
    164149         ! 
  • branches/2014/dev_CNRS_CICE/NEMOGCM/NEMO/OPA_SRC/SBC/sbccpl.F90

    r4933 r4935  
    160160       
    161161#if ! defined key_lim3 && ! defined key_lim2 && ! defined key_cice 
    162       ALLOCATE( a_i(jpi,jpj,1) , STAT=ierr(2) ) 
     162      ALLOCATE( a_i(jpi,jpj,1) , STAT=ierr(2) )  ! used in sbcice_if.F90 (done here as there is no sbc_ice_if_init) 
    163163#endif 
    164164      ALLOCATE( xcplmask(jpi,jpj,nn_cplmodel) , STAT=ierr(3) ) 
     
    454454      END DO 
    455455      ! Allocate taum part of frcv which is used even when not received as coupling field 
    456       IF ( .NOT. srcv(jpr_taum)%laction ) ALLOCATE( frcv(jpr_taum)%z3(jpi,jpj,srcv(jn)%nct) ) 
     456      IF ( .NOT. srcv(jpr_taum)%laction ) ALLOCATE( frcv(jpr_taum)%z3(jpi,jpj,srcv(jpr_taum)%nct) ) 
    457457      ! Allocate itx1 and ity1 as they are used in sbc_cpl_ice_tau even if srcv(jpr_itx1)%laction = .FALSE. 
    458458      IF( k_ice /= 0 ) THEN 
    459          IF ( .NOT. srcv(jpr_itx1)%laction ) ALLOCATE( frcv(jpr_itx1)%z3(jpi,jpj,srcv(jn)%nct) ) 
    460          IF ( .NOT. srcv(jpr_ity1)%laction ) ALLOCATE( frcv(jpr_ity1)%z3(jpi,jpj,srcv(jn)%nct) ) 
     459         IF ( .NOT. srcv(jpr_itx1)%laction ) ALLOCATE( frcv(jpr_itx1)%z3(jpi,jpj,srcv(jpr_itx1)%nct) ) 
     460         IF ( .NOT. srcv(jpr_ity1)%laction ) ALLOCATE( frcv(jpr_ity1)%z3(jpi,jpj,srcv(jpr_ity1)%nct) ) 
    461461      END IF 
    462462 
Note: See TracChangeset for help on using the changeset viewer.