MODULE init_grid_param_mod USE compute_diagnostics_mod USE compute_rhodz_mod USE compute_pression_mod USE compute_temperature_mod USE vertical_interp_mod USE compute_caldyn_mod USE compute_pvort_only_mod USE compute_theta_mod USE compute_geopot_mod USE compute_caldyn_fast_mod USE compute_caldyn_slow_hydro_mod USE compute_caldyn_coriolis_mod IMPLICIT NONE PRIVATE SAVE PUBLIC :: init_grid_param CONTAINS SUBROUTINE init_grid_param(is_mpi_root) USE grid_param USE ioipsl, ONLY : getin USE init_unstructured_mod, ONLY : open_local_mesh_file LOGICAL :: is_mpi_root CHARACTER(len=255) :: grid_type_var grid_type_var='icosahedral' CALL getin("grid_type",grid_type_var) SELECT CASE(grid_type_var) CASE('icosahedral') grid_type = grid_ico IF (is_mpi_root) PRINT *,'DYNAMICO mesh is icosahedral.' CALL getin('nbp',iim_glo) IF(is_mpi_root) PRINT *, 'GETIN nbp = ',iim_glo iim_glo=iim_glo+1 jjm_glo=iim_glo CALL select_compute_hex CASE('unstructured') grid_type = grid_unst ! is_omp_level_master=.TRUE. ! omp_level_size=1 CALL open_local_mesh_file IF (is_mpi_root) PRINT *,'DYNAMICO mesh is unstructured/LAM.' CALL select_compute_unst CASE DEFAULT PRINT *, 'Invalid value of grid_type :',TRIM(grid_type_var) PRINT *, 'Valid values are : ' STOP END SELECT nqtot=1 CALL getin('nqtot',nqtot) CALL getin('llm',llm) IF(is_mpi_root) THEN PRINT *, 'GETIN llm = ',llm PRINT *, 'GETIN nqtot = ',nqtot END IF END SUBROUTINE init_grid_param SUBROUTINE select_compute_hex ! diagnostics compute_rhodz => compute_rhodz_hex compute_pression => compute_pression_hex compute_pression_mid => compute_pression_mid_hex compute_temperature => compute_temperature_hex compute_hydrostatic_pressure => compute_hydrostatic_pressure_hex compute_vertical_interp => compute_vertical_interp_hex ! dynamics compute_pvort_only => compute_pvort_only_hex compute_theta => compute_theta_hex compute_geopot => compute_geopot_hex compute_caldyn_fast => compute_caldyn_fast_hex compute_caldyn_slow_hydro => compute_caldyn_slow_hydro_hex compute_caldyn_coriolis => compute_caldyn_coriolis_hex END SUBROUTINE select_compute_hex SUBROUTINE select_compute_unst ! diagnostics compute_rhodz => compute_rhodz_unst compute_pression => compute_pression_unst compute_pression_mid => compute_pression_mid_unst compute_temperature => compute_temperature_unst compute_hydrostatic_pressure => compute_hydrostatic_pressure_unst compute_vertical_interp => compute_vertical_interp_unst ! dynamics compute_pvort_only => compute_pvort_only_unst compute_theta => compute_theta_unst compute_geopot => compute_geopot_unst compute_caldyn_fast => compute_caldyn_fast_unst compute_caldyn_slow_hydro => compute_caldyn_slow_hydro_unst compute_caldyn_coriolis => compute_caldyn_coriolis_unst END SUBROUTINE select_compute_unst END MODULE init_grid_param_mod