Ignore:
Timestamp:
Jun 15, 2021, 1:18:14 PM (3 years ago)
Author:
crisi
Message:

replace files by symbloic liks from phylmdiso towards phylmd.
Many files at once

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/phylmdiso/ocean_forced_mod.F90

    r3927 r3940  
    1919       AcoefH, AcoefQ, BcoefH, BcoefQ, &
    2020       AcoefU, AcoefV, BcoefU, BcoefV, &
    21        ps, u1, v1, gustiness, &
     21       ps, u1, v1, gustiness, tsurf_in, &
    2222       radsol, snow, agesno, &
    2323       qsurf, evap, fluxsens, fluxlat, flux_u1, flux_v1, &
    24        tsurf_new, dflux_s, dflux_l &
     24       tsurf_new, dflux_s, dflux_l, sens_prec_liq, rhoa &
    2525#ifdef ISO
    2626            ,xtprecip_rain, xtprecip_snow, xtspechum,Roce,rlat, &
     
    4040    USE indice_sol_mod
    4141    USE phys_output_var_mod, ONLY : sens_prec_liq_o, sens_prec_sol_o, lat_prec_liq_o, lat_prec_sol_o
     42    use config_ocean_skin_m, only: activate_ocean_skin
    4243#ifdef ISO
    4344  USE infotrac_phy, ONLY: ntraciso,niso
     
    5354    INCLUDE "YOMCST.h"
    5455    INCLUDE "clesphys.h"
    55 
     56    INCLUDE "flux_arp.h"
    5657
    5758! Input arguments
     
    6869    REAL, DIMENSION(klon), INTENT(IN)        :: ps
    6970    REAL, DIMENSION(klon), INTENT(IN)        :: u1, v1, gustiness
     71    REAL, DIMENSION(klon), INTENT(IN)        :: tsurf_in
     72    real, intent(in):: rhoa(:) ! (knon) density of moist air  (kg / m3)
     73
    7074#ifdef ISO
    7175    REAL, DIMENSION(ntraciso,klon), INTENT(IN)    :: xtprecip_rain, xtprecip_snow
     
    9195    REAL, DIMENSION(klon), INTENT(OUT)       :: tsurf_new
    9296    REAL, DIMENSION(klon), INTENT(OUT)       :: dflux_s, dflux_l
     97    REAL, intent(out):: sens_prec_liq(:) ! (knon)
     98
    9399#ifdef ISO     
    94100    REAL, DIMENSION(ntraciso,klon), INTENT(OUT)    :: xtevap ! isotopes in evaporation flux
     
    104110    REAL, DIMENSION(klon)       :: u1_lay, v1_lay
    105111    LOGICAL                     :: check=.FALSE.
    106     REAL, DIMENSION(klon) :: sens_prec_liq, sens_prec_sol   
     112    REAL sens_prec_sol(knon)
    107113    REAL, DIMENSION(klon) :: lat_prec_liq, lat_prec_sol   
    108114
     
    139145!!jyg    if (knon.eq.1) then ! single-column model
    140146    if (klon_glo.eq.1) then ! single-column model
    141       CALL read_tsurf1d(knon,tsurf_lim) ! new
    142 #ifdef ISO
    143       write(*,*) 'ocean_forced_mod 143: isotopes pas prévus ici'
    144       stop
    145 #endif
     147      ! EV: now surface Tin flux_arp.h
     148      !CALL read_tsurf1d(knon,tsurf_lim) ! new
     149       DO i = 1, knon
     150        tsurf_lim(i) = tg
     151       ENDDO
     152
    146153    else ! GCM
    147154      CALL limit_read_sst(knon,knindex,tsurf_lim &
     
    159166!****************************************************************************************
    160167! Set some variables for calcul_fluxs
    161     cal = 0.
    162     beta = 1.
    163     dif_grnd = 0.
     168    !cal = 0.
     169    !beta = 1.
     170    !dif_grnd = 0.
     171   
     172   
     173    ! EV: use calbeta to calculate beta
     174    ! Need to initialize qsurf for calbeta but it is not modified by this routine
     175    qsurf(:)=0.
     176    CALL calbeta(dtime, is_oce, knon, snow, qsurf, beta, cal, dif_grnd)
     177
     178
    164179    alb_neig(:) = 0.
    165180    agesno(:) = 0.
    166     sens_prec_liq = 0.; sens_prec_sol = 0.; lat_prec_liq = 0.; lat_prec_sol = 0.
     181    lat_prec_liq = 0.; lat_prec_sol = 0.
    167182
    168183! Suppose zero surface speed
     
    174189! Calcul de tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l and qsurf
    175190    CALL calcul_fluxs(knon, is_oce, dtime, &
    176          tsurf_lim, p1lay, cal, beta, cdragh, cdragq, ps, &
     191         merge(tsurf_in, tsurf_lim, activate_ocean_skin == 2), p1lay, cal, &
     192         beta, cdragh, cdragq, ps, &
    177193         precip_rain, precip_snow, snow, qsurf,  &
    178194         radsol, dif_grnd, temp_air, spechum, u1_lay, v1_lay, gustiness, &
    179195         f_qsat_oce,AcoefH, AcoefQ, BcoefH, BcoefQ, &
    180196         tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l, &
    181          sens_prec_liq, sens_prec_sol, lat_prec_liq, lat_prec_sol)
     197         sens_prec_liq, sens_prec_sol, lat_prec_liq, lat_prec_sol, rhoa)
     198    if (activate_ocean_skin == 2) tsurf_new = tsurf_lim
    182199
    183200    do j = 1, knon
     
    233250       radsol, snow, qsol, agesno, tsoil, &
    234251       qsurf, alb1_new, alb2_new, evap, fluxsens, fluxlat, flux_u1, flux_v1, &
    235        tsurf_new, dflux_s, dflux_l &
     252       tsurf_new, dflux_s, dflux_l, rhoa &
    236253#ifdef ISO
    237254            ,xtprecip_rain, xtprecip_snow, xtspechum,Roce, &
     
    262279#endif
    263280
    264 !    INCLUDE "indicesol.h"
     281!   INCLUDE "indicesol.h"
    265282    INCLUDE "dimsoil.h"
    266283    INCLUDE "YOMCST.h"
    267284    INCLUDE "clesphys.h"
     285    INCLUDE "flux_arp.h"
    268286
    269287! Input arguments
     
    281299    REAL, DIMENSION(klon), INTENT(IN)    :: ps
    282300    REAL, DIMENSION(klon), INTENT(IN)    :: u1, v1, gustiness
     301    real, intent(in):: rhoa(:) ! (knon) density of moist air  (kg / m3)
    283302#ifdef ISO
    284303    REAL, DIMENSION(ntraciso,klon), INTENT(IN)    :: xtprecip_rain, xtprecip_snow
     
    323342    REAL, DIMENSION(klon)       :: u0, v0
    324343    REAL, DIMENSION(klon)       :: u1_lay, v1_lay
    325     REAL, DIMENSION(klon)       :: sens_prec_liq, sens_prec_sol   
     344    REAL sens_prec_liq(knon), sens_prec_sol (knon)
    326345    REAL, DIMENSION(klon)       :: lat_prec_liq, lat_prec_sol   
    327346
     
    354373    tsurf_tmp(:) = tsurf_in(:)
    355374
    356 ! calculate the parameters cal, beta, capsol and dif_grnd
     375! calculate the parameters cal, beta, capsol and dif_grnd and then recalculate cal
    357376    CALL calbeta(dtime, is_sic, knon, snow, qsol, beta, capsol, dif_grnd)
    358377
     
    370389    ENDIF
    371390
    372     beta = 1.0
    373     sens_prec_liq = 0.; sens_prec_sol = 0.; lat_prec_liq = 0.; lat_prec_sol = 0.
     391!    beta = 1.0
     392    lat_prec_liq = 0.; lat_prec_sol = 0.
    374393
    375394! Suppose zero surface speed
     
    384403         f_qsat_oce,AcoefH, AcoefQ, BcoefH, BcoefQ, &
    385404         tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l, &
    386          sens_prec_liq, sens_prec_sol, lat_prec_liq, lat_prec_sol)
     405         sens_prec_liq, sens_prec_sol, lat_prec_liq, lat_prec_sol, rhoa)
    387406    do j = 1, knon
    388407      i = knindex(j)
     
    489508! 1D case
    490509!************************************************************************
    491   SUBROUTINE read_tsurf1d(knon,sst_out)
    492 
     510!  SUBROUTINE read_tsurf1d(knon,sst_out)
     511!
    493512! This subroutine specifies the surface temperature to be used in 1D simulations
    494 
    495       USE dimphy, ONLY : klon
    496 
    497       INTEGER, INTENT(IN)                  :: knon     ! nomber of points on compressed grid
    498       REAL, DIMENSION(klon), INTENT(OUT)   :: sst_out  ! tsurf used to force the single-column model
    499 
    500        INTEGER :: i
     513!
     514!      USE dimphy, ONLY : klon
     515!
     516!      INTEGER, INTENT(IN)                  :: knon     ! nomber of points on compressed grid
     517!      REAL, DIMENSION(klon), INTENT(OUT)   :: sst_out  ! tsurf used to force the single-column model
     518!
     519!       INTEGER :: i
    501520! COMMON defined in lmdz1d.F:
    502        real ts_cur
    503        common /sst_forcing/ts_cur
    504 
    505        DO i = 1, knon
    506         sst_out(i) = ts_cur
    507        ENDDO
    508 
    509       END SUBROUTINE read_tsurf1d
    510 
     521!       real ts_cur
     522!       common /sst_forcing/ts_cur
     523!
     524!       DO i = 1, knon
     525!        sst_out(i) = ts_cur
     526!       ENDDO
     527!
     528!      END SUBROUTINE read_tsurf1d
     529!
    511530!
    512531!************************************************************************
    513 !
    514532END MODULE ocean_forced_mod
    515533
Note: See TracChangeset for help on using the changeset viewer.