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

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

devel : split read_dump_partition into open_local_mesh_file and read_local_mesh

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