Changeset 409 for codes/icosagcm


Ignore:
Timestamp:
06/09/16 02:17:06 (8 years ago)
Author:
ymipsl
Message:

adapt dcmip 2016 kessler physic
YM

File:
1 edited

Legend:

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

    r397 r409  
    6565    ! Physics-specific data 
    6666    ALLOCATE(precl_packed(ngrid)) 
    67     precl_packed(:)=0. 
    6867    CALL allocate_field(f_precl, field_t,type_real) 
    6968 
     
    8584    CALL unpack_field(f_precl, precl_packed) 
    8685    CALL output_field("precl",f_precl) 
    87     precl_packed(:)=0. 
    88      
     86        
    8987  END SUBROUTINE write_physics 
    9088 
     
    9391    USE dcmip2016_simple_physics_mod 
    9492    USE dcmip2016_kessler_physic_mod 
     93    USE earth_const 
    9594    USE terminator 
    9695    IMPLICIT NONE 
     
    144143          vfi(ij,l)=v(ij,ll) 
    145144          qfi(ij,l,:)=q(ij,ll,:) 
    146           Tfi(ij,l)=Temp(ij,ll)/(1+0.608*qfi(ij,l,1))   
     145          IF (physics_thermo==thermo_fake_moist) THEN 
     146            Tfi(ij,l)=Temp(ij,ll)/(1+0.608*qfi(ij,l,1))  
     147          ELSE 
     148            Tfi(ij,l)=Temp(ij,ll) 
     149          ENDIF 
    147150       ENDDO 
    148151    ENDDO 
     
    153156      IF (testcase==cyclone) simple_physic_testcase=0 
    154157      CALL simple_physics(ngrid, llm, dt_phys, lat, tfi, qfi(:,:,1) , ufi, vfi, pmid, pint, pdel, 1./pdel, ps, precl, & 
    155                           simple_physic_testcase, .TRUE., .FALSE.) 
     158                          simple_physic_testcase, .FALSE., .FALSE.) 
    156159    ENDIF 
    157160 
     
    163166           ll=llm+1-l 
    164167           rho(l) = pmid(ij,ll)/(287*Temp(ij,l)) 
    165            z(l)=lastz+ (p(ij,l)-p(ij,l+1)) /g / rho(l) 
    166            lastz=z(l) 
    167 !           theta(l)= Tfi(ij,ll)*(1+0.608*qfi(ij,ll,1)) / ( pk(ij,l) / cpp) 
     168           z(l)=lastz 
     169           lastz=lastz+ (p(ij,l)-p(ij,l+1)) /g / rho(l) 
    168170           theta(l)= Tfi(ij,ll) / ( pk(ij,l) / cpp) 
    169171          ENDDO 
     
    173175          qr(:)=qfi(ij,llm:1:-1,3) 
    174176           
    175 !          CALL KESSLER(theta(:), qv, qc, qr, rho(:),  & 
    176 !                       pk(ij,:), dt_phys, z(:), llm, precl(ij))  
     177          CALL KESSLER(theta(:), qv, qc, qr, rho(:),  & 
     178                       pk(ij,:)/cpp, dt_phys, z(:), llm, precl(ij))  
    177179           
    178180           
    179181          DO l=1,llm 
    180182           ll=llm+1-l 
    181 !           Tfi(ij,ll) = theta(l) /(1+0.608*qfi(ij,ll,1)) * ( pk(ij,l) / cpp) 
    182183           Tfi(ij,ll) = theta(l)  * ( pk(ij,l) / cpp) 
    183184          ENDDO 
     
    205206       ll=llm+1-l 
    206207       DO ij=1,ngrid 
    207           dTemp(ij,l) = inv_dt * ( Tfi(ij,ll)*(1+0.608*qfi(ij,ll,1)) - Temp(ij,l) ) 
     208          IF (physics_thermo==thermo_fake_moist) THEN 
     209            dTemp(ij,l) = inv_dt * ( Tfi(ij,ll)*(1+0.608*qfi(ij,ll,1)) - Temp(ij,l) ) 
     210          ELSE 
     211            dTemp(ij,l) = inv_dt * ( Tfi(ij,ll) - Temp(ij,l) ) 
     212          ENDIF 
     213           
    208214          du(ij,l) = inv_dt * (ufi(ij,ll) - u(ij,l)) 
    209215          dv(ij,l) = inv_dt * (vfi(ij,ll) - v(ij,l)) 
Note: See TracChangeset for help on using the changeset viewer.