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

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

devel : interfaces for caldyn_coriolis

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