Merge remote-tracking branch 'origin/release-v4.6.1'
[WRF.git] / external / io_pio / module_wrfsi_static.F90
blobda408bf5768d18221692a1d1c9bbee57c25ff2fe
1 MODULE wrfsi_static
2   use wrf_data_pio
3   include 'wrf_status_codes.h'
4   type (iosystem_desc_t), pointer :: iosystem
6 CONTAINS
7   SUBROUTINE open_wrfsi_static(dataroot, FileDesc)
8     use pio
9     use pio_kinds
10     IMPLICIT NONE
11     CHARACTER(LEN=*),  INTENT(IN)  :: dataroot
12     type(file_desc_t), INTENT(OUT) :: FileDesc
13     CHARACTER(LEN=255)             :: staticfile
14     LOGICAL                        :: static_exists
15     INTEGER                        :: status
17     allocate(iosystem)
19     staticfile = TRIM(dataroot) // '/static/static.wrfsi'
20     INQUIRE(FILE=staticfile, EXIST=static_exists)
21     IF (static_exists) THEN
22       status = PIO_openfile(iosystem, FileDesc, &
23                             PIO_iotype_pnetcdf, TRIM(staticfile))
24       IF (status .NE. PIO_NOERR) THEN
25         PRINT '(A,I5)', 'NetCDF error opening WRF static file: ',status
26         STOP 'open_wrfsi_static'
27       END IF 
28     ELSE
29       staticfile = TRIM(dataroot) // '/static/static.wrfsi.rotlat'
30       INQUIRE(FILE=staticfile, EXIST=static_exists)
31       IF(static_exists) THEN
32         status = PIO_openfile(iosystem, FileDesc, &
33                               PIO_iotype_pnetcdf, TRIM(staticfile))
34         IF(status .NE. PIO_NOERR) THEN
35           PRINT '(A,I5)', 'NetCDF error opening WRF static file: ',status
36           STOP 'open_wrfsi_static'
37         END IF
38       ELSE
39         PRINT '(A)', 'rotlat Static file not found, either: ', staticfile
40         STOP 'open_wrfsi_static'
41       ENDIF
43     ENDIF
45     RETURN
46   END SUBROUTINE open_wrfsi_static      
48 !--------------------------------------------------------------------
49   SUBROUTINE get_wrfsi_static_dims(dataroot, nx, ny)
50   
51     ! Subroutine to return the horizontal dimensions of WRF static file
52     ! contained in the input dataroot
54     use pio
55     use pio_kinds
57     IMPLICIT NONE
58     CHARACTER(LEN=*), INTENT(IN)  :: dataroot
59     INTEGER         , INTENT(OUT) :: nx
60     INTEGER         , INTENT(OUT) :: ny
62     INTEGER                       :: vid, status
63     type (file_desc_t)            :: FileDesc
65     CALL open_wrfsi_static(dataroot, FileDesc)
66     status = pio_inq_dimid(FileDesc, 'x', vid)
67     status = pio_inq_dimlen(FileDesc, vid, nx)
68     status = pio_inq_dimid(FileDesc, 'y', vid)
69     status = pio_inq_dimlen(FileDesc, vid, ny)
70     write(unit=*, fmt='(2(A,I5))') 'WRF X-dimension = ',nx, &
71                                  ', WRF Y-dimension = ',ny  
72     call pio_closefile(FileDesc)
73     deallocate(iosystem)
74     RETURN
75   END SUBROUTINE get_wrfsi_static_dims     
77 !--------------------------------------------------------------------
78   SUBROUTINE get_wrfsi_static_2d(dataroot, varname, data)
79     use pio
80     use pio_kinds
81     IMPLICIT NONE
82    !Gets any 2D variable from the static file
83     CHARACTER(LEN=*), INTENT(IN)  :: dataroot
84     CHARACTER(LEN=*), INTENT(IN)  :: varname
85     REAL, INTENT(OUT)             :: data(:,:)
87     INTEGER                       :: vid, status
88     type (file_desc_t)            :: FileDesc
89    
90     CALL open_wrfsi_static(dataroot, FileDesc)
91     status = pio_inq_varid(FileDesc, varname, vid)
92     status = pio_get_var(FileDesc, vid, data)
93    !status = get_var_2d_real(FileDesc, vid, data)
94     IF(status .NE. PIO_NOERR) THEN
95       write(unit=*, fmt='(A)') 'Problem getting 2D data.'
96     ENDIF 
97     call pio_closefile(FileDesc)
98     deallocate(iosystem)
99     RETURN
100   END SUBROUTINE get_wrfsi_static_2d    
101 END MODULE wrfsi_static