Ignore:
Timestamp:
06/08/16 01:51:21 (8 years ago)
Author:
dubos
Message:

Introduced entropy as prognostic variable - tested with JW06

File:
1 edited

Legend:

Unmodified
Added
Removed
  • codes/icosagcm/trunk/src/caldyn_kernels_base.f90

    r377 r401  
    3737 
    3838    INTEGER :: i,j,ij,l 
    39     REAL(rstd) :: p_ik, exner_ik 
     39    REAL(rstd) :: Rd, p_ik, exner_ik, temp_ik 
    4040    INTEGER    :: ij_omp_begin_ext, ij_omp_end_ext 
    41  
    4241 
    4342    CALL trace_start("compute_geopot") 
     
    4746    ij_omp_end_ext=ij_omp_end_ext+ij_begin_ext-1 
    4847 
     48    Rd = kappa*cpp 
     49 
    4950    IF(caldyn_eta==eta_mass .AND. .NOT. DEC) THEN 
    5051!!! Compute exner function and geopotential 
     52       STOP 
    5153       DO l = 1,llm 
    5254          !DIR$ SIMD 
     
    8991          END DO 
    9092          ! now pk contains the Lagrange multiplier (pressure) 
    91        ELSE ! non-Boussinesq, compute geopotential and Exner pressure 
     93       ELSE ! non-Boussinesq, compute pressure, Exner pressure or temperature, then geopotential 
    9294          ! uppermost layer 
    9395 
     
    109111             END DO 
    110112          END IF 
    111           ! specific volume v = kappa*theta*pi/p = dphi/g/rhodz 
     113 
    112114          DO l = 1,llm 
    113              !DIR$ SIMD 
    114              DO ij=ij_omp_begin_ext,ij_omp_end_ext          
    115                 p_ik = pk(ij,l) 
    116                 exner_ik = cpp * (p_ik/preff) ** kappa 
    117                 pk(ij,l) = exner_ik 
    118                 geopot(ij,l+1) = geopot(ij,l) + (g*kappa)*rhodz(ij,l)*theta(ij,l)*exner_ik/p_ik  
    119              ENDDO 
     115             SELECT CASE(caldyn_thermo) 
     116             CASE(thermo_theta) 
     117                !DIR$ SIMD 
     118                DO ij=ij_omp_begin_ext,ij_omp_end_ext 
     119                   p_ik = pk(ij,l) 
     120                   exner_ik = cpp * (p_ik/preff) ** kappa 
     121                   pk(ij,l) = exner_ik 
     122                   ! specific volume v = kappa*theta*pi/p = dphi/g/rhodz 
     123                   geopot(ij,l+1) = geopot(ij,l) + (g*kappa)*rhodz(ij,l)*theta(ij,l)*exner_ik/p_ik 
     124                ENDDO 
     125             CASE(thermo_entropy) ! theta is in fact entropy = cpp*log(theta/Treff) = cpp*log(T/Treff) - Rd*log(p/preff) 
     126                !DIR$ SIMD 
     127                DO ij=ij_omp_begin_ext,ij_omp_end_ext 
     128                   p_ik = pk(ij,l) 
     129                   temp_ik = Treff*exp((theta(ij,l) + Rd*log(p_ik/preff))/cpp) 
     130                   pk(ij,l) = temp_ik 
     131                   ! specific volume v = Rd*T/p = dphi/g/rhodz 
     132                   geopot(ij,l+1) = geopot(ij,l) + (g*Rd)*rhodz(ij,l)*temp_ik/p_ik 
     133                ENDDO 
     134             CASE DEFAULT 
     135                STOP 
     136             END SELECT 
    120137          ENDDO 
    121138       END IF 
Note: See TracChangeset for help on using the changeset viewer.