1 | PROGRAM rearrange_startphy |
---|
2 | |
---|
3 | USE netcdf |
---|
4 | |
---|
5 | IMPLICIT NONE |
---|
6 | |
---|
7 | INTEGER :: ncid |
---|
8 | INTEGER :: dimids(4) |
---|
9 | INTEGER :: varid |
---|
10 | INTEGER :: ierr |
---|
11 | INTEGER :: nvar |
---|
12 | INTEGER :: ndim |
---|
13 | CHARACTER(LEN=100) :: varname |
---|
14 | INTEGER :: varname_dimids(4) |
---|
15 | |
---|
16 | INTEGER :: i,j,k,nb_cells |
---|
17 | INTEGER,ALLOCATABLE :: cell_index(:) |
---|
18 | REAL,ALLOCATABLE :: ref_lon(:) |
---|
19 | REAL,ALLOCATABLE :: ref_lat(:) |
---|
20 | REAL,ALLOCATABLE :: lon(:) |
---|
21 | REAL,ALLOCATABLE :: lat(:) |
---|
22 | REAL,ALLOCATABLE :: ref_field(:),field(:) |
---|
23 | REAL :: lati,loni |
---|
24 | REAL :: diff_lat,diff_lon |
---|
25 | CHARACTER(LEN=*),PARAMETER :: ref_file="startphy_icosa_ref.nc" |
---|
26 | CHARACTER(LEN=*),PARAMETER :: file="startphy_icosa.nc" |
---|
27 | |
---|
28 | ! load coordinates from files |
---|
29 | ierr=NF90_OPEN(ref_file, NF90_NOWRITE, ncid) |
---|
30 | ierr=NF90_INQ_DIMID(ncid,"points_physiques",dimids(1)) |
---|
31 | ierr=NF90_INQUIRE_DIMENSION(ncid, dimids(1), len=nb_cells) |
---|
32 | write(*,*) "nb_cells=",nb_cells,"dimids(1)=",dimids(1) |
---|
33 | allocate(ref_lat(nb_cells),ref_lon(nb_cells)) |
---|
34 | |
---|
35 | ierr=NF90_INQ_VARID(ncid,"latitude",varid) |
---|
36 | ierr=NF90_GET_VAR(ncid,varid,ref_lat) |
---|
37 | if (ierr /= nf90_noerr) then |
---|
38 | write(*,*) "cannot load latitude from ",trim(ref_file) |
---|
39 | else |
---|
40 | write(*,*) "ref_lat(1:5)=",ref_lat(1:5) |
---|
41 | endif |
---|
42 | ierr=NF90_INQ_VARID(ncid,"longitude",varid) |
---|
43 | ierr=NF90_GET_VAR(ncid,varid,ref_lon) |
---|
44 | if (ierr /= nf90_noerr) then |
---|
45 | write(*,*) "cannot load longitude from ",trim(ref_file) |
---|
46 | else |
---|
47 | write(*,*) "ref_lon(1:5)=",ref_lon(1:5) |
---|
48 | endif |
---|
49 | ierr=NF90_CLOSE(ncid) |
---|
50 | |
---|
51 | ierr=NF90_OPEN(file, NF90_WRITE, ncid) |
---|
52 | allocate(lat(nb_cells),lon(nb_cells)) |
---|
53 | ierr=NF90_INQ_VARID(ncid,"lat",varid) |
---|
54 | ierr=NF90_GET_VAR(ncid,varid,lat) |
---|
55 | if (ierr /= nf90_noerr) then |
---|
56 | write(*,*) "cannot load lat from ",trim(file) |
---|
57 | else |
---|
58 | write(*,*) "lat(1:5)=",lat(1:5) |
---|
59 | endif |
---|
60 | ierr=NF90_INQ_VARID(ncid,"lon",varid) |
---|
61 | ierr=NF90_GET_VAR(ncid,varid,lon) |
---|
62 | if (ierr /= nf90_noerr) then |
---|
63 | write(*,*) "cannot load lat from ",trim(file) |
---|
64 | else |
---|
65 | write(*,*) "lon(1:5)=",lon(1:5) |
---|
66 | endif |
---|
67 | |
---|
68 | ! find correspondances between lon/ref_lon & lat/ref_lat |
---|
69 | allocate(cell_index(nb_cells)) |
---|
70 | cell_index(:)=0 |
---|
71 | do i=1,nb_cells |
---|
72 | lati=lat(i) ; loni=lon(i) |
---|
73 | do j=1,nb_cells |
---|
74 | if (lati/=0) then ! use relative difference, if possible |
---|
75 | diff_lat=abs((lati-ref_lat(j))/lati) |
---|
76 | else |
---|
77 | diff_lat=abs(lati-ref_lat(j)) |
---|
78 | endif |
---|
79 | if (loni/=0) then ! use relative difference, if possible |
---|
80 | diff_lon=abs((loni-ref_lon(j))/loni) |
---|
81 | else |
---|
82 | diff_lon=abs(loni-ref_lon(j)) |
---|
83 | endif |
---|
84 | |
---|
85 | if ((diff_lat <= 1.e-6).and.(diff_lon <= 1.e-6)) then |
---|
86 | cell_index(i)=j |
---|
87 | write(*,*)"j=",j," lati=",lati," ref_lat(j)=",ref_lat(j) |
---|
88 | write(*,*)"j=",j," loni=",loni," ref_lon(j)=",ref_lon(j) |
---|
89 | endif |
---|
90 | enddo ! of do j=1,nb_cells |
---|
91 | write(*,*) ">> i=",i,"cell_index(i)=",cell_index(i) |
---|
92 | |
---|
93 | ! sanity check: |
---|
94 | if (cell_index(i)==0) then |
---|
95 | write(*,*) "Error, could not find lon-lat match for i=",i |
---|
96 | write(*,*) " lat(i)=",lat(i)," lon(i)=",lon(i) |
---|
97 | stop |
---|
98 | endif |
---|
99 | enddo ! of do i=1,nb_cells |
---|
100 | |
---|
101 | ! do i=1,nb_cells |
---|
102 | ! write(*,*) "i=",i," cell_index(i)=",cell_index(i) |
---|
103 | ! write(*,*) " lat(i)=",lat(i),"ref_lat(cell_index(i))=",ref_lat(cell_index(i)) |
---|
104 | ! enddo |
---|
105 | |
---|
106 | ! load, rearrange and write variables |
---|
107 | ierr=NF90_INQ_DIMID(ncid,"cell",dimids(1)) |
---|
108 | ierr=NF90_INQUIRE(ncid,nVariables=nvar) |
---|
109 | write(*,*) "nvar=",nvar |
---|
110 | allocate(ref_field(nb_cells),field(nb_cells)) |
---|
111 | ! loop over variables: |
---|
112 | do k=1,nvar |
---|
113 | ierr=NF90_INQUIRE_VARIABLE(ncid,k,name=varname,ndims=ndim,dimids=varname_dimids) |
---|
114 | if (ierr /= nf90_noerr) then |
---|
115 | write(*,*) "error for variable k=",k |
---|
116 | write(*,*) nf90_strerror(ierr) |
---|
117 | endif |
---|
118 | if ((ndim==1).and.(varname_dimids(1)==dimids(1))) then |
---|
119 | write(*,*) "processing ",trim(varname) |
---|
120 | ! load field |
---|
121 | ierr=NF90_INQ_VARID(ncid,varname,varid) |
---|
122 | ierr=NF90_GET_VAR(ncid,varid,ref_field) |
---|
123 | ! rearrange field |
---|
124 | do i=1,nb_cells |
---|
125 | field(cell_index(i))=ref_field(i) |
---|
126 | enddo |
---|
127 | ! write field |
---|
128 | ierr=NF90_PUT_VAR(ncid,varid,field) |
---|
129 | endif |
---|
130 | enddo |
---|
131 | |
---|
132 | END PROGRAM rearrange_startphy |
---|