Changeset 562


Ignore:
Timestamp:
09/28/17 21:58:12 (7 years ago)
Author:
dubos
Message:

devel : per-kernel activation of macro-generated code

Location:
codes/icosagcm/devel/src/dynamics
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • codes/icosagcm/devel/src/dynamics/caldyn.f90

    r531 r562  
    22  USE icosa 
    33  PRIVATE 
     4  SAVE 
    45  CHARACTER(LEN=255),SAVE :: caldyn_type 
    56!$OMP THREADPRIVATE(caldyn_type) 
    6    
    7   PUBLIC init_caldyn, caldyn, caldyn_BC 
     7  
     8  PUBLIC init_caldyn, caldyn, caldyn_BC, dysl 
    89   
    910CONTAINS 
     
    2829    END SELECT 
    2930         
    30        
     31    dysl=.FALSE. 
     32    CALL getin("dysl",dysl) 
     33    dysl_geopot=dysl 
     34    CALL getin("dysl_geopot",dysl_geopot) 
     35    dysl_caldyn_fast=dysl 
     36    CALL getin("dysl_caldyn_fast",dysl_caldyn_fast) 
     37    dysl_slow_hydro=dysl 
     38    CALL getin("dysl_slow_hydro",dysl_slow_hydro) 
     39    dysl_pvort_only=dysl 
     40    CALL getin("dysl_pvort_only",dysl_pvort_only) 
     41    dysl_caldyn_coriolis=dysl 
     42    CALL getin("dysl_caldyn_coriolis",dysl_caldyn_coriolis) 
     43 
    3144  END SUBROUTINE init_caldyn 
    3245 
  • codes/icosagcm/devel/src/dynamics/caldyn_hevi.f90

    r559 r562  
    4848    TYPE(t_field) :: f_dPhi_fast(:) 
    4949     
    50     REAL(rstd),POINTER :: ps(:), dps(:) 
     50    REAL(rstd),POINTER :: ps(:), dps(:), phis(:) 
    5151    REAL(rstd),POINTER :: mass(:,:), theta_rhodz(:,:,:), dtheta_rhodz(:,:,:) 
    5252    REAL(rstd),POINTER :: du(:,:), dW(:,:), dPhi(:,:), hflux(:,:), wflux(:,:) 
     
    115115          CALL compute_geopot(mass,theta, ps,pk,geopot) 
    116116       ELSE 
     117          phis = f_phis(ind) 
    117118          W = f_W(ind) 
    118119          dW = f_dW_fast(ind) 
     
    121122          m_il = f_wil(ind) 
    122123          pres = f_gradPhi2(ind) 
    123           CALL compute_caldyn_solver(tau,mass,theta,pk,geopot,W, m_il,pres, dPhi,dW,du) ! computes d(Phi,W,du)_fast and updates Phi,W 
     124          CALL compute_caldyn_solver(tau,phis, mass,theta,pk,geopot,W, m_il,pres, dPhi,dW,du) ! computes d(Phi,W,du)_fast and updates Phi,W 
    124125       END IF 
    125126       u=f_u(ind) 
  • codes/icosagcm/devel/src/dynamics/caldyn_kernels_base.F90

    r558 r562  
    4949    Rd = kappa*cpp 
    5050 
     51    IF(dysl_geopot) THEN 
    5152#ifdef CPP_DYSL 
    52 !#if 0 
    5353#include "../kernels/compute_geopot.k90" 
    5454#else 
    55  
     55    STOP 'dysl_geopot=.TRUE. but DYNAMICO has been compiled without the -dysl option' 
     56#endif 
     57    ELSE 
    5658    ! Pressure is computed first top-down (temporarily stored in pk) 
    5759    ! Then Exner pressure and geopotential are computed bottom-up 
     
    164166    END IF 
    165167 
    166 #endif 
     168    END IF ! dysl 
    167169 
    168170    !ym flush geopot 
  • codes/icosagcm/devel/src/dynamics/caldyn_kernels_hevi.F90

    r558 r562  
    99  PRIVATE 
    1010 
    11   REAL(rstd), PARAMETER :: pbot=1e5, Phi_bot=0., rho_bot=1e6 ! FIXME 
     11  REAL(rstd), PARAMETER :: pbot=1e5, rho_bot=1e6 
    1212 
    1313  LOGICAL, SAVE :: debug_hevi_solver = .FALSE. 
    14   LOGICAL, PARAMETER :: rigid=.TRUE. 
    1514 
    1615  PUBLIC :: compute_theta, compute_pvort_only, compute_caldyn_Coriolis, & 
     
    6261    CALL trace_start("compute_pvort_only")   
    6362!!! Compute shallow-water potential vorticity 
     63    IF(dysl_pvort_only) THEN 
    6464#ifdef CPP_DYSL 
    6565#include "../kernels/pvort_only.k90" 
    6666#else 
     67        STOP 'dysl_pvort_only=.TRUE. but DYNAMICO is compiled without the -dysl option' 
     68#endif 
     69    ELSE 
     70 
    6771    radius_m2=radius**(-2) 
    6872    DO l = ll_begin,ll_end 
     
    9498 
    9599    ENDDO 
    96 #endif 
     100    
     101    END IF ! dysl 
    97102    CALL trace_end("compute_pvort_only") 
    98103 
    99104  END SUBROUTINE compute_pvort_only 
    100105 
    101   SUBROUTINE compute_NH_geopot(tau, m_ik, m_il, theta, W_il, Phi_il) 
     106  SUBROUTINE compute_NH_geopot(tau, phis, m_ik, m_il, theta, W_il, Phi_il) 
    102107    REAL(rstd),INTENT(IN)    :: tau ! solve Phi-tau*dPhi/dt = Phi_rhs 
     108    REAL(rstd),INTENT(IN)    :: phis(iim*jjm) 
    103109    REAL(rstd),INTENT(IN)    :: m_ik(iim*jjm,llm) 
    104110    REAL(rstd),INTENT(IN)    :: m_il(iim*jjm,llm+1) 
     
    125131 
    126132#ifdef CPP_DYSL 
     133#define PHI_BOT(ij) phis(ij) 
    127134#include "../kernels/compute_NH_geopot.k90" 
    128135#else 
     
    264271  END SUBROUTINE compute_NH_geopot 
    265272 
    266   SUBROUTINE compute_caldyn_solver(tau,rhodz,theta,pk, geopot,W, m_il,pres, dPhi,dW,du) 
     273  SUBROUTINE compute_caldyn_solver(tau,phis, rhodz,theta,pk, geopot,W, m_il,pres, dPhi,dW,du) 
    267274    REAL(rstd),INTENT(IN) :: tau ! "solve" Phi-tau*dPhi/dt = Phi_rhs 
     275    REAL(rstd),INTENT(IN)    :: phis(iim*jjm) 
    268276    REAL(rstd),INTENT(IN)    :: rhodz(iim*jjm,llm) 
    269277    REAL(rstd),INTENT(IN)    :: theta(iim*jjm,llm,nqdyn) 
     
    287295#ifdef CPP_DYSL 
    288296!$OMP BARRIER 
     297#define PHI_BOT(ij) phis(ij) 
     298#define PHI_BOT_VAR phis 
    289299#include "../kernels/caldyn_solver.k90" 
    290300!$OMP BARRIER 
     
    396406    Rd=cpp*kappa 
    397407 
     408    IF(dysl_caldyn_fast) THEN 
    398409#ifdef CPP_DYSL 
    399410#include "../kernels/caldyn_fast.k90" 
    400411#else 
     412    STOP 'dysl_caldyn_fast=.TRUE. but DYNAMICO is compiled without the -dysl option' 
     413#endif 
     414    ELSE 
     415 
    401416    ! Compute Bernoulli term 
    402417    IF(boussinesq) THEN 
     
    496511       END IF 
    497512    END DO 
    498 #endif        
     513 
     514    END IF ! dysl 
    499515    CALL trace_end("compute_caldyn_fast") 
    500516 
     
    515531    CALL trace_start("compute_caldyn_Coriolis") 
    516532 
     533    IF(dysl_caldyn_coriolis) THEN 
    517534#ifdef CPP_DYSL 
    518535#include "../kernels/coriolis.k90" 
    519536#else 
     537    STOP 'dysl_caldyn_coriolis is .TRUE. but DYNAMICO is compiled without the -dysl option' 
     538#endif 
     539 
     540    ELSE 
    520541#define FTHETA(ij) Ftheta(ij,1) 
    521542 
     
    653674    END SELECT 
    654675#undef FTHETA 
    655 #endif 
     676 
     677    END IF ! dysl 
    656678 
    657679    CALL trace_end("compute_caldyn_Coriolis") 
     
    672694    CALL trace_start("compute_caldyn_slow_hydro") 
    673695 
     696    IF(dysl_slow_hydro) THEN 
    674697#ifdef CPP_DYSL 
    675698#define BERNI(ij,l) berni(ij,l) 
     
    677700#undef BERNI 
    678701#else 
     702        STOP 'dysl_slow_hydro=.TRUE. but DYNAMICO is compiled without the -dysl option' 
     703#endif 
     704 
     705     ELSE 
     706 
    679707#define BERNI(ij) berni(ij,1) 
    680708 
     
    726754    END DO 
    727755#undef BERNI 
    728 #endif 
     756    END IF ! dysl 
    729757    CALL trace_end("compute_caldyn_slow_hydro")     
    730758  END SUBROUTINE compute_caldyn_slow_hydro 
Note: See TracChangeset for help on using the changeset viewer.