updated top-level README and version_decl for V4.4.2 (#1795)
[WRF.git] / share / wrf_tsin.F
blob0ba972976363afc112145732fbc68851eb8c59ae
1 SUBROUTINE wrf_tsin ( grid , ierr )
3     USE module_domain
4     USE module_utility
5     USE module_configure, ONLY : model_config_rec, grid_config_rec_type, model_to_grid_config_rec
6     USE module_string_tools, ONLY : capitalize
8     IMPLICIT NONE
10 #include "wrf_io_flags.h"
11 #include "wrf_status_codes.h"
13     TYPE(domain), INTENT(INOUT) :: grid
14     TYPE (grid_config_rec_type) :: config_flags
15     INTEGER, INTENT(INOUT) :: ierr
17     LOGICAL, EXTERNAL :: wrf_dm_on_monitor
18     INTEGER, EXTERNAL :: get_unused_unit
20     INTEGER :: istatus, iunit
21     LOGICAL :: exists
22     CHARACTER (LEN=256) :: errmess
23     CHARACTER (LEN=256) :: IorLat,JorLon
25     ierr = 0
27 #if ((EM_CORE == 1) && (DA_CORE != 1))
28     IF ( grid%dfi_opt == DFI_NODFI .OR. (grid%dfi_opt /= DFI_NODFI .AND. grid%dfi_stage == DFI_SETUP) ) THEN
29 #endif
30     CALL model_to_grid_config_rec ( grid%id , model_config_rec , config_flags ) 
31        grid%ntsloc = 0
32        grid%have_calculated_tslocs = .FALSE.
33    
34        IF ( grid%max_ts_locs <= 0 ) RETURN
35    
36        IF ( wrf_dm_on_monitor() ) THEN
38           CALL wrf_tsin_exist ( exists )
39    
40           IF (exists) THEN
42              iunit = get_unused_unit()
43              IF ( iunit <= 0 ) THEN
44                 CALL wrf_error_fatal('Error in wrf_tsin: could not find a free Fortran unit.')
45              END IF
47              ! Input time series locations
48              OPEN(UNIT=iunit, FILE='tslist', FORM='formatted', STATUS='old', IOSTAT=istatus)
49              IF (istatus == 0) THEN
50    
51                 ! The header will be parsed to see if lat/lon or i/j is given...
52                 READ(UNIT=iunit, FMT='(1X)')
53                 READ(UNIT=iunit, FMT='(32X,A7,2X,A7)') IorLat, JorLon
54                 READ(UNIT=iunit, FMT='(1X)')
55                 grid%tslist_ij = .false.
56                 ! If the header contains "LAT" and "LON", 
57                 !    then it will expect lat/lon coords in the file
58                 ! If the header has "I" and "J", 
59                 !    then it will expect grid index coords in the file
60                 IorLat = capitalize(IorLat)
61                 JorLon = capitalize(JorLon)
62                 if(index(IorLat,'LAT').ne.0 .and. index(JorLon,'LON').ne.0) then
63                     grid%tslist_ij = .false.
64                 elseif(index(IorLat,'I').ne.0 .and. index(JorLon,'J').ne.0) then
65                     grid%tslist_ij = .true.
66                 else
67                     CALL wrf_error_fatal('Error in wrf_tsin: Header line requires either LAT LON or I J')
68                 endif
72    
73                 ! Read in time series locations
74                 istatus = 0
75                 DO WHILE (istatus == 0)
76                    IF (config_flags%map_proj == 0 .OR. grid%tslist_ij) THEN !ideal run will only use i,j
77                        READ(UNIT=iunit, FMT='(A25,1X,A5,1X,I7,1X,I8)', IOSTAT=istatus)            &
78                        grid%desctsloc(grid%ntsloc+1), grid%nametsloc(grid%ntsloc+1), &
79                        grid%itsloc(grid%ntsloc+1), grid%jtsloc(grid%ntsloc+1)
80                    ELSE
81                        READ(UNIT=iunit, FMT='(A25,1X,A5,1X,F7.3,1X,F8.3)', IOSTAT=istatus)            &
82                        grid%desctsloc(grid%ntsloc+1), grid%nametsloc(grid%ntsloc+1), &
83                        grid%lattsloc(grid%ntsloc+1), grid%lontsloc(grid%ntsloc+1)
84                    END IF
85                    IF (istatus == 0) grid%ntsloc = grid%ntsloc + 1
86                    IF (istatus > 0) THEN
87                       WRITE(errmess, FMT='(I4)') grid%ntsloc + 4   ! Three extra for the header of the file
88                                                                    ! One extra for the line we incorrectly read
89                       CALL wrf_message('Error in tslist, line '//trim(errmess))
90                       CALL wrf_error_fatal('Error --- Maybe check that the header (I,J) vs (LAT,LON) matches the provided information')
91                       EXIT    ! (technically unecessary, as we will exit the loop anyway)
92                    END IF
93                    IF ( ( grid%ntsloc == 1 ) .and. ( .NOT. grid%tslist_ij ) ) THEN
94                       IF ( ( ABS(grid%lattsloc(grid%ntsloc)) <= 0.1 ) .and. &
95                            ( ABS(grid%lontsloc(grid%ntsloc)) <= 0.1 ) ) THEN
96                          CALL wrf_message('WARNING ')
97                          CALL wrf_message('WARNING --- Maybe you have (I,J) locations for the (LAT,LON) values in tslist?')
98                          CALL wrf_message('WARNING --- Are you purposefully studying Null Island?')
99                          CALL wrf_message('WARNING ')
100                       END IF
101                    END IF
102                    IF ( grid%ntsloc >= grid%max_ts_locs ) THEN
103                       IF ( istatus == 0 ) THEN                 ! Assume there were more lines in the file
104                          WRITE(errmess, FMT='(A,I4,A)') 'Ignoring all time series locations beyond #', &
105                                                     grid%ntsloc,'. Increase max_ts_locs in namelist.input'
106                          CALL wrf_message(trim(errmess))
107                       END IF
108                       EXIT
109                    END IF
110                 END DO
111       
112                 CLOSE(iunit)
113    
114              END IF
116           END IF  ! tslist file exists
117    
118        END IF
120 #ifdef DM_PARALLEL
121        CALL wrf_dm_bcast_integer(grid%ntsloc, 1)
122        CALL wrf_dm_bcast_integer(grid%tslist_ij, 1)
123        CALL wrf_dm_bcast_real(grid%lattsloc, grid%max_ts_locs)
124        CALL wrf_dm_bcast_real(grid%lontsloc, grid%max_ts_locs)
125        CALL wrf_dm_bcast_integer(grid%itsloc, grid%max_ts_locs)
126        CALL wrf_dm_bcast_integer(grid%jtsloc, grid%max_ts_locs)
127 #endif
128 #if ((EM_CORE == 1) && (DA_CORE != 1))
129     END IF
130 #endif
132 END SUBROUTINE wrf_tsin
134 SUBROUTINE wrf_tsin_exist ( exists )
135    IMPLICIT NONE
136    LOGICAL , INTENT(OUT) :: exists
137    INQUIRE(FILE='tslist', EXIST=exists)
138 END SUBROUTINE wrf_tsin_exist
141 INTEGER FUNCTION get_unused_unit()
143     IMPLICIT NONE
145     INTEGER, PARAMETER :: min_unit_number = 30
146     INTEGER, PARAMETER :: max_unit_number = 99 
148     LOGICAL :: opened
150     DO get_unused_unit = min_unit_number, max_unit_number
151        INQUIRE(UNIT=get_unused_unit, OPENED=opened)
152        IF ( .NOT. opened ) RETURN
153     END DO
155     get_unused_unit = -1
157     RETURN
158     
159 END FUNCTION get_unused_unit