Ignore:
Timestamp:
Oct 22, 2020, 2:50:18 PM (4 years ago)
Author:
evignon
Message:

Premiere comission Etienne: changements pour le 1D (forcage en Ts au dessus des continents) et inclusion drag arbres dans yamada4_num=6

File:
1 edited

Legend:

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

    r3327 r3780  
    3838    INCLUDE "YOMCST.h"
    3939    INCLUDE "clesphys.h"
    40 
     40    INCLUDE "flux_arp.h"
    4141
    4242! Input arguments
     
    7676    REAL, DIMENSION(klon)       :: u1_lay, v1_lay
    7777    LOGICAL                     :: check=.FALSE.
    78     REAL, DIMENSION(klon) :: sens_prec_liq, sens_prec_sol   
    79     REAL, DIMENSION(klon) :: lat_prec_liq, lat_prec_sol   
     78    REAL, DIMENSION(klon)       :: sens_prec_liq, sens_prec_sol   
     79    REAL, DIMENSION(klon)       :: lat_prec_liq, lat_prec_sol   
    8080
    8181!****************************************************************************************
     
    9292!!jyg    if (knon.eq.1) then ! single-column model
    9393    if (klon_glo.eq.1) then ! single-column model
    94       CALL read_tsurf1d(knon,tsurf_lim) ! new
     94      ! EV: now surface Tin flux_arp.h
     95      !CALL read_tsurf1d(knon,tsurf_lim) ! new
     96       DO i = 1, knon
     97        tsurf_lim(i) = tg
     98       ENDDO
     99
    95100    else ! GCM
    96101      CALL limit_read_sst(knon,knindex,tsurf_lim)
     
    104109!****************************************************************************************
    105110! Set some variables for calcul_fluxs
    106     cal = 0.
    107     beta = 1.
    108     dif_grnd = 0.
     111    !cal = 0.
     112    !beta = 1.
     113    !dif_grnd = 0.
     114    ! EV: use calbeta to calculate beta
     115   
     116    CALL calbeta(dtime, is_oce, knon, snow, beta*0., beta, cal, dif_grnd)
     117
     118
    109119    alb_neig(:) = 0.
    110120    agesno(:) = 0.
     
    172182    INCLUDE "YOMCST.h"
    173183    INCLUDE "clesphys.h"
     184    INCLUDE "flux_arp.h"
    174185
    175186! Input arguments
     
    233244    tsurf_tmp(:) = tsurf_in(:)
    234245
    235 ! calculate the parameters cal, beta, capsol and dif_grnd
    236     CALL calbeta(dtime, is_sic, knon, snow, qsol, beta, capsol, dif_grnd)
     246! calculate the parameters cal, beta, capsol and dif_grnd and then recalculate cal
     247    CALL calbeta(dtime, is_sic, knon, snow, qsol, beta, cal, dif_grnd)
    237248
    238249   
     
    249260    ENDIF
    250261
    251     beta = 1.0
     262    !beta = 1.0
    252263    sens_prec_liq = 0.; sens_prec_sol = 0.; lat_prec_liq = 0.; lat_prec_sol = 0.
    253264
     
    304315  END SUBROUTINE ocean_forced_ice
    305316
     317!
    306318!************************************************************************
    307 ! 1D case
    308 !************************************************************************
    309   SUBROUTINE read_tsurf1d(knon,sst_out)
    310 
    311 ! This subroutine specifies the surface temperature to be used in 1D simulations
    312 
    313       USE dimphy, ONLY : klon
    314 
    315       INTEGER, INTENT(IN)                  :: knon     ! nomber of points on compressed grid
    316       REAL, DIMENSION(klon), INTENT(OUT)   :: sst_out  ! tsurf used to force the single-column model
    317 
    318        INTEGER :: i
    319 ! COMMON defined in lmdz1d.F:
    320        real ts_cur
    321        common /sst_forcing/ts_cur
    322 
    323        DO i = 1, knon
    324         sst_out(i) = ts_cur
    325        ENDDO
    326 
    327       END SUBROUTINE read_tsurf1d
    328 
    329 !
    330 !************************************************************************
    331319!
    332320END MODULE ocean_forced_mod
Note: See TracChangeset for help on using the changeset viewer.