Ignore:
Timestamp:
06/17/19 17:38:58 (5 years ago)
Author:
dubos
Message:

devel : compute_pression for unstructured mesh

File:
1 edited

Legend:

Unmodified
Added
Removed
  • codes/icosagcm/devel/src/diagnostics/theta_rhodz.f90

    r533 r913  
    11MODULE theta2theta_rhodz_mod 
     2  USE icosa 
    23  USE field_mod 
     4  USE compute_diagnostics_mod 
     5  IMPLICIT NONE 
    36  PRIVATE 
     7 
    48  TYPE(t_field), POINTER, SAVE  :: f_p(:) 
    59 
     
    1216   
    1317  SUBROUTINE init_theta2theta_rhodz 
    14   USE icosa 
    15   USE field_mod 
    16   IMPLICIT NONE 
    1718    CALL allocate_field(f_p,field_t,type_real,llm+1,name='p (theta2theta_rhodz_mod)')     
    1819  END SUBROUTINE init_theta2theta_rhodz 
     
    2021 
    2122  SUBROUTINE theta_rhodz2theta(f_ps,f_theta_rhodz,f_theta) 
    22   USE icosa 
    23   IMPLICIT NONE 
    2423    TYPE(t_field), POINTER :: f_ps(:) 
    2524    TYPE(t_field), POINTER :: f_theta_rhodz(:) 
     
    4645 
    4746  SUBROUTINE theta_rhodz2temperature(f_ps,f_theta_rhodz,f_temp) 
    48   USE icosa 
    49   USE pression_mod 
    50   IMPLICIT NONE 
    5147    TYPE(t_field), POINTER :: f_ps(:) 
    5248    TYPE(t_field), POINTER :: f_theta_rhodz(:) 
     
    7874  
    7975  SUBROUTINE temperature2theta_rhodz(f_ps,f_temp,f_theta_rhodz) 
    80   USE icosa 
    81   USE pression_mod 
    8276  USE exner_mod 
    8377  IMPLICIT NONE 
     
    113107     
    114108  SUBROUTINE theta2theta_rhodz(f_ps,f_theta,f_theta_rhodz) 
    115   USE icosa 
    116   IMPLICIT NONE 
    117109    TYPE(t_field), POINTER :: f_ps(:) 
    118110    TYPE(t_field), POINTER :: f_theta(:) 
     
    139131   
    140132  SUBROUTINE compute_theta2theta_rhodz(ps,theta, theta_rhodz,offset) 
    141   USE icosa 
    142133  USE disvert_mod 
    143134  USE omp_para 
    144   IMPLICIT NONE 
    145135    REAL(rstd),INTENT(IN) :: ps(iim*jjm) 
    146136    REAL(rstd),INTENT(IN) :: theta(iim*jjm,llm) 
     
    166156 
    167157  SUBROUTINE compute_theta_rhodz2theta(ps,theta_rhodz,theta,offset) 
    168   USE icosa 
    169158  USE disvert_mod 
    170159  USE omp_para 
    171   IMPLICIT NONE 
    172160    REAL(rstd),INTENT(IN) :: ps(iim*jjm) 
    173161    REAL(rstd),INTENT(IN) :: theta_rhodz(iim*jjm,llm) 
     
    198186 
    199187  SUBROUTINE compute_theta_rhodz2temperature(p,theta_rhodz,temp,offset) 
    200   USE icosa 
    201   USE pression_mod 
    202188  USE exner_mod 
    203189  USE omp_para 
    204   IMPLICIT NONE 
    205190    REAL(rstd),INTENT(IN) :: p(iim*jjm,llm+1) 
    206191    REAL(rstd),INTENT(IN) :: theta_rhodz(iim*jjm,llm) 
     
    227212 
    228213  SUBROUTINE compute_temperature2theta_rhodz(p,temp,theta_rhodz,offset) 
    229   USE icosa 
    230   USE pression_mod 
    231214  USE exner_mod 
    232215  USE omp_para 
    233   IMPLICIT NONE 
    234216    REAL(rstd),INTENT(IN)  :: p(iim*jjm,llm+1) 
    235217    REAL(rstd),INTENT(OUT) :: theta_rhodz(iim*jjm,llm) 
Note: See TracChangeset for help on using the changeset viewer.