c*********************************************************** REAL (kind=dp) FUNCTION rconv_mean(r0,r_moyen) c routine private du module mod_static c estimation du rayon moyen de la convection c R* = R0 + alpha/2 Hp(R*), R0 rayon à la base de la ZC c entrées c r0 : rayon inférieur de la ZC c r_moyen : rayon de calcul c Auteur: P.Morel, laboratoire Lagrange, O.C.A. c----------------------------------------------------------------------- USE mod_donnees, ONLY : alpha, en_m23, g, 1 m_ch, msol, nchim, ne, nucleo, ord_rot, pi, rsol USE mod_etat, ONLY : etat USE mod_kind USE mod_numerique, ONLY : bsp1dn, no_croiss USE mod_opa, ONLY : opa, dehors USE mod_variables, ONLY: bp, chim, knot, knotc, knotr, inter, 1 q, qt, mc, mct, m_stat, n_ch, n_qs, r_stat, sortie IMPLICIT NONE REAL(kind=dp), INTENT(in) :: r_moyen, r0 REAL(kind=dp), DIMENSION(ne) :: dfdq, f REAL(kind=dp), DIMENSION(nchim) :: dxchim, xchim REAL(kind=dp), SAVE :: cte4 REAL (kind=dp) :: alfa, beta, cp, delta, deltap, deltat, deltax, 1 dcpp, dcpt, dcpx, dgradadp, dgradadt, dgradadx, drop, drot, 2 drox, dup, dut, dux, gamma1, gradad, m_moyen, nu, p, ro, 3 r_eff, t, u INTEGER, SAVE :: lc=1 LOGICAL, SAVE :: init=.TRUE. c------------------------------------------------------------------- 2000 FORMAT(8es10.3) c initialisations IF(init)THEN init=.FALSE. cte4=alpha*rsol/2.d0/g/msol ENDIF c r_eff: rayon moyen en m^2/3 ou m^1/3 IF(en_m23)THEN r_eff=r_moyen**2 ELSE r_eff=r_moyen ENDIF c variables en r_moyen (r_eff), m_moyen en m/Msol, nu en m^2/3 CALL inter('r',bp,q,qt,n_qs,knot,r_eff,f,dfdq,r_stat,m_stat) p=EXP(f(1)) ; t=EXP(f(2)) IF(en_m23)THEN nu=ABS(f(5)) m_moyen=SQRT(nu)**3 ELSE nu=f(5)**2 m_moyen=ABS(f(5))**3 ENDIF c composition chimique en r_moyen (nu=m^2/3) CALL bsp1dn(nchim,chim,mc,mct,n_ch,m_ch, 1 knotc,.TRUE.,MAX(mc(1),MIN(nu,mc(n_ch))),lc,xchim,dxchim) c pression gazeuse (Pgas + Prad) xchim=xchim*nucleo !xchim par gramme CALL etat(p,t,xchim,.FALSE., 1 ro,drop,drot,drox,u,dup,dut,dux, 2 delta,deltap,deltat,deltax,cp,dcpp,dcpt,dcpx, 3 gradad,dgradadp,dgradadt,dgradadx,alfa,beta,gamma1) c R* rconv_mean=r0+cte4*p*r_moyen**2/m_moyen/ro RETURN END FUNCTION rconv_mean