source: flexpart.git/flexpart_code/grib2nc4/grib2nc4.F90 @ 857dfd0

FPv9.3.2grib2nc4_repair
Last change on this file since 857dfd0 was 8624a75, checked in by Don Morton <Don.Morton@…>, 7 years ago

Enhancements to FPv9.3.2

Documented in Ticket #182 (as well as CTBTO ticket 357)

  • Property mode set to 100644
File size: 6.5 KB
Line 
1PROGRAM grib2nc4
2
3    !*************************************************************************
4    !  This program uses the met file preprocessing capabilities of          *
5    !  FLEXPART to extract key 3d variables, process them into the FP        *
6    !  coordinate system, and write to NetCDF4.                              *
7    !                                                                        *
8    !        Don Morton (Boreal Scientific Computing LLC)                    *
9    !        Preprocessing methods, M. Harustak                              *
10    !                                                                        *
11    !        May 2016                                                        *
12    !*************************************************************************
13   !   M. Harustak                                                          *
14   !   -) modification to generate the output in single precission          *
15   !   -) possibility to add a lat lon selection to obtain the met variables*
16   !      in the vertical levels defined in that location                   *
17   !*************************************************************************
18
19    USE par_mod
20    USE com_mod
21
22    USE netcdf
23    USE fp2nc4io_mod   ! Specialised module to interface preprocessed
24                       ! FP met data with NetCDF4 files
25
26    IMPLICIT NONE
27
28    LOGICAL :: metfile_exists, coordinates_provided, lat_provided, lon_provided
29    INTEGER :: i, j, k
30    INTEGER :: num_optional_vars, num_vars
31    INTEGER, PARAMETER :: DEFLATE_LEVEL = 2  ! Compression level (0-9)
32    CHARACTER(LEN=512) :: met_filepath, netcdf4_filepath, param_str, coord_name_str, coord_val_str
33    CHARACTER, DIMENSION(:), ALLOCATABLE :: vars_list  ! list of variables
34    INTEGER :: coordX, coordY, stat
35    REAL :: coord_lat, coord_lon
36    INTEGER :: metdata_format = UNKNOWN_METDATA  ! From FP par_mod
37
38    !--------------------------------------------------------
39
40    ! Read in mandatory arguments
41    IF (IARGC() < 2) THEN
42        PRINT *, 'Usage: grib2netcdf4 <inpath> <outpath> [lon=X lat=Y] [optional varnames]'
43        STOP
44    ELSE
45        CALL GETARG(1, met_filepath)
46        !PRINT *, 'met_filepath: ', met_filepath
47        CALL GETARG(2, netcdf4_filepath)
48    ENDIF
49
50    ! We want to insert 'u', 'v', and 't' into vars_list, by default
51    ! So, our list needs to have three elements, plus any optional args
52    ! from the command line
53
54    ! First, get the number of optional args and allocate vars_list,
55    ! and fill the first three elements
56    coordinates_provided = .FALSE.
57    lat_provided = .FALSE.
58    lon_provided = .FALSE.
59    ALLOCATE( vars_list(IARGC()+3),stat=stat )
60
61    vars_list(1) = 'u'
62    vars_list(2) = 'v'
63    vars_list(3) = 't'
64       
65    num_vars = 3
66    DO i=3,IARGC()
67        CALL GETARG(i,param_str)
68        param_str = TRIM(param_str)
69        j = SCAN(param_str,"=")
70        if (j>1) then
71            coord_name_str=param_str(1:j-1)
72            coord_val_str=param_str(j+1:)
73            IF ( coord_name_str == "lat" .or. coord_name_str == "LAT" ) THEN
74                read(coord_val_str,*,iostat=stat) coord_lat
75                if ( stat == 0 ) then
76                    lat_provided = .TRUE.
77                else
78                    print *, "Incorrect coordinates: ", coord_val_str
79                    stop
80                endif
81            ELSE IF ( coord_name_str == "lon" .or. coord_name_str == "LON" ) THEN
82                read(coord_val_str,*,iostat=stat) coord_lon
83                if ( stat == 0 ) then
84                    lon_provided = .TRUE.
85                else
86                    print *, "Incorrect coordinates: ", coord_val_str
87                    stop
88                endif
89            ENDIF
90        else
91            num_vars = num_vars + 1
92            vars_list(num_vars) = param_str
93        endif
94    ENDDO
95    IF (lat_provided .AND. lon_provided) THEN
96        coordinates_provided = .TRUE.
97    ENDIF
98
99    ! Before proceeding, let's make sure the vars_list is good - otherwise,
100    ! we don't want to waste time processing before finding out
101    IF ( .NOT. fp2nc4io_vars_are_valid(num_vars, vars_list) ) THEN
102        PRINT *, 'The variables list has an invalid variable...'
103        PRINT *, 'Valid variables: '
104        CALL fp2nc4io_print_valid_vars
105
106        PRINT *,
107        PRINT *, 'Your vars_list:'
108        DO i=1,num_vars
109            PRINT *, vars_list(i)
110        ENDDO
111        PRINT *,
112        PRINT *, 'Exiting...'
113        STOP
114    ENDIF
115
116
117    ! Insure that metfile_path is valid.  If so, put the file info
118    ! in com_mod variables numbwf and wfname
119    INQUIRE( FILE=met_filepath, EXIST=metfile_exists )
120    IF ( metfile_exists ) THEN
121        numbwf = 1
122        wfname(1) = met_filepath
123    ELSE
124        PRINT *, 'Unable to find metfile: ', TRIM(met_filepath)
125        STOP
126    ENDIF
127
128    ! Check the type of metdata using FP routine detectformat()
129    CALL detectformat(metdata_format)
130    IF (metdata_format == ECMWF_METDATA) THEN
131        PRINT *, ("ECMWF met data detected...")
132    ELSEIF (metdata_format == GFS_METDATA) THEN
133        PRINT *, ("NCEP met data detected...")
134    ELSE
135        PRINT *, ("Unknown met data detected...")
136        STOP
137    ENDIF
138
139    ! Set a couple of com_mod variables - I honestly don't know the reason
140    ! for this now, but it was done in GRIB2FLEXPART, so I'm repeating it here.
141    ! The comment in there says "Reset the times of the wind fields that are
142    ! kept in memory to no time"
143    DO i=1,2
144        memind(i) = i
145        memtime(i) = 999999999
146    ENDDO
147
148    ! Read the model grid specifications,
149    ! both for the mother domain and eventual nests
150    !**********************************************
151    if (metdata_format == ECMWF_METDATA) CALL gridcheck_ecmwf
152    if (metdata_format == GFS_METDATA) CALL gridcheck_gfs
153
154    ! This is not yet implemented for nests.  It would probably be trivial
155    ! to do so
156    !CALL gridcheck_nests
157
158    ! If the coordinates are provided, then we need to obtain
159    !  the corresponding grid indexes since this is what verttransform needs
160    if ( coordinates_provided ) then
161        coordX = (coord_lon-xlon0)/dx
162        coordY = (coord_lat-ylat0)/dy
163        print *, "Coordinates: "
164        print *, "lon: ", coord_lon, ", lat: ",coord_lat
165        print *, "x: ", coordX, ", y: ", coordY
166    endif
167
168    PRINT *, 'Calling processmetfields()...'
169    call processmetfields( 1, metdata_format, coordinates_provided, coordX, coordY)
170
171    PRINT *, 'Calling fp2nc4io_dump()...'
172    call fp2nc4io_dump( netcdf4_filepath, num_vars, vars_list, DEFLATE_LEVEL)
173
174    PRINT *, 'End of grib2nc4'
175
176
177END PROGRAM grib2nc4
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG