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

Last change on this file since 1034 was 1034, checked in by dubos, 4 years ago

devel : work around PGI compiler complaints (bugs ?)

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