MODULE iceforcing !!====================================================================== !! *** MODULE iceforcing *** !! Sea-Ice : air-ice forcing fields !!===================================================================== !! History : 4.0 ! 2017-08 (C. Rousset) Original code !!---------------------------------------------------------------------- #if defined key_lim3 !!---------------------------------------------------------------------- !! 'key_lim3' : LIM 3.0 sea-ice model !!---------------------------------------------------------------------- USE oce ! ocean dynamics and tracers USE dom_oce ! ocean space and time domain USE ice ! sea-ice variables USE sbc_oce ! Surface boundary condition: ocean fields USE sbc_ice ! Surface boundary condition: ice fields USE usrdef_sbc ! user defined: surface boundary condition USE sbcblk ! Surface boundary condition: bulk USE sbccpl ! Surface boundary condition: coupled interface USE icealb ! ice albedo ! USE iom ! I/O manager library USE in_out_manager ! I/O manager USE lbclnk ! lateral boundary condition - MPP link USE lib_mpp ! MPP library USE lib_fortran ! USE timing ! Timing IMPLICIT NONE PRIVATE PUBLIC ice_forcing_tau ! routine called by icestp.F90 PUBLIC ice_forcing_flx ! routine called by icestp.F90 !! * Substitutions # include "vectopt_loop_substitute.h90" !!---------------------------------------------------------------------- !! NEMO/ICE 4.0 , UCL NEMO Consortium (2017) !! $Id: icestp.F90 8319 2017-07-11 15:00:44Z clem $ !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) !!---------------------------------------------------------------------- CONTAINS SUBROUTINE ice_forcing_tau( kt, ksbc, utau_ice, vtau_ice ) !!--------------------------------------------------------------------- !! *** ROUTINE ice_forcing_tau *** !! !! ** Purpose : provide surface boundary condition for sea ice (momentum) !! !! ** Action : It provides the following fields: !! utau_ice, vtau_ice : surface ice stress (U- & V-points) [N/m2] !!--------------------------------------------------------------------- INTEGER, INTENT(in) :: kt ! ocean time step INTEGER, INTENT(in) :: ksbc ! type of sbc flux ( 1 = user defined formulation, ! 3 = bulk formulation, ! 4 = Pure Coupled formulation) REAL(wp), DIMENSION(jpi,jpj), INTENT(out) :: utau_ice, vtau_ice !! INTEGER :: ji, jj ! dummy loop index REAL(wp), DIMENSION(jpi,jpj) :: zutau_ice, zvtau_ice !!---------------------------------------------------------------------- IF( nn_timing == 1 ) CALL timing_start('ice_forcing_tau') IF( kt == nit000 .AND. lwp ) THEN WRITE(numout,*) WRITE(numout,*)'ice_forcing_tau: Surface boundary condition for sea ice (momentum)' WRITE(numout,*)'~~~~~~~~~~~~~~~' ENDIF SELECT CASE( ksbc ) CASE( jp_usr ) ; CALL usrdef_sbc_ice_tau( kt ) ! user defined formulation CASE( jp_blk ) ; CALL blk_ice_tau ! Bulk formulation CASE( jp_purecpl ) ; CALL sbc_cpl_ice_tau( utau_ice , vtau_ice ) ! Coupled formulation END SELECT IF( ln_mixcpl) THEN ! Case of a mixed Bulk/Coupled formulation CALL sbc_cpl_ice_tau( zutau_ice , zvtau_ice ) DO jj = 2, jpjm1 DO ji = 2, jpim1 utau_ice(ji,jj) = utau_ice(ji,jj) * xcplmask(ji,jj,0) + zutau_ice(ji,jj) * ( 1. - xcplmask(ji,jj,0) ) vtau_ice(ji,jj) = vtau_ice(ji,jj) * xcplmask(ji,jj,0) + zvtau_ice(ji,jj) * ( 1. - xcplmask(ji,jj,0) ) END DO END DO CALL lbc_lnk_multi( utau_ice, 'U', -1., vtau_ice, 'V', -1. ) ENDIF IF( nn_timing == 1 ) CALL timing_stop('ice_forcing_tau') ! END SUBROUTINE ice_forcing_tau SUBROUTINE ice_forcing_flx( kt, ksbc ) !!--------------------------------------------------------------------- !! *** ROUTINE ice_forcing_flx *** !! !! ** Purpose : provide surface boundary condition for sea ice (flux) !! !! ** Action : It provides the following fields used in sea ice model: !! fr1_i0 , fr2_i0 = 1sr & 2nd fraction of qsr penetration in ice [%] !! emp_oce , emp_ice = E-P over ocean and sea ice [Kg/m2/s] !! sprecip = solid precipitation [Kg/m2/s] !! evap_ice = sublimation [Kg/m2/s] !! qsr_tot , qns_tot = solar & non solar heat flux (total) [W/m2] !! qsr_ice , qns_ice = solar & non solar heat flux over ice [W/m2] !! dqns_ice = non solar heat sensistivity [W/m2] !! qemp_oce, qemp_ice, qprec_ice, qevap_ice = sensible heat (associated with evap & precip) [W/m2] !! + some fields that are not used outside this module: !! qla_ice = latent heat flux over ice [W/m2] !! dqla_ice = latent heat sensistivity [W/m2] !! tprecip = total precipitation [Kg/m2/s] !! alb_ice = albedo above sea ice !!--------------------------------------------------------------------- INTEGER, INTENT(in) :: kt ! ocean time step INTEGER, INTENT(in) :: ksbc ! flux formulation (user defined, bulk or Pure Coupled) ! INTEGER :: ji, jj, jl ! dummy loop index REAL(wp), DIMENSION(jpi,jpj,jpl) :: zalb_os, zalb_cs ! ice albedo under overcast/clear sky REAL(wp), DIMENSION(jpi,jpj) :: zalb ! 2D workspace !!---------------------------------------------------------------------- ! IF( nn_timing == 1 ) CALL timing_start('ice_forcing_flx') IF( kt == nit000 .AND. lwp ) THEN WRITE(numout,*) WRITE(numout,*)'ice_forcing_flx: Surface boundary condition for sea ice (flux)' WRITE(numout,*)'~~~~~~~~~~~~~~~' ENDIF ! --- cloud-sky and overcast-sky ice albedos --- ! CALL ice_alb( t_su, ht_i, ht_s, a_ip_frac, h_ip, ln_pnd_rad, zalb_cs, zalb_os ) ! albedo depends on cloud fraction because of non-linear spectral effects !!gm cldf_ice is a real, DOCTOR naming rule: start with cd means CHARACTER passed in argument ! alb_ice(:,:,:) = ( 1. - cldf_ice ) * zalb_cs(:,:,:) + cldf_ice * zalb_os(:,:,:) SELECT CASE( ksbc ) !== fluxes over sea ice ==! ! CASE( jp_usr ) !--- user defined formulation CALL usrdef_sbc_ice_flx( kt ) ! CASE( jp_blk ) !--- bulk formulation CALL blk_ice_flx( t_su, alb_ice ) ! IF( ln_mixcpl ) CALL sbc_cpl_ice_flx( picefr=at_i_b, palbi=alb_ice, psst=sst_m, pist=t_su ) IF( nn_limflx /= 2 ) CALL ice_flx_dist( t_su, alb_ice, qns_ice, qsr_ice, dqns_ice, evap_ice, devap_ice, nn_limflx ) ! CASE ( jp_purecpl ) !--- coupled formulation CALL sbc_cpl_ice_flx( picefr=at_i_b, palbi=alb_ice, psst=sst_m, pist=t_su ) IF( nn_limflx == 2 ) CALL ice_flx_dist( t_su, alb_ice, qns_ice, qsr_ice, dqns_ice, evap_ice, devap_ice, nn_limflx ) ! END SELECT IF( iom_use('icealb') ) THEN !--- output ice albedo WHERE( at_i_b <= epsi06 ) ; zalb(:,:) = rn_alb_oce ELSEWHERE ; zalb(:,:) = SUM( alb_ice * a_i_b, dim=3 ) / at_i_b END WHERE CALL iom_put( "icealb" , zalb(:,:) ) ! ice albedo ENDIF IF( iom_use('albedo') ) THEN !--- surface albedo zalb(:,:) = SUM( alb_ice * a_i_b, dim=3 ) + rn_alb_oce * ( 1._wp - at_i_b ) CALL iom_put( "albedo" , zalb(:,:) ) ENDIF ! IF( nn_timing == 1 ) CALL timing_stop('ice_forcing_flx') ! END SUBROUTINE ice_forcing_flx SUBROUTINE ice_flx_dist( ptn_ice, palb_ice, pqns_ice, pqsr_ice, pdqn_ice, pevap_ice, pdevap_ice, k_limflx ) !!--------------------------------------------------------------------- !! *** ROUTINE ice_flx_dist *** !! !! ** Purpose : update the ice surface boundary condition by averaging !! and/or redistributing fluxes on ice categories !! !! ** Method : average then redistribute !! !! ** Action : !!--------------------------------------------------------------------- INTEGER , INTENT(in ) :: k_limflx ! =-1 do nothing; =0 average ; ! ! = 1 average and redistribute ; =2 redistribute REAL(wp), DIMENSION(:,:,:), INTENT(in ) :: ptn_ice ! ice surface temperature REAL(wp), DIMENSION(:,:,:), INTENT(in ) :: palb_ice ! ice albedo REAL(wp), DIMENSION(:,:,:), INTENT(inout) :: pqns_ice ! non solar flux REAL(wp), DIMENSION(:,:,:), INTENT(inout) :: pqsr_ice ! net solar flux REAL(wp), DIMENSION(:,:,:), INTENT(inout) :: pdqn_ice ! non solar flux sensitivity REAL(wp), DIMENSION(:,:,:), INTENT(inout) :: pevap_ice ! sublimation REAL(wp), DIMENSION(:,:,:), INTENT(inout) :: pdevap_ice ! sublimation sensitivity ! INTEGER :: jl ! dummy loop index ! REAL(wp), DIMENSION(jpi,jpj) :: z1_at_i ! inverse of concentration ! REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: z_qsr_m ! Mean solar heat flux over all categories REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: z_qns_m ! Mean non solar heat flux over all categories REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: z_evap_m ! Mean sublimation over all categories REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: z_dqn_m ! Mean d(qns)/dT over all categories REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: z_devap_m ! Mean d(evap)/dT over all categories REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: zalb_m ! Mean albedo over all categories REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: ztem_m ! Mean temperature over all categories !!---------------------------------------------------------------------- ! IF( nn_timing == 1 ) CALL timing_start('ice_flx_dist') ! WHERE ( at_i (:,:) > 0._wp ) ; z1_at_i(:,:) = 1._wp / at_i (:,:) ELSEWHERE ; z1_at_i(:,:) = 0._wp END WHERE SELECT CASE( k_limflx ) !== averaged on all ice categories ==! ! CASE( 0 , 1 ) ! ALLOCATE( z_qns_m(jpi,jpj), z_qsr_m(jpi,jpj), z_dqn_m(jpi,jpj), z_evap_m(jpi,jpj), z_devap_m(jpi,jpj) ) ! z_qns_m (:,:) = SUM( a_i(:,:,:) * pqns_ice (:,:,:) , dim=3 ) * z1_at_i(:,:) z_qsr_m (:,:) = SUM( a_i(:,:,:) * pqsr_ice (:,:,:) , dim=3 ) * z1_at_i(:,:) z_dqn_m (:,:) = SUM( a_i(:,:,:) * pdqn_ice (:,:,:) , dim=3 ) * z1_at_i(:,:) z_evap_m (:,:) = SUM( a_i(:,:,:) * pevap_ice (:,:,:) , dim=3 ) * z1_at_i(:,:) z_devap_m(:,:) = SUM( a_i(:,:,:) * pdevap_ice(:,:,:) , dim=3 ) * z1_at_i(:,:) DO jl = 1, jpl pqns_ice (:,:,jl) = z_qns_m (:,:) pqsr_ice (:,:,jl) = z_qsr_m (:,:) pdqn_ice (:,:,jl) = z_dqn_m (:,:) pevap_ice (:,:,jl) = z_evap_m(:,:) pdevap_ice(:,:,jl) = z_devap_m(:,:) END DO ! DEALLOCATE( z_qns_m, z_qsr_m, z_dqn_m, z_evap_m, z_devap_m ) ! END SELECT ! SELECT CASE( k_limflx ) !== redistribution on all ice categories ==! ! CASE( 1 , 2 ) ! ALLOCATE( zalb_m(jpi,jpj), ztem_m(jpi,jpj) ) ! zalb_m(:,:) = SUM( a_i(:,:,:) * palb_ice(:,:,:) , dim=3 ) * z1_at_i(:,:) ztem_m(:,:) = SUM( a_i(:,:,:) * ptn_ice (:,:,:) , dim=3 ) * z1_at_i(:,:) DO jl = 1, jpl pqns_ice (:,:,jl) = pqns_ice (:,:,jl) + pdqn_ice (:,:,jl) * ( ptn_ice(:,:,jl) - ztem_m(:,:) ) pevap_ice(:,:,jl) = pevap_ice(:,:,jl) + pdevap_ice(:,:,jl) * ( ptn_ice(:,:,jl) - ztem_m(:,:) ) pqsr_ice (:,:,jl) = pqsr_ice (:,:,jl) * ( 1._wp - palb_ice(:,:,jl) ) / ( 1._wp - zalb_m(:,:) ) END DO ! DEALLOCATE( zalb_m, ztem_m ) ! END SELECT ! IF( nn_timing == 1 ) CALL timing_stop('ice_flx_dist') ! END SUBROUTINE ice_flx_dist #else !!---------------------------------------------------------------------- !! Default option : Empty module NO LIM sea-ice model !!---------------------------------------------------------------------- #endif !!====================================================================== END MODULE iceforcing