Changeset 955


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

devel : fixed diagnosis of hydrostatic pressure for Lagrangian vertical coordinate

Location:
codes/icosagcm/devel/src
Files:
5 edited

Legend:

Unmodified
Added
Removed
  • codes/icosagcm/devel/src/base/init_grid_param.f90

    r952 r955  
    7070    compute_pression_mid => compute_pression_mid_hex 
    7171    compute_temperature  => compute_temperature_hex 
     72    compute_hydrostatic_pressure => compute_hydrostatic_pressure_hex 
    7273    ! dynamics 
    7374    compute_pvort_only        => compute_pvort_only_hex 
     
    8586    compute_pression_mid => compute_pression_mid_unst 
    8687    compute_temperature  => compute_temperature_unst 
     88    compute_hydrostatic_pressure => compute_hydrostatic_pressure_unst 
    8789    ! dynamics 
    8890    compute_pvort_only         => compute_pvort_only_unst 
  • codes/icosagcm/devel/src/diagnostics/compute_diagnostics.f90

    r952 r955  
    3131    END SUBROUTINE comp_temperature 
    3232 
     33    SUBROUTINE comp_hydro_press(rhodz, theta_rhodz, ps, p) 
     34      IMPORT 
     35      REAL(rstd),INTENT(IN)  :: rhodz(iim_jjm_i, llm_) 
     36      REAL(rstd),INTENT(IN)  :: theta_rhodz(iim_jjm_i, llm_, nqdyn_) 
     37      REAL(rstd),INTENT(OUT) :: ps(iim_jjm_i) 
     38      REAL(rstd),INTENT(OUT) :: p(iim_jjm_i, llm_) 
     39    END SUBROUTINE comp_hydro_press 
     40 
    3341  END INTERFACE 
    3442 
     
    3644  PROCEDURE(comp_pression),    POINTER :: compute_pression => NULL(), compute_pression_mid => NULL() 
    3745  PROCEDURE(comp_temperature), POINTER :: compute_temperature => NULL() 
     46  PROCEDURE(comp_hydro_press), POINTER :: compute_hydrostatic_pressure => NULL() 
    3847 
    39   PUBLIC :: compute_rhodz, compute_pression, compute_pression_mid, compute_temperature 
     48  PUBLIC :: compute_rhodz, compute_pression, compute_pression_mid, compute_temperature, compute_hydrostatic_pressure 
    4049 
    4150END MODULE compute_diagnostics_mod 
  • 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 
  • codes/icosagcm/devel/src/diagnostics/observable.f90

    r919 r955  
    4343    USE xios_mod 
    4444    USE earth_const 
    45     USE compute_pression_mod, ONLY : pression_mid 
     45    USE compute_pression_mod, ONLY : pression_mid, hydrostatic_pressure 
    4646    USE compute_temperature_mod 
    4747    USE compute_velocity_mod 
     
    9898    END IF 
    9999 
    100     CALL pression_mid(f_ps, f_pmid) 
     100    CALL hydrostatic_pressure(f_mass, f_theta_rhodz, f_ps, f_pmid)  
    101101    CALL temperature(f_pmid, f_q, f_buf_i) ! f_buf_i : IN = theta, out = T 
    102102 
  • codes/icosagcm/devel/src/dynamics/compute_geopot.F90

    r937 r955  
    1717 
    1818#ifdef BEGIN_DYSL 
    19  
    20 #define THECELL {{ thecell }} 
    2119 
    2220{# ---------------- macro to generate code computing pressure top-down --------------- 
     
    5957 
    6058#define END_GEOPOT {% endcall %} 
     59 
     60#define THECELL {{ thecell }} 
     61 
     62KERNEL(compute_hydrostatic_pressure) 
     63  SELECT CASE(caldyn_thermo) 
     64  CASE(thermo_boussinesq) 
     65    ! use hydrostatic balance with theta*rhodz to find pk (=Lagrange multiplier=pressure) 
     66    BALANCE( theta_rhodz(THECELL,1) ) 
     67  CASE(thermo_theta, thermo_entropy, thermo_variable_Cp) 
     68    BALANCE( rhodz(THECELL) ) 
     69  CASE(thermo_moist) 
     70    BALANCE( (rhodz(THECELL)+theta_rhodz(THECELL,2)) ) 
     71  END SELECT 
     72END_BLOCK 
    6173 
    6274KERNEL(compute_geopot) 
Note: See TracChangeset for help on using the changeset viewer.