Ignore:
Timestamp:
06/14/16 21:54:26 (8 years ago)
Author:
dubos
Message:

theta-related cleanup

File:
1 edited

Legend:

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

    r295 r428  
    11MODULE etat0_academic_mod 
    2  
    3  
    4  
    5  
     2  USE icosa 
     3  IMPLICIT NONE 
     4 
     5  PRIVATE 
     6   
     7  PUBLIC :: etat0 
     8   
    69CONTAINS 
    710   
     
    912  USE icosa 
    1013  USE kinetic_mod 
    11   IMPLICIT NONE 
    1214    TYPE(t_field),POINTER,SAVE :: f_ps(:) 
    1315    TYPE(t_field),POINTER,SAVE :: f_phis(:) 
     
    2123    REAL(rstd),POINTER :: temp(:) 
    2224    INTEGER :: ind 
    23      
    24      
     25         
    2526    CALL allocate_field(f_ps,field_t,type_real) 
    2627    CALL allocate_field(f_phis,field_t,type_real) 
     
    4041     
    4142  END SUBROUTINE test_etat0_academic 
    42     
    4343     
    4444  SUBROUTINE etat0(f_ps,f_phis,f_theta_rhodz,f_u, f_q) 
    4545  USE icosa 
    46   IMPLICIT NONE 
    4746    TYPE(t_field),POINTER :: f_ps(:) 
    4847    TYPE(t_field),POINTER :: f_phis(:) 
     
    5655    REAL(rstd),POINTER :: u(:,:) 
    5756    INTEGER :: ind 
    58      
     57 
     58    PRINT *, 'etat0_academic needs an upgrade for 4D theta' 
     59    PRINT *, 'STOP in etat0_academic.f90/etat0' 
     60    STOP 
     61 
    5962    DO ind=1,ndomain 
    6063      IF (.NOT. assigned_domain(ind)) CYCLE 
     
    7780  USE geopotential_mod 
    7881  USE theta2theta_rhodz_mod 
    79   IMPLICIT NONE   
    8082  REAL(rstd),INTENT(OUT) :: ps(iim*jjm) 
    8183  REAL(rstd),INTENT(OUT) :: phis(iim*jjm) 
     
    99101  REAL(rstd) :: fact(3*iim*jjm) 
    100102  REAL(rstd) :: ut(3*iim*jjm,llm) 
    101    
    102    
     103     
    103104    DO l=1,llm 
    104105       zsig=ap(l)/preff+bp(l) 
     
    137138    CALL compute_pression(ps,p,1)      
    138139!$OMP BARRIER 
    139     CALL compute_exner(ps,p,pks,pk,1)   
    140 !$OMP BARRIER 
    141     CALL compute_geopotential(phis,pks,pk,theta,phi,1) 
     140    CALL compute_geopotential(phis,ps,theta,phi,1) 
    142141 
    143142 
Note: See TracChangeset for help on using the changeset viewer.