source: CONFIG_DEVT/IPSLCM6.5_work_ENSEMBLES/oasis3-mct/examples/test_1bin_ocnice/read_grid.F90 @ 5725

Last change on this file since 5725 was 5725, checked in by aclsce, 3 years ago

Added new oasis3-MCT version to be used to handle ensembles simulations with XIOS.

File size: 3.9 KB
Line 
1  !****************************************************************************************
2  SUBROUTINE read_grid (nlon,nlat,corners_ij_lus, &
3                                       data_filename, w_unit, FILE_Debug, &
4                                       gridlon,gridlat, &
5                                       gridclo,gridcla, &
6                                       gridsrf, &
7                                       indice_mask)
8  !**************************************************************************************
9  !
10  USE netcdf
11  IMPLICIT NONE
12  !
13  INTEGER                  :: i,j,k,w_unit,FILE_Debug
14  !
15  INTEGER                  :: il_file_id,il_grid_id,il_lon_id, &
16                              il_lat_id,il_clo_id,il_cla_id,il_srf_id,il_indice_id, &
17                              lon_dims,lat_dims,clo_dims,cla_dims,&
18                              imask_dims
19  !
20  INTEGER, DIMENSION(NF90_MAX_VAR_DIMS) :: lon_dims_ids,lat_dims_ids,clo_dims_ids,&
21                                           cla_dims_ids,imask_dims_ids,lon_dims_len,&
22                                           lat_dims_len,clo_dims_len,cla_dims_len,&
23                                           imask_dims_len 
24  !               
25  INTEGER, INTENT(in)     :: nlon,nlat,corners_ij_lus
26  !
27  CHARACTER(len=30)        :: data_filename
28  !
29  INTEGER,  DIMENSION(3)   :: ila_dim
30  INTEGER,  DIMENSION(3)   :: ila_corners,ila_what
31  !
32  DOUBLE PRECISION, DIMENSION(nlon,nlat)                :: gridlon,gridlat,gridsrf
33  DOUBLE PRECISION, DIMENSION(nlon,nlat,corners_ij_lus) :: gridclo,gridcla
34  INTEGER, DIMENSION(nlon,nlat)                      :: indice_mask
35  !
36  !
37  ! Dimensions
38  !
39  CALL hdlerr(NF90_OPEN(data_filename, NF90_NOWRITE, il_file_id), __LINE__ )
40  !
41  !
42  CALL hdlerr( NF90_INQ_VARID(il_file_id, 'lon' , il_lon_id), __LINE__ )
43  CALL hdlerr( NF90_INQ_VARID(il_file_id, 'lat' , il_lat_id), __LINE__ )
44  CALL hdlerr( NF90_INQ_VARID(il_file_id, 'clo' , il_clo_id), __LINE__ )
45  CALL hdlerr( NF90_INQ_VARID(il_file_id, 'cla' , il_cla_id), __LINE__ )
46  CALL hdlerr( NF90_INQ_VARID(il_file_id, 'srf' , il_srf_id), __LINE__ )
47  CALL hdlerr( NF90_INQ_VARID(il_file_id, 'imask' , il_indice_id), __LINE__ )
48  !
49  ila_what(:)=1
50  !
51  ila_dim(1)=nlon
52  ila_dim(2)=nlat
53  ila_dim(3)=1
54  !
55  ila_corners(1)=nlon
56  ila_corners(2)=nlat
57  ila_corners(3)=corners_ij_lus
58  !
59  ! Data
60  !
61  CALL hdlerr( NF90_OPEN(data_filename, NF90_NOWRITE, il_file_id), __LINE__ )
62  !
63  CALL hdlerr( NF90_GET_VAR (il_file_id, il_lon_id, gridlon, &
64     ila_what(1:2), ila_dim(1:2)), __LINE__ )
65  IF (FILE_Debug >= 2) THEN
66      WRITE(w_unit,*) 'Global grid longitudes reading done'
67      CALL FLUSH(w_unit)
68  ENDIF
69  !
70  CALL hdlerr( NF90_GET_VAR (il_file_id, il_lat_id, gridlat, &
71     ila_what(1:2), ila_dim(1:2)), __LINE__ )
72  IF (FILE_Debug >= 2) THEN
73      WRITE(w_unit,*) 'Global grid latitudes reading done'
74      CALL FLUSH(w_unit)
75  ENDIF
76  !
77  CALL hdlerr( NF90_GET_VAR(il_file_id, il_clo_id, gridclo, &
78     ila_what, ila_corners), __LINE__ )
79  IF (FILE_Debug >= 2) THEN
80      WRITE(w_unit,*) 'Global grid longitude corners reading done'
81      CALL FLUSH(w_unit)
82  ENDIF
83  !
84  CALL hdlerr( NF90_GET_VAR (il_file_id, il_cla_id, gridcla, &
85     ila_what, ila_corners), __LINE__ )
86  IF (FILE_Debug >= 2) THEN
87      WRITE(w_unit,*) 'Global grid latitude corners reading done'
88      CALL FLUSH(w_unit)
89  ENDIF
90  !
91  CALL hdlerr( NF90_GET_VAR (il_file_id, il_srf_id, gridsrf, &
92     ila_what(1:2), ila_dim(1:2)), __LINE__ )
93  IF (FILE_Debug >= 2) THEN
94      WRITE(w_unit,*) 'Global grid surfaces reading done'
95      CALL FLUSH(w_unit)
96  ENDIF
97  !
98  CALL hdlerr( NF90_GET_VAR (il_file_id, il_indice_id, indice_mask, &
99     ila_what, ila_dim), __LINE__ )
100  IF (FILE_Debug >= 2) THEN
101      WRITE(w_unit,*) 'Global grid mask reading done'
102      CALL FLUSH(w_unit)
103  ENDIF
104  !
105  CALL hdlerr( NF90_CLOSE(il_file_id), __LINE__ )
106  !
107  IF (FILE_Debug >= 2) THEN
108      WRITE(w_unit,*) 'End of routine read_grid'
109      CALL FLUSH(w_unit)
110  ENDIF
111  !
112END SUBROUTINE read_grid
Note: See TracBrowser for help on using the repository browser.