source: flexpart.git/src/gributils/test/testdrive.f90 @ 61e07ba

10.4.1_peseiGFS_025bugfixes+enhancementsdevrelease-10release-10.4.1scaling-bugunivie
Last change on this file since 61e07ba was 61e07ba, checked in by Espen Sollum ATMOS <eso@…>, 7 years ago

Adding files from CTBTO project wo_17

  • Property mode set to 100644
File size: 2.2 KB
Line 
1PROGRAM testdrive
2
3    USE class_gribfile
4
5    IMPLICIT NONE
6
7    CHARACTER(LEN=256) :: the_file_path
8
9    INTEGER, PARAMETER :: NCASES = 6
10    CHARACTER(LEN=256), DIMENSION(NCASES) :: file_paths
11    CHARACTER(LEN=256), DIMENSION(NCASES) :: descriptions
12
13    TYPE(gribfile_object) :: my_gribfile
14
15    INTEGER :: case_number
16
17    !!!!!!!!!!!!!!!!!!!
18    ! These define the header and the grib file used for each test
19    descriptions(1) = "ECMWF GRIB1 on global 1.0 degree domain"
20    file_paths(1) = "../../../devtest/case_data/met_data/ecmwf/t1_03h_ec1p0d/EN13062503"
21
22    descriptions(2) = "ECMWF GRIB1/2 on tiny domain"
23    file_paths(2) = "../../../devtest/case_data/met_data/ecmwf/t1_33h_ec1p0d/EL14091909"
24
25    descriptions(3) = "ECMWF GRIB1/2 on global 1.0 degree domain"
26    file_paths(3) = "../../../devtest/case_data/met_data/ecmwf/t1_03h_ec1p0d_grib1-2/EE13110700"
27
28    descriptions(4) = "ECMWF GRIB2 on global 1.0 degree domain"
29    file_paths(4) = "../../../devtest/case_data/met_data/ecmwf/t1_03h_ec1p0d_grib2/EN13110700"
30
31    descriptions(5) = "NCEP GRIB1 on global 1.0 degree domain"
32    file_paths(5) = "../../../devtest/case_data/met_data/ncep/t1_06h_nc1p0d_grib1/GD05051406"
33
34    descriptions(6) = "NCEP GRIB2 on global 1.0 degree domain"
35    file_paths(6) = "../../../devtest/case_data/met_data/ncep/t1_03h_nc1p0d/GF15021603"
36    !!!!!!!!!!!!!!!!!!!
37
38    DO case_number = 1,NCASES
39        PRINT *,
40        PRINT *, TRIM( descriptions( case_number) )
41
42        my_gribfile = gribfile_object_create( file_paths(case_number) )
43        PRINT *,
44        PRINT *, 'Output from calling gribfile_printobj()...'
45        PRINT *, '++++++++++'
46        CALL gribfile_printobj(my_gribfile)
47        PRINT *, '++++++++++'
48        PRINT *,
49       
50        PRINT *, 'Output from the getter methods...'
51        PRINT *, 'gribfile_center()   : ', gribfile_centre( file_paths(case_number) )
52
53        PRINT *, 'gribfile_num_xlon   : ', gribfile_num_xlon(my_gribfile)
54        PRINT *, 'gribfile_num_ylat   : ', gribfile_num_ylat(my_gribfile)
55        PRINT *, 'gribfile_num_zlevel : ', gribfile_num_zlevel(my_gribfile)
56        PRINT *,
57        PRINT *, '----------------------------'
58    ENDDO
59
60
61END PROGRAM testdrive
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG