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

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

devel and trunk : let iim_glo=nbp+1 so that MOD(nbp,npslit_X)==0 implies equal-sized domains and good load balancing

File size: 2.1 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
10  IMPLICIT NONE
11  PRIVATE
12  SAVE
13 
14  PUBLIC :: init_grid_param
15
16CONTAINS
17
18  SUBROUTINE init_grid_param(is_mpi_root)
19    USE grid_param
20    USE ioipsl, ONLY : getin
21    USE init_unstructured_mod, ONLY : open_local_mesh_file
22    LOGICAL :: is_mpi_root
23    CHARACTER(len=255) :: grid_type_var
24   
25    grid_type_var='icosahedral'
26    CALL getin("grid_type",grid_type_var)
27    SELECT CASE(grid_type_var)
28    CASE('icosahedral')
29       grid_type = grid_ico
30       IF (is_mpi_root) PRINT *,'DYNAMICO mesh is icosahedral.'
31       CALL getin('nbp',iim_glo)
32       IF(is_mpi_root) PRINT *, 'GETIN nbp = ',iim_glo
33       iim_glo=iim_glo+1
34       jjm_glo=iim_glo
35       CALL select_compute_hex
36    CASE('unstructured')
37       grid_type = grid_unst
38       !       is_omp_level_master=.TRUE.
39       !       omp_level_size=1
40       CALL open_local_mesh_file
41       IF (is_mpi_root) PRINT *,'DYNAMICO mesh is unstructured/LAM.'
42       CALL select_compute_unst
43    CASE DEFAULT
44       PRINT *, 'Invalid value of grid_type :',TRIM(grid_type_var)
45       PRINT *, 'Valid values are : <icosahedral> <unstructured>'
46       STOP
47    END SELECT
48   
49    nqtot=1
50    CALL getin('nqtot',nqtot)
51    CALL getin('llm',llm)
52    IF(is_mpi_root) THEN
53       PRINT *, 'GETIN llm = ',llm
54       PRINT *, 'GETIN nqtot = ',nqtot
55    END IF
56   
57  END SUBROUTINE  init_grid_param
58
59
60  SUBROUTINE select_compute_hex
61    ! diagnostics
62    compute_rhodz        => compute_rhodz_hex
63    compute_pression     => compute_pression_hex
64    compute_pression_mid => compute_pression_mid_hex
65    ! dynamics
66    compute_pvort_only   => compute_pvort_only_hex
67  END SUBROUTINE select_compute_hex
68
69  SUBROUTINE select_compute_unst
70    ! diagnostics
71    compute_rhodz        => compute_rhodz_unst
72    compute_pression     => compute_pression_unst
73    compute_pression_mid => compute_pression_mid_unst
74    ! dynamics
75    compute_pvort_only   => compute_pvort_only_unst
76  END SUBROUTINE select_compute_unst
77
78 
79END MODULE init_grid_param_mod
Note: See TracBrowser for help on using the repository browser.