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

    r533 r913  
    11MODULE exner_mod 
     2  USE icosa 
     3  IMPLICIT NONE 
     4  PRIVATE 
     5  SAVE 
    26 
    3   INTEGER,SAVE :: caldyn_exner 
     7  INTEGER :: caldyn_exner 
    48!$OMP THREADPRIVATE(caldyn_exner) 
    59 
    610  INTEGER, PARAMETER :: lmdz=3, direct=4 
     11   
     12  PUBLIC :: exner, compute_exner 
    713 
    814CONTAINS 
    915   
    1016  SUBROUTINE exner(f_ps,f_p,f_pks,f_pk) 
    11   USE icosa 
    12   IMPLICIT NONE 
    1317    TYPE(t_field), POINTER :: f_ps(:)  ! IN 
    1418    TYPE(t_field), POINTER :: f_p(:)   ! IN 
     
    3842   
    3943  SUBROUTINE compute_exner(ps,p,pks,pk,offset) 
    40   USE icosa 
    41   USE disvert_mod 
    42   USE pression_mod 
    43   USE omp_para 
    44   IMPLICIT NONE 
     44    USE disvert_mod 
     45    USE omp_para 
    4546    REAL(rstd),INTENT(IN) :: ps(iim*jjm) 
    4647    REAL(rstd),INTENT(IN) :: p(iim*jjm,llm+1) 
Note: See TracChangeset for help on using the changeset viewer.