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

Last change on this file since 821 was 813, checked in by jisesh, 5 years ago

devel ; towards Fortran driver for unstructured/LAM meshes

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