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 8637 for branches/2017/dev_r7881_ENHANCE09_RK3/NEMOGCM/NEMO/OPA_SRC/SBC/sbccpl.F90 – NEMO

Ignore:
Timestamp:
2017-10-18T19:14:32+02:00 (7 years ago)
Author:
gm
Message:

#1911 (ENHANCE-09): PART I.3 - phasing with updated branch dev_r8183_ICEMODEL revision 8626

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2017/dev_r7881_ENHANCE09_RK3/NEMOGCM/NEMO/OPA_SRC/SBC/sbccpl.F90

    r8586 r8637  
    3333   USE geo2ocean      !  
    3434   USE oce   , ONLY : tsn, un, vn, sshn, ub, vb, sshb, fraqsr_1lev 
    35    USE albedooce      !  
     35   USE ocealb         !  
    3636   USE eosbn2         !  
    3737   USE sbcrnf, ONLY : l_rnfcpl 
     
    173173                                         !   -> file cplmask.nc with the float variable called cplmask (jpi,jpj,nn_cplmodel) 
    174174   TYPE ::   DYNARR      
    175       REAL(wp), POINTER, DIMENSION(:,:,:)    ::   z3    
     175      REAL(wp), POINTER, DIMENSION(:,:,:) ::   z3    
    176176   END TYPE DYNARR 
    177177 
    178178   TYPE( DYNARR ), SAVE, DIMENSION(jprcv) ::   frcv                     ! all fields recieved from the atmosphere 
    179179 
    180    REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   albedo_oce_mix    ! ocean albedo sent to atmosphere (mix clear/overcast sky) 
     180   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   alb_oce_mix    ! ocean albedo sent to atmosphere (mix clear/overcast sky) 
    181181 
    182182   REAL(wp) ::   rpref = 101000._wp   ! reference atmospheric pressure[N/m2]  
     
    202202      ierr(:) = 0 
    203203      ! 
    204       ALLOCATE( albedo_oce_mix(jpi,jpj), nrcvinfo(jprcv),  STAT=ierr(1) ) 
     204      ALLOCATE( alb_oce_mix(jpi,jpj), nrcvinfo(jprcv),  STAT=ierr(1) ) 
    205205       
    206206#if ! defined key_lim3 && ! defined key_cice 
     
    736736      !     2. receiving mixed oce-ice solar radiation  
    737737      IF ( TRIM ( sn_snd_alb%cldes ) == 'mixed oce-ice' .OR. TRIM ( sn_rcv_qsr%cldes ) == 'mixed oce-ice' ) THEN 
    738          CALL albedo_oce( zaos, zacs ) 
     738         CALL oce_alb( zaos, zacs ) 
    739739         ! Due to lack of information on nebulosity : mean clear/overcast sky 
    740          albedo_oce_mix(:,:) = ( zacs(:,:) + zaos(:,:) ) * 0.5 
     740         alb_oce_mix(:,:) = ( zacs(:,:) + zaos(:,:) ) * 0.5 
    741741      ENDIF 
    742742 
     
    18851885!       ( see OASIS3 user guide, 5th edition, p39 ) 
    18861886         zqsr_ice(:,:,1) = frcv(jpr_qsrmix)%z3(:,:,1) * ( 1.- palbi(:,:,1) )   & 
    1887             &            / (  1.- ( albedo_oce_mix(:,:  ) * ziceld(:,:)       & 
    1888             &                     + palbi         (:,:,1) * picefr(:,:) ) ) 
     1887            &            / (  1.- ( alb_oce_mix(:,:  ) * ziceld(:,:)       & 
     1888            &                     + palbi      (:,:,1) * picefr(:,:) ) ) 
    18891889      END SELECT 
    18901890      IF( ln_dm2dc .AND. ln_cpl ) THEN   ! modify qsr to include the diurnal cycle 
     
    20522052                   ztmp1(:,:) = SUM( alb_ice (:,:,1:jpl) * a_i(:,:,1:jpl), dim=3 ) / SUM( a_i(:,:,1:jpl), dim=3 ) 
    20532053                ELSEWHERE 
    2054                    ztmp1(:,:) = albedo_oce_mix(:,:) 
     2054                   ztmp1(:,:) = alb_oce_mix(:,:) 
    20552055                END WHERE 
    20562056             CASE default   ;   CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_alb%clcat' ) 
     
    20802080 
    20812081      IF( ssnd(jps_albmix)%laction ) THEN                         ! mixed ice-ocean 
    2082          ztmp1(:,:) = albedo_oce_mix(:,:) * zfr_l(:,:) 
     2082         ztmp1(:,:) = alb_oce_mix(:,:) * zfr_l(:,:) 
    20832083         DO jl=1,jpl 
    20842084            ztmp1(:,:) = ztmp1(:,:) + alb_ice(:,:,jl) * a_i(:,:,jl) 
    2085          ENDDO 
     2085         END DO 
    20862086         CALL cpl_snd( jps_albmix, isec, RESHAPE ( ztmp1, (/jpi,jpj,1/) ), info ) 
    20872087      ENDIF 
Note: See TracChangeset for help on using the changeset viewer.