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

Changeset 1468


Ignore:
Timestamp:
2009-06-11T10:52:29+02:00 (15 years ago)
Author:
smasson
Message:

Improve readability of sbc_cpl_ice_flx, see ticket:451

Location:
trunk/NEMO/OPA_SRC/SBC
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMO/OPA_SRC/SBC/sbccpl.F90

    r1467 r1468  
    848848    
    849849 
    850    SUBROUTINE sbc_cpl_ice_flx( p_frld  , palbi   , psst     , pist    ,   & 
     850   SUBROUTINE sbc_cpl_ice_flx( p_frld  ,                                  & 
    851851      &                        pqns_tot, pqns_ice, pqsr_tot , pqsr_ice,   & 
    852       &                        pemp_tot, pemp_ice, pdqns_ice, psprecip ) 
     852      &                        pemp_tot, pemp_ice, pdqns_ice, psprecip,   & 
     853      &                        palbi   , psst    , pist                 ) 
    853854      !!---------------------------------------------------------------------- 
    854855      !!             ***  ROUTINE sbc_cpl_ice_flx_rcv  *** 
     
    895896      !!---------------------------------------------------------------------- 
    896897      REAL(wp), INTENT(in   ), DIMENSION(jpi,jpj,jpl) ::   p_frld     ! lead fraction                [0 to 1] 
    897       REAL(wp), INTENT(in   ), DIMENSION(jpi,jpj,jpl) ::   palbi      ! ice albedo 
    898       REAL(wp), INTENT(in   ), DIMENSION(jpi,jpj    ) ::   psst       ! sea surface temperature      [Celcius] 
    899       REAL(wp), INTENT(in   ), DIMENSION(jpi,jpj,jpl) ::   pist       ! ice surface temperature      [Kelvin] 
    900898      REAL(wp), INTENT(  out), DIMENSION(jpi,jpj    ) ::   pqns_tot   ! total non solar heat flux    [W/m2] 
    901899      REAL(wp), INTENT(  out), DIMENSION(jpi,jpj,jpl) ::   pqns_ice   ! ice   non solar heat flux    [W/m2] 
     
    906904      REAL(wp), INTENT(  out), DIMENSION(jpi,jpj    ) ::   psprecip   ! Net solid precipitation (=emp_ice) [Kg/m2/s] 
    907905      REAL(wp), INTENT(  out), DIMENSION(jpi,jpj,jpl) ::   pdqns_ice  ! d(Q non solar)/d(Temperature) over ice 
     906      ! optional arguments, used only in 'mixed oce-ice' case 
     907      REAL(wp), INTENT(in   ), DIMENSION(jpi,jpj,jpl), OPTIONAL ::   palbi   ! ice albedo  
     908      REAL(wp), INTENT(in   ), DIMENSION(jpi,jpj    ), OPTIONAL ::   psst    ! sea surface temperature     [Celcius] 
     909      REAL(wp), INTENT(in   ), DIMENSION(jpi,jpj,jpl), OPTIONAL ::   pist    ! ice surface temperature     [Kelvin] 
    908910     !! 
    909911      INTEGER ::   ji, jj           ! dummy loop indices 
     
    12201222   END SUBROUTINE sbc_cpl_ice_tau 
    12211223   ! 
    1222    SUBROUTINE sbc_cpl_ice_flx( p_frld  , palbi   , psst     , pist    ,   & 
     1224   SUBROUTINE sbc_cpl_ice_flx( p_frld  ,                                  & 
    12231225      &                        pqns_tot, pqns_ice, pqsr_tot , pqsr_ice,   & 
    1224       &                        pemp_tot, pemp_ice, pdqns_ice, psprecip ) 
     1226      &                        pemp_tot, pemp_ice, pdqns_ice, psprecip,   & 
     1227      &                        palbi   , psst    , pist                ) 
    12251228      REAL(wp), INTENT(in   ), DIMENSION(:,:,:) ::   p_frld     ! lead fraction                [0 to 1] 
    1226       REAL(wp), INTENT(in   ), DIMENSION(:,:,:) ::   palbi      ! ice albedo 
    1227       REAL(wp), INTENT(in   ), DIMENSION(:,:  ) ::   psst       ! sea surface temperature      [Celcius] 
    1228       REAL(wp), INTENT(in   ), DIMENSION(:,:,:) ::   pist       ! ice surface temperature      [Kelvin] 
    12291229      REAL(wp), INTENT(  out), DIMENSION(:,:  ) ::   pqns_tot   ! total non solar heat flux    [W/m2] 
    12301230      REAL(wp), INTENT(  out), DIMENSION(:,:,:) ::   pqns_ice   ! ice   non solar heat flux    [W/m2] 
     
    12351235      REAL(wp), INTENT(  out), DIMENSION(:,:,:) ::   pdqns_ice  ! d(Q non solar)/d(Temperature) over ice 
    12361236      REAL(wp), INTENT(  out), DIMENSION(:,:  ) ::   psprecip   ! solid precipitation          [Kg/m2/s] 
    1237       WRITE(*,*) 'sbc_cpl_snd: You should not have seen this print! error?', p_frld(1,1,1), palbi(1,1,1), psst(1,1), pist(1,1,1) 
     1237      REAL(wp), INTENT(in   ), DIMENSION(:,:,:), OPTIONAL ::   palbi   ! ice albedo 
     1238      REAL(wp), INTENT(in   ), DIMENSION(:,:  ), OPTIONAL ::   psst    ! sea surface temperature      [Celcius] 
     1239      REAL(wp), INTENT(in   ), DIMENSION(:,:,:), OPTIONAL ::   pist    ! ice surface temperature      [Kelvin] 
     1240      WRITE(*,*) 'sbc_cpl_snd: You should not have seen this print! error?', p_frld(1,1,1) 
    12381241      ! stupid definition to avoid warning message when compiling... 
    12391242      pqns_tot(:,:) = 0. ; pqns_ice(:,:,:) = 0. ; pdqns_ice(:,:,:) = 0. 
  • trunk/NEMO/OPA_SRC/SBC/sbcice_lim_2.F90

    r1465 r1468  
    184184         ENDIF 
    185185#if defined key_coupled 
    186          IF( ksbc == 5    )             CALL sbc_cpl_ice_flx( frld   , zalb_ice_cs , sst_m   , sist   ,   & 
    187       &                                                       qns_tot, qns_ice     , qsr_tot , qsr_ice,   & 
    188       &                                                       emp_tot, emp_ice     , dqns_ice, sprecip ) 
     186         IF( ksbc == 5    )             CALL sbc_cpl_ice_flx( frld   ,                               & 
     187      &                                                       qns_tot, qns_ice, qsr_tot , qsr_ice,   & 
     188      &                                                       emp_tot, emp_ice, dqns_ice, sprecip,   & 
     189      !                                      optional arguments, used only in 'mixed oce-ice' case 
     190      &                                                       palbi = zalb_ice_cs, psst = sst_m, pist = sist ) 
    189191#endif 
    190192                                        CALL lim_thd_2      ( kt )      ! Ice thermodynamics  
Note: See TracChangeset for help on using the changeset viewer.