Ignore:
Timestamp:
06/14/19 01:17:50 (5 years ago)
Author:
dubos
Message:

devel : compute_rhodz for unstructured mesh

File:
1 edited

Legend:

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

    r863 r906  
    11MODULE init_grid_param_mod 
     2 
     3  USE compute_diagnostics_mod 
     4  USE compute_rhodz_mod 
     5 
     6  USE compute_caldyn_mod 
     7  USE compute_pvort_only_mod 
     8 
    29  IMPLICIT NONE 
     10  PRIVATE 
     11  SAVE 
     12   
     13  PUBLIC :: init_grid_param 
    314 
    415CONTAINS 
     
    2031       jjm_glo=iim_glo 
    2132       IF(is_mpi_root) PRINT *, 'GETIN nbp = ',iim_glo 
     33       CALL select_compute_hex 
    2234    CASE('unstructured') 
    2335       grid_type = grid_unst 
     
    2638       CALL open_local_mesh_file 
    2739       IF (is_mpi_root) PRINT *,'DYNAMICO mesh is unstructured/LAM.' 
     40       CALL select_compute_unst 
    2841    CASE DEFAULT 
    2942       PRINT *, 'Invalid value of grid_type :',TRIM(grid_type_var) 
     
    4154     
    4255  END SUBROUTINE  init_grid_param 
     56 
     57 
     58  SUBROUTINE select_compute_hex 
     59    compute_rhodz      => compute_rhodz_hex 
     60    compute_pvort_only => compute_pvort_only_hex 
     61  END SUBROUTINE select_compute_hex 
     62 
     63  SUBROUTINE select_compute_unst 
     64    compute_rhodz      => compute_rhodz_unst 
     65    compute_pvort_only => compute_pvort_only_unst 
     66  END SUBROUTINE select_compute_unst 
     67 
    4368   
    4469END MODULE init_grid_param_mod 
    45      
Note: See TracChangeset for help on using the changeset viewer.