Ignore:
Timestamp:
12/30/17 02:00:38 (7 years ago)
Author:
dubos
Message:

devel/unstructured : updated kernels

Location:
codes/icosagcm/devel/src/unstructured
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • codes/icosagcm/devel/src/unstructured/caldyn_unstructured.F90

    r650 r658  
    2121#define DECLARE_VERTICES INTEGER VERTICES 
    2222#define PHI_BOT(ij) Phi_bot 
    23 #define PHI_BOT_VAR 0. 
    2423 
    2524#define BINDC_(thename) BIND(C, name=#thename) 
     
    4039#define HASNAN(field) (ANY(.NOT.ABS(field)<1e20)) 
    4140 
     41#define START_TRACE(id,nprimal,ndual,nedge) CALL enter_trace(id, 8*llm*((nprimal)*primal_num+(ndual)*dual_num+(nedge)*edge_num) ) 
     42#define STOP_TRACE CALL exit_trace() 
     43 
    4244!----------------------------- Non-Hydrostatic ----------------------------- 
    4345 
    44 SUBROUTINE compute_NH_geopot(tau,dummy, m_ik, m_il, theta, W_il, Phi_il) 
    45   FIELD_MASS   :: m_ik, theta, p_ik, A_ik, C_ik   ! IN*2,LOCAL*3 
    46   FIELD_GEOPOT :: m_il, W_il, Phi_il, Phi_star_il, R_il, x_il, B_il, D_il  ! IN,INOUT*2, LOCAL*5  
    47   DBL :: tau, dummy, gamma, rho_ij, X_ij, Y_ij, wil, tau2_g, g2, gm2, ml_g2, c2_mik 
    48   DECLARE_INDICES 
     46SUBROUTINE compute_NH_geopot(tau, m_ik, m_il, theta, W_il, Phi_il) 
     47  FIELD_MASS   :: m_ik, theta   ! IN*2 
     48  FIELD_GEOPOT :: m_il, W_il, Phi_il, Phi_star_il  ! IN,INOUT*2, LOCAL*5  
     49  DBL :: tau, gamma, tau2_g, tau2_g2, g2, gm2, vreff, Rd_preff 
    4950  INTEGER :: iter 
     51  DECLARE_INDICES 
     52  DBL :: rho_ij, X_ij, Y_ij, wil, rho_c2_mik, c2_mik, ml_g2 
     53#define COLUMN 0 
     54#if COLUMN  
     55  DOUBLE1(llm)  :: pk, Ak, Ck 
     56  DOUBLE1(llm+1):: Rl, Bl, Dl, xl 
     57#define p_ik(l,ij) pk(l) 
     58#define A_ik(l,ij) Ak(l) 
     59#define C_ik(l,ij) Ck(l) 
     60#define R_il(l,ij) Rl(l) 
     61#define B_il(l,ij) Bl(l) 
     62#define D_il(l,ij) Dl(l) 
     63#define x_il(l,ij) xl(l) 
     64#else 
     65  FIELD_MASS :: p_ik, A_ik, C_ik 
     66  FIELD_GEOPOT :: R_il, B_il, D_il, x_il 
     67#endif 
     68 
     69  START_TRACE(id_NH_geopot, 7,0,0) 
    5070#include "../kernels_unst/compute_NH_geopot.k90" 
     71  STOP_TRACE   
     72 
     73#if COLUMN 
     74#undef p_ik 
     75#undef A_ik 
     76#undef C_ik 
     77#undef R_il 
     78#undef B_il 
     79#undef D_il 
     80#undef x_il 
     81#endif 
     82#undef COLUMN 
    5183END SUBROUTINE compute_NH_geopot 
    5284 
     
    5991  DECLARE_EDGES 
    6092  DBL :: W_el, W2_el, gPhi2, dP, divG, u2, uu 
     93  START_TRACE(id_slow_NH, 5,0,3) 
    6194#include "../kernels_unst/caldyn_slow_NH.k90" 
     95  STOP_TRACE 
    6296END SUBROUTINE compute_caldyn_slow_NH 
    6397 
     
    69103  FIELD_U      :: du                     ! OUT 
    70104  DECLARE_INDICES 
    71   DBL :: X_ij, rho_ij, T_ij, gamma, Cvd, vreff 
     105  DBL :: X_ij, rho_ij, T_ij, gamma, Cvd, vreff, Rd_preff 
     106#include "../kernels_unst/caldyn_mil.k90" 
     107  IF(tau>0) THEN ! solve implicit problem for geopotential 
     108    CALL compute_NH_geopot(tau, rhodz, m_il, theta, W, geopot) 
     109  END IF 
     110  START_TRACE(id_solver, 7,0,1) 
    72111#include "../kernels_unst/caldyn_solver.k90" 
     112  STOP_TRACE 
    73113END SUBROUTINE compute_caldyn_solver 
    74114 
     
    79119  DECLARE_INDICES 
    80120  DBL :: w_ij, wflux_ij 
     121  START_TRACE(id_vert_NH, 6,0,1) 
    81122#include "../kernels_unst/caldyn_vert_NH.k90" 
     123  STOP_TRACE 
    82124END SUBROUTINE compute_caldyn_vert_NH 
    83125 
     
    91133  DECLARE_INDICES 
    92134  DBL :: gdz, ke, uu, chi, gv, exner_ik, temp_ik, p_ik, qv, Rmix 
     135  START_TRACE(id_geopot, 3,0,3) 
    93136#include "../kernels_unst/compute_geopot.k90" 
     137  STOP_TRACE 
    94138END SUBROUTINE compute_geopot 
    95139! 
     
    102146  LOGICAL, PARAMETER :: zero=.TRUE. 
    103147  DBL :: ke, uu 
     148  START_TRACE(id_slow_hydro, 3,0,3) 
    104149#include "../kernels_unst/caldyn_slow_hydro.k90" 
     150  STOP_TRACE 
    105151END SUBROUTINE compute_caldyn_slow_hydro 
    106152 
     
    118164  wwuu=0. 
    119165  !$OMP BARRIER 
     166  START_TRACE(id_vert, 5,0,3) 
    120167#include "../kernels_unst/caldyn_wflux.k90" 
    121168#include "../kernels_unst/caldyn_dmass.k90" 
    122169#include "../kernels_unst/caldyn_vert.k90" 
     170  STOP_TRACE 
    123171END SUBROUTINE caldyn_vert 
    124172 
     
    130178  DECLARE_EDGES 
    131179  DBL :: divF, du_trisk 
     180  START_TRACE(id_coriolis, 3,4,0) ! primal, dual, edge 
    132181#include "../kernels_unst/coriolis.k90" 
     182  STOP_TRACE 
    133183END SUBROUTINE 
    134184 
     
    139189  DECLARE_INDICES 
    140190  DBL :: m 
     191  START_TRACE(id_theta, 3,0,0) ! primal, dual, edge 
    141192#include "../kernels_unst/theta.k90" 
     193  STOP_TRACE 
    142194END SUBROUTINE 
    143195 
     
    150202  DECLARE_VERTICES 
    151203  DBL :: etav, hv 
     204  START_TRACE(id_pvort_only, 1,1,2) ! primal, dual, edge 
    152205#include "../kernels_unst/pvort_only.k90" 
     206  STOP_TRACE 
    153207END SUBROUTINE compute_pvort_only 
    154208 
     
    162216  DECLARE_EDGES 
    163217  DBL          :: due 
    164  
     218  START_TRACE(id_fast, 4,0,2) ! primal, dual, edge 
    165219#include "../kernels_unst/caldyn_fast.k90" 
    166  
     220  STOP_TRACE 
    167221END SUBROUTINE compute_caldyn_fast 
    168222 
  • codes/icosagcm/devel/src/unstructured/data_unstructured.F90

    r651 r658  
    4444  INTEGER(C_INT), BIND(C) :: comm_icosa 
    4545 
    46   INTEGER, PARAMETER :: id_pvort_only=1, id_slow_hydro=2, id_fast=3, id_coriolis=4, id_theta=5, & 
    47        id_vert_NH=6, id_solver=7, id_slow_NH=8, id_NH_geopot=9, id_vert=10, id_NH_Phi_star=11, nb_routines=11 
     46  INTEGER, PARAMETER :: id_dev1=1, id_dev2=2, & 
     47       id_pvort_only=3, id_slow_hydro=4, id_fast=5, id_coriolis=6, id_theta=7, id_geopot=8, id_vert=9, & 
     48       id_solver=10, id_slow_NH=11, id_NH_geopot=12, id_vert_NH=13, id_update=14, nb_routines=14  
    4849  DBL, PRIVATE :: start_time, time_spent(nb_routines) ! time spent in each kernel 
    4950  INTEGER, PRIVATE :: current_id, nb_calls(nb_routines), bytes(nb_routines) ! bytes read or written be each kernel 
    5051  CHARACTER(len = 10) :: id_name(nb_routines) = & 
    51        (/'pvort_only', 'slow_hydro', 'fast      ', 'coriolis  ', 'theta     ', & 
    52        'vert_NH   ', 'solver    ', 'slow_NH   ', 'NH_geopot ', 'vert      ', & 
    53        'Phi_star  '/) 
     52       (/'dev1      ', 'dev2      ', & 
     53       'pvort_only', 'slow_hydro', 'fast      ', 'coriolis  ', 'theta     ', 'geopot    ', 'vert      ', & 
     54       'solver    ', 'slow_NH   ', 'NH_geopot ', 'vert_NH   ',  'update    ' /) 
    5455 
    5556CONTAINS 
  • codes/icosagcm/devel/src/unstructured/timestep_unstructured.F90

    r652 r658  
    219219    ! 
    220220    INTEGER :: l, ij 
     221    CALL enter_trace(id_update, 8*sz*(j+1) ) 
    221222    !  PRINT *, clj(1:j,j) 
    222223    SELECT CASE(j) 
     
    263264       END DO 
    264265    END SELECT 
     266    CALL exit_trace() 
    265267  END SUBROUTINE update 
    266268   
Note: See TracChangeset for help on using the changeset viewer.