source: codes/icosagcm/devel/src/base/init_grid_param.f90 @ 958

Last change on this file since 958 was 958, checked in by dubos, 5 years ago

devel : vertical interpolation for unstructured mesh

File size: 3.2 KB
Line 
1MODULE init_grid_param_mod
2
3  USE compute_diagnostics_mod
4  USE compute_rhodz_mod
5  USE compute_pression_mod
6  USE compute_temperature_mod
7  USE vertical_interp_mod
8
9  USE compute_caldyn_mod
10  USE compute_pvort_only_mod
11  USE compute_theta_mod
12  USE compute_geopot_mod
13  USE compute_caldyn_fast_mod
14  USE compute_caldyn_slow_hydro_mod
15  USE compute_caldyn_coriolis_mod
16
17  IMPLICIT NONE
18  PRIVATE
19  SAVE
20 
21  PUBLIC :: init_grid_param
22
23CONTAINS
24
25  SUBROUTINE init_grid_param(is_mpi_root)
26    USE grid_param
27    USE ioipsl, ONLY : getin
28    USE init_unstructured_mod, ONLY : open_local_mesh_file
29    LOGICAL :: is_mpi_root
30    CHARACTER(len=255) :: grid_type_var
31   
32    grid_type_var='icosahedral'
33    CALL getin("grid_type",grid_type_var)
34    SELECT CASE(grid_type_var)
35    CASE('icosahedral')
36       grid_type = grid_ico
37       IF (is_mpi_root) PRINT *,'DYNAMICO mesh is icosahedral.'
38       CALL getin('nbp',iim_glo)
39       IF(is_mpi_root) PRINT *, 'GETIN nbp = ',iim_glo
40       iim_glo=iim_glo+1
41       jjm_glo=iim_glo
42       CALL select_compute_hex
43    CASE('unstructured')
44       grid_type = grid_unst
45       !       is_omp_level_master=.TRUE.
46       !       omp_level_size=1
47       CALL open_local_mesh_file
48       IF (is_mpi_root) PRINT *,'DYNAMICO mesh is unstructured/LAM.'
49       CALL select_compute_unst
50    CASE DEFAULT
51       PRINT *, 'Invalid value of grid_type :',TRIM(grid_type_var)
52       PRINT *, 'Valid values are : <icosahedral> <unstructured>'
53       STOP
54    END SELECT
55   
56    nqtot=1
57    CALL getin('nqtot',nqtot)
58    CALL getin('llm',llm)
59    IF(is_mpi_root) THEN
60       PRINT *, 'GETIN llm = ',llm
61       PRINT *, 'GETIN nqtot = ',nqtot
62    END IF
63   
64  END SUBROUTINE  init_grid_param
65
66
67  SUBROUTINE select_compute_hex
68    ! diagnostics
69    compute_rhodz        => compute_rhodz_hex
70    compute_pression     => compute_pression_hex
71    compute_pression_mid => compute_pression_mid_hex
72    compute_temperature  => compute_temperature_hex
73    compute_hydrostatic_pressure => compute_hydrostatic_pressure_hex
74    compute_vertical_interp => compute_vertical_interp_hex
75    ! dynamics
76    compute_pvort_only        => compute_pvort_only_hex
77    compute_theta             => compute_theta_hex
78    compute_geopot            => compute_geopot_hex
79    compute_caldyn_fast       => compute_caldyn_fast_hex
80    compute_caldyn_slow_hydro => compute_caldyn_slow_hydro_hex
81    compute_caldyn_coriolis   => compute_caldyn_coriolis_hex
82  END SUBROUTINE select_compute_hex
83
84  SUBROUTINE select_compute_unst
85    ! diagnostics
86    compute_rhodz        => compute_rhodz_unst
87    compute_pression     => compute_pression_unst
88    compute_pression_mid => compute_pression_mid_unst
89    compute_temperature  => compute_temperature_unst
90    compute_hydrostatic_pressure => compute_hydrostatic_pressure_unst
91    compute_vertical_interp => compute_vertical_interp_unst
92    ! dynamics
93    compute_pvort_only         => compute_pvort_only_unst
94    compute_theta              => compute_theta_unst
95    compute_geopot             => compute_geopot_unst
96    compute_caldyn_fast        => compute_caldyn_fast_unst
97    compute_caldyn_slow_hydro  => compute_caldyn_slow_hydro_unst
98    compute_caldyn_coriolis    => compute_caldyn_coriolis_unst
99  END SUBROUTINE select_compute_unst
100 
101END MODULE init_grid_param_mod
Note: See TracBrowser for help on using the repository browser.