Ignore:
Timestamp:
07/15/19 23:21:31 (5 years ago)
Author:
dubos
Message:

devel : fixed diagnosis of hydrostatic pressure for Lagrangian vertical coordinate

File:
1 edited

Legend:

Unmodified
Added
Removed
  • codes/icosagcm/devel/src/diagnostics/compute_pression.F90

    r913 r955  
    33  USE icosa 
    44  USE omp_para 
    5   USE disvert_mod, ONLY : ap, bp, ap_bp_present 
     5  USE disvert_mod, ONLY : ap, bp, ap_bp_present, ptop, caldyn_eta, eta_lag 
    66  IMPLICIT NONE 
    77  PRIVATE 
     
    1010 
    1111  PUBLIC :: pression, compute_pression_hex, compute_pression_unst, & 
    12        pression_mid, compute_pression_mid_hex, compute_pression_mid_unst 
     12       pression_mid, compute_pression_mid_hex, compute_pression_mid_unst, & 
     13       hydrostatic_pressure, compute_hydrostatic_pressure_unst, compute_hydrostatic_pressure_hex 
    1314 
    1415CONTAINS 
     
    9293  END SUBROUTINE pression_mid 
    9394 
     95  SUBROUTINE hydrostatic_pressure(f_rhodz, f_theta_rhodz, f_ps, f_p) 
     96    TYPE(t_field), POINTER :: f_rhodz(:), f_theta_rhodz(:), f_ps(:), f_p(:) 
     97    REAL(rstd), POINTER :: ps(:), rhodz(:,:), p(:,:), theta_rhodz(:,:,:) 
     98    INTEGER :: ind 
     99    DO ind=1,ndomain 
     100      IF (.NOT. assigned_domain(ind)) CYCLE 
     101      CALL swap_dimensions(ind) 
     102      CALL swap_geometry(ind) 
     103      rhodz=f_rhodz(ind) 
     104      theta_rhodz=f_theta_rhodz(ind) 
     105      ps=f_ps(ind) 
     106      p=f_p(ind) 
     107      CALL compute_hydrostatic_pressure(rhodz, theta_rhodz, ps, p) 
     108    ENDDO 
     109  END SUBROUTINE hydrostatic_pressure 
     110 
    94111!------------- hexagonal-mesh compute kernels -------- 
    95112 
     
    115132#undef AP 
    116133#undef BP 
     134 
     135  SUBROUTINE compute_hydrostatic_pressure_hex(rhodz, theta_rhodz, ps, pk) 
     136    REAL(rstd),INTENT(IN)  :: rhodz(iim*jjm,llm) ! mass per unit surface in each model level 
     137    REAL(rstd),INTENT(IN)  :: theta_rhodz(iim*jjm,llm, nqdyn) ! dynamical tracers (theta/entropy) 
     138    REAL(rstd),INTENT(OUT) :: ps(iim*jjm)        ! surface pressure, diagnosed if Lagrangian vertical coordinate  
     139    REAL(rstd),INTENT(OUT) :: pk(iim*jjm,llm)    ! pressure at full levels 
     140    INTEGER :: ij,l, ij_omp_begin_ext, ij_omp_end_ext 
     141    !$OMP BARRIER 
     142    CALL distrib_level(ij_begin_ext,ij_end_ext, ij_omp_begin_ext,ij_omp_end_ext) 
     143#include "../kernels_hex/compute_hydrostatic_pressure.k90" 
     144    !$OMP BARRIER 
     145  END SUBROUTINE compute_hydrostatic_pressure_hex 
    117146 
    118147!----------- unstructured-mesh compute kernels -------- 
     
    140169#undef BP 
    141170 
     171  SUBROUTINE compute_hydrostatic_pressure_unst(rhodz, theta_rhodz, ps, pk) 
     172    FIELD_MASS,  INTENT(IN)  :: rhodz ! mass per unit surface in each model level 
     173    FIELD_THETA, INTENT(IN)  :: theta_rhodz(iim*jjm,llm, nqdyn) ! dynamical tracers (theta/entropy) 
     174    FIELD_PS,    INTENT(OUT) :: ps(iim*jjm)        ! surface pressure, diagnosed if Lagrangian vertical coordinate  
     175    FIELD_MASS,  INTENT(OUT) :: pk(iim*jjm,llm)    ! pressure at full levels 
     176    DECLARE_INDICES 
     177#include "../kernels_unst/compute_hydrostatic_pressure.k90" 
     178  END SUBROUTINE compute_hydrostatic_pressure_unst 
     179   
     180 
    142181END MODULE compute_pression_mod 
Note: See TracChangeset for help on using the changeset viewer.