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/etat0.f90

    r388 r401  
    172172         CALL compute_etat0_collocated(ps,mass, phis, temp, u, geopot, W, q) 
    173173      ENDIF 
     174 
     175      IF( TRIM(etat0_type)/='williamson91.6' ) CALL compute_temperature2entropy(ps,temp,q,theta_rhodz, 1) 
     176     
    174177    ENDDO 
    175178     
    176     IF( TRIM(etat0_type)/='williamson91.6' ) CALL temperature2theta_rhodz(f_ps,f_temp,f_theta_rhodz) 
    177      
    178179    CALL deallocate_field(f_temp) 
    179180     
    180181  END SUBROUTINE etat0_collocated 
     182 
     183  SUBROUTINE compute_temperature2entropy(ps,temp,q,theta_rhodz,offset) 
     184    USE icosa 
     185    USE pression_mod 
     186    USE exner_mod 
     187    USE omp_para 
     188    IMPLICIT NONE 
     189    REAL(rstd),INTENT(IN)  :: ps(iim*jjm) 
     190    REAL(rstd),INTENT(IN)  :: temp(iim*jjm,llm) 
     191    REAL(rstd),INTENT(IN)  :: q(iim*jjm,llm,nqtot) 
     192    REAL(rstd),INTENT(OUT) :: theta_rhodz(iim*jjm,llm) 
     193    INTEGER,INTENT(IN) :: offset 
     194 
     195    REAL(rstd) :: p(iim*jjm,llm+1) 
     196    REAL(rstd) :: cppd,Rd, mass, p_ij, q_ij,r_ij, chi,nu, entropy, theta 
     197    INTEGER :: i,j,ij,l 
     198 
     199    cppd=cpp 
     200    Rd=kappa*cppd 
     201 
     202    CALL compute_pression(ps,p,offset) 
     203    ! flush p 
     204    !$OMP BARRIER 
     205    DO    l    = ll_begin, ll_end 
     206       DO j=jj_begin-offset,jj_end+offset 
     207          DO i=ii_begin-offset,ii_end+offset 
     208             ij=(j-1)*iim+i 
     209             mass = (p(ij,l)-p(ij,l+1))/g ! dry+moist mass 
     210             p_ij = .5*(p(ij,l)+p(ij,l+1))  ! pressure at full level 
     211             SELECT CASE(caldyn_thermo) 
     212             CASE(thermo_theta) 
     213                theta = temp(ij,l)*(p_ij/preff)**(-kappa)  
     214                theta_rhodz(ij,l) = mass * theta 
     215             CASE(thermo_entropy) 
     216                nu = log(p_ij/preff) 
     217                chi = log(temp(ij,l)/Treff) 
     218                entropy = cppd*chi-Rd*nu 
     219                theta_rhodz(ij,l) = mass * entropy 
     220!             CASE(thermo_moist) 
     221!                q_ij=q(ij,l,1) 
     222!                r_ij=1.-q_ij 
     223!                mass=mass*(1-q_ij) ! dry mass 
     224!                nu = log(p_ij/preff) 
     225!                chi = log(temp(ij,l)/Treff) 
     226!                entropy = r_ij*(cppd*chi-Rd*nu) + q_ij*(cppv*chi-Rv*nu) 
     227!                theta_rhodz(ij,l) = mass * entropy                 
     228                CASE DEFAULT 
     229                   STOP 
     230             END SELECT 
     231          ENDDO 
     232       ENDDO 
     233    ENDDO 
     234    !$OMP BARRIER   
     235  END SUBROUTINE compute_temperature2entropy 
    181236 
    182237  SUBROUTINE compute_etat0_collocated(ps,mass,phis,temp_i,u, geopot,W, q) 
Note: See TracChangeset for help on using the changeset viewer.