Changeset 657


Ignore:
Timestamp:
12/30/17 01:56:49 (6 years ago)
Author:
dubos
Message:

devel/hex : updated kernels

Location:
codes/icosagcm/devel/src
Files:
1 added
3 edited

Legend:

Unmodified
Added
Removed
  • codes/icosagcm/devel/src/dynamics/caldyn_kernels_hevi.F90

    r612 r657  
    118118    REAL(rstd) :: D_il(iim*jjm,llm+1)    ! Thomas algorithm 
    119119    REAL(rstd) :: gamma, rho_ij, X_ij, Y_ij 
    120     REAL(rstd) :: wil, tau2_g, g2, gm2, ml_g2, c2_mik 
     120    REAL(rstd) :: wil, tau2_g, g2, gm2, ml_g2, c2_mik, vreff 
    121121 
    122122    INTEGER    :: iter, ij, l, ij_omp_begin_ext, ij_omp_end_ext 
     
    282282    REAL(rstd) :: berni(iim*jjm,llm)         ! (W/m_il)^2 
    283283    REAL(rstd) :: berni1(iim*jjm)         ! (W/m_il)^2 
    284     REAL(rstd) :: gamma, rho_ij, T_ij, X_ij, Y_ij, vreff, Rd, Cvd 
     284    REAL(rstd) :: gamma, rho_ij, T_ij, X_ij, Y_ij, vreff, Rd, Cvd, Rd_preff 
    285285    INTEGER    :: ij, l 
    286286 
     
    292292 
    293293!$OMP BARRIER 
     294 
     295#include "../kernels_hex/caldyn_mil.k90" 
     296  IF(tau>0) THEN ! solve implicit problem for geopotential 
     297    CALL compute_NH_geopot(tau,phis, rhodz, m_il, theta, W, geopot) 
     298  END IF 
    294299#define PHI_BOT(ij) phis(ij) 
    295 #define PHI_BOT_VAR phis 
    296300#include "../kernels_hex/caldyn_solver.k90" 
    297 #undef PHI_BOT_VAR 
    298301#undef PHI_BOT 
    299302!$OMP BARRIER 
  • codes/icosagcm/devel/src/kernels_hex/caldyn_solver.k90

    r578 r657  
    11   !-------------------------------------------------------------------------- 
    22   !---------------------------- caldyn_solver ---------------------------------- 
    3    IF (ll_begin==1) THEN 
    4       !DIR$ SIMD 
    5       DO ij=ij_begin_ext, ij_end_ext 
    6          m_il(ij,1) = .5*rhodz(ij,1) 
    7       END DO 
    8    END IF 
    9    DO l = ll_beginp1, ll_end 
    10       !DIR$ SIMD 
    11       DO ij=ij_begin_ext, ij_end_ext 
    12          m_il(ij,l) = .5*(rhodz(ij,l)+rhodz(ij,l-1)) 
    13       END DO 
    14    END DO 
    15    IF(ll_endp1==llm+1) THEN 
    16       !DIR$ SIMD 
    17       DO ij=ij_begin_ext, ij_end_ext 
    18          m_il(ij,llm+1) = .5*rhodz(ij,llm+1 -1) 
    19       END DO 
    20    END IF 
    21    ! 
    22    IF(tau>0) THEN ! solve implicit problem for geopotential 
    23       CALL compute_NH_geopot(tau,PHI_BOT_VAR, rhodz, m_il, theta, W, geopot) 
    24    END IF 
    253   ! 
    264   ! Compute pressure (pres) and Exner function (pk) 
     
    308   gamma = 1./(1.-kappa) 
    319   vreff = Rd*Treff/preff ! reference specific volume 
    32    Cvd = cpp-Rd 
     10   Cvd = 1./(cpp-Rd) 
     11   Rd_preff = kappa*cpp/preff 
    3312   DO l = ll_begin, ll_end 
    3413      !DIR$ SIMD 
     
    3615         SELECT CASE(caldyn_thermo) 
    3716         CASE(thermo_theta) 
    38             rho_ij = g*rhodz(ij,l)/(geopot(ij,l+1)-geopot(ij,l)) 
    39             X_ij = (cpp/preff)*kappa*theta(ij,l,1)*rho_ij 
     17            rho_ij = 1./(geopot(ij,l+1)-geopot(ij,l)) 
     18            rho_ij = rho_ij*g*rhodz(ij,l) 
     19            X_ij = Rd_preff*theta(ij,l,1)*rho_ij 
    4020            ! kappa.theta.rho = p/exner 
    4121            ! => X = (p/p0)/(exner/Cp) 
     
    4626            pk(ij,l) = cpp*((pres(ij,l)/preff)**kappa) ! Exner 
    4727         CASE(thermo_entropy) 
    48             rho_ij = g*rhodz(ij,l)/(geopot(ij,l+1)-geopot(ij,l)) 
    49             T_ij = Treff*exp( (theta(ij,l,1)+Rd*log(vreff*rho_ij))/Cvd ) 
     28            rho_ij = 1./(geopot(ij,l+1)-geopot(ij,l)) 
     29            rho_ij = rho_ij*g*rhodz(ij,l) 
     30            T_ij = Treff*exp( (theta(ij,l,1)+Rd*log(vreff*rho_ij))*Cvd ) 
    5031            pres(ij,l) = rho_ij*Rd*T_ij 
    5132            pk(ij,l) = T_ij 
  • codes/icosagcm/devel/src/kernels_hex/compute_NH_geopot.k90

    r563 r657  
    44   g2=g*g 
    55   gm2 = 1./g2 
     6   vreff = Treff*cpp/preff*kappa 
    67   gamma = 1./(1.-kappa) 
    78   !$OMP BARRIER 
     
    3031            DO ij=ij_omp_begin_ext,ij_omp_end_ext 
    3132               rho_ij = (g*m_ik(ij,l))/(Phi_il(ij,l+1)-Phi_il(ij,l)) 
    32                X_ij = Treff*exp(theta(ij,l)/cpp) ! theta = Tref.exp(s/Cp) 
    33                X_ij = (cpp/preff)*kappa*X_ij*rho_ij 
    34                p_ik(ij,l) = preff*(X_ij**gamma) 
     33               X_ij = log(vreff*rho_ij) + theta(ij,l)/cpp 
     34               p_ik(ij,l) = preff*exp(X_ij*gamma) 
    3535               c2_mik = gamma*p_ik(ij,l)/(rho_ij*m_ik(ij,l)) ! c^2 = gamma*R*T = gamma*p/rho 
    3636               A_ik(ij,l) = c2_mik*(tau/g*rho_ij)**2 
Note: See TracChangeset for help on using the changeset viewer.