Changeset 935 for codes/icosagcm/devel


Ignore:
Timestamp:
07/03/19 17:15:11 (5 years ago)
Author:
dubos
Message:

devel : interfaces for caldyn_fast and caldyn_slow_hydro

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

Legend:

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

    r926 r935  
    77  USE compute_caldyn_mod 
    88  USE compute_pvort_only_mod 
     9  USE compute_theta_mod 
     10  USE compute_geopot_mod 
     11  USE compute_caldyn_fast_mod 
     12  USE compute_caldyn_slow_hydro_mod 
    913 
    1014  IMPLICIT NONE 
     
    6468    compute_pression_mid => compute_pression_mid_hex 
    6569    ! dynamics 
    66     compute_pvort_only   => compute_pvort_only_hex 
     70    compute_pvort_only        => compute_pvort_only_hex 
     71    compute_theta             => compute_theta_hex 
     72    compute_geopot            => compute_geopot_hex 
     73    compute_caldyn_fast       => compute_caldyn_fast_hex 
     74    compute_caldyn_slow_hydro => compute_caldyn_slow_hydro_hex 
    6775  END SUBROUTINE select_compute_hex 
    6876 
     
    7381    compute_pression_mid => compute_pression_mid_unst 
    7482    ! dynamics 
    75     compute_pvort_only   => compute_pvort_only_unst 
     83    compute_pvort_only         => compute_pvort_only_unst 
     84    compute_theta              => compute_theta_unst 
     85!    compute_geopot           => compute_geopot_unst 
     86    compute_caldyn_fast        => compute_caldyn_fast_unst 
     87    compute_caldyn_slow_hydro  => compute_caldyn_slow_hydro_unst 
    7688  END SUBROUTINE select_compute_unst 
    77  
    7889   
    7990END MODULE init_grid_param_mod 
  • codes/icosagcm/devel/src/dynamics/caldyn_hevi.f90

    r928 r935  
    55  USE compute_caldyn_vert_mod, ONLY : compute_caldyn_vert => compute_caldyn_vert_manual 
    66  USE compute_caldyn_vert_NH_mod, ONLY : compute_caldyn_vert_NH => compute_caldyn_vert_NH_manual 
    7   USE compute_theta_mod, ONLY : compute_theta => compute_theta_manual 
    8   USE compute_geopot_mod, ONLY : compute_geopot => compute_geopot_manual 
    97  USE compute_caldyn_kv_mod, ONLY : compute_caldyn_kv 
    108  USE compute_caldyn_Coriolis_mod, ONLY : compute_caldyn_Coriolis => compute_caldyn_Coriolis_manual 
     
    1210  USE compute_caldyn_slow_NH_mod, ONLY : compute_caldyn_slow_NH 
    1311  USE compute_caldyn_solver_mod, ONLY : compute_caldyn_solver 
    14   USE compute_caldyn_fast_mod, ONLY : compute_caldyn_fast => compute_caldyn_fast_manual 
    1512  USE compute_NH_geopot_mod, ONLY : compute_NH_geopot 
    1613  IMPLICIT NONE 
     
    3532    USE output_field_mod 
    3633    USE checksum_mod 
    37     USE compute_caldyn_mod, ONLY : compute_pvort_only 
     34    USE compute_caldyn_mod, ONLY : compute_pvort_only, compute_theta, & 
     35         compute_geopot, compute_caldyn_fast 
    3836    IMPLICIT NONE 
    3937    LOGICAL,INTENT(IN)    :: write_out 
  • codes/icosagcm/devel/src/dynamics/compute_caldyn.f90

    r884 r935  
    11MODULE compute_caldyn_mod 
     2  USE prec, ONLY : rstd 
    23  IMPLICIT NONE 
    34  SAVE 
     5   
     6  ! fake array dimensions, for interfaces 
     7  INTEGER, PARAMETER :: iim_jjm_i=1, iim_jjm_u=1, iim_jjm_v =1, llm_=1, llm1=1, nqdyn_=1 
    48 
    59  INTERFACE 
     10      
     11    SUBROUTINE comp_pvort_only(u,rhodz,qu,qv, hv) 
     12      IMPORT 
     13      REAL(rstd),INTENT(IN)  :: u(iim_jjm_i, llm_) 
     14      REAL(rstd),INTENT(INOUT) :: rhodz(iim_jjm_i, llm_) 
     15      REAL(rstd),INTENT(OUT) :: qu(iim_jjm_u, llm_) 
     16      REAL(rstd),INTENT(OUT) :: qv(iim_jjm_v, llm_) 
     17      REAL(rstd),INTENT(OUT) :: hv(iim_jjm_v, llm_) 
     18    END SUBROUTINE comp_pvort_only 
    619 
    7     SUBROUTINE comp_pvort_only(u,rhodz,qu,qv, hv_) 
    8       USE prec, ONLY : rstd 
    9       REAL(rstd),INTENT(IN)  :: u(1,1) 
    10       REAL(rstd),INTENT(INOUT) :: rhodz(1,1) 
    11       REAL(rstd),INTENT(OUT) :: qu(1,1) 
    12       REAL(rstd),INTENT(OUT) :: qv(1,1) 
    13       REAL(rstd),INTENT(OUT) :: hv_(1,1) 
    14     END SUBROUTINE comp_pvort_only 
     20    SUBROUTINE comp_theta(mass_col,theta_rhodz, rhodz,theta) 
     21      IMPORT 
     22      REAL(rstd),INTENT(IN)    :: mass_col(iim_jjm_i) 
     23      REAL(rstd),INTENT(IN)    :: theta_rhodz(iim_jjm_i, llm_, nqdyn_) 
     24      REAL(rstd),INTENT(INOUT) :: rhodz(iim_jjm_i, llm_) 
     25      REAL(rstd),INTENT(OUT)   :: theta(iim_jjm_i, llm_, nqdyn_) 
     26    END SUBROUTINE comp_theta 
     27 
     28    SUBROUTINE comp_geopot(rhodz,theta, ps,pk,geopot)  
     29      IMPORT 
     30      REAL(rstd),INTENT(IN)    :: rhodz(iim_jjm_i, llm_)         ! rho*dz = mass per unit surface in each full model level 
     31      REAL(rstd),INTENT(IN)    :: theta(iim_jjm_i, llm_, nqdyn_) ! active scalars : theta/entropy, moisture, ... 
     32      REAL(rstd),INTENT(INOUT) :: ps(iim_jjm_i)                  ! surface pressure 
     33      REAL(rstd),INTENT(OUT)   :: pk(iim_jjm_i, llm_)            ! Exner function (compressible) /Lagrange multiplier (Boussinesq) 
     34      REAL(rstd),INTENT(INOUT) :: geopot(iim_jjm_i, llm1)        ! geopotential 
     35    END SUBROUTINE comp_geopot 
     36 
     37    SUBROUTINE comp_caldyn_fast(tau,theta,geopot, pk,berni,du,u) 
     38      IMPORT 
     39      REAL(rstd),INTENT(IN)    :: tau                ! "solve" u-tau*du/dt = rhs 
     40      REAL(rstd),INTENT(IN)    :: theta(iim_jjm_i, llm_, nqdyn_) 
     41      REAL(rstd),INTENT(IN)    :: geopot(iim_jjm_i, llm1) 
     42      REAL(rstd),INTENT(INOUT) :: pk(iim_jjm_i, llm_) 
     43      REAL(rstd),INTENT(INOUT) :: berni(iim_jjm_i, llm_)  ! partial Bernoulli function 
     44      REAL(rstd),INTENT(INOUT) :: du(iim_jjm_u, llm_) 
     45      REAL(rstd),INTENT(INOUT) :: u(iim_jjm_u, llm_)   ! INOUT if tau>0 
     46    END SUBROUTINE comp_caldyn_fast 
     47 
     48  SUBROUTINE comp_caldyn_slow_hydro(zero, u,rhodz,hv,Kv, berni, hflux,du) 
     49    IMPORT 
     50    LOGICAL, INTENT(IN) :: zero 
     51    REAL(rstd),INTENT(IN)  :: u(iim_jjm_u, llm_)    ! prognostic "velocity" 
     52    REAL(rstd),INTENT(IN)  :: rhodz(iim_jjm_i, llm_) 
     53    REAL(rstd),INTENT(IN)  :: hv(iim_jjm_v, llm_)   ! height/mass averaged to vertices 
     54    REAL(rstd),INTENT(IN)  :: Kv(iim_jjm_v, llm_)   ! kinetic energy at vertices 
     55    REAL(rstd), INTENT(OUT) :: berni(iim_jjm_i, llm_)  ! Bernoulli function 
     56    REAL(rstd),INTENT(OUT) :: hflux(iim_jjm_u, llm_) ! hflux in kg/s  
     57    REAL(rstd),INTENT(INOUT) :: du(iim_jjm_u, llm_) 
     58  END SUBROUTINE comp_caldyn_slow_hydro 
    1559 
    1660  END INTERFACE 
    1761 
    18   PROCEDURE(comp_pvort_only), POINTER :: compute_pvort_only => NULL() 
     62  PROCEDURE(comp_pvort_only),        POINTER :: compute_pvort_only        => NULL() 
     63  PROCEDURE(comp_theta),             POINTER :: compute_theta             => NULL() 
     64  PROCEDURE(comp_geopot),            POINTER :: compute_geopot            => NULL() 
     65  PROCEDURE(comp_caldyn_fast),       POINTER :: compute_caldyn_fast       => NULL() 
     66  PROCEDURE(comp_caldyn_slow_hydro), POINTER :: compute_caldyn_slow_hydro => NULL() 
    1967 
    2068END MODULE compute_caldyn_mod 
  • codes/icosagcm/devel/src/dynamics/compute_caldyn_fast.F90

    r921 r935  
    1717#ifdef BEGIN_DYSL 
    1818 
    19 KERNEL(caldyn_fast) 
    20 ! 
     19{% macro case_caldyn_fast(name) %} 
     20  CASE({{name}}) 
     21    FORALL_CELLS() 
     22      ON_PRIMAL 
     23        Phi_ik = .5*(geopot(CELL)+geopot(UP(CELL))) 
     24        {{ caller() }} 
     25      END_BLOCK 
     26    END_BLOCK 
     27{%- endmacro %} 
     28 
     29KERNEL(caldyn_fast)  
     30  ! 
    2131  SELECT CASE(caldyn_thermo) 
    2232  CASE(thermo_boussinesq) 
    23     FORALL_CELLS() 
    24       ON_PRIMAL 
    25         berni(CELL) = pk(CELL) 
    26         ! from now on pk contains the vertically-averaged geopotential 
    27         pk(CELL) = .5*(geopot(CELL)+geopot(UP(CELL))) 
    28       END_BLOCK 
    29     END_BLOCK 
    30   CASE(thermo_theta) 
    31     FORALL_CELLS() 
    32       ON_PRIMAL 
    33         berni(CELL) = .5*(geopot(CELL)+geopot(UP(CELL))) 
    34       END_BLOCK 
    35     END_BLOCK 
    36   CASE(thermo_entropy) 
    37     FORALL_CELLS() 
    38       ON_PRIMAL 
    39         berni(CELL) = .5*(geopot(CELL)+geopot(UP(CELL))) 
    40         berni(CELL) = berni(CELL) + pk(CELL)*(cpp-theta(CELL,1)) ! Gibbs = Cp.T-Ts = T(Cp-s) 
    41       END_BLOCK 
    42     END_BLOCK 
    43   CASE(thermo_variable_Cp) 
     33     FORALL_CELLS() 
     34       ON_PRIMAL 
     35         berni(CELL) = pk(CELL) 
     36         ! from now on pk contains the vertically-averaged geopotential 
     37         pk(CELL) = .5*(geopot(CELL)+geopot(UP(CELL))) 
     38       END_BLOCK 
     39     END_BLOCK 
     40  {% call case_caldyn_fast('thermo_theta') %} 
     41     berni(CELL) = Phi_ik 
     42  {%- endcall %} 
     43  {% call case_caldyn_fast('thermo_entropy') %} 
     44     berni(CELL) = Phi_ik + pk(CELL)*(cpp-theta(CELL,1)) ! Gibbs = Cp.T-Ts = T(Cp-s) 
     45  {%- endcall %} 
     46  {% call case_caldyn_fast('thermo_variable_Cp') %} 
    4447    ! thermodynamics with variable Cp 
    4548    !           Cp(T) = Cp0 * (T/T0)^nu 
    4649    ! =>            h = Cp(T).T/(nu+1) 
    47  
    48     FORALL_CELLS() 
    49       ON_PRIMAL 
    50         berni(CELL) = .5*(geopot(CELL)+geopot(UP(CELL))) 
    51         cp_ik = cpp*(pk(CELL)/Treff)**nu 
    52         berni(CELL) = berni(CELL) + pk(CELL)*(cp_ik/(nu+1.)-theta(CELL,1)) ! Gibbs = h-Ts = T(Cp/(nu+1)-s) 
    53       END_BLOCK 
    54     END_BLOCK 
     50     cp_ik = cpp*(pk(ij,l)/Treff)**nu 
     51     berni(CELL) = Phi_ik + pk(CELL)*(cp_ik/(nu+1.)-theta(CELL,1)) ! Gibbs = h-Ts = T(Cp/(nu+1)-s) 
     52  {%- endcall %} 
    5553  CASE DEFAULT 
    5654    PRINT *, 'Unsupported value of caldyn_thermo : ',caldyn_thermo  ! FIXME 
     
    8381    DECLARE_INDICES 
    8482    DECLARE_EDGES 
    85     NUM          :: due, cp_ik 
     83    NUM          :: due, cp_ik, Phi_ik 
    8684    START_TRACE(id_fast, 4,0,2) ! primal, dual, edge 
    8785#include "../kernels_unst/caldyn_fast.k90" 
     
    10199 
    102100    INTEGER :: ij,l 
    103     REAL(rstd) :: cp_ik, qv, temp, chi, log_p_preff, due, due_right, due_lup, due_ldown 
     101    REAL(rstd) :: due, cp_ik, Phi_ik 
    104102 
    105103    CALL trace_start("compute_caldyn_fast") 
    106104#include "../kernels_hex/caldyn_fast.k90" 
    107105    CALL trace_end("compute_caldyn_fast") 
     106     
    108107  END SUBROUTINE compute_caldyn_fast_hex 
    109108 
  • codes/icosagcm/devel/src/dynamics/compute_caldyn_slow_hydro.F90

    r921 r935  
    7373    LOGICAL, INTENT(IN) :: zero 
    7474    REAL(rstd),INTENT(IN)  :: u(3*iim*jjm,llm)    ! prognostic "velocity" 
     75    REAL(rstd),INTENT(IN)  :: rhodz(iim*jjm,llm) 
     76    REAL(rstd),INTENT(IN)  :: hv(2*iim*jjm,llm)   ! height/mass averaged to vertices 
    7577    REAL(rstd),INTENT(IN)  :: Kv(2*iim*jjm,llm)   ! kinetic energy at vertices 
    76     REAL(rstd),INTENT(IN)  :: hv(2*iim*jjm,llm)   ! height/mass averaged to vertices 
    77     REAL(rstd),INTENT(IN)  :: rhodz(iim*jjm,llm) 
     78    REAL(rstd), INTENT(OUT) :: berni(iim*jjm,llm)  ! Bernoulli function 
    7879    REAL(rstd),INTENT(OUT) :: hflux(3*iim*jjm,llm) ! hflux in kg/s 
    7980    REAL(rstd),INTENT(INOUT) :: du(3*iim*jjm,llm) 
    80      
    81     REAL(rstd) :: berni(iim*jjm,llm)  ! Bernoulli function 
    8281    REAL(rstd) :: berni1(iim*jjm)  ! Bernoulli function 
    8382    REAL(rstd) :: uu_right, uu_lup, uu_ldown, ke, uu 
  • codes/icosagcm/devel/src/kernels_hex/caldyn_fast.k90

    r837 r935  
    1616         !DIR$ SIMD 
    1717         DO ij=ij_begin, ij_end 
    18             berni(ij,l) = .5*(geopot(ij,l)+geopot(ij,l+1)) 
     18            Phi_ik = .5*(geopot(ij,l)+geopot(ij,l+1)) 
     19            berni(ij,l) = Phi_ik 
    1920         END DO 
    2021      END DO 
     
    2324         !DIR$ SIMD 
    2425         DO ij=ij_begin, ij_end 
    25             berni(ij,l) = .5*(geopot(ij,l)+geopot(ij,l+1)) 
    26             berni(ij,l) = berni(ij,l) + pk(ij,l)*(cpp-theta(ij,l,1)) ! Gibbs = Cp.T-Ts = T(Cp-s) 
     26            Phi_ik = .5*(geopot(ij,l)+geopot(ij,l+1)) 
     27            berni(ij,l) = Phi_ik + pk(ij,l)*(cpp-theta(ij,l,1)) ! Gibbs = Cp.T-Ts = T(Cp-s) 
    2728         END DO 
    2829      END DO 
    2930   CASE(thermo_variable_Cp) 
    30       ! thermodynamics with variable Cp 
    31       ! Cp(T) = Cp0 * (T/T0)^nu 
    32       ! => h = Cp(T).T/(nu+1) 
    3331      DO l = ll_begin, ll_end 
    3432         !DIR$ SIMD 
    3533         DO ij=ij_begin, ij_end 
    36             berni(ij,l) = .5*(geopot(ij,l)+geopot(ij,l+1)) 
     34            Phi_ik = .5*(geopot(ij,l)+geopot(ij,l+1)) 
     35            ! thermodynamics with variable Cp 
     36            ! Cp(T) = Cp0 * (T/T0)^nu 
     37            ! => h = Cp(T).T/(nu+1) 
    3738            cp_ik = cpp*(pk(ij,l)/Treff)**nu 
    38             berni(ij,l) = berni(ij,l) + pk(ij,l)*(cp_ik/(nu+1.)-theta(ij,l,1)) ! Gibbs = h-Ts = T(Cp/(nu+1)-s) 
     39            berni(ij,l) = Phi_ik + pk(ij,l)*(cp_ik/(nu+1.)-theta(ij,l,1)) ! Gibbs = h-Ts = T(Cp/(nu+1)-s) 
    3940         END DO 
    4041      END DO 
  • codes/icosagcm/devel/src/kernels_unst/caldyn_fast.k90

    r837 r935  
    1919         !DIR$ SIMD 
    2020         DO l = 1, llm 
    21             berni(l,ij) = .5*(geopot(l,ij)+geopot(l+1,ij)) 
     21            Phi_ik = .5*(geopot(l,ij)+geopot(l+1,ij)) 
     22            berni(l,ij) = Phi_ik 
    2223         END DO 
    2324      END DO 
     
    2829         !DIR$ SIMD 
    2930         DO l = 1, llm 
    30             berni(l,ij) = .5*(geopot(l,ij)+geopot(l+1,ij)) 
    31             berni(l,ij) = berni(l,ij) + pk(l,ij)*(cpp-theta(l,ij,1)) ! Gibbs = Cp.T-Ts = T(Cp-s) 
     31            Phi_ik = .5*(geopot(l,ij)+geopot(l+1,ij)) 
     32            berni(l,ij) = Phi_ik + pk(l,ij)*(cpp-theta(l,ij,1)) ! Gibbs = Cp.T-Ts = T(Cp-s) 
    3233         END DO 
    3334      END DO 
    3435      !$OMP END DO 
    3536   CASE(thermo_variable_Cp) 
    36       ! thermodynamics with variable Cp 
    37       ! Cp(T) = Cp0 * (T/T0)^nu 
    38       ! => h = Cp(T).T/(nu+1) 
    3937      !$OMP DO SCHEDULE(STATIC) 
    4038      DO ij = 1, primal_num 
    4139         !DIR$ SIMD 
    4240         DO l = 1, llm 
    43             berni(l,ij) = .5*(geopot(l,ij)+geopot(l+1,ij)) 
    44             cp_ik = cpp*(pk(l,ij)/Treff)**nu 
    45             berni(l,ij) = berni(l,ij) + pk(l,ij)*(cp_ik/(nu+1.)-theta(l,ij,1)) ! Gibbs = h-Ts = T(Cp/(nu+1)-s) 
     41            Phi_ik = .5*(geopot(l,ij)+geopot(l+1,ij)) 
     42            ! thermodynamics with variable Cp 
     43            ! Cp(T) = Cp0 * (T/T0)^nu 
     44            ! => h = Cp(T).T/(nu+1) 
     45            cp_ik = cpp*(pk(ij,l)/Treff)**nu 
     46            berni(l,ij) = Phi_ik + pk(l,ij)*(cp_ik/(nu+1.)-theta(l,ij,1)) ! Gibbs = h-Ts = T(Cp/(nu+1)-s) 
    4647         END DO 
    4748      END DO 
  • codes/icosagcm/devel/src/unstructured/caldyn_unstructured.F90

    r837 r935  
    203203  DECLARE_INDICES 
    204204  DECLARE_EDGES 
    205   NUM          :: due, cp_ik 
     205  NUM          :: due, cp_ik, Phi_ik 
    206206  START_TRACE(id_fast, 4,0,2) ! primal, dual, edge 
    207207#include "../kernels_unst/caldyn_fast.k90" 
Note: See TracChangeset for help on using the changeset viewer.