source: codes/icosagcm/devel/src/unstructured/init_unstructured.f90 @ 833

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

devel : merged init_grid_param and init_grid_type

File size: 7.4 KB
Line 
1MODULE init_unstructured_mod
2  USE mpipara, ONLY : is_mpi_master
3  USE data_unstructured_mod
4  IMPLICIT NONE
5  SAVE
6  PRIVATE
7
8  ! these buffers are used when reading from the grid file
9  REAL(8), ALLOCATABLE :: Ddata_read1(:),Ddata_read2(:,:),Ddata_read3(:,:,:)
10  INTEGER, ALLOCATABLE :: Idata_read1(:),Idata_read2(:,:),Idata_read3(:,:,:)
11
12  PUBLIC :: read_dump_partition
13
14CONTAINS
15
16  SUBROUTINE free_data_read()
17    IF(ALLOCATED(Idata_read1)) DEALLOCATE(Idata_read1) 
18    IF(ALLOCATED(Idata_read2)) DEALLOCATE(Idata_read2) 
19    IF(ALLOCATED(Idata_read3)) DEALLOCATE(Idata_read3) 
20    IF(ALLOCATED(Ddata_read1)) DEALLOCATE(Ddata_read1) 
21    IF(ALLOCATED(Ddata_read2)) DEALLOCATE(Ddata_read2) 
22    IF(ALLOCATED(Ddata_read3)) DEALLOCATE(Ddata_read3) 
23  END SUBROUTINE free_data_read
24
25  SUBROUTINE read_from_gridfile(id_nc, data_type, name)
26    use netcdf_mod
27    CHARACTER(*)    :: data_type, name
28    INTEGER :: id_nc, id_var, status
29    INTEGER :: dim_1, dim_2, dim_3
30    INTEGER :: numDims, dimIDs(3) !max_var_dims
31
32    !-------------------Reading variable-------------------------------
33    status = nf90_inq_varid(id_nc, name,id_var)
34    IF(status /= 0) THEN
35        print *, "Not able to read variable from gridfile :", name
36        STOP "Exit"
37    ENDIF
38    !inquire dimension
39    status = nf90_inquire_variable(id_nc,id_var,dimids=dimIDs,ndims=numDims)
40    status = nf90_inquire_dimension(id_nc, dimIDs(1), len = dim_1)
41    status = nf90_inquire_dimension(id_nc, dimIDs(2), len = dim_2)
42    status = nf90_inquire_dimension(id_nc, dimIDs(3), len = dim_3)
43    SELECT CASE(numDims)
44    CASE(3)
45    print *,"Size of array, ",name,":", dim_1,dim_2,dim_3
46    CASE(2)
47    print *,"Size of array, ",name,":", dim_1,dim_2
48    CASE DEFAULT
49    print *,"Size of array, ",name,":", dim_1
50    END SELECT
51
52    CALL free_data_read
53    SELECT CASE(data_type)
54    CASE('integer')
55       SELECT CASE(numDims)
56       CASE(3)
57          allocate(Idata_read3(dim_1,dim_2,dim_3))
58          status = nf90_get_var(id_nc, id_var,Idata_read3)
59          print *,"First value of array, ",name,":", Idata_read3(1,1,1)
60       CASE(2)
61          allocate(Idata_read2(dim_1,dim_2))
62          status = nf90_get_var(id_nc, id_var,Idata_read2)
63          print *,"First value of array, ",name,":", Idata_read2(1,1)
64       CASE DEFAULT
65          allocate(Idata_read1(dim_1))
66          status = nf90_get_var(id_nc, id_var,Idata_read1)
67          print *,"First value of array, ",name,":", Idata_read1(1)
68       END SELECT
69    CASE DEFAULT
70       SELECT CASE(numDims)
71       CASE(3)
72          allocate(Ddata_read3(dim_1,dim_2,dim_3))
73          status = nf90_get_var(id_nc, id_var,Ddata_read3)
74          print *,"First value of array, ",name,":", Ddata_read3(1,1,1)
75       CASE(2)
76          allocate(Ddata_read2(dim_1,dim_2))
77          status = nf90_get_var(id_nc, id_var,Ddata_read2)
78          print *,"First value of array, ",name,":", Ddata_read2(1,1)
79       CASE DEFAULT
80          allocate(Ddata_read1(dim_1))
81          status = nf90_get_var(id_nc, id_var,Ddata_read1)
82          print *,"First value of array, ",name,":", Ddata_read1(1)
83       END SELECT
84    END SELECT
85   
86    IF(status /= nf90_NoErr) THEN
87        print *, "Error when reading from grid file : ", name
88        STOP "Exit"
89    ENDIF
90
91  END SUBROUTINE read_from_gridfile
92
93
94  SUBROUTINE read_dump_partition
95    use netcdf_mod
96    USE ioipsl
97    USE field_mod
98    IMPLICIT NONE
99
100    !!-------------Declare local variables-------------------
101    CHARACTER(LEN=*),PARAMETER :: f="mesh_information.nc"
102    INTEGER :: id_nc, ierr, status, descriptionLength
103    CHARACTER(LEN= 80) :: description
104
105    print *,"------------------ READING FILE " , f, "----------------------- "
106    !open and read the input file
107    ierr = nf90_open(f, NF90_NOWRITE, id_nc)
108    if (ierr /= nf90_noerr) then
109      print *, trim(nf90_strerror(ierr))
110      stop "Error reading file"
111    end if
112
113    status = nf90_inquire_attribute(id_nc, nf90_global, "description", len =descriptionLength)
114    IF(status /= 0 .or. len(description) < descriptionLength) THEN
115        print *, "Not enough space to put NetCDF attribute values."
116        STOP "Error reading file"
117    ENDIF
118
119    !-------------------Reading global attributes-----------------------
120    status = nf90_get_att(id_nc, nf90_global, "description", description)
121    print *,"Data file description :",description
122
123    !status = nf90_get_att(id_nc, nf90_global, "primal_num", primal_num)
124    !status = nf90_get_att(id_nc, nf90_global, "dual_num", dual_num)
125    !status = nf90_get_att(id_nc, nf90_global, "edge_num", edge_num)
126    !print *,primal_num,dual_num,edge_num
127
128    CALL read_from_gridfile(id_nc, 'integer', 'primal_deg')
129    ALLOCATE(primal_deg, source = Idata_read1)
130    CALL read_from_gridfile(id_nc, 'integer', 'primal_edge')
131    ALLOCATE(primal_edge, source = Idata_read2)
132    CALL read_from_gridfile(id_nc, 'integer', 'primal_ne')
133    ALLOCATE(primal_ne, source = Idata_read2)
134    CALL read_from_gridfile(id_nc, 'integer', 'dual_deg')
135    ALLOCATE(dual_deg, source = Idata_read1)
136    CALL read_from_gridfile(id_nc, 'integer', 'dual_edge')
137    ALLOCATE(dual_edge, source = Idata_read2)
138    CALL read_from_gridfile(id_nc, 'integer', 'dual_ne')
139    ALLOCATE(dual_ne, source = Idata_read2)
140    CALL read_from_gridfile(id_nc, 'integer', 'primal_vertex') 
141    ALLOCATE(primal_vertex, source = Idata_read2)
142    CALL read_from_gridfile(id_nc, 'integer', 'left')
143    ALLOCATE(left, source = Idata_read1)
144    CALL read_from_gridfile(id_nc, 'integer', 'right')
145    ALLOCATE(right, source = Idata_read1)
146    CALL read_from_gridfile(id_nc, 'integer', 'up')
147    ALLOCATE(up, source = Idata_read1)
148    CALL read_from_gridfile(id_nc, 'integer', 'down')
149    ALLOCATE(down, source = Idata_read1)
150    CALL read_from_gridfile(id_nc, 'integer', 'trisk_deg')
151    ALLOCATE(trisk_deg, source = Idata_read1)
152    CALL read_from_gridfile(id_nc, 'integer', 'trisk')
153    ALLOCATE(trisk, source = Idata_read2)
154    CALL read_from_gridfile(id_nc, 'float', 'Ai')
155    ALLOCATE(Ai, source = Ddata_read1)
156    CALL read_from_gridfile(id_nc, 'float', 'Av')
157    ALLOCATE(Av, source = Ddata_read1)
158    CALL read_from_gridfile(id_nc, 'float', 'le_de')
159    ALLOCATE(le_de, source = Ddata_read1)
160    CALL read_from_gridfile(id_nc, 'float', 'Riv2')
161    ALLOCATE(Riv2, source = Ddata_read2)
162    CALL read_from_gridfile(id_nc, 'float', 'wee')
163    ALLOCATE(wee, source = Ddata_read2)
164    CALL read_from_gridfile(id_nc, 'float', 'fv') !
165    ALLOCATE(fv, source = Ddata_read1)
166    CALL read_from_gridfile(id_nc, 'integer', 'dual_vertex') 
167    ALLOCATE(dual_vertex, source = Idata_read2)
168
169    CALL free_data_read ! free buffers after reading all data from grid file
170
171    edge_num = SIZE(le_de)
172    primal_num = SIZE(Ai)
173    dual_num = SIZE(Av)
174    max_primal_deg = SIZE(primal_edge,1)
175    max_dual_deg = SIZE(dual_edge,1)
176    max_trisk_deg = SIZE(trisk,1)
177
178  END SUBROUTINE read_dump_partition
179
180  SUBROUTINE init_grid_type
181    USE grid_param, ONLY : grid_type, grid_unst, grid_ico   
182    USE getin_mod, ONLY : getin
183    CHARACTER(len=255) :: grid_type_var
184    grid_type_var='icosahedral'
185    CALL getin("grid_type",grid_type_var)
186    SELECT CASE(grid_type_var)
187    CASE('unstructured')
188       grid_type = grid_unst
189!       is_omp_level_master=.TRUE.
190!       omp_level_size=1
191       CALL read_dump_partition
192       IF (is_mpi_master) PRINT *,'Using unstructured grid type'
193    CASE DEFAULT
194       grid_type = grid_ico
195       IF (is_mpi_master) PRINT *,'Using default grid type'
196    END SELECT 
197  END SUBROUTINE init_grid_type
198
199END MODULE init_unstructured_mod
Note: See TracBrowser for help on using the repository browser.