Ignore:
Timestamp:
Jul 1, 2020, 6:57:48 PM (4 years ago)
Author:
lguez
Message:

Store delta_sst instead of sst_nff

Store as a state variable the difference between ocean-air interface
temperature and bulk SST instead of sst_nff, which can be either
interface temperature or bulk SST. This is clearer. Also, it is
analoguous to what we will do with salinity.

So replace the two dummy arguments tsurf_in and sst_nff of
procedure cpl_send_ocean_fields by a single dummy argument
delta_sst. Replace dummy argument sst_nff of procedures
ocean_cpl_noice and surf_ocean by dummy argument
delta_sst. Replace variable sst_nff of module phys_state_var_mod
by variable delta_sst. Rename local variable ysst_nff of procedure
pbl_surface to ydelta_sst. Set variable delta_sst of module
phys_state_var_mod to 0 for an appearing ocean fraction and a
missing startup field. Replace variable o_sst_nff of module
phys_output_ctrlout_mod by variable o_delta_sst.

Rename variables cpl_delta_temp and cpl_delta_temp_2D of module
cpl_mod to cpl_delta_sst and cpl_delta_sst_2D, clearer. Rename
variable ids_delta_temp of module oasis to ids_delta_sst. Change
infosend(ids_delta_temp)%name to "CODELSST".

File:
1 edited

Legend:

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

    r3740 r3744  
    4949  !$OMP THREADPRIVATE(cpl_snow,cpl_evap,cpl_tsol)
    5050
    51   REAL, ALLOCATABLE, SAVE:: cpl_delta_temp(:), cpl_s_int(:)
    52   !$OMP THREADPRIVATE(cpl_delta_temp, cpl_s_int)
     51  REAL, ALLOCATABLE, SAVE:: cpl_delta_sst(:), cpl_s_int(:)
     52  !$OMP THREADPRIVATE(cpl_delta_sst, 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_delta_temp_2D(:,:), cpl_s_int_2D(:,:)
    97   !$OMP THREADPRIVATE(cpl_delta_temp_2D, cpl_s_int_2D)
     96  REAL, ALLOCATABLE, SAVE:: cpl_delta_sst_2D(:,:), cpl_s_int_2D(:,:)
     97  !$OMP THREADPRIVATE(cpl_delta_sst_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_delta_temp(klon), cpl_s_int(klon), stat = error)
     239          ALLOCATE(cpl_delta_sst(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, tsurf_in, &
    648        sst_nff, s_int)
     647       sens_prec_liq, sens_prec_sol, lat_prec_liq, lat_prec_sol, delta_sst, &
     648       s_int)
    649649
    650650    ! This subroutine cumulates some fields for each time-step during
     
    672672    REAL, INTENT(IN):: sens_prec_liq(:), sens_prec_sol(:) ! (knon)
    673673    REAL, DIMENSION(klon), INTENT(IN)       :: lat_prec_liq, lat_prec_sol
    674     real, intent(in):: tsurf_in(:) ! (klon)
    675    
    676     REAL, intent(in):: sst_nff(:) ! (knon)
    677     ! SST not used to compute surface fluxes, in K. If
    678     ! activate_ocean_skin == 0 then it is not defined; if
    679     ! activate_ocean_skin == 1 then it is the ocean-air interface
    680     ! temperature; if activate_ocean_skin == 2 then it is the bulk SST.
     674   
     675    REAL, intent(in):: delta_sst(:) ! (knon)
     676    ! Ocean-air interface temperature minus bulk SST, in
     677    ! K. Defined only if activate_ocean_skin >= 1.
    681678
    682679    real, intent(in):: s_int(:) ! (knon) ocean-air interface salinity, in ppt
     
    718715
    719716       if (activate_ocean_skin == 2) then
    720           cpl_delta_temp(:knon) = 0.
     717          cpl_delta_sst(:knon) = 0.
    721718          cpl_s_int = 0.
    722719       end if
     
    764761
    765762       if (activate_ocean_skin == 2) then
    766           cpl_delta_temp(ig) = cpl_delta_temp(ig) &
    767                + (tsurf_in(ig) - sst_nff(ig)) / REAL(nexca)
     763          cpl_delta_sst(ig) = cpl_delta_sst(ig) + delta_sst(ig) / REAL(nexca)
    768764          cpl_s_int(ig) = cpl_s_int(ig) + s_int(ig) / REAL(nexca)
    769765       end if
     
    815811
    816812          if (activate_ocean_skin == 2) then
    817              ALLOCATE(cpl_delta_temp_2D(nbp_lon, jj_nb), &
     813             ALLOCATE(cpl_delta_sst_2D(nbp_lon, jj_nb), &
    818814                  cpl_s_int_2D(nbp_lon, jj_nb), stat = error)
    819815             sum_error = sum_error + error
     
    875871            CALL gath2cpl(cpl_atm_co2(:,cpl_index), cpl_atm_co22D(:,:), knon, knindex)
    876872       if (activate_ocean_skin == 2) then
    877           CALL gath2cpl(cpl_delta_temp, cpl_delta_temp_2D, knon, knindex)
     873          CALL gath2cpl(cpl_delta_sst, cpl_delta_sst_2D, knon, knindex)
    878874          CALL gath2cpl(cpl_s_int, cpl_s_int_2D, knon, knindex)
    879875       end if
     
    12731269
    12741270    if (activate_ocean_skin == 2) then
    1275        tab_flds(:, :, ids_delta_temp) = cpl_delta_temp_2D
     1271       tab_flds(:, :, ids_delta_sst) = cpl_delta_sst_2D
    12761272       tab_flds(:, :, ids_s_int) = cpl_s_int_2D
    12771273    end if
     
    15121508    ENDIF
    15131509
    1514     if (activate_ocean_skin == 2) deallocate(cpl_delta_temp_2d, cpl_s_int_2d)
     1510    if (activate_ocean_skin == 2) deallocate(cpl_delta_sst_2d, cpl_s_int_2d)
    15151511
    15161512    IF (sum_error /= 0) THEN
Note: See TracChangeset for help on using the changeset viewer.