MI - Fimex
fimex2d_example.F90

Example on using the high-level 2d fimex-fortran interface

1 
3 PROGRAM fimex2d_example
4  !
5  !
6  USE fimex, ONLY : fimexio,set_filetype,filetype_rw
9  IMPLICIT NONE
10  CHARACTER(LEN=1024) :: arg,infile,outfile,fileformat,configfile
11  CHARACTER(LEN=1024) :: ctemp2m="air_temperature_2m"
12  CHARACTER(LEN=1024) :: dimname_t
13  CHARACTER(LEN=10) :: cdtg
14  INTEGER :: i,t
15  INTEGER(KIND=IKIND) :: nx,ny
16  LOGICAL :: found12
17  TYPE(fimexio) :: fio_in,fio_out
18  REAL(KIND=8),DIMENSION(:,:),ALLOCATABLE :: t2m
19  INTEGER,DIMENSION(:),ALLOCATABLE :: times
20  REAL(KIND=8),DIMENSION(:),ALLOCATABLE :: ztimes
21  REAL(KIND=8) :: basetime,ztime
22  INTEGER :: ntimes,ierr
23 
24  ! Set arguments
25  IF ((command_argument_count() /= 3 ) .AND. (command_argument_count() /= 4 ) ) THEN
26  WRITE(*,*) "Usage: ./fimex2d_example infile outfile infile-fileformat [configfile]"
27  CALL abort
28  ENDIF
29 
30  configfile=""
31  DO i = 1, command_argument_count()
32  CALL get_command_argument(i, arg)
33  SELECT CASE (i)
34  CASE(1)
35  infile=arg
36  CASE(2)
37  outfile=arg
38  CASE(3)
39  fileformat=arg
40  SELECT CASE (fileformat)
41  CASE("felt","FELT","FLT","flt")
42  fileformat="felt"
43  CASE("GRIB","grib","grb","GRB","GRIB2","grib2","grb2","GRB2")
44  fileformat="grib"
45  CASE("netcdf","NETCDF","nc","NC")
46  fileformat="netcdf"
47  CASE DEFAULT
48  WRITE(*,*) "Invalid file format: "//fileformat
49  CALL abort
50  END SELECT
51  CASE(4)
52  IF (command_argument_count() == 4 ) THEN
53  configfile=arg
54  ENDIF
55  END SELECT
56  END DO
57  IF (( trim(fileformat) == "felt" ) .OR. ( trim(fileformat) == "grib" )) THEN
58  IF ( configfile == "" ) THEN
59  WRITE(*,*) 'No config file provided, but is mandatory for '//fileformat
60  CALL abort
61  ENDIF
62  ENDIF
63 
64  ierr=fio_in%OPEN(trim(infile),configfile,set_filetype(fileformat))
65  IF ( ierr /= 0 ) CALL fi_error("Error opening "//trim(infile))
66  ierr=fio_out%OPEN(trim(outfile),"",set_filetype("netcdf",filetype_rw))
67  IF ( ierr /= 0 ) CALL fi_error("Error opening "//trim(outfile))
68 
69  WRITE(*,*) "List variables in input file "//trim(infile)
70  DO i = 1,int(fio_in%VARIABLES_SIZE())
71  WRITE(*,*) "Found: ",i, " ", trim(fio_in%GET_VARNAME(i))
72  END DO
73 
74  ! Get dimensions from temperature variable
75  CALL fi_get_dimensions(fio_in,trim(ctemp2m),nx=nx,ny=ny,ntimes=ntimes,dimname_t=dimname_t,basetime=basetime)
76 
77  ! Read times in file
78  ALLOCATE(times(0:ntimes-1))
79  ALLOCATE(ztimes(0:ntimes-1))
80  WRITE(*,*) 'Listing times in file:'
81  CALL fi_read_dimension(fio_in,ntimes,trim(dimname_t),ztimes,"seconds since 1970-01-01 00:00:00 +00:00")
82  DO i=0,ntimes-1
83  times(i)=epoch2dtg(ztimes(i))
84  WRITE(*,*) i,times(i)
85  ENDDO
86  DEALLOCATE(ztimes)
87 
88  ALLOCATE(t2m(nx,ny))
89  ! Loop forecast and set variables
90  found12=.false.
91  time_loop: DO t=0,ntimes-1
92 
93  WRITE(cdtg,'(I10.10)') times(t)
94  IF ( cdtg(9:10) == "12" ) THEN
95  IF (.NOT. found12 ) THEN
96  CALL fi_read_field(fio_in,trim(ctemp2m),nx,ny,t2m,t,cunit="celsius",time=ztime,verbosity=2)
97  IF ( times(t) /= epoch2dtg(ztime)) CALL fi_error("Mismatch in time for T2M")
98  found12=.true.
99  EXIT time_loop
100  ENDIF
101  ENDIF
102  ENDDO time_loop
103 
104  IF (found12) THEN
105  CALL fi_write_field(fio_out,trim(ctemp2m),nx,ny,t2m,verbosity=2)
106  ELSE
107  CALL fi_error("Variable for 12 UTC was not found")
108  ENDIF
109 
110  ierr=fio_in%CLOSE()
111  ierr=fio_out%CLOSE()
112 
113  ! Deallocation
114  DEALLOCATE(times)
115  DEALLOCATE(t2m)
116 
117 END PROGRAM fimex2d_example