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 4901 for branches/2014/dev_CNRS_2014/NEMOGCM/NEMO/OPA_SRC/SBC/sbcice_cice.F90 – NEMO

Ignore:
Timestamp:
2014-11-27T16:41:22+01:00 (10 years ago)
Author:
cetlod
Message:

2014/dev_CNRS_2014 : merge the 3rd branch onto dev_CNRS_2014, see ticket #1415

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2014/dev_CNRS_2014/NEMOGCM/NEMO/OPA_SRC/SBC/sbcice_cice.F90

    r4897 r4901  
    9595   END FUNCTION sbc_ice_cice_alloc 
    9696 
    97    SUBROUTINE sbc_ice_cice( kt, nsbc ) 
     97   SUBROUTINE sbc_ice_cice( kt, ksbc ) 
    9898      !!--------------------------------------------------------------------- 
    9999      !!                  ***  ROUTINE sbc_ice_cice  *** 
     
    113113      !!--------------------------------------------------------------------- 
    114114      INTEGER, INTENT(in) ::   kt      ! ocean time step 
    115       INTEGER, INTENT(in) ::   nsbc    ! surface forcing type 
     115      INTEGER, INTENT(in) ::   ksbc    ! surface forcing type 
    116116      !!---------------------------------------------------------------------- 
    117117      ! 
     
    123123 
    124124         ! Make sure any fluxes required for CICE are set 
    125          IF ( nsbc == 2 ) THEN 
     125         IF      ( ksbc == jp_flx ) THEN 
    126126            CALL cice_sbc_force(kt) 
    127          ELSE IF ( nsbc == 5 ) THEN 
     127         ELSE IF ( ksbc == jp_cpl ) THEN 
    128128            CALL sbc_cpl_ice_flx( 1.0-fr_i  ) 
    129129         ENDIF 
    130130 
    131          CALL cice_sbc_in ( kt, nsbc ) 
     131         CALL cice_sbc_in  ( kt, ksbc ) 
    132132         CALL CICE_Run 
    133          CALL cice_sbc_out ( kt, nsbc ) 
    134  
    135          IF ( nsbc == 5 )  CALL cice_sbc_hadgam(kt+1) 
     133         CALL cice_sbc_out ( kt, ksbc ) 
     134 
     135         IF ( ksbc == jp_cpl )  CALL cice_sbc_hadgam(kt+1) 
    136136 
    137137      ENDIF                                          ! End sea-ice time step only 
     
    141141   END SUBROUTINE sbc_ice_cice 
    142142 
    143    SUBROUTINE cice_sbc_init (nsbc) 
     143   SUBROUTINE cice_sbc_init (ksbc) 
    144144      !!--------------------------------------------------------------------- 
    145145      !!                    ***  ROUTINE cice_sbc_init  *** 
    146146      !! ** Purpose: Initialise ice related fields for NEMO and coupling 
    147147      !! 
    148       INTEGER, INTENT( in  ) ::   nsbc                ! surface forcing type 
     148      INTEGER, INTENT( in  ) ::   ksbc                ! surface forcing type 
    149149      REAL(wp), DIMENSION(:,:), POINTER :: ztmp1, ztmp2 
    150150      REAL(wp) ::   zcoefu, zcoefv, zcoeff            ! local scalar 
     
    165165 
    166166! Do some CICE consistency checks 
    167       IF ( (nsbc == 2) .OR. (nsbc == 5) ) THEN 
     167      IF ( (ksbc == jp_flx) .OR. (ksbc == jp_cpl) ) THEN 
    168168         IF ( calc_strair .OR. calc_Tsfc ) THEN 
    169169            CALL ctl_stop( 'STOP', 'cice_sbc_init : Forcing option requires calc_strair=F and calc_Tsfc=F in ice_in' ) 
    170170         ENDIF 
    171       ELSEIF (nsbc == 4) THEN 
     171      ELSEIF (ksbc == jp_core) THEN 
    172172         IF ( .NOT. (calc_strair .AND. calc_Tsfc) ) THEN 
    173173            CALL ctl_stop( 'STOP', 'cice_sbc_init : Forcing option requires calc_strair=T and calc_Tsfc=T in ice_in' ) 
     
    190190 
    191191      CALL cice2nemo(aice,fr_i, 'T', 1. ) 
    192       IF ( (nsbc == 2).OR.(nsbc == 5) ) THEN 
     192      IF ( (ksbc == jp_flx) .OR. (ksbc == jp_cpl) ) THEN 
    193193         DO jl=1,ncat 
    194194            CALL cice2nemo(aicen(:,:,jl,:),a_i(:,:,jl), 'T', 1. ) 
     
    232232 
    233233    
    234    SUBROUTINE cice_sbc_in (kt, nsbc) 
     234   SUBROUTINE cice_sbc_in (kt, ksbc) 
    235235      !!--------------------------------------------------------------------- 
    236236      !!                    ***  ROUTINE cice_sbc_in  *** 
     
    238238      !!--------------------------------------------------------------------- 
    239239      INTEGER, INTENT(in   ) ::   kt   ! ocean time step 
    240       INTEGER, INTENT(in   ) ::   nsbc ! surface forcing type 
     240      INTEGER, INTENT(in   ) ::   ksbc ! surface forcing type 
    241241 
    242242      INTEGER  ::   ji, jj, jl                   ! dummy loop indices       
     
    262262! forced and coupled case  
    263263 
    264       IF ( (nsbc == 2).OR.(nsbc == 5) ) THEN 
     264      IF ( (ksbc == jp_flx).OR.(ksbc == jp_cpl) ) THEN 
    265265 
    266266         ztmpn(:,:,:)=0.0 
     
    287287 
    288288! Surface downward latent heat flux (CI_5) 
    289          IF (nsbc == 2) THEN 
     289         IF (ksbc == jp_flx) THEN 
    290290            DO jl=1,ncat 
    291291               ztmpn(:,:,jl)=qla_ice(:,:,1)*a_i(:,:,jl) 
     
    316316! GBM conductive flux through ice (CI_6) 
    317317!  Convert to GBM 
    318             IF (nsbc == 2) THEN 
     318            IF (ksbc == jp_flx) THEN 
    319319               ztmp(:,:) = botmelt(:,:,jl)*a_i(:,:,jl) 
    320320            ELSE 
     
    325325! GBM surface heat flux (CI_7) 
    326326!  Convert to GBM 
    327             IF (nsbc == 2) THEN 
     327            IF (ksbc == jp_flx) THEN 
    328328               ztmp(:,:) = (topmelt(:,:,jl)+botmelt(:,:,jl))*a_i(:,:,jl)  
    329329            ELSE 
     
    333333         ENDDO 
    334334 
    335       ELSE IF (nsbc == 4) THEN 
     335      ELSE IF (ksbc == jp_core) THEN 
    336336 
    337337! Pass CORE forcing fields to CICE (which will calculate heat fluxes etc itself) 
     
    458458 
    459459 
    460    SUBROUTINE cice_sbc_out (kt,nsbc) 
     460   SUBROUTINE cice_sbc_out (kt,ksbc) 
    461461      !!--------------------------------------------------------------------- 
    462462      !!                    ***  ROUTINE cice_sbc_out  *** 
     
    464464      !!--------------------------------------------------------------------- 
    465465      INTEGER, INTENT( in  ) ::   kt   ! ocean time step 
    466       INTEGER, INTENT( in  ) ::   nsbc ! surface forcing type 
     466      INTEGER, INTENT( in  ) ::   ksbc ! surface forcing type 
    467467       
    468468      INTEGER  ::   ji, jj, jl                 ! dummy loop indices 
     
    510510! Freshwater fluxes  
    511511 
    512       IF (nsbc == 2) THEN 
     512      IF (ksbc == jp_flx) THEN 
    513513! Note that emp from the forcing files is evap*(1-aice)-(tprecip-aice*sprecip) 
    514514! What we want here is evap*(1-aice)-tprecip*(1-aice) hence manipulation below 
     
    516516! Better to use evap and tprecip? (but for now don't read in evap in this case) 
    517517         emp(:,:)  = emp(:,:)+fr_i(:,:)*(tprecip(:,:)-sprecip(:,:)) 
    518       ELSE IF (nsbc == 4) THEN 
     518      ELSE IF (ksbc == jp_core) THEN 
    519519         emp(:,:)  = (1.0-fr_i(:,:))*emp(:,:)         
    520       ELSE IF (nsbc ==5) THEN 
     520      ELSE IF (ksbc == jp_cpl) THEN 
    521521! emp_tot is set in sbc_cpl_ice_flx (called from cice_sbc_in above)  
    522522! This is currently as required with the coupling fields from the UM atmosphere 
     
    543543! Scale qsr and qns according to ice fraction (bulk formulae only) 
    544544 
    545       IF (nsbc == 4) THEN 
     545      IF (ksbc == jp_core) THEN 
    546546         qsr(:,:)=qsr(:,:)*(1.0-fr_i(:,:)) 
    547547         qns(:,:)=qns(:,:)*(1.0-fr_i(:,:)) 
    548548      ENDIF 
    549549! Take into account snow melting except for fully coupled when already in qns_tot 
    550       IF (nsbc == 5) THEN 
     550      IF (ksbc == jp_cpl) THEN 
    551551         qsr(:,:)= qsr_tot(:,:) 
    552552         qns(:,:)= qns_tot(:,:) 
     
    575575 
    576576      CALL cice2nemo(aice,fr_i,'T', 1. ) 
    577       IF ( (nsbc == 2).OR.(nsbc == 5) ) THEN 
     577      IF ( (ksbc == jp_flx).OR.(ksbc == jp_cpl) ) THEN 
    578578         DO jl=1,ncat 
    579579            CALL cice2nemo(aicen(:,:,jl,:),a_i(:,:,jl), 'T', 1. ) 
     
    611611 
    612612 
    613 #if defined key_oasis3 || defined key_oasis4 
    614613   SUBROUTINE cice_sbc_hadgam( kt ) 
    615614      !!--------------------------------------------------------------------- 
     
    653652   END SUBROUTINE cice_sbc_hadgam 
    654653 
    655 #else 
    656    SUBROUTINE cice_sbc_hadgam( kt )    ! Dummy routine 
    657       INTEGER, INTENT( in  ) ::   kt   ! ocean time step 
    658       WRITE(*,*) 'cice_sbc_hadgam: You should not have seen this print! error?' 
    659    END SUBROUTINE cice_sbc_hadgam 
    660 #endif 
    661654 
    662655   SUBROUTINE cice_sbc_final 
     
    1001994CONTAINS 
    1002995 
    1003    SUBROUTINE sbc_ice_cice ( kt, nsbc )     ! Dummy routine 
     996   SUBROUTINE sbc_ice_cice ( kt, ksbc )     ! Dummy routine 
    1004997      WRITE(*,*) 'sbc_ice_cice: You should not have seen this print! error?', kt 
    1005998   END SUBROUTINE sbc_ice_cice 
    1006999 
    1007    SUBROUTINE cice_sbc_init (nsbc)    ! Dummy routine 
     1000   SUBROUTINE cice_sbc_init (ksbc)    ! Dummy routine 
    10081001      WRITE(*,*) 'cice_sbc_init: You should not have seen this print! error?' 
    10091002   END SUBROUTINE cice_sbc_init 
Note: See TracChangeset for help on using the changeset viewer.