Changeset 916


Ignore:
Timestamp:
06/18/19 14:17:55 (5 years ago)
Author:
dubos
Message:

devel : added variable Cp to compute_temperature

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

Legend:

Unmodified
Added
Removed
  • codes/icosagcm/devel/src/diagnostics/compute_temperature.F90

    r915 r916  
    11MODULE compute_temperature_mod 
    2   USE earth_const, ONLY : cpp, cppv, kappa, Rd, Rv, preff, Treff, & 
    3        caldyn_thermo, physics_thermo, & 
    4        thermo_theta, thermo_entropy, thermo_moist, thermo_fake_moist 
     2  USE earth_const, ONLY : cpp, cppv, kappa, Rd, Rv, preff, Treff, nu, & 
     3       caldyn_thermo, physics_thermo, thermo_fake_moist, & 
     4       thermo_theta, thermo_entropy, thermo_variable_Cp, thermo_moist 
    55  USE grid_param 
    66  IMPLICIT NONE 
     
    7979        temp_ik = Treff*exp((theta_ik + Rd*log(p_ik/preff))/cpp) 
    8080     {% endcall %} 
     81  CASE(thermo_variable_Cp) 
     82     {% call loop_compute_temperature() %} 
     83       Cp_ik = nu*( theta_ik + Rd*log(p_ik/preff) ) 
     84       temp_ik = Treff* (Cp_ik/cpp)**(1./nu)   
     85     {% endcall %} 
    8186  CASE(thermo_moist) 
    8287     {% call loop_compute_temperature() %} 
     
    95100    REAL(rstd),INTENT(IN)    :: q(llm, primal_num, nqtot) 
    96101    REAL(rstd),INTENT(INOUT) :: temp(llm, primal_num) 
    97     REAL(rstd) :: p_ik, theta_ik, temp_ik, qv, chi, Rmix   
     102    REAL(rstd) :: p_ik, theta_ik, temp_ik, qv, chi, Rmix, Cp_ik 
    98103    DECLARE_INDICES 
    99104#include "../kernels_unst/compute_temperature.k90" 
     
    107112    REAL(rstd),INTENT(INOUT) :: temp(iim*jjm,llm) 
    108113 
    109     REAL(rstd) :: p_ik, theta_ik, temp_ik, qv, chi, Rmix 
     114    REAL(rstd) :: p_ik, theta_ik, temp_ik, qv, chi, Rmix, Cp_ik 
    110115    INTEGER :: ij,l 
    111116#include "../kernels_hex/compute_temperature.k90" 
  • codes/icosagcm/devel/src/kernels_hex/compute_temperature.k90

    r915 r916  
    5252         END DO 
    5353      END IF 
     54   CASE(thermo_variable_Cp) 
     55      DO l = ll_begin, ll_end 
     56         !DIR$ SIMD 
     57         DO ij=ij_begin, ij_end 
     58            p_ik = pmid(ij,l) 
     59            theta_ik = temp(ij,l) 
     60            qv = q(ij,l,1) ! water vapor mixing ratio = mv/md 
     61            Cp_ik = nu*( theta_ik + Rd*log(p_ik/preff) ) 
     62            temp_ik = Treff* (Cp_ik/cpp)**(1./nu) 
     63            temp(ij,l) = temp_ik 
     64         END DO 
     65      END DO 
    5466   CASE(thermo_moist) 
    5567      DO l = ll_begin, ll_end 
  • codes/icosagcm/devel/src/kernels_unst/compute_temperature.k90

    r915 r916  
    6060         !$OMP END DO 
    6161      END IF 
     62   CASE(thermo_variable_Cp) 
     63      !$OMP DO SCHEDULE(STATIC) 
     64      DO ij = 1, primal_num 
     65         !DIR$ SIMD 
     66         DO l = 1, llm 
     67            p_ik = pmid(l,ij) 
     68            theta_ik = temp(l,ij) 
     69            qv = q(l,ij,1) ! water vapor mixing ratio = mv/md 
     70            Cp_ik = nu*( theta_ik + Rd*log(p_ik/preff) ) 
     71            temp_ik = Treff* (Cp_ik/cpp)**(1./nu) 
     72            temp(l,ij) = temp_ik 
     73         END DO 
     74      END DO 
     75      !$OMP END DO 
    6276   CASE(thermo_moist) 
    6377      !$OMP DO SCHEDULE(STATIC) 
Note: See TracChangeset for help on using the changeset viewer.