Ignore:
Timestamp:
05/29/19 20:33:00 (5 years ago)
Author:
jisesh
Message:

devel: moved DYSL into compute_caldyn_solver.F90,compute_theta.F90 and compute_NH_geopot.F90

File:
1 edited

Legend:

Unmodified
Added
Removed
  • codes/icosagcm/devel/src/dynamics/compute_theta.F90

    r831 r878  
    44  PRIVATE 
    55 
     6#include "../unstructured/unstructured.h90" 
     7 
    68  PUBLIC :: compute_theta 
    79 
    810CONTAINS 
     11 
     12#ifdef BEGIN_DYSL 
     13 
     14KERNEL(theta) 
     15  IF(caldyn_eta==eta_mass) THEN ! Compute mass 
     16    ! FIXME : here mass_col is computed from rhodz 
     17    ! so that the DOFs are the same whatever caldyn_eta 
     18    ! in DYNAMICO mass_col is prognosed rather than rhodz 
     19    SEQUENCE_C1 
     20      PROLOGUE(0) 
     21        mass_col(HIDX(CELL))=0. 
     22      END_BLOCK 
     23      BODY('1,llm') 
     24          mass_col(HIDX(CELL)) = mass_col(HIDX(CELL)) + rhodz(CELL) 
     25      END_BLOCK 
     26    END_BLOCK 
     27    FORALL_CELLS_EXT() 
     28      ON_PRIMAL 
     29        ! FIXME : formula below (used in DYNAMICO) is for dak, dbk based on 
     30        ! pressure rather than mass 
     31        !        m = mass_dak(CELL)+(mass_col(HIDX(CELL))*g+ptop)*mass_dbk(CELL) 
     32        !        rhodz(CELL) = m/g  
     33        rhodz(CELL) = MASS_DAK(CELL) + mass_col(HIDX(CELL))*MASS_DBK(CELL) 
     34      END_BLOCK 
     35    END_BLOCK 
     36  END IF 
     37  DO iq=1,nqdyn 
     38    FORALL_CELLS_EXT() 
     39      ON_PRIMAL 
     40        theta(CELL,iq) = theta_rhodz(CELL,iq)/rhodz(CELL) 
     41      END_BLOCK 
     42    END_BLOCK 
     43  END DO 
     44END_BLOCK 
     45 
     46#endif END_DYSL 
     47 
     48SUBROUTINE compute_theta_unst(mass_col,rhodz,theta_rhodz, theta) 
     49  USE ISO_C_BINDING, only : C_DOUBLE, C_FLOAT 
     50  USE data_unstructured_mod, ONLY : id_theta,primal_num,dual_num,edge_num, & 
     51    enter_trace, exit_trace 
     52  USE grid_param, ONLY : nqdyn 
     53  USE disvert_mod, ONLY : mass_dak, mass_dbk, caldyn_eta, eta_mass, ptop 
     54  FIELD_PS :: mass_col 
     55  FIELD_MASS :: rhodz 
     56  FIELD_THETA :: theta, theta_rhodz 
     57  DECLARE_INDICES 
     58  NUM :: m 
     59  START_TRACE(id_theta, 3,0,0) ! primal, dual, edge   
     60#define MASS_DAK(l,ij) mass_dak(l) 
     61#define MASS_DBK(l,ij) mass_dbk(l) 
     62#include "../kernels_unst/theta.k90" 
     63#undef MASS_DAK 
     64#undef MASS_DBK 
     65  STOP_TRACE 
     66END SUBROUTINE 
    967 
    1068  SUBROUTINE compute_theta(ps,theta_rhodz, rhodz,theta) 
Note: See TracChangeset for help on using the changeset viewer.