Ignore:
Timestamp:
Feb 4, 2020, 10:36:32 PM (4 years ago)
Author:
lguez
Message:

If the ocean skin parameterization is working actively
(activate_ocean_skin == 2) and we are coupled to the ocean then send
ocean-air interface salinity to the ocean. New dummy argument s_int
of procedures ocean_cpl_noice and cpl_send_ocean_fields. We can
only send interface salinity from the previous time-step since
communication with the ocean is before the call to bulk_flux. So make
s_int a state variable: move s_int from phys_output_var_mod to
phys_state_var_mod. Still, we only read s_int from startphy,
define it before the call to surf_ocean and write it to restartphy
if activate_ocean_skin == 2 and type_ocean == 'couple'. In
procedure pbl_surface, for clarity, move the definition of output
variables t_int, dter, dser, tkt, tks, rf, taur to missing_val to
after the call to surf_ocean, with the definition of s_int,
ds_ns, dt_ns to missing_val. This does not change anything for
t_int, dter, dser, tkt, tks, rf, taur. In pbl_surface_newfrac, we
choose to set s_int to 35 for an appearing ocean point, this is
questionable. In surf_ocean, change the intent of s_int from out
to inout.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/Ocean_skin/libf/phylmd/cpl_mod.F90

    r3627 r3628  
    4949  !$OMP THREADPRIVATE(cpl_snow,cpl_evap,cpl_tsol)
    5050
    51   REAL, ALLOCATABLE, SAVE:: cpl_t_int(:)
    52   !$OMP THREADPRIVATE(cpl_t_int)
     51  REAL, ALLOCATABLE, SAVE:: cpl_t_int(:), cpl_s_int(:)
     52  !$OMP THREADPRIVATE(cpl_t_int, cpl_s_int)
    5353 
    5454  REAL, ALLOCATABLE, DIMENSION(:,:), SAVE   :: cpl_fder, cpl_albe, cpl_taux, cpl_tauy
     
    9494  !$OMP THREADPRIVATE(cpl_snow2D, cpl_evap2D, cpl_tsol2D)
    9595
    96   REAL, ALLOCATABLE, SAVE:: cpl_t_int_2D(:,:)
    97   !$OMP THREADPRIVATE(cpl_t_int_2D)
     96  REAL, ALLOCATABLE, SAVE:: cpl_t_int_2D(:,:), cpl_s_int_2D(:,:)
     97  !$OMP THREADPRIVATE(cpl_t_int_2D, cpl_s_int_2D)
    9898
    9999  REAL, ALLOCATABLE, DIMENSION(:,:,:), SAVE :: cpl_fder2D, cpl_albe2D
     
    237237   
    238238       if (activate_ocean_skin == 2) then
    239           ALLOCATE(cpl_t_int(klon), stat = error)
     239          ALLOCATE(cpl_t_int(klon), cpl_s_int(klon), stat = error)
    240240          sum_error = sum_error + error
    241241       end if
     
    645645       swdown, lwdown, fluxlat, fluxsens, &
    646646       precip_rain, precip_snow, evap, tsurf, fder, albsol, taux, tauy, windsp,&
    647        sens_prec_liq, sens_prec_sol, lat_prec_liq, lat_prec_sol, t_int)
     647       sens_prec_liq, sens_prec_sol, lat_prec_liq, lat_prec_sol, t_int, s_int)
    648648
    649649    ! This subroutine cumulates some fields for each time-step during
     
    672672    REAL, DIMENSION(klon), INTENT(IN)       :: lat_prec_liq, lat_prec_sol
    673673    real, intent(in):: t_int(:) ! (klon) ocean-air interface temperature, in K
     674    real, intent(in):: s_int(:) ! (knon) ocean-air interface salinity, in ppt
    674675
    675676! Local variables
     
    707708       cpl_taumod(1:knon,cpl_index) = 0.0
    708709       IF (carbon_cycle_cpl) cpl_atm_co2(1:knon,cpl_index) = 0.0
    709        if (activate_ocean_skin == 2) cpl_t_int(:knon) = 0.
     710
     711       if (activate_ocean_skin == 2) then
     712          cpl_t_int(:knon) = 0.
     713          cpl_s_int = 0.
     714       end if
    710715    ENDIF
    711716       
     
    750755       ENDIF
    751756
    752        if (activate_ocean_skin == 2) &
    753             cpl_t_int(ig) = cpl_t_int(ig) + t_int(ig) / REAL(nexca)
     757       if (activate_ocean_skin == 2) then
     758          cpl_t_int(ig) = cpl_t_int(ig) + t_int(ig) / REAL(nexca)
     759          cpl_s_int(ig) = cpl_s_int(ig) + s_int(ig) / REAL(nexca)
     760       end if
    754761     ENDDO
    755762
     
    799806
    800807          if (activate_ocean_skin == 2) then
    801              ALLOCATE(cpl_t_int_2D(nbp_lon, jj_nb), stat = error)
     808             ALLOCATE(cpl_t_int_2D(nbp_lon, jj_nb), &
     809                  cpl_s_int_2D(nbp_lon, jj_nb), stat = error)
    802810             sum_error = sum_error + error
    803811          end if
     
    857865       IF (carbon_cycle_cpl) &
    858866            CALL gath2cpl(cpl_atm_co2(:,cpl_index), cpl_atm_co22D(:,:), knon, knindex)
    859        if (activate_ocean_skin == 2) &
    860             CALL gath2cpl(cpl_t_int, cpl_t_int_2D, knon, knindex)
     867       if (activate_ocean_skin == 2) then
     868          CALL gath2cpl(cpl_t_int, cpl_t_int_2D, knon, knindex)
     869          CALL gath2cpl(cpl_s_int, cpl_s_int_2D, knon, knindex)
     870       end if
    861871    ENDIF
    862872
     
    12521262    tab_flds(:,:,ids_qraiic) = cpl_sens_rain2D(:,:,2)
    12531263    tab_flds(:,:,ids_qsnoic) = cpl_sens_snow2D(:,:,2)
    1254     if (activate_ocean_skin == 2) tab_flds(:, :, ids_t_int) = cpl_t_int_2D
     1264
     1265    if (activate_ocean_skin == 2) then
     1266       tab_flds(:, :, ids_t_int) = cpl_t_int_2D
     1267       tab_flds(:, :, ids_s_int) = cpl_s_int_2D
     1268    end if
    12551269   
    12561270    IF (version_ocean=='nemo') THEN
     
    14891503    ENDIF
    14901504
    1491     if (activate_ocean_skin == 2) deallocate(cpl_t_int_2d)
     1505    if (activate_ocean_skin == 2) deallocate(cpl_t_int_2d, cpl_s_int_2d)
    14921506
    14931507    IF (sum_error /= 0) THEN
Note: See TracChangeset for help on using the changeset viewer.