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

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

devel : compute_rhodz for unstructured mesh

File size: 1.8 KB
Line 
1MODULE 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
9  IMPLICIT NONE
10  PRIVATE
11  SAVE
12 
13  PUBLIC :: init_grid_param
14
15CONTAINS
16
17  SUBROUTINE init_grid_param(is_mpi_root)
18    USE grid_param
19    USE ioipsl, ONLY : getin
20    USE init_unstructured_mod, ONLY : open_local_mesh_file
21    LOGICAL :: is_mpi_root
22    CHARACTER(len=255) :: grid_type_var
23   
24    grid_type_var='icosahedral'
25    CALL getin("grid_type",grid_type_var)
26    SELECT CASE(grid_type_var)
27    CASE('icosahedral')
28       grid_type = grid_ico
29       IF (is_mpi_root) PRINT *,'DYNAMICO mesh is icosahedral.'
30       CALL getin('nbp',iim_glo)
31       jjm_glo=iim_glo
32       IF(is_mpi_root) PRINT *, 'GETIN nbp = ',iim_glo
33       CALL select_compute_hex
34    CASE('unstructured')
35       grid_type = grid_unst
36       !       is_omp_level_master=.TRUE.
37       !       omp_level_size=1
38       CALL open_local_mesh_file
39       IF (is_mpi_root) PRINT *,'DYNAMICO mesh is unstructured/LAM.'
40       CALL select_compute_unst
41    CASE DEFAULT
42       PRINT *, 'Invalid value of grid_type :',TRIM(grid_type_var)
43       PRINT *, 'Valid values are : <icosahedral> <unstructured>'
44       STOP
45    END SELECT
46   
47    nqtot=1
48    CALL getin('nqtot',nqtot)
49    CALL getin('llm',llm)
50    IF(is_mpi_root) THEN
51       PRINT *, 'GETIN llm = ',llm
52       PRINT *, 'GETIN nqtot = ',nqtot
53    END IF
54   
55  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
68 
69END MODULE init_grid_param_mod
Note: See TracBrowser for help on using the repository browser.